
Hi Haskell-Caféists! I have a small DSL for a game. Some instructions have effects (change the game state), some not. -> In short, my question is: how can I semantically separate instructions with effect from the others? i.e. how can I mark down and track those effects? Here is a simplified version of the DSL I use. First some boilerplate:
{-# LANGUAGE GADTs #-} import Control.Monad import Control.Monad.State import Control.Monad.Free
This is the DSL:
data Exp a where ReadAccount :: Exp Int WriteAccount :: Exp Int -> Exp () SetVictory :: Exp Bool -> Exp () OnTimer :: Exp () -> Exp () Return :: a -> Exp a Bind :: Exp a -> (a -> Exp b) -> Exp b
It can read and write to an account (belonging to the state of the game), set a victory condition, and trigger some event every minute.
instance Monad Exp where return = Return (>>=) = Bind
instance Functor Exp where fmap f e = Bind e $ Return . f
With that you can write:
victoryRule :: Exp () victoryRule = SetVictory $ do m <- ReadAccount return (m > 100)
"victoryRule" sets the victory condition to be: "if there is more than 100 gold in the account, you win." This is the game state:
data Game = Game { bankAccount :: Int, victory :: Exp Bool, timerEvent :: Exp ()}
The evaluation of "Exp" can be:
eval :: Exp a -> State Game a eval (SetVictory v) = modify (\g -> g{victory = v}) eval ReadAccount = get >>= return . bankAccount eval _ = undefined -- etc.
If you evaluate "victoryRule", you change the Game state by setting the victory field. Then, each time you will evaluate the victory field, you will know if you won or not (depending on your account...). This is all well and good, but imagine if you write:
victoryRule' :: Exp () victoryRule' = SetVictory $ do m <- ReadAccount WriteAccount (return $ m + 1) return (m > 100)
Ho no! Now each time a player is refreshing his screen (on the web interface), the victory condition is re-evaluated to be displayed again, and the bank account is increased by 1! This is not what we want. We should allow only effect-less (pure) instructions in the victory field, like readAccount, but not WriteAccount. How would you do that? I tried with the Free monad to delimit those effects. I re-write each primitives, marking them with the special type "Effect", when needed.
type Effect = Free Exp
-- readAccount remain the same: it has no effect readAccount :: Exp Int readAccount = ReadAccount
--writeAccount is marked as having an effect writeAccount :: Exp Int -> Effect (Exp ()) writeAccount ei = Pure $ WriteAccount ei
--onTimer is able to trigger an effect every minute onTimer :: Effect (Exp ()) -> Effect (Exp ()) onTimer e = Pure $ OnTimer $ iter join e
--victoryRule can be re-written like this, note that effects are rejected now victoryRule'' :: Effect (Exp ()) victoryRule'' = Pure $ SetVictory $ do m <- readAccount --writeAccount (return $ m + 1) --will be rejected at compile time (good)! return (m > 100)
--increase my bank account by 1 every minute myTimer :: Effect (Exp ()) myTimer = onTimer $ do m <- lift readAccount writeAccount (return $ m + 1)
I don't know if I got it right at all... How does it sound? It only bothers me that in this context "Pure" really means "Impure" :) Do you think of any other solution? Cheers, Corentin

The simplest way would be to add a phantom type parameter to Exp, i.e. data Exp e a where The 'e' variable would be used to track (and propagate) effects. It is then up to you to design your 'effect system' as you wish. Jacques On 2014-01-28 6:03 AM, Corentin Dupont wrote:
-> In short, my question is: how can I semantically separate instructions with effect from the others? i.e. how can I mark down and track those effects?
This is the DSL:
data Exp a where ReadAccount :: Exp Int WriteAccount :: Exp Int -> Exp () SetVictory :: Exp Bool -> Exp () OnTimer :: Exp () -> Exp () Return :: a -> Exp a Bind :: Exp a -> (a -> Exp b) -> Exp b

Hi Jacques, I thought about that, but I wasn't able to push it further. It would look like that:
data Effect = Effect
data Exp e a where ReadAccount :: Exp () Int WriteAccount :: Exp () Int -> Exp Effect () SetVictory :: Exp () Bool -> Exp Effect () OnTimer :: Exp Effect () -> Exp Effect ()
Is that right? Should Exp () and Exp Effect belong to two different monads?
I was thinking of monad transformers to bridge between the two...
On Tue, Jan 28, 2014 at 1:29 PM, Jacques Carette
The simplest way would be to add a phantom type parameter to Exp, i.e. data Exp e a where
The 'e' variable would be used to track (and propagate) effects. It is then up to you to design your 'effect system' as you wish.
Jacques
On 2014-01-28 6:03 AM, Corentin Dupont wrote:
-> In short, my question is: how can I semantically separate instructions with effect from the others? i.e. how can I mark down and track those effects?
This is the DSL:
data Exp a where ReadAccount :: Exp Int WriteAccount :: Exp Int -> Exp () SetVictory :: Exp Bool -> Exp () OnTimer :: Exp () -> Exp () Return :: a -> Exp a Bind :: Exp a -> (a -> Exp b) -> Exp b

You can use type classes and polymorphism to get the restrictions you want.
class Monad m => ReadExp m where
readAccount :: m Int
onTimer :: m () -> m ()
class ReadExp m => WriteExp m where
writeAccount :: Int -> m ()
setVistory :: Bool -> m ()
instance ReadExp Exp ...
instance WriteExp exp ...
-- works fine
victoryRule :: ReadExp m => m ()
...
-- ends up being a type error for the implementation you gave
victoryRule' :: ReadExp m => m ()
...
And nicely, you can still use both of them in more general computations
that also need write access.
On Tue, Jan 28, 2014 at 6:03 AM, Corentin Dupont
Hi Haskell-Caféists! I have a small DSL for a game. Some instructions have effects (change the game state), some not. -> In short, my question is: how can I semantically separate instructions with effect from the others? i.e. how can I mark down and track those effects?
Here is a simplified version of the DSL I use. First some boilerplate:
{-# LANGUAGE GADTs #-} import Control.Monad import Control.Monad.State import Control.Monad.Free
This is the DSL:
data Exp a where ReadAccount :: Exp Int WriteAccount :: Exp Int -> Exp () SetVictory :: Exp Bool -> Exp () OnTimer :: Exp () -> Exp () Return :: a -> Exp a Bind :: Exp a -> (a -> Exp b) -> Exp b
It can read and write to an account (belonging to the state of the game), set a victory condition, and trigger some event every minute.
instance Monad Exp where return = Return (>>=) = Bind
instance Functor Exp where fmap f e = Bind e $ Return . f
With that you can write:
victoryRule :: Exp () victoryRule = SetVictory $ do m <- ReadAccount return (m > 100)
"victoryRule" sets the victory condition to be: "if there is more than 100 gold in the account, you win."
This is the game state:
data Game = Game { bankAccount :: Int, victory :: Exp Bool, timerEvent :: Exp ()}
The evaluation of "Exp" can be:
eval :: Exp a -> State Game a eval (SetVictory v) = modify (\g -> g{victory = v}) eval ReadAccount = get >>= return . bankAccount eval _ = undefined -- etc.
If you evaluate "victoryRule", you change the Game state by setting the victory field. Then, each time you will evaluate the victory field, you will know if you won or not (depending on your account...). This is all well and good, but imagine if you write:
victoryRule' :: Exp () victoryRule' = SetVictory $ do m <- ReadAccount WriteAccount (return $ m + 1) return (m > 100)
Ho no! Now each time a player is refreshing his screen (on the web interface), the victory condition is re-evaluated to be displayed again, and the bank account is increased by 1! This is not what we want. We should allow only effect-less (pure) instructions in the victory field, like readAccount, but not WriteAccount.
How would you do that?
I tried with the Free monad to delimit those effects. I re-write each primitives, marking them with the special type "Effect", when needed.
type Effect = Free Exp
-- readAccount remain the same: it has no effect readAccount :: Exp Int readAccount = ReadAccount
--writeAccount is marked as having an effect writeAccount :: Exp Int -> Effect (Exp ()) writeAccount ei = Pure $ WriteAccount ei
--onTimer is able to trigger an effect every minute onTimer :: Effect (Exp ()) -> Effect (Exp ()) onTimer e = Pure $ OnTimer $ iter join e
--victoryRule can be re-written like this, note that effects are rejected now victoryRule'' :: Effect (Exp ()) victoryRule'' = Pure $ SetVictory $ do m <- readAccount --writeAccount (return $ m + 1) --will be rejected at compile time (good)! return (m > 100)
--increase my bank account by 1 every minute myTimer :: Effect (Exp ()) myTimer = onTimer $ do m <- lift readAccount writeAccount (return $ m + 1)
I don't know if I got it right at all... How does it sound? It only bothers me that in this context "Pure" really means "Impure" :) Do you think of any other solution?
Cheers, Corentin
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

That's nice! I will experiment with that...
On Tue, Jan 28, 2014 at 3:53 PM, Jake McArthur
You can use type classes and polymorphism to get the restrictions you want.
class Monad m => ReadExp m where readAccount :: m Int onTimer :: m () -> m ()
class ReadExp m => WriteExp m where writeAccount :: Int -> m () setVistory :: Bool -> m ()
instance ReadExp Exp ...
instance WriteExp exp ...
-- works fine victoryRule :: ReadExp m => m () ...
-- ends up being a type error for the implementation you gave victoryRule' :: ReadExp m => m () ...
And nicely, you can still use both of them in more general computations that also need write access.
On Tue, Jan 28, 2014 at 6:03 AM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
Hi Haskell-Caféists! I have a small DSL for a game. Some instructions have effects (change the game state), some not. -> In short, my question is: how can I semantically separate instructions with effect from the others? i.e. how can I mark down and track those effects?
Here is a simplified version of the DSL I use. First some boilerplate:
{-# LANGUAGE GADTs #-} import Control.Monad import Control.Monad.State import Control.Monad.Free
This is the DSL:
data Exp a where ReadAccount :: Exp Int WriteAccount :: Exp Int -> Exp () SetVictory :: Exp Bool -> Exp () OnTimer :: Exp () -> Exp () Return :: a -> Exp a Bind :: Exp a -> (a -> Exp b) -> Exp b
It can read and write to an account (belonging to the state of the game), set a victory condition, and trigger some event every minute.
instance Monad Exp where return = Return (>>=) = Bind
instance Functor Exp where fmap f e = Bind e $ Return . f
With that you can write:
victoryRule :: Exp () victoryRule = SetVictory $ do m <- ReadAccount return (m > 100)
"victoryRule" sets the victory condition to be: "if there is more than 100 gold in the account, you win."
This is the game state:
data Game = Game { bankAccount :: Int, victory :: Exp Bool, timerEvent :: Exp ()}
The evaluation of "Exp" can be:
eval :: Exp a -> State Game a eval (SetVictory v) = modify (\g -> g{victory = v}) eval ReadAccount = get >>= return . bankAccount eval _ = undefined -- etc.
If you evaluate "victoryRule", you change the Game state by setting the victory field. Then, each time you will evaluate the victory field, you will know if you won or not (depending on your account...). This is all well and good, but imagine if you write:
victoryRule' :: Exp () victoryRule' = SetVictory $ do m <- ReadAccount WriteAccount (return $ m + 1) return (m > 100)
Ho no! Now each time a player is refreshing his screen (on the web interface), the victory condition is re-evaluated to be displayed again, and the bank account is increased by 1! This is not what we want. We should allow only effect-less (pure) instructions in the victory field, like readAccount, but not WriteAccount.
How would you do that?
I tried with the Free monad to delimit those effects. I re-write each primitives, marking them with the special type "Effect", when needed.
type Effect = Free Exp
-- readAccount remain the same: it has no effect readAccount :: Exp Int readAccount = ReadAccount
--writeAccount is marked as having an effect writeAccount :: Exp Int -> Effect (Exp ()) writeAccount ei = Pure $ WriteAccount ei
--onTimer is able to trigger an effect every minute onTimer :: Effect (Exp ()) -> Effect (Exp ()) onTimer e = Pure $ OnTimer $ iter join e
--victoryRule can be re-written like this, note that effects are rejected now victoryRule'' :: Effect (Exp ()) victoryRule'' = Pure $ SetVictory $ do m <- readAccount --writeAccount (return $ m + 1) --will be rejected at compile time (good)! return (m > 100)
--increase my bank account by 1 every minute myTimer :: Effect (Exp ()) myTimer = onTimer $ do m <- lift readAccount writeAccount (return $ m + 1)
I don't know if I got it right at all... How does it sound? It only bothers me that in this context "Pure" really means "Impure" :) Do you think of any other solution?
Cheers, Corentin
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Jan 28, 2014 at 3:03 AM, Corentin Dupont
Hi Haskell-Caféists! I have a small DSL for a game. Some instructions have effects (change the game state), some not. -> In short, my question is: how can I semantically separate instructions with effect from the others? i.e. how can I mark down and track those effects?
Hi, Corentin, This is very much like what we did in our work on adding fine-grained effect specification to the Par monad in the LVish library (http://hackage.haskell.org/package/lvish). Just as Jacques suggested up-thread, we did it by adding an extra phantom type parameter to the monad which we call the "determinism level". At its simplest, there are only two of these levels, Det and QuasiDet, for deterministic and quasi-deterministic: data Determinism = Det | QuasiDet and the first parameter passed to the Par type constructor is of kind Determinism (we have to turn on the DataKinds extension for this). Doing so allows the static type of a Par computation to reflect its determinism or quasi-determinism guarantee. (The effects you can perform in deterministic computations are a subset of the ones you can do in quasi-deterministic computations.) The beginning of section 6 of our POPL paper on LVish (http://www.cs.indiana.edu/~lkuper/papers/lvish-popl14.pdf) discusses this feature. In more recent work, we've extended this to allow a more fine-grained menu of effects to choose from, to the point where we've begun calling it an "effect level" rather than merely "determinism level". Good luck with it! Lately I have gotten a lot of mileage out of thinking of monads as embedded DSLs. Projects like yours really put that analogy to use. :) Lindsey
participants (4)
-
Corentin Dupont
-
Jacques Carette
-
Jake McArthur
-
Lindsey Kuper