The easily extensible entity enigma

A simple entity component system based on extensible-effects.
Posted on October 25, 2014 by Florian Hofmann (fho@f12n.de)

I spend some time thinking about entity component systems and how to implement them in an extensible way in Haskell.

TL;DR: I use the extensible-effects package to implement a simple to use entity component system that shouldn’t have much overhead due to being readily extensible.

Entity Component System Overview

According to Wikipedia a entity component system “implements concepts from composition-over-inheritance using a database-like structure”. Basically what this means is that instead of using structures or classes data is scattered in multiple container structures.

Object orientation doesn’t help here

Traditionally code is centered around objects that gather per-entity data. Instances of these objects are than gathered in a container to represent the current world state:


-- create some newtypes, these will prove themselves useful later
newtype Position = Pos (V2 Float)
newtype Velocity = Vel (V2 Float)
newtype Color    = Col (V3 Float)

-- traditional "object oriented" model
data GameObject {
    position :: Position,
    velocity :: Velocity,
    color    :: Color
}

newtype World = World [GameObject]

This model has several problems, one of them is that it is not readily extensible. Even in our simple example above this is evident. Some entities may not be able to move (eg walls), these will need a position but not the velocity property. Other entities might need a property that marks them as visible. Should we extend GameObject?

Aside: In OO languages this is often solved via inheritance. We could easily create an HasVisibilty interface. But nevertheless this will lead to a big bunch of instanceof queries and type casts littering the processing functions.

Another problem is that this model really hurts cache-locality and thereby directly effects performance. Consider that the rendering part of a game engine will only need the position and the color properties of the entities. On the other hand, the physics engine only requires position and velocity.

Despite this fact the processor will always fetch the whole object into the caches as they are layed out serial in memory. This in effect puts unnecessary burden on the memory lanes and increases cache misses.

A simpler approach

Entity component systems solve these problems by storing these properties (called components) in separate containers indexed by an unique id per entity:

newtype ID = ID Int

data World = World {
  positions       :: Map ID Position,
  velocities      :: Map ID Velocity,
  colors          :: Map ID Color
}

Aside: I use generic Maps and Sets here for brevity. These would be replaced by appropriate implementations in a real implementation. On the other hand as Edward Kmett mentions here: “Data.Map has excellent constant factors!”. Aside Aside: I wonder what happened to this project of him.

A nice benefit of this is that now you can use set functions on the property containers to only process the entities that you actually care about:

render :: Position -> Color -> IO ()

-- | only processes entities that have a position and a color
renderAll :: World -> IO
renderAll w = sequence_ $ intersectionWith render ps cs
    where ps = positions w
          cs = colors    w

Adding our visibility property is just a matter of adding it to our world state. But in effect we are still passing around all of our world state. Can we do better? Maybe even making explicit which parts of the world state each functions needs?


Introducing extensible-effects (again)

Extensible Effects is “an alternative to monad transformers” introduced by Oleg Kiselyov, Amr Sabry and Cameron Swords in their paper Extensible Effects.

Without going into detail of the implementation one of the advantages over monad transformer stacks is that extensible effects use a set of effects. Effectively removing the overhead that is required to lift actions through big transformer stacks. Another benefit is that it is possible to selectively specify which of the available effects a functions uses.

Prelude

From this part on this post is a literate haskell file, so here is the usual header:

