And is this Haskell?


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

> module Fix where

> data Fix f = In (f (Fix f))

> newtype (:+:) f g x = Plus (Either (f x) (g x))
> newtype (:*:) f g x = Times (f x, g x)
> newtype K a x = K a
> newtype I x = I x

> type ListF x = K () :+: (K x :*: I)

> type List x = Fix (ListF x)

> pattern NilF = Plus (Left (K ()))
> pattern ConsF x xs = Plus (Right (Times (K x, I xs)))
> pattern Nil = In NilF
> pattern Cons x xs = In (ConsF x xs)

> foldFix :: Functor f => (f t -> t) -> Fix f -> t
> foldFix phi (In xs) = phi (fmap (foldFix phi) xs)

> (+++) :: List x -> List x -> List x
> xs +++ ys = foldFix phi xs where
>   phi NilF = ys
>   phi (ConsF x xs) = Cons x xs

> blat :: List x -> [x]
> blat = foldFix phi where
>   phi NilF = []
>   phi (ConsF x xs) = x : xs

> talb :: [x] -> List x
> talb = foldr Cons Nil

> instance (Functor f, Functor g) => Functor (f :+: g) where
>   fmap p (Plus (Left fx)) = Plus (Left (fmap p fx))
>   fmap p (Plus (Right gx)) = Plus (Right (fmap p gx))

> instance (Functor f, Functor g) => Functor (f :*: g) where
>   fmap p (Times (fx, gx)) = Times (fmap p fx, fmap p gx)

> instance Functor (K a) where
>   fmap p (K a) = K a

> instance Functor I where
>   fmap p (I a) = I (p a)

I’ve pushed some patches, and now it is!

6 Responses to “And is this Haskell?”

  1. Pepe Iborra says:

    Yay !

  2. Conor says:

    I just added an example file with treeSort, mostly to test that pattern synonyms are propagated along with module imports (via the mysterious and entirely readable .hers file that she creates). A few more bits and pieces (idiom brackets that work, some vaguely aspecty gadgets) and we’re set for a summer of hacking. I’m quite sure she’s full of quirks and infelicities just now, and slow to boot, but things will improve as and when they need to.

  3. Pepe Iborra says:

    Can we have this in he (the manly GHC of course) please ?

  4. Conor says:

    I’m keen to help that to happen.

  5. Daniel says:

    This (and the previous blog entry) looks exciting! Do you have an overview somewhere of what your end goal is here?

  6. Conor says:

    I haven’t written that piece yet. So far, it’s partly a feasibility study and partly about tooling up for Epigram hacking. I’ve been working with SPJ and Dimitris Vytiniotis on doing the {..} stuff for real: this is just a mockup to let people try out examples. Pattern synonyms are there to support “datatype coding” in general. If you code your data as fixpoints of sums of products, you get lots of generic goodies cheap but your type-specific functions look ugly as sin: pattern synonyms get you back where you were. You can see what happens if you put the two ideas together here.

    In a similar vein, the Epigram implementation is quite reflective, so we need to write Haskell programs manipulating Epigram data structures. Pattern synonyms let us write Nil instead of Pair [Z [], Void []] or whatever it turns out to be. More code will survive the inevitable changes of internal representation.

    To sum up, there’s no grand plan: it’s a bunch of loosely related experiments and some kit whose absence we’ve felt in the past.

Leave a Reply