[Haskell-cafe] Variants of a recursive data structure

Nicolas Frisby nicolas.frisby at gmail.com
Thu Aug 3 16:07:00 EDT 2006


Howdy. I've been working with this stuff pretty intimately in the last
few days; here's what I came up with. It's similar to Josef's except
let's us have many labels.

"Type-level currying" requires newtypes because any appearance of a
type synonym must be fulled applied. newtypes relax that restraint.


-- An annotated functor is the applied functor with a label
newtype Anno f l x = Anno (f x, l)

anno f_x l = Anno (f_x, l)
unAnno  (Anno (f_x, _)) = f_x
getAnno (Anno (_, l)) = l

-- it keeps it functor property
instance Functor f => Functor (Anno f l) where
    fmap f (Anno (f_x, l)) = Anno (fmap f f_x, l)



-- An annotated AST is created by annotating the functor before
fixing.
newtype AnnoAST f l = AnnoAST { unAnnoAST :: Fix (Anno f l) }

-- this function takes a normal term and annotates it with all ()
fromAST :: Functor f => Fix f -> AnnoAST f ()
fromAST = AnnoAST . cata phi
    where phi = inn . (`anno` ())

toAST :: Functor f => AnnoAST f lab -> Fix f
toAST = cata phi . unAnnoAST
    where phi = inn . unAnno

cata phi = phi . fmap (cata phi) . out



-- finally, your request is served
data Exp x = Num Integer
                 | Add x x

type SimpleExp = Fix Exp
type LabelledExp = AnnoAST Exp String

unLabel term = toAST term




I'm a little late on this post, but I think this is the general form
of labeling (within the solution involving explicit functors and fixed
points). Now you could, for instance, label your AST with types
instead of just strings--anything for that matter.

To take it one step further (this is what I just spent the last couple
days coding so it works for any language constructed this way), check
out:

  "Comonadic functional attribute evaluation" by Tarmo Uustalu and Varmo Vene

It's pretty cool.

HTH,
Nick


On 8/3/06, Josef Svenningsson <josef.svenningsson at gmail.com> wrote:
> 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
> >
> _______________________________________________
> 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