Map constructor in a DSL

Hello café, I have a little DSL in my program as follow. Now I'd like to add a Map constructor in it. Thats where I would need help!
data Obs a where
AllPlayers :: Obs [Int] Plus :: (Num a) => Obs a -> Obs a -> Obs a And :: Obs Bool -> Obs Bool -> Obs Bool Vote :: Obs String -> Obs Int -> Obs Bool *Map :: (Obs a -> Obs b) -> Obs [a] -> Obs [b]* -- and others
Here is the evaluator for Obs:
evalObs :: Obs a -> Evaluator a evalObs (Konst a) = return $ pure a evalObs (Not a) = liftE not (evalObs a) evalObs (Plus a b) = liftE2 (+) (evalObs a) (evalObs b) evalObs (Minus a b) = liftE2 (-) (evalObs a) (evalObs b) evalObs (Time a b) = liftE2 (*) (evalObs a) (evalObs b) evalObs (And a b) = liftE2 (&&) (evalObs a) (evalObs b) evalObs (Or a b) = liftE2 (||) (evalObs a) (evalObs b) evalObs (Equ a b) = liftE2 (==) (evalObs a) (evalObs b) evalObs (If a b c) = liftE3 (if3) (evalObs a) (evalObs b) (evalObs c)
How you can see it is quite neat... But how can I write the evaluator for Map? Actually I have some half baked solution, 15 lines long that I don't dare to show ;) Actually compiling code excerpt is here: http://hpaste.org/40897/map_contstructor_in_a_dsl Thanks for your help. Corentin Below is some helper code: type Evaluator a = StateT Game Comm a (Either Actions a) -- | Combined lifters for Evaluator liftE = liftM . liftA liftE2 = liftM2 . liftA2 liftE3 = liftM3 . liftA3 instance Applicative (Either Actions) where pure x = Right x (Right f) <*> (Right x) = Right $ f x (Right _) <*> (Left u) = Left u (Left u) <*> (Right _) = Left u (Left u) <*> (Left v) = Left $ u ++ v

On 26 October 2010 18:07, Dupont Corentin
But how can I write the evaluator for Map?
Where do values for PlayerNumber come from? Unless I'm mistaken, the only thing that Map can be used with is Obs [PlayerNumber], a list of values PlayerNumber which we have no means of acquiring in order to provide to the Map function.

Hey Chris!
Values for PlayerNumber are acquired at evaluation time, from the state of
the system.
I have not included the evaluation of AllPlayers.
Here how it looks:
evalObs AllPlayers = return . pure =<< gets players
But when you build your Obs, you have yet no idea how much players it will
be.
This is just symbolic at this stage.
To give you a better insight, here is want I want to do with Map:
everybodyVote :: Obs [Bool]
everybodyVote = Map (Vote (Konst "Please vote")) AllPlayers
In memory, everybodyVote is just a tree.
This rule can be executed latter whenever I want to perform this democratic
vote ;)
Hope this answer to your question.
Corentin
On Tue, Oct 26, 2010 at 7:17 PM, Christopher Done
On 26 October 2010 18:07, Dupont Corentin
wrote: But how can I write the evaluator for Map?
Where do values for PlayerNumber come from? Unless I'm mistaken, the only thing that Map can be used with is Obs [PlayerNumber], a list of values PlayerNumber which we have no means of acquiring in order to provide to the Map function.

