You can use type classes and polymorphism to get the restrictions you want.class Monad m => ReadExp m where
readAccount :: m IntonTimer :: m () -> m ()
class ReadExp m => WriteExp m wherewriteAccount :: Int -> m ()setVistory :: Bool -> m ()instance ReadExp Exp ...instance WriteExp exp ...
-- works finevictoryRule :: ReadExp m => m ()...-- ends up being a type error for the implementation you gavevictoryRule' :: 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:
_______________________________________________CorentinCheers,Hi Haskell-Caféists!Do you think of any other solution?
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" :)
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe