[Haskell-cafe] Variants of a recursive data structure

Christophe Poucet christophe.poucet at gmail.com
Thu Aug 3 08:00:29 EDT 2006


Hello Klaus,

Indeed I am reerring to the ICFP'06 paper.  However after reading your other posts, it seems you want tags to be something that are guaranteed by the type.  I wanted this too for my highlevel AST (but as you can see with the newtype stuff, it can be very unpretty).  However once I had completely typed my input and added the necessary tagging to ensure everything was correct, I then moved onto a lower AST (namely ANF) where I used the proposed solution.  However if you want the type-guaranteed labelling per node, this solution will not work.

cheers

Klaus Ostermann wrote:
> Hi Christophe,
> 
> you are right of course. It works with a custom newtype.
> 
> I still wonder whether it is possible to do the same by reusing the "Mu"
> type constructor. It captures exactly the recursion structure you use for
> the LabeledExp type, hence it would be nice to reuse it here.
> 
> Thanks for the GADT suggestion. I assume you are referring to Bringert's
> ICFP'06 paper? I will take a look.
> 
> Klaus
> 
> -----Original Message-----
> From: Christophe Poucet [mailto:christophe.poucet at gmail.com] 
> Sent: Thursday, August 03, 2006 1:02 PM
> To: Klaus Ostermann
> Cc: haskell-cafe at haskell.org
> Subject: Re: [Haskell-cafe] Variants of a recursive data structure
> 
> Hello,
> 
> I have had similar difficulties.  My first approach (for my AST) was to use
> indirect composite.  You seem to have the beginnings of that.  However it
> would require a custom newtype for each AST form:
> 
> data Exp e = Num Int | Add e e
> 
> newtype SimpleExp = Exp SimpleExp
> newtype LabeledExp = Labelled (Exp LabeledExp)
> 
> 
> For my reduced AST, however, I switched to a different principle.  I
> combined the idea of tagging with the concepts of GADTs and this worked
> quite succesfully.  It even makes it very easy to remove any tagging:
> 
> data Exp_;
> 
> data Exp :: * -> *
>   Num :: Int -> Exp a 
>   Exp :: Exp a -> Exp a -> Exp a
>   Tag :: a -> Exp a -> Exp a
> 
> I have combined this with bringert's GADT paper and that worked quite
> successfully.  (However in my case it is a GADT with two parameters as I
> don't only have Exp's, so it would look more like this:
> 
> data Exp_;
> data Var_;
> data Value_;
> data Exp :: * -> * -> * where
>   VDef   :: String -> Exp Var_ tag
>   VVar   :: Exp Var_ tag -> Exp Value_ tag
>   EValue :: Exp Value_ tag -> Exp Exp_ tag
>   EAdd   :: Exp Exp_ tag -> Exp Exp_ tag -> Exp Exp_ tag
>   Tag    :: tag -> Exp a tag -> Exp a tag
> 
> )
> 
> Hope this helps,
> 
> Cheers
> 
> Klaus Ostermann 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
>>
> 
> 


-- 
Christophe Poucet
Ph.D. Student
DESICS - DDT

Phone:+32 16 28 87 20
E-mail: Christophe (dot) Poucet (at) imec (dot) be
IMEC vzw – Register of Legal Entities Leuven VAT BE 0425.260.668 – Kapeldreef 75, B-3001 Leuven, Belgium – http://www.imec.be
--------------------------------------------------------------------------------
<IMEC e-mail disclaimer: http://www.imec.be/wwwinter/email-disclaimer.shtml>


More information about the Haskell-Cafe mailing list