Instead of answering your question directly, I'll give you some code
for a different DSL:
data Exp ref a where
EVar :: ref a -> Exp ref a
ELam :: (ref a -> Exp ref b) -> Exp ref (a -> b)
EAp :: Exp ref (a -> b) -> Exp ref a -> Exp ref b
-- simple data structures
EPair :: Exp ref a -> Exp ref b -> Exp ref (a,b)
EFst :: Exp ref (a,b) -> Exp ref a
ESnd :: Exp ref (a,b) -> Exp ref b
ELeft :: Exp ref a -> Exp ref (Either a b)
ERight :: Exp ref b -> Exp ref (Either a b)
EEither :: Exp ref (a -> c) -> Exp ref (b -> c) -> Exp ref (Either
a b) -> Exp ref c
-- closed expressions can work for any reference type
typedef CExp a = (forall ref. CExp ref a)
newtype SimpleRef a = SR a
evalSimple :: Exp SimpleRef a -> a
evalSimple (EVar (SR a)) = a
evalSimple (ELam f) = \x -> evalSimple $ f (SR x)
evalSimple (EAp e1 e2) = evalSimple e1 $ evalSimple e2
evalSimple (EPair e1 e2) = (evalSimple e1, evalSimple e2)
evalSimple (EFst e) = fst $ evalSimple e
evalSimple (ESnd e) = snd $ evalSimple e
evalSimple (ELeft e) = Left $ evalSimple e
evalSimple (ERight e) = Right $ evalSimple e
evalSimple (EEither l r e) = either (evalSimple l) (evalSimple r) (evalSimple e)
eval :: CExp a -> a
eval = evalSimple
-- some examples
eid :: CExp (a -> a)
eid = ELam (\r -> EVar r)
type EBool = Either (a -> a) (a -> a)
true :: CExp EBool
true = ELeft eid
false :: CExp EBool
false = ERight eid
eif :: CExp (EBool -> a -> a -> a)
eif = ELam $ \b -> ELam $ \t -> ELam $ \f -> EEither (ELam $ \_ ->
EVar t) (ELam $ \_ -> EVar f) b
The key is in EVar/ELam; this gives you the ability to do actual
abstraction. And you can use different reference types to create
different kinds of interpreters. A fun exercise is writing an
interpreter that prints out the expression; that is, implement
"showExp :: CExp -> String". My implementation shows eif as
ELam (\x -> ELam (\y -> ELam (\z -> EEither (ELam (\w -> EVar y))
(ELam (\w -> EVar z)) x)
I'm assuming that the inside of "evalObs (Map ...)" is a giant mess of
operations. This 'higher order' way of representing expressions has
tended to simplify that mess for me.
-- ryan
On Tue, Oct 26, 2010 at 10:42 AM, Dupont Corentin
Hey Chris! Values for PlayerNumber are acquired at evaluation time, from the state of the system.
I have not included the evaluation of AllPlayers. Here how it looks:
evalObs AllPlayers = return . pure =<< gets players
But when you build your Obs, you have yet no idea how much players it will be. This is just symbolic at this stage.
To give you a better insight, here is want I want to do with Map:
everybodyVote :: Obs [Bool] everybodyVote = Map (Vote (Konst "Please vote")) AllPlayers
In memory, everybodyVote is just a tree. This rule can be executed latter whenever I want to perform this democratic vote ;)
Hope this answer to your question. Corentin
On Tue, Oct 26, 2010 at 7:17 PM, Christopher Done
wrote: On 26 October 2010 18:07, Dupont Corentin
wrote: But how can I write the evaluator for Map?
Where do values for PlayerNumber come from? Unless I'm mistaken, the only thing that Map can be used with is Obs [PlayerNumber], a list of values PlayerNumber which we have no means of acquiring in order to provide to the Map function.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi,
I think you may want to over think your types again.
Especially your Evaluator-Monad, and maybe your Map constructor.
The Problem is, due to your use of Either and the need for evalObs to
finally transform from "Obs [a]" type to "Evaluator [a]" you will end
up in another Monad for Either:
instance Monad (Either Actions) where
return = Right
(Left x) >>= _ = Left x
(Right a) >>= f = f a
Then one solution may be:
evalObs (Map f obs) = evalMap (f.Konst) (evalObs obs)
evalMap :: (a -> Obs b) -> Evaluator [a] -> Evaluator [b]
evalMap f o = liftE (map evalObs) (liftE (map f) o) >>= \x ->
case x of
Left actions -> return $ Left actions
Right evals -> sequence evals >>= return .
sequence
-- first "sequence evals" creates [Either Actions a]
-- second "sequence" create Either Actions [a]
After building up the "Evaluator [a]" construct inside your Evaluator-
Monad, you have to join the construct "evals" back into your real
Monad and since you pass around results using Either inside your
Evaluator-Monad, you have to treat the Either-type just like another
Monad.
If you get stuck on your types, define new toplevel functions (as
undefined) each taking one argument less and play with the types in
your files and in ghci until it begins to make sense.
On 26 Okt., 19:42, Dupont Corentin
Hey Chris! Values for PlayerNumber are acquired at evaluation time, from the state of the system.
I have not included the evaluation of AllPlayers. Here how it looks:
evalObs AllPlayers = return . pure =<< gets players
But when you build your Obs, you have yet no idea how much players it will be. This is just symbolic at this stage.
To give you a better insight, here is want I want to do with Map:
everybodyVote :: Obs [Bool] everybodyVote = Map (Vote (Konst "Please vote")) AllPlayers
In memory, everybodyVote is just a tree. This rule can be executed latter whenever I want to perform this democratic vote ;)
Hope this answer to your question. Corentin
On Tue, Oct 26, 2010 at 7:17 PM, Christopher Done
wrote: On 26 October 2010 18:07, Dupont Corentin
wrote: But how can I write the evaluator for Map?
Where do values for PlayerNumber come from? Unless I'm mistaken, the only thing that Map can be used with is Obs [PlayerNumber], a list of values PlayerNumber which we have no means of acquiring in order to provide to the Map function.
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

