[Haskell-cafe] Map constructor in a DSL
Ryan Ingram
ryani.spam at gmail.com
Tue Oct 26 16:53:35 EDT 2010
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
<corentin.dupont at gmail.com> 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 <chrisdone at googlemail.com>
> wrote:
>>
>> On 26 October 2010 18:07, Dupont Corentin <corentin.dupont at gmail.com>
>> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
More information about the Haskell-Cafe
mailing list