Higgledy-Piggledy rides again

We like to organise Epigram source by feature rather than by component. Nicolas and I wrote some dodgy scissors-and-stickytape code to rearrange our files before we compiled them, along with some bad Makefile voodoo. I’ve built more or less the same functionality into she, so it’s just as dodgy, but the build is easier. Here’s an example trio of files.


> {-# OPTIONS_GHC -F -pgmF she #-}
> {-# LANGUAGE TypeOperators, KindSignatures, GADTs #-}
> module Pig where

> import Control.Applicative
> import Data.Char
> import Parsley

> import Hig
> import Jig

> data ExpF :: * -> * where
>   import < - ExpF

> instance Functor ExpF where
>   import < - FunctorExpF

> data Free :: (* -> *) -> * -> * where
>   V :: x -> Free f x
>   C :: f (Free f x) -> Free f x

> fEval :: Functor f => (x -> t) -> (f t -> t) -> Free f x -> t
> fEval g f (V x)  = g x
> fEval g f (C fe) = f (fmap (fEval g f) fe)

> type Exp = Free ExpF
> import < - ExpPS

> eval :: (x -> Int) -> Exp x -> Int
> eval g = fEval g $ \ e -> case e of
>   import < - EvAlg

> pExp :: P Char (Exp Char)
> pExp = V < $> tok isAlpha
>   import < - EvParser

What are these import ← Blah things? She replaces them with the code fragments accumulated against the Blah tag, found in the .hers files of the imported modules. Here's Hig:


> {-# OPTIONS_GHC -F -pgmF she #-}
> {-# LANGUAGE TypeOperators #-}

> module Hig where

> import -> ExpF where
>   AddF :: t -> t -> ExpF t

> import -> ExpPS where
>   pattern Add x y = C (AddF x y)

> import -> FunctorExpF where
>   fmap f (AddF a b) = AddF (f a) (f b)

> import -> EvAlg where
>   AddF u v -> u + v

> import -> EvParser where
>   < |> Add < $ teq '(' <*> pExp < * teq '+' <*> pExp < * teq ')'

and here's Jig


> {-# OPTIONS_GHC -F -pgmF she #-}
> {-# LANGUAGE TypeOperators #-}

> module Jig where

> import -> ExpF where
>   NegF :: t -> ExpF t

> import -> ExpPS where
>   pattern Neg x = C (NegF x)

> import -> FunctorExpF where
>   fmap f (NegF a) = NegF (f a)

> import -> EvAlg where
>   NegF u -> negate u

> import -> EvParser where
>   < |> Neg < $ teq '-' <*> pExp

Sorry about the import →, rather than ‘export’. I didn’t want to eat yet another keyword.

As you can see, it’s bargain basement stuff. The only vague wit involved is mangaging the indentation properly, so you don’t have to count spaces. Your accumulated blocks drop in at the indentation level of the import which asks for them. It sort of works in expressions too! I had to improve my layout parsing to get this to work. Ouch.

Anyhow, this stuff, plus lhs2TeX, is a good way to develop and document code.

4 Responses to “Higgledy-Piggledy rides again”

  1. Daniel says:

    I can’t say I’m a fan of the import import -> ExpF where
    > AddF :: t -> t -> ExpF t

    This one is fine, but with a more complicated signature it might be hard to understand something like this.

    Not sure if you’re taking votes on this, but I’d also prefer export/import instead of import -> and import < – :)

  2. Daniel says:

    Ack, it looks like the blog syntax ate some of my text! I just said that I didn’t like the syntax much but liked the idea.

  3. Conor says:

    I’m certainly open to suggestions. I’m not a big fan of import -> but I didn’t want to make yet another new keyword. But it’s not exactly difficult to do so. Would there be any takers for something like

    aspect Blah where
    mutter mutter mutter

    and something like

    import aspect Blah

    or even just aspect Blah?

    Anyhow, this way lies Wadler’s Law, and I’m having enough of that with idiom brackets.

  4. Conor says:

    Indent that

      mutter mutter mutter

    Sodding space-eating blog.

Leave a Reply