Indirect composite

From HaskellWiki
Revision as of 09:25, 7 October 2011 by Danr (talk | contribs) (Add two-level-types article link)
Jump to navigation Jump to search

Sometimes you want different versions of an algebraic data type. For example, you might want one version with decorating structures and one without, or you might want to use hash consing to build your data structures. However, you don't want to duplicate constructors for all of the different versions of what is essentially the same data structure.

A solution is to make the recursion in the type indirect.

Take, for example, this simple lambda calculus type :

data Expr
    = EApp Expr Expr
    | EVar String
    | ELambda String Expr
    | ELet String Expr Expr

An indirectly recursive version is this:

data Expr' expr
    = EApp expr expr
    | EVar String 
    | ELambda String expr
    | ELet String expr expr

newtype Expr = Expr (Expr' Expr)

-- Alternative version which uses a type-level [[fixed point combinator]]
newtype Fix f = In { out :: f (Fix f) }

type Expr2 = Fix Expr'

You can then produce a version with decorations:

data DExpr d
    = DExpr d (Expr' (DExpr d))

or a mutable version which uses IORefs:

newtype IOExpr
    = IOExpr (Expr' (IORef IOExpr))

or a non-recursive version ready for hash consing:

type HCExpr
    = Expr' Int

User:AndrewBromage

An excellent article which discusses this in more detail is [http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.83.500

Two-level types and parameterized modules (2003)], 

by Tim Sheard and Emir Pasalic.