Ah, it's too early in the morning... There is still some room to simplify (e.g. fuse the liftE (map ...) ops). Here a simpler Version: evalObs (Map f obs) = liftE (map (evalObs.f.Konst)) (evalObs obs)
= either (return.Left) (sequence >=> return . sequence)
On 27 Okt., 06:12, steffen
Hi,
I think you may want to over think your types again. Especially your Evaluator-Monad, and maybe your Map constructor.
The Problem is, due to your use of Either and the need for evalObs to finally transform from "Obs [a]" type to "Evaluator [a]" you will end up in another Monad for Either:
instance Monad (Either Actions) where return = Right (Left x) >>= _ = Left x (Right a) >>= f = f a
Then one solution may be:
evalObs (Map f obs) = evalMap (f.Konst) (evalObs obs)
evalMap :: (a -> Obs b) -> Evaluator [a] -> Evaluator [b] evalMap f o = liftE (map evalObs) (liftE (map f) o) >>= \x -> case x of Left actions -> return $ Left actions Right evals -> sequence evals >>= return . sequence -- first "sequence evals" creates [Either Actions a] -- second "sequence" create Either Actions [a]
After building up the "Evaluator [a]" construct inside your Evaluator- Monad, you have to join the construct "evals" back into your real Monad and since you pass around results using Either inside your Evaluator-Monad, you have to treat the Either-type just like another Monad.
If you get stuck on your types, define new toplevel functions (as undefined) each taking one argument less and play with the types in your files and in ghci until it begins to make sense.
On 26 Okt., 19:42, Dupont Corentin
wrote: Hey Chris! Values for PlayerNumber are acquired at evaluation time, from the state of the system.
I have not included the evaluation of AllPlayers. Here how it looks:
evalObs AllPlayers = return . pure =<< gets players
But when you build your Obs, you have yet no idea how much players it will be. This is just symbolic at this stage.
To give you a better insight, here is want I want to do with Map:
everybodyVote :: Obs [Bool] everybodyVote = Map (Vote (Konst "Please vote")) AllPlayers
In memory, everybodyVote is just a tree. This rule can be executed latter whenever I want to perform this democratic vote ;)
Hope this answer to your question. Corentin
On Tue, Oct 26, 2010 at 7:17 PM, Christopher Done
wrote: On 26 October 2010 18:07, Dupont Corentin
wrote: But how can I write the evaluator for Map?
Where do values for PlayerNumber come from? Unless I'm mistaken, the only thing that Map can be used with is Obs [PlayerNumber], a list of values PlayerNumber which we have no means of acquiring in order to provide to the Map function.
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

Thank you for your rich responses. Indeed I think I miss some thinks in my DSL, that would make things easier to deal with lists and first class functions. I don't really know what for now. Perhaps a List Constructor? Or a constructor on functions like yours Ryan? EAp :: Exp ref (a -> b) -> Exp ref a -> Exp ref b It's from which DSL? It is accessible on the net? Chris suggested me that I can only define the Foldr constructor and deduce Map from it. But maybe I have to add a List constructor for that. But in the suggestions from Ryan and Brandon I don't understand why I should add an extra type parameter and what it is! Steffen: Wow nice. I'll integrate that ;) I'm also looking at the Atom's DSL to get inspiration. Something I don't understand in it is that it has two languages, on typed: data E a where VRef :: V a -> E a Const :: a -> E a Cast :: (NumE a, NumE b) => E a -> E b Add :: NumE a => E a -> E a -> E a etc. And, along with it, an untyped counterpart: -- | An untyped term. data UE = UVRef UV | UConst Const | UCast Type UE | UAdd UE UE etc. What that for? What's the use of having beautiful GADT if you have to maintain an untyped ADT aside?? Corentin

I think you would love to have a look at AwesomePrelude[1] or a fork
of AwesomePrelude using associated types[2]
Some more background information by Tom Lokhorst [3][4].
[1] http://github.com/tomlokhorst/AwesomePrelude
[2] http://github.com/urso/AwesomePrelude
[3] http://tom.lokhorst.eu/2009/09/deeply-embedded-dsls
[4] http://tom.lokhorst.eu/2010/02/awesomeprelude-presentation-video
On 28 Okt., 12:09, Dupont Corentin
Thank you for your rich responses.
Indeed I think I miss some thinks in my DSL, that would make things easier to deal with lists and first class functions. I don't really know what for now. Perhaps a List Constructor? Or a constructor on functions like yours Ryan? EAp :: Exp ref (a -> b) -> Exp ref a -> Exp ref b It's from which DSL? It is accessible on the net?
Chris suggested me that I can only define the Foldr constructor and deduce Map from it. But maybe I have to add a List constructor for that.
But in the suggestions from Ryan and Brandon I don't understand why I should add an extra type parameter and what it is!
Steffen: Wow nice. I'll integrate that ;)
I'm also looking at the Atom's DSL to get inspiration. Something I don't understand in it is that it has two languages, on typed:
data E a where VRef :: V a -> E a Const :: a -> E a Cast :: (NumE a, NumE b) => E a -> E b Add :: NumE a => E a -> E a -> E a etc.
And, along with it, an untyped counterpart:
-- | An untyped term. data UE = UVRef UV | UConst Const | UCast Type UE | UAdd UE UE etc.
What that for? What's the use of having beautiful GADT if you have to maintain an untyped ADT aside??
Corentin
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

