Posted on August 15, 2023
Let’s say you are making a game and you want to have a scripting language for your game. There are many benefits to doing so:
- You can make your game more moddable, by loading player made scripts at runtime.
- You can make your game designers job easier, because they don’t have to be familiar with the entire codebase to make changes, just the API for the language.
- You can make increase your productivity by reducing compile times, because you don’t have to recompile the entire game to make changes, you can just reload the scripts at runtime.
- You can make your game more debuggable, by allowing you to inspect the state and even change it at runtime.
But implementing a whole interpreter is a lot of work! Especially if you’ve never written a compiler or interpreter before. You’ll have to deal with parsing grammars, program semantics, evaluation, and more. And if you want to make your language more powerful or performant, that means more work, which means less time spent actually making the game. But what if I told you that you can get all of these benefits with a fraction of the work? Well, you can, by using free monads.
What is a Free Monad in Category Theory?
A free monad is a monad that is generated by a functor in a way that is analogous to how a free group is generated by a set. A free monad can be seen as a way of representing the syntax of a computation without specifying its semantics. A free monad can also be used to combine different effects in a single monad, using the technique of monad transformers.
To understand what a free monad is, let us first recall what a monad is in category theory. A monad on a category C is an endofunctor T: C -> C, together with two natural transformations: eta: 1_C -> T (the unit) and mu: T^2 -> T (the multiplication), that satisfy the monad laws. Intuitively, a monad can be thought of as adding some extra structure or context to the objects and morphisms of C.
A functor F: C -> D is said to be forgetful if it “forgets” some of the structure or properties of the objects and morphisms in C. For example, the functor U: Grp -> Set that maps a group to its underlying set and a group homomorphism to its underlying function is forgetful, because it ignores the group operations and axioms. A functor that is not forgetful is called faithful.
A functor F: C -> D is said to be free if it has a left adjoint G: D -> C, such that F ∘ G is naturally isomorphic to the identity functor on D. This means that for any object X in D, there is an object G(X) in C, such that F(G(X)) is naturally isomorphic to X, and for any morphism f: X -> Y in D, there is a unique morphism g: G(X) -> G(Y) in C, such that F(g) = f. Intuitively, a free functor can be thought of as adding the minimal amount of structure or properties to the objects and morphisms in D, such that they become objects and morphisms in C.
A free monad on a category C is a monad T: C -> C that is free as an endofunctor. This means that there is a functor U: C -> C, such that T ∘ U is naturally isomorphic to the identity functor on C, and for any endofunctor F: C -> C, there is a unique natural transformation t: U ∘ F -> F, such that T(t) = F. Intuitively, a free monad can be thought of as adding the minimal amount of structure or context to the objects and morphisms of C, such that they become objects and morphisms in T(C).
A simple example of a free monad
Now given a brief theoretical overview of free monads, let’s implement a simple free monad in Haskell, to understand how they work in practice. We will implement a free monad for a simple language of arithmetic expressions, and then we will interpret the expressions in the language.
First, we define the language of arithmetic expressions as a data type:
data Expr t a
= Add t t (t -> a)
| Mul t t (t -> a)
deriving FunctorThe Expr type is parameterized by a type a, which is used to represent the context of the expression. The a parameter is used to represent the context of the expression, for example, if we want to represent the expression 1 + 2 * 3, we can use the Expr type as follows:
expr :: Expr Int (Expr Int ())
expr = Mul 2 3 (\x -> Add x 1 (const ()))But clearly this is very unergonomic, and annoying to use, so let’s use the free monad to fix things. Now here’s the definition of the free monad. At least one of them, there are others with different definitions and better performance, like this. I choose this definition since it’s the simplest one to wrap your head around (but also painfully slow):
data Free f a
= Pure a
| Free (f (Free f a))The Free type is parameterized by a functor f and a type a. The Pure constructor represents a value, and the Free constructor represents a value that is generated by the functor f. One way to think about Free f is like a list, where Pure is Nil and Free is Cons, except here Free is not linear but a tree. The Free type is a monad and applicative with the following definitions:
instance Functor f => Applicative (Free f) where
pure = Pure
Pure a <*> Pure b = Pure $ a b
Pure a <*> Free mb = Free $ fmap a <$> mb
Free ma <*> b = Free $ fmap (<*> b) ma
instance Functor f => Monad (Free f) where
Pure a >>= f = f a
Free m >>= f = Free (fmap (>>= f) m)Now we can define a function liftF that lifts a functor f into the free monad Free f, retract that unwraps the functor f from the free monad Free f, and foldFree which implements the natural transformation from Free f a to another monad m a:
liftF :: Functor f => f a -> Free f a
liftF = Free . fmap Pure
retract :: Monad f => Free f a -> f a
retract (Pure a) = return a
retract (Free m) = m >>= retract
foldFree :: Monad m => (forall x. f x -> m x) -> Free f a -> m a
foldFree _ (Pure a) = return a
foldFree f (Free as) = f as >>= foldFree fFor ease of use we should declare some helper functions that lift our constructors into the free monad:
type FreeExpr t = Free (Expr t)
add :: t -> t -> FreeExpr t t
add x y = liftF $ Add x y id
mul :: t -> t -> FreeExpr t t
mul x y = liftF $ Mul x y idNow lets write a new program using the free monad and do notation:
program :: FreeExpr Int Int
program = do
result <- add 12 13
mul result 2This program by itself does not do anything, however, we can write an eval function which can interpret our program into IO monad:
eval :: (Num a, Show a) => FreeExpr a a -> IO a
eval = foldFree eval' where
eval' (Add x y k) = putStrLn (show x ++ " + " ++ show y) >> pure (k (x + y))
eval' (Mul x y k) = putStrLn (show x ++ " * " ++ show y) >> pure (k (x * y))Here’s what we get when we run this program:
> eval program >>= print
12 + 13
25 * 2
50
Important note is that the evaluation function can be from our free monad to any monad, not just IO. For example, we can write an interpreter that puts the expressions into a list instead of printing them immediately:
evalToList :: (Num a, Show a) => FreeExpr a a -> [String]
evalToList (Pure a) = [show a]
evalToList (Free (Add x y k)) = (show x ++ " + " ++ show y) : evalToList (k (x + y))
evalToList (Free (Mul x y k)) = (show x ++ " * " ++ show y) : evalToList (k (x * y))Now we get the following result:
> evalToList program
["12 + 13","25 * 2", "50"]
So hopefully that gave you a good idea of what a free monad is and how it works. Now let’s see how we can use it to implement a scripting language for our game.
Free monads for game scripting
Say you’re making an RPG for example, and you want to allows status effects to be added, removed and composed within the scripting language. This way the game designers and modders can add new status effects based on the primitives that you provide. So let’s define a data type for our scripting language:
data ScriptExpr t a
= AddEffect TargetName EffectName a
| RemoveEffect TargetName EffectName a
| NewEffect EffectName a
deriving Functor
type EffectName = String
type TargetName = String
type FreeScript t = Free (ScriptExpr t)We are using type synonyms to easily change our types later, since String is not a great representation, but let’s roll with it for now. Now we can define some helper functions to lift our constructors into the free monad:
addEffect :: TargetName -> EffectName -> FreeScript t ()
addEffect target effect = liftF $ AddEffect target effect ()
removeEffect :: TargetName -> EffectName -> FreeScript t ()
removeEffect target effect = liftF $ RemoveEffect target effect ()
newEffect :: EffectName -> FreeScript t a -> FreeScript t a
newEffect effect script = Free $ NewEffect effect scriptFor newEffect we can’t use liftF so we have to use Free directly. So let me explain what our scripting language is meant to do. AddEffect and RemoveEffect will add add or remove an effect from a target. NewEffect will create a new effect, and then run the script that is passed to it. This way we can compose effects together. Now let’s write two simple scripts to demonstrate:
applyBurn :: FreeScript t ()
applyBurn = do
addEffect "player" "burn"
removeEffect "player" "wet"
poisonBurnEffect :: FreeScript t ()
poisonBurnEffect = do
newEffect "poisonBurn" $ do
addEffect "player" "poison"
applyBurnThe first script applies the burn effect to the player, and removes the wet effect. The second script creates a new effect called poisonBurn, which applies the poison effect to the player, and then applies the burn effect. Now let’s write an interpreter for our language. Now as much as I love Haskell, the vast majority of video games are made in a C like language, so instead of interpreting to IO, let’s interpret to some (pseudo) C code:
toC :: ScriptExpr t a -> String
toC (AddEffect target effect k) = target ++ "." ++ "addEffect(" ++ show effect ++ ");"
toC (RemoveEffect target effect k) = target ++ "." ++ "removeEffect(" ++ show effect ++ ");"
toC (NewEffect effect k) = "void " ++ effect ++ "() {"
evalToC :: FreeScript t a -> [String]
evalToC (Pure a) = []
evalToC (Free (AddEffect target effect k)) = toC (AddEffect target effect k) : evalToC k
evalToC (Free (RemoveEffect target effect k)) = toC (AddEffect target effect k) : evalToC k
evalToC (Free (NewEffect effect k)) = toC (NewEffect effect k) : (evalToC k ++ ["}"])Now let’s see what we get when we run our scripts:
> unlines evalToC applyBurn
player.addEffect("poison");
player.addEffect("burn");
> unlines evalToC poisonBurnEffect
void poisonBurn() {
player.addEffect("poison");
player.addEffect("burn");
player.addEffect("wet");
}Wow! In essence we just wrote a full compiler for our scripting language directly into C! And we didn’t have to write a single parser, or lexer! We just wrote a simple interpreter, and we got a full compiler for free! If your using something like Unity, you can “easily” compile this code at runtime into a DLL, and then load it into your game. With a few helper functions in C# you can hot reload the active scripts! If you’re not using Unity then most languages have a FFI to C, which you can use to dynamically load code and call functions. Then when you ship your game you have to include your interpreter and GHC so that the user can interpret the scripts themselves into C, then your game can compile the C at runtime (how would I do this?) and use the FFI to call the user written functions. This approach makes your game easily moddable for your users! This method also resolves another issue in common in custom scripting languages is that they lack a proper ecosystem, and so common utilities like syntax highlighting and IDE support are not available. But with this method you can use any editor that supports Haskell, and ensure that all scripts are well typed and well formed. You also limit the power of the scripting language to only what you expose in the API, so you can ensure that the scripts are not too powerful and can’t break the game (or have malware like this infamous case).
Let’s finish up by making our language a bit more practical. First we want a way to dynamically pick a target and not just hardcode it into the script.
data ScriptExpr t a
= AddEffect TargetName EffectName a
| RemoveEffect TargetName EffectName a
| NewEffect EffectName a
| GetCurrentPlayer a
| GetCurrentTarget a
deriving Functor
getCurrentPlayer :: FreeScript t TargetName
getCurrentPlayer = liftF $ GetCurrentPlayer "getCurrentPlayer()"
getCurrentTarget :: FreeScript t TargetName
getCurrentTarget = liftF $ GetCurrentTarget "getCurrentTarget()"
applyBurn :: TargetName -> FreeScript t ()
applyBurn player = do
addEffect player "burn"
removeEffect player "wet"
poisonBurnEffect :: FreeScript t ()
poisonBurnEffect = do
newEffect "poisonBurn" $ do
target <- getCurrentTarget
addEffect target "poison"
applyBurn targetNow if we interpret our new script we get:
> unlines evalToC poisonBurnEffect
void poisonBurn() {
getCurrentTarget().addEffect("poison");
getCurrentTarget().addEffect("burn");
getCurrentTarget().addEffect("wet");
}We can easily expand this into a full scripting language just by adding additional constructors to our data type. But I think you get the point from this demonstration.
Why use free monads for game scripting?
Now let’s talk about some advantages and disadvantages to this method. Firstly, one of the advantages that matter to the functional programmers is that you get to use Haskell. Most of game development is firmly in the imperative C-like languages territory, and thus so are the scripting languages. Lua and C# are some of the most common off the shelf scripting languages, which needless to say are not functional. But with this method you can use Haskell, which is a functional language, and thus you can use functional programming techniques to make your game. Another advantage is that you get to use the full power of Haskell, including the type system, which means that you can ensure that your scripts are well typed and well formed. This means that you can catch more errors at compile time, instead of at runtime. However, more advanced errors do depend on the API design. Our current API would be able to catch errors relating to the use of variables, but it cannot protect from errors such as swapping the target name and effect name. This could be remedied by introducing a type constructor and a data type for both the types, since currently both are just type synonyms for String. Another beneficial aspect of free monads is the the flexibility, which means that you can easily extend the language with new features, and you can even combine multiple languages together. Free monads unlike normal monads are always composable, so you can have many languages which excel for a specific use case, while still offering computability with each other. The flexibility of interpreting the free monad into any monad also allows for a single script to be used in many ways. In our example we made our interpreter produce pseudo C, however, we could also interpret the script into IO, if we were making our game in Haskell, and we wouldn’t have to change the game logic itself, only the interpreter.
However, these benefits come with some drawbacks as well. One major drawback for game developers using established game engines is that these ecosystems often provide a scripting language. So in that case there is no need to reinvent the wheel. Even if the game engine does not have a scripting language, often it is easier to integrate with an existing language than to create your own. Lua is a small performant embedded language frequently used for this purpose. Speaking of performance free monads are not known for their performance. The free monad is a very simple and elegant solution, but it is not fast, the implementation we used requires the entire monad to be traversed, each time we return it from a function. There are other free monad implementations that are more performant, but they are more complex and harder to understand, but luckily there are well established libraries which mostly solve this issue (like this). Another aspect that reduces the elegance of free monads is the amount of boilerplate. For each constructor in our functor we have to create a function that makes an lifted version of it, and we have to create a function that interprets it. This can be remedied by using Template Haskell to generate the boilerplate, but that is a bit more advanced. Another issue is that free monads are not very ergonomic to use. The syntax is not very nice, and it is not very easy to debug. This can be remedied by using a library that provides better ergonomics like Polysemy. Polysemy provides a DSL for free monads. However, Polysemy is not very beginner friendly and it has a steep learning curve. The debugging issue is more frustrating to resolve, since by nature the free monad does not perform any actual computations, instead you have to implement your own methods of logging of tracing using an interpreter.
Overall, the free monad provides a powerful abstraction over monadic operations. If you are determined to create your own scripting language then I believe that the free monad is the simplest way to do it, especially if your game is made in Haskell. It is simple, elegant, flexible and it allows you to use the full power of Haskell. However, if are using an established game engine like Unity and just want a scripting system, then you should leverage the existing ecosystem. Game development is hard enough as is, and if there is no need to complicate it further, then don’t.
I hope you learned something new from this article, and maybe for you next project you’ll consider whether the free monad is the right abstraction for you!