Variants of a recursive data structure

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

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@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
--------------------------------------------------------------------------------

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
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@gmail.com] Sent: Thursday, August 03, 2006 1:02 PM To: Klaus Ostermann Cc: haskell-cafe@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: 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@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
----------------------------------------------------------------------------
----

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@gmail.com] Sent: Thursday, August 03, 2006 1:02 PM To: Klaus Ostermann Cc: haskell-cafe@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
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
Klaus Ostermann wrote: 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@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
--------------------------------------------------------------------------------

Hi, I'm no expert, but was wondering, why not make labelled AST a tree, which nodes are tupples holding a node of unlabeled tree and a label ? Regards, -- Intelligence is like a river: the deeper it is, the less noise it makes

On 03/08/06, Piotr Kalinowski
I'm no expert, but was wondering, why not make labelled AST a tree, which nodes are tupples holding a node of unlabeled tree and a label ?
Ups, I'm stupid. I guess I should think more before typing anything next time... Regards, -- Intelligence is like a river: the deeper it is, the less noise it makes

On Thu, Aug 03, 2006 at 12:51:01PM +0200, Klaus Ostermann wrote:
To: haskell-cafe@haskell.org From: Klaus Ostermann
Date: Thu, 3 Aug 2006 12:51:01 +0200 Subject: [Haskell-cafe] Variants of a recursive data structure 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.
if you don't need to enforce that an exp is either completely labelled or not at all, how about this?: data Exp = Num Int | Add Exp Exp | Label Exp String this allows you to attach labels wherever you want, at the cost of an extra case each time you take an expression apart, which can be done in a separate function: unlabel :: Exp -> Exp unlabel (Label e _) = unlabel e unlabel (Add e e') = Add (unlabel e) (unlabel e')
The icing on the cake would be if it would also be possible to have a function
unlabel :: LabeledExp -> Exp
that function is almost identical to the one above. cheers, matthias

Dear Matthias, I did not choose your approach because I want the type system to enforce that I have either completely labelled AST or completely unlabelled ASTs. Klaus

Hello Klaus, Thursday, August 3, 2006, 2:51:01 PM, you wrote:
data SimpleExp = Num Int | Add SimpleExp SimpleExp
data LabelledExp = LNum Int String | LAdd LabelledExp LabelledExp String
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?
Template Haskell (compile-time code generator) can be used to automatically generate unlabel and SimpleExp from the LabelledExp definition. you can also see to other generic programming solutions which was overviewed in http://dfa.imn.htwk-leipzig.de/~waldmann/draft/meta-haskell/second.pdf -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Oops again, not only am I addicted to flags, I also don't think before
I write. Sorry for spamming like this. :-(
The definition of the Or class I gave is incorrect. Of course it needs
a functional dependency to work correctly, like this:
class (TBool a, TBool b, TBool c) => Or a b c | a b -> c
instance Or TFalse TFalse TFalse
instance (TBool x) => Or TTrue x TTrue
instance Or TFalse TTrue TTrue
Still no flags needed as there is no overlap between the instances.
And this time I've actually verified that it works. ;-)
/Niklas
On 8/3/06, Niklas Broberg
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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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@gmail.com]
Sent: Thursday, August 03, 2006 5:15 PM
To: Klaus Ostermann
Cc: haskell-cafe@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
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
wrote: Hi all,
I have a problem which is probably not a problem at all for Haskell
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
experts, 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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 8/3/06, Klaus Ostermann
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)
I'm not sure it *is* better, I guess it's a matter of taste, and just what you want to do with it. I also realize that it's not quite what you wanted in your first post, since my definition will not require every subexpression to be labelled, and there can be labels on already labelled expressions. None of this is possible with the two-tier indirect composite you show above, but on the other hand it will guarantee that it follows a given structure (this guarantee could be added to my data type with more type class hackery though). The main advantage I can see is that functions written to work over full expressions, Exp a, automatically work on simple expressions, since it's the same data type. For instance, if you write eval :: Exp a -> Int eval (Num n) = n eval (Add e1 e2) = eval e1 + eval e2 eval (Label _ e) = eval e you could use eval on terms of type SimpleExp without further ado. But if you have no use for this functionality, then it won't be an advantage to you. Something that could be considered a disadvantage is that it requires the use of GADTs, which are only supported by GHC, and that support is still somewhat shaky. Hope this helps you in deciding what to use! :-) /Niklas

