Manage Effects in DSLs

How to mark down and track effects in your DSLs

Published on January 30, 2014

I have a small DSL for my Nomyx game.
Some instructions have effects (change the game state), some not. In this blog post, we’ll try to solve the following question: how can we semantically separate instructions with effect from the others? i.e. how can I mark down and track those effects?

To show you the problem, here is a simplified version of the DSL I use. First some boilerplate (this post is literate Haskell, you can copy/paste it and run it as-is):

{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds, KindSignatures #-}
module DSLEffects where
import Control.Monad.State

This is the DSL:

data Exp a where
  ReadAccount  :: Exp Int
  WriteAccount :: Int -> Exp () 
  SetVictory   :: Exp Bool -> Exp ()
  OnTimer      :: Exp () -> Exp ()
  Const        :: 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 set an expression to be triggered every minute. The Monad instance is pretty straightforward:

instance Monad Exp where
   return = Const
   (>>=)  = Bind

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 ()}

It contains your amount of gold, the victory condition, and the expression that must be triggered every minute by the system. Note that the field victory is not a boolean: it’s an expression. 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 (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.

Here is one solution. We need to separate the DSL instructions that have effects from the ones that have no effect. First, we need to define a data kind, called Eff. This is done by first writing a data type Eff, and then promoting it to the kind level. This is accomplished automatically with the pragma DataKind.

data Eff = Effect | NoEffect

Then, we specify that the first type parameter of an expression must be of kind Eff, to allow us to mark effects:

data Exp' :: Eff -> * -> * where
  ReadAccount'  :: Exp' r Int  --ReadAccount can be used in whatever monad
  --WriteAccount takes an effect-less expression, and returns an effectfull expression
  WriteAccount' :: Int -> Exp' Effect ()  
  SetVictory'   :: Exp' NoEffect Bool -> Exp' Effect ()
  --OnTime can trigger whatever expression, in particular effectful ones
  OnTimer'      :: Exp' Effect () -> Exp' Effect () 
  Const'        :: a -> Exp' r a
  Bind'         :: Exp' r a -> (a -> Exp' r b) -> Exp' r b

instance Monad (Exp' a) where
   return = Const'
   (>>=)  = Bind'

Each instruction of our language can now specify if it allows effects or not in its parameters and return type. That time, we can re-write victoryRule:

victoryRule'' :: Exp' Effect ()
victoryRule'' = SetVictory' $ do
  m <- ReadAccount'
  --WriteAccount (m + 1) --won't compil (good)!
  return (m > 100)

We cannot add effectful instructions in the victory condition anymore: mission accomplished!

We can also define a timer. Unlike SetVictory, the OnTimer instruction accepts effectful instructions as a parameter. myTimer hereunder sets a rule that will increment my bank account by 1 gold every minute:

myTimer :: Exp' Effect ()
myTimer = OnTimer' $ do
  m <- ReadAccount'
  WriteAccount' (m + 1)

Note that ReadAccount’ being polymorphic on its type (by using the type parameter r), it can be used in both an effect-full or an effect-less context!

In the next post, we will see how to solve the same problem, this time using type classes.

Comments