Re: [Haskell-cafe] extensible data types in Haskell?

2008-07-08 Thread David Walker
thanks for everyone's help -- it seems the simplest solution is to use
the Typeable class, existential types and type-safe cast.

Cheers,
Dave

On Sun, Jul 6, 2008 at 9:18 PM, Don Stewart <[EMAIL PROTECTED]> wrote:
> princedpw:
>> 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
>> classesthough 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).
>
> You should probably use Typeable here, for the type matching, rather
> than a custom matcher. class Typeable a => Extensible a, this leads to a
> fairly straighforward extensible data type, where the open instance
> definition lets you add variants on the fly.
>
>> 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.
>
> There's a number of ways to do this, including fully statically via type
> classes and existential types, or via the Dynamic type.
>
> Googling for "expression problem Haskell" will turn up some things. Some
> implementions of open data types in use can be found in xmonad, and the
> extensible exceptions proposal here,
>
>
> http://209.85.173.104/search?q=cache:xeXhle5KAqkJ:www.haskell.org/~simonmar/papers/ext-exceptions.pdf
>
> -- Don
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] extensible data types in Haskell?

2008-07-08 Thread Pablo Nogueira
I prefer Bruno's approach, though. It allows meta-level type-checking
of expressions and there's the possibility of closing the extension
with a wrapper:
(References: "Generics as a Library" and his PhD thesis)

- GADT as a type class (or encode the type as it's fold):

 class Exp e where
 lit  :: TyRange a => a -> e a
 plus :: e Int -> e Int -> e Int
 and  :: e Bool -> e Bool -> e Bool

- Notice we cannot construct an ill-typed expression, the Haskell
type-checker complains.

- |TyRange| is the class of indices:

class TyRange a
instance TyRange Int
instance TyRange Bool

- The behaviour is given by instances:

newtype Eval a = Eval {eval :: a}

instance Exp Eval where
 lit   = Eval
 plus x y  = Eval (eval x + eval y)
 and  x y  = Eval (eval x && eval y)

Extension is easy:

class Exp e => ExpIf e where
   ifOp :: TyRange a => e Bool -> e a -> e a -> e a

instance ExpIf Eval where
   ifOp c t e = Eval (if (eval c) then (eval t) else (eval e))

class Exp e => ExpMult e where
mult :: e Int -> e Int -> e Int

instance ExpMult Eval where
mult x y = Eval (eval x * eval y)

- Adding new meta-level types is easy:

instance TyRange a => TyRange [a]
instance TyRange Char

class Exp e => ExpConcat e where
conc :: e [Char] -> e [Char] -> e [Char]

instance ExpConcat Eval where
conc x y = Eval (eval x ++ eval y)

- Closing expressions is also easy:  wrap around a type and provide
new functions:

data TyRange a => Wrap a = Wrap (forall e. (Exp e, ExpIf e, ExpMult e,
ExpConcat e) => e a)

> evalExp :: TyRange a => Wrap a -> a
> evalExp (Wrap x) = eval x

- Some expresions:

Compare:

exp1 :: Exp e => e Int
exp1 = plus (lit 3) (lit 3)
val1 = eval exp1

With:

exp1' :: Eval Int
exp1' = plus (lit 3) (lit 3)
va1'  = eval exp1
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] extensible data types in Haskell?

2008-07-07 Thread Ryan Ingram
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 <[EMAIL PROTECTED]> 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
> classesthough 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@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


Re: [Haskell-cafe] extensible data types in Haskell?

2008-07-06 Thread Don Stewart
princedpw:
> 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
> classesthough 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).

You should probably use Typeable here, for the type matching, rather
than a custom matcher. class Typeable a => Extensible a, this leads to a
fairly straighforward extensible data type, where the open instance
definition lets you add variants on the fly.

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

There's a number of ways to do this, including fully statically via type
classes and existential types, or via the Dynamic type.

Googling for "expression problem Haskell" will turn up some things. Some
implementions of open data types in use can be found in xmonad, and the
extensible exceptions proposal here,


http://209.85.173.104/search?q=cache:xeXhle5KAqkJ:www.haskell.org/~simonmar/papers/ext-exceptions.pdf

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] extensible data types in Haskell?

2008-07-06 Thread David Walker
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
classesthough 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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe