This eval function takes an expression (called Nomex), that can possibly have effects.
It returns a state monad, to allow you to modify the game state.
But for effectless instructions, it would be better to run the evaluator in the reader monad:
evalNoEffect :: Nomex NoEffect a -> Reader Game a
So you can have additional guaranties that evaluating your expression will not have effects.
I tried (see below), but it doesn't work for the moment:
> {-# LANGUAGE GADTs #-}
> {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables,
> MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances #-}
> module DSLEffects where
> import Control.Monad.Error
> import Control.Monad.State
> import Control.Monad.Reader
> import Data.Typeable
This is the DSL:
> data Effects = Effect | NoEffect
> data Nomex :: Effects -> * -> * where
> ReadAccount :: Nomex r Int --ReadAccount has no effect: it can be run in whatever monad
> WriteAccount :: Int -> Nomex Effect () --WriteAccount has effect
> SetVictory :: Nomex NoEffect Bool -> Nomex Effect () --SetVictory don't accept effectful computations
> Bind :: Nomex m a -> (a -> Nomex m b) -> Nomex m b
> Return :: a -> Nomex r a --wrapping a constant has no effect
> instance Monad (Nomex a) where
> return = Return
> (>>=) = Bind
> noEff :: Nomex NoEffect ()
> noEff = return ()
> hasEffect :: Nomex Effect ()
> hasEffect = do
> a <- ReadAccount
> WriteAccount a
> data Game = Game { victory :: Nomex NoEffect Bool,
> account :: Int}
> eval :: Nomex r a -> State Game a
> eval a@ReadAccount = liftEval $ evalNoEffect a
> eval (WriteAccount a) = modify (\g -> g{account = a})
> eval (SetVictory v) = modify (\g -> g{victory = v})
> eval a@(Return _) = liftEval $ evalNoEffect a
> eval (Bind exp f) = eval exp >>= eval . f
> evalNoEffect :: Nomex NoEffect a -> Reader Game a
> evalNoEffect ReadAccount = asks account
> evalNoEffect (Return a) = return a
> evalNoEffect (Bind exp f) = evalNoEffect exp >>= evalNoEffect . f
> liftEval :: Reader Game a -> State Game a
> liftEval r = get >>= return . runReader r
This is not compiling:
exceptEffect.lhs:60:15:
Couldn't match type 'NoEffect with 'Effect
Inaccessible code in
a pattern with constructor
WriteAccount :: Int -> Nomex 'Effect (),
in an equation for `evalEffect'
In the pattern: WriteAccount a
In an equation for `evalEffect':
evalEffect (WriteAccount a) = modify (\ g -> g {account = a})
It seems that the type of effectless computations (NoEffect) leaks in the type of effectful ones (due to the pattern matching)...
Thanks,
Corentin