[Haskell-cafe] Variants of a recursive data structure

Klaus Ostermann ostermann at informatik.tu-darmstadt.de
Thu Aug 3 11:25:07 EDT 2006


Hi Niklas,

thanks for your suggestion. Can you explain how your solution is better than
the very simple one, i.e.,

data Exp e = Num Int | Add e e
data Labeled  = L String e
newtype SimpleExp = Exp SimpleExp
newtype LabeledExp = Labelled (Exp LabeledExp)

Klaus

-----Original Message-----
From: Niklas Broberg [mailto:niklas.broberg at gmail.com] 
Sent: Thursday, August 03, 2006 5:15 PM
To: Klaus Ostermann
Cc: haskell-cafe at haskell.org
Subject: Re: [Haskell-cafe] Variants of a recursive data structure

Oops, sorry, I think I'm getting too addicted to flags. ;-)
The module I wrote actually doesn't need neither overlapping nor
undecidable instances, so just -fglasgow-exts will do just fine.

/Niklas

On 8/3/06, Niklas Broberg <niklas.broberg at gmail.com> wrote:
> If you want the non-labelledness to be guaranteed by the type system,
> you could combine a GADT with some type level hackery. Note the flags
> to GHC - they're not that scary really. :-)
>
> In the following I've used the notion of type level booleans (TBool)
> to flag whether or not an expression could contain a label or not. A
> term of type Exp TFalse is guaranteed to not contain any labels, a
> term of type Exp TTrue is guaranteed *to* contain at least one label
> somewhere in the tree, and a term Exp a could contain a label, but
> doesn't have to.
>
>
---------------------------------------------------------------------------
> {-# OPTIONS_GHC -fglasgow-exts -fallow-overlapping-instances
> -fallow-undecidable-instances #-}
> module Exp where
>
> data TTrue
> data TFalse
>
> class TBool a
> instance TBool TTrue
> instance TBool TFalse
>
> class (TBool a, TBool b, TBool c) => Or a b c
>
> instance Or TFalse TFalse TFalse
> instance (TBool x, TBool y) => Or x y TTrue
>
> data TBool l => Exp l where
>  Num :: Int -> Exp TFalse
>  Add :: Or a b c => Exp a -> Exp b -> Exp c
>  Label :: String -> Exp a -> Exp TTrue
>
> type SimpleExp = Exp TFalse
>
> unlabel :: Exp a -> SimpleExp
> unlabel n@(Num _) = n
> unlabel (Add x y) = Add (unlabel x) (unlabel y)
> unlabel (Label _ x) = unlabel x
>
----------------------------------------------------------------------------
---
>
> Cheers,
>
> /Niklas
>
> 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