[Haskell-cafe] extensible data types in Haskell?

Ryan Ingram ryani.spam at gmail.com
Mon Jul 7 18:13:31 EDT 2008


I like the approach the "Data Types a la Carte" paper takes to solve
this problem.

There's a small discussion here:
http://wadler.blogspot.com/2008/02/data-types-la-carte.html

Summary: if you model your data types as functors, typeclass machinery
lets you combine them into an extensible whole, while maintaining type
safety.  You then create an "interpretation" class which allows data
to choose how it interacts with a particular computation.

The biggest weakness is that you need a type annotation at the point
of calling the "interpretation" function.  An example (leaving out the
"library" bits):

class Functor a => EvalSimple a where
    evalSimple :: a Int -> Int
instance (EvalSimple a, EvalSimple b) => EvalSimple (a :+: b) where
    evalSimple (Inl a) = evalSimple a
    evalSimple (Inr b) = evalSimple b

-- foldExpr :: Functor e => (e a -> a) -> Expr e -> a
-- eval :: EvalSimple e => Expr e -> Int
eval e = foldExpr evalSimple e

newtype Val a = Val Int -- "trivial" functor
instance Functor Val where fmap _ (Val x) = (Val x)
instance EvalSimple Val where evalSimple (Val x) = x
val x = inject (Val x)
-- inject :: a :<: e => a (Expr e) -> Expr e
-- val :: Val :<: e => Int -> Expr e


data Add a = Add a a -- "pair" functor
instance Functor Add where fmap f (Add a b) = Add (f a) (f b)
add a b = inject (Add a b)
instance EvalSimple Add where evalSimple (Add a b) = a + b

-- here is where we need the type annotation
sample :: Expr (Val :+: Add)
sample = add (add (val 1) (val 2)) (val 3)

sampleResult = eval sample  -- is 6

On 7/6/08, David Walker <princedpw at gmail.com> wrote:
> Hi all,
>
> SML conveniently contains the type "exn" which is an instance of an
> "extensible data type".  In other words, unlike normal data types that
> are "closed" (can't admit new constructors once defined), SML's exn
> type is "open," allowing programmers to keep adding new alternatives
> as often as they choose.  Like normal datatypes, the elimination form
> for an extensible data type is a case statement (or match function).
>
> Friends have told me that Haskell doesn't have extensible data types.
> However, it seems fairly straightforward to code them up using type
> classes....though the solution I'm thinking of has a little bit of
> boilerplate I'd like to scrap (you have to define a new type
> declaration *and* an instance of a type class with a "match" method)
> and matching occurs through a string comparison (which can lead to
> silly programmer errors if there is accidentally a typo in the
> string).
>
> Anyway, it's possible with some thought I could come up with a better
> solution, but before worrying about it, I figured I'd ask if anybody
> else already has a package that does this.  It seems like a pretty
> natural feature to want to have.
>
> Thanks in advance,
> Dave
> _______________________________________________
> 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