[Haskell-cafe] Cyclic Type-synonyms

Christophe Poucet christophe.poucet at gmail.com
Wed Jul 5 11:16:08 EDT 2006


Hello,

I use the Indirect Composite pattern a lot, and this means that typically,
especially with recursive types (such as an AST), you end up with a lot of
data-constructors.  I understand that it is not possible to have pure cyclic
types (because haskell requires iso-recursive and not equi-recursive
types).  However I wonder why certain cases can not be allowed.

For instance, assume the following somewhat simplified AST:

data Exp e =
    ELet String e e    -- let x = a in b
  | ECond e e e       -- If then else construct

Now if I wanted to decorate this structure, I would use something like:

data AnnotExp a = AE {
  unAE :: Exp (AnnotExp a),
  note :: a
}

However, and this example might be slightly too trivial to motivate it,
however it does exemplify what can be done, one might not want to annotate
at all and just have a recursive data AST.  At this point, one either uses
AnnotExp () or creates a new data type.  It would be nice if instead one
could use cyclic type-declarations, with the knowledge that we're going
through a data-constructor and hence the type iso-recursive and not
equi-recursive:

type AST = Exp AST  -- This is iso-recursive as it goes through the data
constructors ELet and ECond

Sadly this is not possible with the current GHC (I'm using 6..4.2).  Is this
possible with 6.6?  Is there any reason why this is not possible.  Feedback
regarding this is welcome.  A more motivating example can be seen below.

Cheers,
Christophe

-----------------------------
data Exp var ident func exp stm =
    ELit Lit                -- ^ Literals
  | EVar ident              -- ^ Identifiers
  | EData Const [exp]       -- ^ Data Constructors
  | ECall func              -- ^ Function Calls
  | ELet var stm stm        -- ^ Scoping
  | ECond exp stm stm       -- ^ Conditional
  | ELoop exp stm           -- ^ Looping
  deriving (Eq, Show)

data AExp exp annot = AExp {
  unAExp    :: exp,
  aexpNote  :: annot,
  aexpLoc   :: Location
}

type UnCorExp var annot =
  Exp
    var                                   -- ^ Let-binders
    var                                   -- ^ Named identifiers
    (Ident, [AExp UnCorExp var annot])    -- ^ Function calls
    (AExp UnCorExp var annot)             -- ^ Expressions
    (AExp UnCorExp var annot)             -- ^ Statements

-- Flattened AST: function parameters can only be variables, similar for
while- and if- conditions
type UnSimExp var annot
  Exp
    var                                   -- ^ Let-binders
    var                                   -- ^ Named identifiers
    (Ident, [var])                        -- ^ Function calls
    (var)                                 -- ^ Expressions
    (AExp UnSimExp var annot)             -- ^ Statements
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org//pipermail/haskell-cafe/attachments/20060705/19b9790f/attachment-0001.htm


More information about the Haskell-Cafe mailing list