Hi Niklas,
thanks for your suggestion. Can you explain how your solution is better
On Thu, Aug 03, 2006 at 05:25:07PM +0200, Klaus Ostermann wrote: 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)
hmm, I'm not sure it works, if at all. With the above definition how do you construct a vallue of SimpleExp? In hugs, I type Main> :t Num 1 Num 1 :: Exp a but then Main> Num 1 :: SimpleExp ERROR - Type error in type annotation *** Term : Num 1 *** Type : Exp a *** Does not match : SimpleExp Here is a solution to your original problem. The proper way is to do type level fixpoint
data Fix a = Fix (a (Fix a))
(which you called Mu), and also a sum type, which is explained below. So initially you want Exp
data Exp e = Num Int | Add e e
Now, Fix Exp becomes what you want for the simple expression.
type SimpleExp = Fix Exp
Here is a little evaluation function eval :: SimpleExp -> Int eval (Fix (Num i)) = i eval (Fix (Add e1 e2)) = eval e1 + eval e2 But this is not exactly versatile, you may want to extend the eval when you add new data constructors. Here is a better one
e eval (Num i) = i e eval (Add e1 e2) = eval e1 + eval e2
so to evaluate SimpleExp, you use
evalE :: SimpleExp -> Int evalE (Fix e1) = e evalE e1
evalE is actually a fixed point of e. Then you want to label the Exp, but without duplicating the Exp structure.
data Label e = Label String e
the eval for Labelled stuff is just
f eval (Label _ e) = eval e
By now, both Exp and Label are actually type level functions. To make Label as an extension to Exp type, you need the fixed point of the sum of them, i.e., this fixed point is both the fixed point of Exp and Label.
data Sum a b c = Lt (a c) | Rt (b c)
Fix (Sum Exp Label) is all you need!
type LabelledExp = Fix (Sum Exp Label)
eval for the LabelledExp is
g eval (Lt x) = e eval x g eval (Rt y) = f eval y
evalLE :: LabelledExp -> Int evalLE (Fix e1) = g evalLE e1
So we have achieved extending both original data type and evaluation function without modifying them. to easily construct data of LabelledExp, little helpers are handy
num = Fix . Lt . Num add x = Fix . Lt . (Add x) label l = Fix . Rt . (Label l)
here are a few examples of using them
t1 = num 1 t2 = add t1 t1 t1' = label "t1" t1 t2' = label "t2" (add t1' t1')
to convert from LabelledExp to SimpleExp is also easy
unlabel :: LabelledExp -> SimpleExp unlabel (Fix (Rt (Label _ e1))) = unlabel e1 unlabel (Fix (Lt (Num i))) = Fix (Num i) unlabel (Fix (Lt (Add e1 e2))) = Fix (Add (unlabel e1) (unlabel e2))
This solution perhaps isn't what you intended, as it doesn't enforce that there must be a Label for every LabelledExp value. But it is a nice way to show how to extend data types and their functions without modifying them. Regards, Paul Liu

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Klaus Ostermann schrieb:
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.
How about the following simple parameterization? data Exp label = LNum Int label | LAdd (Exp label) (Exp label) label type SimpleExp = Exp () mkNum i = LNum i () type LabelledExp = Exp String Cheers Christian

Christian Maeder schrieb:
How about the following simple parameterization?
data Exp label = LNum Int label | LAdd (Exp label) (Exp label) label
It seems I've forgotten some icing. Usually I provide the following datatype and function for folding in order to avoid many explicit recursive calls. data FoldExp label c = FoldExp { foldLNum :: Exp label -> Int -> label -> c , foldLAdd :: Exp label -> c -> c -> label -> c } foldExp :: FoldExp label c -> Exp label -> c foldExp f e = case e of LNum i l -> foldLNum f e i l LAdd e1 e2 l -> foldLAdd f e (foldExp f e1) (foldExp f e2) l Your mapping can be defined than as: mapLabel :: Exp label -> Exp () mapLabel = foldExp FoldExp { foldLNum = \ _ i _ -> LNum i () , foldLAdd = \ _ e1 e2 _ -> LAdd e1 e2 () } This still requires to list all variants in this case but saves the recursive calls. (The lambda-terms could be shorter if the labels were the first argument of every constructor.) The first argument of each fold-field is not necessary here but may come in handy if you want to process the expressions not only bottom up but also top-down. (The original expression are also available i.e. in a lambda-term "foldLAdd = \ (LAdd o1 o2 _) e1 e2 _ -> ...") The above record datatype and the corresponding fold function(s) could be derived somehow (with TH-haskell) -- even for mutual recursive data types. Cheers Christian
participants (10)
-
Bulat Ziganshin
-
Christian Maeder
-
Christophe Poucet
-
Josef Svenningsson
-
Klaus Ostermann
-
Matthias Fischmann
-
Nicolas Frisby
-
Niklas Broberg
-
paul@theV.net
-
Piotr Kalinowski