[Haskell-cafe] Variants of a recursive data structure

Josef Svenningsson josef.svenningsson at gmail.com
Thu Aug 3 12:15:51 EDT 2006


Klaus,

You've gotten many fine answers to your question. I have yet another
one which is believe is closest to what you had in mind. The key to
the solution is to add an extra type parameter to Labelled like so:

data Labelled f a = L String (f a)

Now you can use it to form new recursive type with Mu:

type LabelledExp = Mu (Labelled Exp)

And it is also possible to write an unlabel function which knows very
little about the structure of Exp:

unlabel :: Functor f => Mu (Labelled f) -> Mu f
unlabel (Mu (L _ r)) = Mu (fmap unlabel r)

Another bonus is that it's all Haskell98.

The name I came up with for the trick of adding a higher-kinded type
parameter to Labelled is "Functor Transformer". "Transformer" -
because it transforms the type it is applied to (in this case Exp),
and "Functor" - because when using Mu to tie the recursive knot one
often require the types to be instances of functor, as I'm sure you're
aware of.

Good luck with whatever it is you need this for.

Josef

On 8/3/06, Klaus Ostermann <ostermann at informatik.tu-darmstadt.de> wrote:
> Hi all,
>
> I have a problem which is probably not a problem at all for Haskell experts,
> but I am struggling with it nevertheless.
>
> I want to model the following situation. I have ASTs for a language in two
> variatns: A "simple" form and a "labelled" form, e.g.
>
> data SimpleExp = Num Int | Add SimpleExp SimpleExp
>
> data LabelledExp = LNum Int String | LAdd LabelledExp LabelledExp String
>
> I wonder what would be the best way to model this situation without
> repeating the structure of the AST.
>
> I tried it using a fixed point operator for types like this:
>
> data Exp e = Num Int | Add e e
>
> data Labelled a = L String a
>
> newtype Mu f = Mu (f (Mu f))
>
> type SimpleExp = Mu Exp
>
> type LabelledExp = Mu Labelled Exp
>
> The "SimpleExp" definition works fine, but the LabeledExp definition doesn't
> because I would need something like "Mu (\a -> Labeled (Exp a))" where "\"
> is a type-level lambda.
>
> However, I don't know how to do this in Haskell. I'd need something like the
> "." operator on the type-level. I also wonder whether it is possible to
> curry type constructors.
>
> The icing on the cake would be if it would also be possible to have a
> function
>
> unlabel :: LabeledExp -> Exp
>
> that does *not* need to know about the full structure of expressions.
>
> So, what options do I have to address this problem in Haskell?
>
> Klaus
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list