> {-# LANGUAGE DeriveDataTypeable #-}
> {-# LANGUAGE FlexibleContexts #-}
> {-# LANGUAGE GeneralizedNewtypeDeriving #-}
> {-# LANGUAGE TypeOperators #-}
>
> module Main where
>
> import Control.Monad           hiding (mapM_)
> import Control.Applicative
>
> import Control.Eff
> import Control.Eff.Fresh
> import Control.Eff.Lift
> import Control.Eff.State.Strict
>
> import Linear
>
> import           Data.IntMap (IntMap)
> import qualified Data.IntMap as IM
>
> import Data.Typeable
> import Data.Maybe
> import Data.Foldable
>
> import Prelude                               hiding (mapM_)

As above we define newtypes for all our properties:

> newtype ID = ID { unID :: Int }
>   deriving (Show,Read,Eq,Ord,Typeable,Enum,Num)
> newtype Position = Position (V3 Double)
>   deriving (Show,Read,Eq,Ord,Typeable,Num)
> newtype Velocity = Velocity (V3 Double)
>   deriving (Show,Read,Eq,Ord,Typeable,Num)
> newtype Color = Color (V4 Double)
>   deriving (Show,Read,Eq,Ord,Typeable,Num)

Working with Worlds

With that out of the way, how is this used? Writing this down is a chicken and egg problem, so I will start with how the processing functions work.

> -- "render" an entity by printing it out to stdout
> display :: IM.Key -> Position -> Color -> IO ()
> display eid pos col = print (eid,pos,col)
>
> -- "render" all renderable entities
> displayAll :: ( SetMember Lift (Lift IO)            r
>               , Member    (State (IntMap Color))    r
>               , Member    (State (IntMap Position)) r
>               ) => Eff r ()
> displayAll = do
>     fMap <- IM.intersectionWithKey display <$> get <*> get
>     lift $ sequenceA_ fMap

There is a lot going on in this code, let’s go through it step by step.

display :: IM.Key -> Position -> Color -> IO ()
display eid pos col = print (eid,pos,col)

Instead of going full scale graphical we will provide rendering by printing out the ID, position and color to stdout.

displayAll :: ( SetMember Lift (Lift IO)            r
              , Member    (State (IntMap Color))    r
              , Member    (State (IntMap Position)) r
              ) => Eff r ()

extensible-effects accurately keeps track on which functions are allowed to use which effects. SetMember Lift (Lift IO) allows us to use lift which is in this case equivalent to liftIO. Member (State (IntMap a)) allows us to use the effects from the underlying state effects. The result of this function is a calculation in the Eff monad that is parametrized on the effects set r and has no result.

displayAll = do
    fMap <- IM.intersectionWithKey display <$> get <*> get
    lift $ sequenceA_ fMap

Now this is interesting. get will retrieve the current value from the state effect. In this case this is the IntMap a. The compiler is easily able to figure out which state to access because of the types of display.

fMap is a map containing all display actions which are consequently executed by sequencing the map and lifting the resulting action.

A minimalistic physics simulation can be created equally easy:

> advance :: Velocity -> Position -> Position
> advance (Velocity v) (Position p) = Position $ p + v
>
> advanceAll :: (Member (State (IntMap Position)) r
>               ,Member (State (IntMap Velocity)) r
>               ) => Eff r ()
> advanceAll = do
>     vs <- get
>     modify (\ps -> IM.intersectionWith advance vs ps `IM.union` ps)

vs <- get will be inferred to mean “get all velocities”. The second line will update all entities that have a position and a velocity. There is probably a more efficient way to do this than to union on the unmodified entities.

Using it

So how do we use this? Basically it is “get a entity id”, “append properties”, “call functions that use the world state”:

> main :: IO ()
> main = runEntities $ do
>

We create three new entity ids. This uses an already available effect called Fresh that just outputs and increases an Enum every time fresh is called:

>     entities@[entityA, entityB, entityC] <- replicateM 3 fresh

Adding properties “just works” because the compiler can infer which map it has to store it to from its type:

>     entityA `addProperty` Position (V3 0 0 0)
>     entityA `addProperty` Velocity (V3 1 0 0)
>
>     entityB `addProperty` (Position (V3 0 0 0))
>     entityB `addProperty` (Velocity (V3 0 1 0))
>     entityB `addProperty` Color (V4 255 255 255 255)
>
>     entityC `addProperty` (Position (V3 0 0 0))
>     entityC `addProperty` Color (V4 0 0 0 0)

Using it:

>     -- print state
>     lift . putStrLn $ "initial state:"
>     displayAll
>
>     -- run 10 steps of a minimalistic physics simulation
>     replicateM_ 10 advanceAll
>
>     -- print state
>     lift . putStrLn $ "final state:"
>     displayAll

This will display:

initial state:
(1,Position (V3 0.0 0.0 0.0),Color (V4 255.0 255.0 255.0 255.0))
(2,Position (V3 0.0 0.0 0.0),Color (V4 0.0 0.0 0.0 0.0))
final state:
(1,Position (V3 0.0 10.0 0.0),Color (V4 255.0 255.0 255.0 255.0))
(2,Position (V3 0.0 0.0 0.0),Color (V4 0.0 0.0 0.0 0.0))

(Only two entities are shown because the last one doesn’t have a color property that is required by displayAll.)

Those who do the real work

> runEntities eff = runLift . evalState (IM.empty :: IntMap Velocity)
>                           . evalState (IM.empty :: IntMap Position)
>                           . evalState (IM.empty :: IntMap Color)
>                           $ runFresh eff (0 :: ID)

This actually runs and defines the effects we are using. Every time we want to add another property we will have to extend this. The type of this function is actually quite long as it includes the set of available effects on the type level.


Conclusion

In my opinion this is a very nice way to write an entitiy component system for the following reasons:

I hope you enjoyed this post as much as I enjoyed getting this working. Feel free to discuss this on the linked reddit thread.

Acknowledgements

Appendix:

> addProperty :: (Member (State (IntMap a)) r, Typeable a) => ID -> a -> Eff r ()
> addProperty eid val = modify $ IM.insert (unID eid) val