This is really cool.
The blog post [3] finally explained to me why I had so much difficulties
implementing the Equal constructor ;)
I shared this in a previous thread:
http://osdir.com/ml/haskell-cafe@haskell.org/2010-06/msg00369.html
Maybe latter I'll shift to a class type based DSL. They seem more generic
than data type based.
Corentin
On Thu, Oct 28, 2010 at 2:02 PM, steffen
I think you would love to have a look at AwesomePrelude[1] or a fork of AwesomePrelude using associated types[2] Some more background information by Tom Lokhorst [3][4].
[1] http://github.com/tomlokhorst/AwesomePrelude [2] http://github.com/urso/AwesomePrelude [3] http://tom.lokhorst.eu/2009/09/deeply-embedded-dsls [4] http://tom.lokhorst.eu/2010/02/awesomeprelude-presentation-video
On 28 Okt., 12:09, Dupont Corentin
wrote: Thank you for your rich responses.
Indeed I think I miss some thinks in my DSL, that would make things easier to deal with lists and first class functions. I don't really know what for now. Perhaps a List Constructor? Or a constructor on functions like yours Ryan? EAp :: Exp ref (a -> b) -> Exp ref a -> Exp ref b It's from which DSL? It is accessible on the net?
Chris suggested me that I can only define the Foldr constructor and deduce Map from it. But maybe I have to add a List constructor for that.
But in the suggestions from Ryan and Brandon I don't understand why I should add an extra type parameter and what it is!
Steffen: Wow nice. I'll integrate that ;)
I'm also looking at the Atom's DSL to get inspiration. Something I don't understand in it is that it has two languages, on typed:
data E a where VRef :: V a -> E a Const :: a -> E a Cast :: (NumE a, NumE b) => E a -> E b Add :: NumE a => E a -> E a -> E a etc.
And, along with it, an untyped counterpart:
-- | An untyped term. data UE = UVRef UV | UConst Const | UCast Type UE | UAdd UE UE etc.
What that for? What's the use of having beautiful GADT if you have to maintain an untyped ADT aside??
Corentin
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp:// www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2010-10-28 12:09, Dupont Corentin skrev:
I'm also looking at the Atom's DSL to get inspiration. Something I don't understand in it is that it has two languages, on typed:
data E a where VRef :: V a -> E a Const :: a -> E a Cast :: (NumE a, NumE b) => E a -> E b Add :: NumE a => E a -> E a -> E a
etc.
And, along with it, an untyped counterpart:
-- | An untyped term. data UE
= UVRef UV | UConst Const
| UCast Type UE | UAdd UE UE
etc.
What that for? What's the use of having beautiful GADT if you have to maintain an untyped ADT aside??
The general reason for this (I can't speak for Atom specifically) is that the typed representation can be quite hard to work with when you want to transform the expressions. But you can still often limit the use of the untyped representation to the last stages in the backend, which means that you can enjoy the typed representation in the initial stages. In the development version of Feldspar, we use a typed representation combined with type-safe casting using Data.Typeable. Although not ideal, this seems to be better than having two different representations. / Emil

On Thu, Oct 28, 2010 at 3:09 AM, Dupont Corentin
EAp :: Exp ref (a -> b) -> Exp ref a -> Exp ref b It's from which DSL? It is accessible on the net?
It's my own, just written off the top of my head as an example. Accessible "on the net": yes, it's in your email. there's nothing more.
But in the suggestions from Ryan and Brandon I don't understand why I should add an extra type parameter and what it is!
I don't know in Brandon's case, but in my case it's for two reasons: (1) It allows you to write multiple interpreters for the language by changing the type of variables passed around. But, that's not important if you are only planning to have a single interpreter. (2) By parametricity, any CExp can't inspect the "insides" of a reference; all ELam can do with its argument is pass it to EVar. If you have a concrete variable type, you can do weird things like ELam (\(V x) -> EVar (V (x+1))) which doesn't quite make sense. (how are you returning a variable containing a different value than the one you passed in? -- ryan
participants (5)
-
Christopher Done
-
Dupont Corentin
-
Emil Axelsson
-
Ryan Ingram
-
steffen