[Haskell-cafe] DSLs and heterogeous lists

Corentin Dupont corentin.dupont at gmail.com
Sat Feb 1 15:55:09 UTC 2014


Hi again,
I have a game in which the user can create/write/read variables, using a
small DSL. The type of the variable created can be whatever chooses the
user, so I'm using existential types to store those variables in a
heterogeneous list.
This works fine, but the problem is that the "Typeable" class tag leaks
into the DSL... The question is, how to get rid of it?

> This is literate Haskell
> {-# LANGUAGE GADTs, ScopedTypeVariables  #-}
> module DSLClass where
> import Control.Monad
> import Control.Monad.State
> import Data.Typeable
>

This is the (simplified) DSL. With it you can read a variable stored in the
game state (creation/writing is not shown).
How can we get rid of the "Typeable a" in the ReadFirstVar constructor?

> -- first type parameter is used to track effects
> data Exp a where
>   ReadFirstVar :: (Typeable a) => Exp a           <----- Ugly
>   Return       :: a -> Exp a
>   Bind         :: Exp a -> (a -> Exp b) -> Exp b

This is the definition of a variable. The type is unknow, so I use
existantial types.

> data Var = forall a . (Typeable a) => Var { v :: a}

This game state. It holds the heterogenous list.

> data Game = Game { variables :: [Var]}

The evaluation of "Exp" can be:

> eval :: Exp a -> State Game a
> eval ReadFirstVar  = do
>   (Game ((Var v):vs)) <- get
>   case cast v of
>      Just val -> return val
>      Nothing -> error "no cast"
> eval (Bind exp f) = do
>   a <- eval exp
>   eval (f a)


As you can see, I'm obliged to cast the variable type to match it with the
expression's type. Is that the right place to do it?

Thanks!!
Corentin
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140201/4aa4c00e/attachment.html>


More information about the Haskell-Cafe mailing list