I often see effects called "fancy," but in 2024 I fail to see how that is the case. If anything, their types are more clear than mtl
in 2024.
I've been using extensible effects (via cleff
[1]) in my gamedev code since 2021 (starting with Ludum Dare 49). I originally used mtl
, but it was almost immediately a pain. I saw cleff
and switched to it within a day (for both library code + my previous game). I can confidently say I'll never use mtl
again if I have any choice. It's archaic and brings no benefit besides somehow being considered less fancy.
I say "somehow" because I don't really understand why mtl
is considered less fancy than cleff
. Maybe it's because it's fancier to implement? But the whole point of Haskell is that you shouldn't need to care about the implementation if the programmer-facing API is simplified. ghc
is plenty more complicated than go
but that doesn't stop us from using Haskell.
So with that in mind, I've pulled some random types from my gamedev codebase that I feel illustrate how effects are not at all complicated to use. And while this project is independent/non-commercial, I'd argue even simple 2D games are more complex to design, program, evolve, and maintain than any "backend" "web service-y" software project I've worked on professionally.
If you're using effects, you'll need to define them. In mtl
, this would mean:
- Defining a
class
for your interface. - Implementing said
class
for all monad transformers that could be in your end-users' stacks. - Choose some mechanism for the end-users' stack to carry the needed state/context for your implementation:
- Define a custom monad transformer. Implement the
class
. Also implement all othermtl
-styleclass
es you might need (n^2
problem). - Or piggyback on
ReaderT
usingHas
or something.
- Define a custom monad transformer. Implement the
- Repeat
(3)
for all possible interpretations of(1)
To do the equivalent for cleff
:
- Define a GADT for your interface.
cleff
has TH that writes the magical plumbing around these GADTs for you.
- Write an interpreter (which is Just a Haskell Function) for each way you wish the interface to be interpreted.
cleff
is superior on multiple fronts:
- Less code
- No need for type class programming
- Unified interface for interpretation that uses functions
forall a. Eff (MyEffect : es) a -> Eff es a
vs bespoke monad transfomer runners
I'm fairly confident if the situation were reversed and cleff
were old hat and mtl
were new, nobody would be clamoring for mtl
. I don't really see why anyone would even invent mtl
in such a world outside of curiousity.
Okay, so what does this look like in practice? Let's look at a simple effect from the engine: SDL_GPU
here. This effect just carries the window/rendering context around.
data SDL_GPU :: Effect where
AskGPU :: SDL_GPU m (Ptr GPU.Target)
AskNativeRez :: SDL_GPU m NativeResolution
And the interpreter just closes over those values and pipes them through:
runSDLGPU :: NativeResolution -> Ptr GPU.Target -> (Eff (SDL_GPU : es) ~> Eff es)
runSDLGPU nativeRez screen = interpret $ \case
AskGPU -> pure screen
AskNativeRez -> pure nativeRez
interpret
does the heavy lifting there (and there's fanciness within), but it's simple to use. You give it a function casing on your GADT to Eff es a
(with the GADT's type index driving that a
.
I had this same effect in this codebase using mtl
and it was not as nice to work with. That step (3)
above was the main pain point. I had to keep extending an uber-record in my ReaderT
with all the context I needed. This is both clunky and bad for codebase scaling: Dogpiling on an uber-record for application context is a common source of compilation chokepoints that has the potential to cause "dependency leakage" over time (i.e. downstream modules end up with ever-increasing import dependencies over time).
Usage is pretty much equivalent to mtl
: You add a constraint and then interact with your interface.
Here's an example of a game using the SDL_GPU
effect to convert mouse location from raw screen coordinates to virtual screen coordinates.
The type is simple. You just declare what effects you need in a constraint:
parseController
:: [IOE, SDL_GPU] :>> es -- | We need IO and our effect
=> [SDL.Event]
-> Eff es Controller -- | Our return type is polymorphic in es - this is like the mtl-style "forall m"
And then in your implementation, you program against the interface abstractly:
parseController es = do
-- Use the interface
screen <- askGPU
-- instance IOE :> es => MonadUnliftIO (Eff es), so we can use
-- the sdl2 bindings directly!
absLoc <- fmap fromIntegral <$> SDL.getAbsoluteMouseLocation
-- Use the screen to munge mouse location
P loc <- liftIO $ GPU.screen2virtual screen absLoc
-- elided - do more work to parse our controls
pure Controller{..}
The constraint you use in cleff
is either SomeEffect :> es
(or [Effect1, Effect2] :>> es
multi-effect sugar) and the return type is always Eff es Stuff
. In mtl
, it would be a MonadEffect m
constraint and return m Stuff
. Outside of syntax, these are equivalent in user-facing fanciness.
One of the biggest advantage of cleff
over mtl
is the ease of having multiple interpretations.
For a classic example, let's look at the logging effect from the mayhem-engine
.
It's defined like this:
data Ctx = Ctx Text Json
data Log :: Effect where
LogJSON :: Json -> Log m ()
LogText :: Text -> Log m ()
WithContext :: [Ctx] -> m a -> Log m a
makeEffect ''Log
Pretty standard - we have a way to log stuff and a way to add scoped context.
It comes with three interpretations:
First, a way to run the logger by doing nothing:
noRun :: Eff (Log : es) a -> Eff es a
noRun = interpret $ \case
LogJSON _ -> pure ()
LogText _ -> pure ()
WithContext _ m -> toEff m
Second, a way to output via traceIO
(which is the preferred way to log for games because it handles Windows properly):
runLog :: forall es a. IOE :> es => [Ctx] -> Eff (Log : es) a -> Eff es a
runLog x = interpret (h x)
where
h :: [Ctx] -> Handler Log es
h ctx = \case
WithContext c m -> toEffWith (h (c ++ ctx)) m
LogJSON j ->
liftIO
$ traceIO
$ Data.ByteString.Char8.unpack
$ Json.toByteString
$ Json.object
$ fmap (\(Ctx k v) -> (k, v))
$ Ctx (Data.Text.pack "body") j : ctx
LogText s ->
liftIO
$ traceIO
$ Data.ByteString.Char8.unpack
$ Json.toByteString
$ Json.object
$ fmap (\(Ctx k v) -> (k, v))
$ Ctx (Data.Text.pack "message") (Json.textString s) : ctx
Finally, an interpreter that uses runLog
but also adds clock information (i.e. which "frame" we are on in our loop). The internals use a mayhem-engine
-abstraction, but if it were written as a bare interpreter, the type would illustrate the point:
runLogClocked :: forall es a. [IOE, Clock] :>> es => [Ctx] -> Eff (Log : es) a -> Eff es a
runLogClocked ctx effa = clockJson >>= \clk -> runLog (Ctx "clock" clk : ctx) effa
If you know how to work with Haskell types abstractly and play type tetris (and essential intermediate/advanced Haskell skill imo), you can write this function. This is Just Haskell Function Composition. A huge win over mtl
.
The fact that cleff
interpreters are Just Haskell Values (instead of TC instances) makes them more "first-class." This allows you to more easily write abstractions over them.
In games and web servers, a common architecture is:
- Have a bunch of effects that thread context to your application code.
- In
main
, allocate and deallocate the context and pass it to the effect runner.
main
is often a bespoke do
block of setup and teardown code. Every time you add an effect, you have to go in and do this by hand and thread things through. If there are dependencies, you have to unwind that graph.
The mayhem-engine
abstracts over interpreters to allow them to be packaged with their setup/teardown. This logic is defined in a decentralized way, alongside the effects themselves. Like is often the case with extensible effects: A place for everything and everything in its place.
-- | Natural transformation
data m :~> n = Run { run :: forall a. m a -> n a }
type Expansion m e (es :: [Effect]) = (Eff es :~> m) -> m (Eff (e : es) :~> m)
The type is a little loopy, but it basically says "given a way to interpret Eff es
down to a bedrock m
, produce an interpreter for e
(Eff (e : es) :~> m
) in a potentially effectful way."
The "potentially effectful way" is the key - expansions can use other effects to build upon each other. Or (most commonly) they can use IO
for setup/teardown.
MonadManaged m
is a nice constraint to put on that m
. It allows you to abstract over those withX
calls in main
. For instance, the expansion for SDL_GPU
has this type:
data SDL_GPU'Config = SDL_GPU'Config
{ enableVsync :: Bool
, nativeRez :: NativeResolution
}
exp'SDL_GPU :: MonadManaged m => SDL_GPU'Config -> Expansion m SDL_GPU es
It initializes sdl2
, the underlying sdl_gpu
library, and does some engine-specific initialization as well. And then at the end of main
, it calls GPU.quit
to teardown.
Now that effects can be packaged with their resource management, our main
becomes a series of >>=
and nothing more! Here's what a main
looks like in a game:
mainWith devmode debugFont ghciPipe gameRez mkWorld mkParams = runLiftIOE
& exp'SDL_GPU SDL_GPU'Config {enableVsync = False, nativeRez = gameRez}
>>= exp'Cute_Sound
>>= exp'Cute_Sound8000
>>= exp'Apecs mkWorld
>>= exp'Params mkParams
>>= exp'Assets @a "assets"
>>= exp'Clock
>>= (if devmode then exp'Stepper else exp'NoStepper)
>>= (if devmode then exp'Debug (debugFont) else exp'NoDebug)
>>= (if devmode then exp'Log'Clocked else exp'NoLog)
>>= maybe exp'GHCiDummy exp'GHCiPipe ghciPipe
This code is initializing windows, reading textures and fonts, setting up MVar
s for hot reloading, allocating sound buffers, etc. But that's all hidden and not polluting main
.