Project 12: Free Monad DSL

Project 12: Free Monad DSL

Separating Description from Execution: The Ultimate Declarative Pattern

  • Main Programming Language: Haskell
  • Alternative Languages: Scala, PureScript, OCaml (with effects)
  • Coolness Level: Level 5: Pure Magic (Super Cool)
  • Difficulty: Level 5: Master
  • Knowledge Area: DSLs / Free Structures / Effect Systems
  • Estimated Time: 2-3 weeks
  • Prerequisites: Projects 6 (Functor/Applicative/Monad), Project 9 (Monad Transformers), solid understanding of functors

Learning Objectives

After completing this project, you will be able to:

  1. Explain what “free” means in free monad - Understand the mathematical concept of free structures and why they matter
  2. Build the Free monad type from scratch - Implement data Free f a = Pure a | Free (f (Free f a))
  3. Design DSL algebras as functors - Create operation types with the functor pattern
  4. Write interpreters for free monads - Transform DSL programs into different target monads
  5. Compose multiple DSLs - Use coproducts of functors to combine effect languages
  6. Test effectful code purely - Write mock interpreters for unit testing
  7. Connect free monads to modern effect systems - Understand how Polysemy, Eff, and similar libraries evolved from free monads

Conceptual Foundation

The Fundamental Problem: Mixing Effects with Logic

Consider a simple program that interacts with a key-value store:

program :: IO Int
program = do
  put "x" 10
  put "y" 20
  x <- get "x"
  y <- get "y"
  return (x + y)

This code has a problem: the logic is tangled with the execution. When you run put "x" 10, it immediately executes against a real database. This makes the code:

  1. Hard to test: You need a real database to run tests
  2. Hard to reason about: Effects happen as you build the program
  3. Impossible to introspect: You can’t ask “what operations will this program do?”
  4. Locked to one interpretation: You can’t run it against a mock, log it, or optimize it

What if the program was just data?

program :: KVStore Int
program = ...  -- Pure description of operations, no actual execution

Now we can:

  • Inspect the program before running it
  • Transform it (add logging, tracing)
  • Interpret it in different ways (real DB, mock, pure state)
  • Test it without side effects

This is what free monads provide.

What Does “Free” Mean?

In mathematics and computer science, a free structure is the most general structure satisfying some laws, with no additional constraints.

Example: Free Monoid (Lists)

A monoid needs:

  • An identity element: mempty
  • An associative binary operation: (<>)

What’s the “freest” monoid? Lists!

mempty = []
(<>) = (++)

Lists are “free” because:

  • They satisfy the monoid laws
  • They add no extra constraints
  • Any other monoid can be “collapsed” from lists
-- Any monoid m can be obtained by folding a list
fold :: Monoid m => [m] -> m
fold = foldr (<>) mempty

fold [Sum 1, Sum 2, Sum 3]  -- Sum 6
fold ["a", "b", "c"]         -- "abc"

Free Monad: The Freest Monad Over a Functor

Given a functor f, the free monad Free f is the freest monad that contains f as operations. It satisfies the monad laws and adds nothing else.

data Free f a
  = Pure a                  -- Return a value (base case)
  | Free (f (Free f a))     -- One operation, then continue

Understanding the Free Monad Structure

Let’s build intuition for Free f a:

data Free f a
  = Pure a
  | Free (f (Free f a))

Pure a: The program is done and returns a. This is the base case of the recursion.

Free (f (Free f a)): The program performs one operation (represented by f), and the operation contains the continuation—what to do next.

Visualizing as a Tree

A free monad value is a tree of operations:

Free f a is like:

         Free (Op1)
              |
         Free (Op2)
              |
         Free (Op3)
              |
           Pure a

Each Free node represents one operation. The functor f wraps the rest of the tree. Eventually, we reach Pure a—the final result.

Why the Functor Must Wrap the Continuation

The type f (Free f a) means the functor contains the rest of the program. This is how operations “carry” their continuations:

data ConsoleF next
  = PrintLine String next      -- Print, then continue with 'next'
  | ReadLine (String -> next)  -- Read, then continue using the input

In PrintLine "hello" next:

  • PrintLine is the operation
  • "hello" is the argument
  • next is what happens after printing

In ReadLine (String -> next):

  • ReadLine is the operation
  • (String -> next) is a function that takes the input and produces the continuation

The Monad Instance: Where the Magic Happens

instance Functor f => Monad (Free f) where
  return = Pure

  Pure a >>= f = f a              -- Apply f directly
  Free fa >>= f = Free (fmap (>>= f) fa)  -- Push bind into the structure

Let’s trace through >>=:

Case 1: Pure a >>= f The program is already done with value a. Just apply f to get the next program.

Case 2: Free fa >>= f The program has an operation fa :: f (Free f a). We need to bind through it:

  1. fmap (>>= f) fa maps the bind over the functor
  2. This pushes the f function into the continuations
  3. Result: Free (f (Free f b))

This is substitution! Binding in a free monad replaces every Pure a in the tree with f a.

Smart Constructors: Making DSLs Ergonomic

Raw free monad construction is ugly:

-- Ugly!
program = Free (PrintLine "hello" (Free (PrintLine "world" (Pure ()))))

Smart constructors make it nice:

liftF :: Functor f => f a -> Free f a
liftF fa = Free (fmap Pure fa)

printLine :: String -> Free ConsoleF ()
printLine s = liftF (PrintLine s ())

readLine :: Free ConsoleF String
readLine = liftF (ReadLine id)

Now we can use do-notation:

program :: Free ConsoleF ()
program = do
  printLine "What's your name?"
  name <- readLine
  printLine ("Hello, " ++ name ++ "!")

This is pure data! No IO has happened yet.

Interpreters: Running DSL Programs

An interpreter transforms a free monad program into a concrete monad:

interpret :: Monad m => (forall x. f x -> m x) -> Free f a -> m a
interpret _ (Pure a) = return a
interpret handler (Free fa) = do
  a <- handler fa          -- Handle this operation
  interpret handler a      -- Interpret the continuation

Wait, there’s a subtlety. The handler returns the result of the operation, but fa :: f (Free f a). We need to extract the continuation!

Let me fix that:

-- For our ConsoleF:
interpretIO :: Free ConsoleF a -> IO a
interpretIO (Pure a) = return a
interpretIO (Free (PrintLine s next)) = do
  putStrLn s
  interpretIO next
interpretIO (Free (ReadLine cont)) = do
  line <- getLine
  interpretIO (cont line)  -- 'cont line' gives us the next program

The key insight: The functor’s structure tells us how to extract the continuation:

  • PrintLine s next: next is the continuation
  • ReadLine cont: cont line gives the continuation after reading line

Multiple Interpreters: The Power of Separation

The same DSL program can be interpreted in different ways:

-- Interpreter 1: IO (real effects)
interpretIO :: Free ConsoleF a -> IO a

-- Interpreter 2: Writer (just collect output)
interpretWriter :: Free ConsoleF a -> Writer [String] a
interpretWriter (Pure a) = return a
interpretWriter (Free (PrintLine s next)) = do
  tell [s]
  interpretWriter next
interpretWriter (Free (ReadLine cont)) = do
  interpretWriter (cont "mock input")

-- Interpreter 3: Pure testing
interpretPure :: [String] -> Free ConsoleF a -> (a, [String])
-- Takes mock inputs, returns result and collected outputs

Same program, three interpretations! Testing becomes trivial.

The Deep Why: Separating Concerns

Free monads achieve a profound separation:

  1. Syntax (the DSL): What operations exist
  2. Semantics (the interpreter): What operations mean

This is the expression problem solution for effects. You can:

  • Add new operations without changing interpreters (open union approach)
  • Add new interpreters without changing the DSL

Compare to direct IO:

-- Tangled: Can't test without real IO
program :: IO ()
program = putStrLn "Hello" >> getLine >>= putStrLn

With free monads:

-- Separated: Test with pure interpreter
program :: Free ConsoleF ()
program = printLine "Hello" >> readLine >>= printLine

-- Test
test = interpretPure ["World"] program == ((), ["Hello", "World"])

Building Complex DSLs: The Key-Value Store Example

Let’s build a complete key-value store DSL:

data KVStoreF k v next
  = Get k (Maybe v -> next)   -- Get returns Maybe v
  | Put k v next               -- Put returns ()
  | Delete k next              -- Delete returns ()
  deriving Functor             -- GHC can derive this!

type KVStore k v = Free (KVStoreF k v)

-- Smart constructors
get :: k -> KVStore k v (Maybe v)
get k = liftF (Get k id)

put :: k -> v -> KVStore k v ()
put k v = liftF (Put k v ())

delete :: k -> KVStore k v ()
delete k = liftF (Delete k ())

Now write programs:

program :: KVStore String Int Int
program = do
  put "x" 10
  put "y" 20
  x <- get "x"
  y <- get "y"
  return $ fromMaybe 0 x + fromMaybe 0 y

Interpreters:

-- In-memory using State
runState :: Ord k => KVStore k v a -> State (Map k v) a
runState (Pure a) = return a
runState (Free (Get k cont)) = do
  m <- State.get
  runState (cont (Map.lookup k m))
runState (Free (Put k v next)) = do
  State.modify (Map.insert k v)
  runState next
runState (Free (Delete k next)) = do
  State.modify (Map.delete k)
  runState next

-- With logging
runLogged :: (Show k, Show v, Ord k) => KVStore k v a -> WriterT [String] (State (Map k v)) a

Composing Multiple DSLs

What if you need both key-value operations AND console operations? Use coproducts:

data (f :+: g) a = InL (f a) | InR (g a)
  deriving Functor

type AppDSL = KVStoreF String Int :+: ConsoleF

Now you can use both:

injectKV :: KVStoreF String Int a -> AppDSL a
injectKV = InL

injectConsole :: ConsoleF a -> AppDSL a
injectConsole = InR

-- Lift operations into the combined DSL
putKV :: String -> Int -> Free AppDSL ()
putKV k v = liftF (injectKV (Put k v ()))

printLine' :: String -> Free AppDSL ()
printLine' s = liftF (injectConsole (PrintLine s ()))

This is the idea behind Data Types a la Carte (Wouter Swierstra’s famous paper).

The Performance Question

Free monads have a performance cost: they build a tree structure that must be traversed at interpretation time. For deeply nested binds, this can be O(n^2).

Solutions:

  1. Codensity transformation: Accumulate continuations in CPS style
  2. Freer monads: Use type-aligned sequences instead of functors
  3. Effect libraries: Polysemy, Eff, fused-effects use optimized representations
-- Freer monad: More efficient
data Freer f a where
  Pure :: a -> Freer f a
  Bind :: f a -> (a -> Freer f b) -> Freer f b

Modern effect systems have essentially eliminated the performance overhead.

Connection to Algebraic Effects

Free monads are the precursor to algebraic effects, a more principled approach to effects:

Free Monads (2008-2015) -> Extensible Effects (2013) -> Algebraic Effects (2015+)

Languages like Eff, Koka, and OCaml 5 have native algebraic effects. Haskell libraries like Polysemy and Effectful provide similar functionality.

The core ideas are the same:

  1. Separate effect definition from interpretation
  2. Compose effects modularly
  3. Enable multiple interpretations

The Mathematical Foundation

Free monads come from category theory. Given a functor F:

  1. Free creates the free monad: Free :: (* -> *) -> (* -> *)
  2. The forgetful functor goes back: Forgets the monad structure
  3. These form an adjunction: Free is left adjoint to forgetful

This adjunction is why free monads are “free”—they’re the minimal structure needed.

For the categorically inclined:

  • Free monads are initial algebras of the functor 1 + F . _
  • They’re related to Kleisli categories
  • The interpreter is an algebra homomorphism

Why Free Monads Matter for Real Software

Beyond academic interest, free monads solve practical problems:

1. Testability

-- Production: real database
runProd :: KVStore String Int a -> IO a

-- Testing: pure mock
runTest :: Map String Int -> KVStore String Int a -> (a, Map String Int)

2. Logging/Tracing (Add without changing DSL programs)

runWithLogging :: KVStore k v a -> WriterT [LogEntry] IO a

3. Optimization (Inspect and transform programs)

optimize :: Free DSLF a -> Free DSLF a
optimize = batchReads . cacheWrites  -- Combine operations!

4. Mocking External Services

-- Test against mock API without network calls
runMock :: [(Request, Response)] -> Free HttpF a -> Either Error a

5. Replay/Undo

-- Record operations, replay later
record :: Free EditorF a -> (a, [EditorOp])
replay :: [EditorOp] -> Free EditorF ()

Historical Context

Free monads became popular in Haskell around 2012-2015:

  • 2012: Gabriel Gonzalez’s “Why Free Monads Matter” blog post
  • 2013: Wouter Swierstra’s “Data Types a la Carte”
  • 2014: Oleg Kiselyov’s extensible effects paper
  • 2015-present: Evolution into effect libraries

Today, pure free monads are less common in production (due to performance), but the patterns and thinking they introduced are everywhere in Haskell.


Project Specification

You will build a domain-specific language using free monads. Your framework should include:

Core Requirements

  1. Free Monad Type
    • data Free f a = Pure a | Free (f (Free f a))
    • Functor, Applicative, and Monad instances
    • liftF for lifting functor values
  2. DSL Definition
    • A key-value store DSL (KVStoreF)
    • A console DSL (ConsoleF)
    • Smart constructors for each operation
  3. Multiple Interpreters
    • In-memory interpreter using State
    • Logging interpreter using Writer
    • IO interpreter for real effects
    • Pure interpreter for testing
  4. DSL Composition
    • Coproduct type (:+:)
    • Combined DSL with multiple effect types
    • Pattern matching interpreters for combined DSLs
  5. Testing
    • Pure tests using mock interpreter
    • Property tests for interpreter consistency

Stretch Goals

  • Implement Freer monads for better performance
  • Add an HTTP client DSL
  • Implement program introspection (count operations, list accessed keys)
  • Build a simple effect library with type-level effect tracking
  • Add transactional semantics (rollback on error)

Solution Architecture

Module Structure

src/
  Free/
    Free.hs         -- Core Free monad type
    LiftF.hs        -- Lifting operations
    Coproduct.hs    -- DSL composition
  DSL/
    KVStore.hs      -- Key-value store DSL
    Console.hs      -- Console I/O DSL
    Combined.hs     -- Combined DSL
  Interpret/
    KVStore/
      Memory.hs     -- In-memory interpreter
      Logging.hs    -- Logging interpreter
    Console/
      IO.hs         -- Real I/O interpreter
      Mock.hs       -- Mock interpreter
  FreeDSL.hs        -- Public API

Core Types

-- The free monad
data Free f a
  = Pure a
  | Free (f (Free f a))

-- DSL coproduct
data (f :+: g) a = InL (f a) | InR (g a)

-- Key-value store operations
data KVStoreF k v next
  = Get k (Maybe v -> next)
  | Put k v next
  | Delete k next

-- Console operations
data ConsoleF next
  = PrintLine String next
  | ReadLine (String -> next)

Key Design Decisions

  1. Derive Functor: Use DeriveFunctor for DSL types
  2. Separate interpreters per DSL: Compose for combined DSLs
  3. Use type aliases: type KVStore k v = Free (KVStoreF k v)
  4. Smart constructors hide implementation: Users never see Free or liftF

Implementation Guide

Phase 1: The Free Monad Core (Days 1-3)

Goal: Implement the free monad type and its instances.

Milestone 1.1: Define the Free type

data Free f a
  = Pure a
  | Free (f (Free f a))

Milestone 1.2: Implement Functor instance

instance Functor f => Functor (Free f) where
  fmap g (Pure a)  = Pure (g a)
  fmap g (Free fa) = Free (fmap (fmap g) fa)

Milestone 1.3: Implement Applicative instance

instance Functor f => Applicative (Free f) where
  pure = Pure
  Pure f  <*> a = fmap f a
  Free ff <*> a = Free (fmap (<*> a) ff)

Milestone 1.4: Implement Monad instance

instance Functor f => Monad (Free f) where
  return = Pure
  Pure a  >>= f = f a
  Free fa >>= f = Free (fmap (>>= f) fa)

Milestone 1.5: Implement liftF

liftF :: Functor f => f a -> Free f a
liftF fa = Free (fmap Pure fa)

Test: Verify monad laws hold (using property tests from Project 10!).

Phase 2: Key-Value Store DSL (Days 4-6)

Goal: Build a complete key-value store DSL.

Milestone 2.1: Define the functor

data KVStoreF k v next
  = Get k (Maybe v -> next)
  | Put k v next
  | Delete k next
  deriving Functor

Milestone 2.2: Create smart constructors

get :: k -> Free (KVStoreF k v) (Maybe v)
get k = liftF (Get k id)

put :: k -> v -> Free (KVStoreF k v) ()
put k v = liftF (Put k v ())

delete :: k -> Free (KVStoreF k v) ()
delete k = liftF (Delete k ())

Milestone 2.3: Write sample programs

transfer :: String -> String -> Int -> KVStore String Int (Maybe String)
transfer from to amount = do
  fromBalance <- get from
  toBalance <- get to
  case (fromBalance, toBalance) of
    (Just fb, Just tb) | fb >= amount -> do
      put from (fb - amount)
      put to (tb + amount)
      return (Just "Success")
    _ -> return Nothing

Test: Programs compose correctly, types line up.

Phase 3: Interpreters (Days 7-10)

Goal: Write multiple interpreters for the KV store DSL.

Milestone 3.1: In-memory interpreter

runMemory :: Ord k => Free (KVStoreF k v) a -> State (Map k v) a
runMemory (Pure a) = return a
runMemory (Free (Get k cont)) = do
  m <- get
  runMemory (cont (Map.lookup k m))
runMemory (Free (Put k v next)) = do
  modify (Map.insert k v)
  runMemory next
runMemory (Free (Delete k next)) = do
  modify (Map.delete k)
  runMemory next

Milestone 3.2: Logging interpreter

data LogEntry = LogGet String | LogPut String String | LogDelete String

runLogged :: (Show k, Show v, Ord k)
          => Free (KVStoreF k v) a
          -> WriterT [LogEntry] (State (Map k v)) a

Milestone 3.3: Pure test interpreter

runPure :: Ord k => Map k v -> Free (KVStoreF k v) a -> (a, Map k v)
runPure initial prog = runState (runMemory prog) initial

Milestone 3.4: IO interpreter (for real database)

runIO :: Free (KVStoreF String String) a -> IO a
-- Uses actual database/file system

Test: Same program gives same results in different interpreters.

Phase 4: Console DSL (Days 11-12)

Goal: Add a second DSL for console I/O.

Milestone 4.1: Define the functor

data ConsoleF next
  = PrintLine String next
  | ReadLine (String -> next)
  deriving Functor

Milestone 4.2: Smart constructors

printLine :: String -> Free ConsoleF ()
printLine s = liftF (PrintLine s ())

readLine :: Free ConsoleF String
readLine = liftF (ReadLine id)

Milestone 4.3: Interpreters

-- Real IO
runConsoleIO :: Free ConsoleF a -> IO a

-- Mock for testing
runConsoleMock :: [String] -> Free ConsoleF a -> (a, [String])
-- Takes input lines, returns output lines

Test: Console programs work in both interpreters.

Phase 5: DSL Composition (Days 13-15)

Goal: Combine multiple DSLs into one.

Milestone 5.1: Define coproduct

data (f :+: g) a = InL (f a) | InR (g a)
  deriving Functor

infixr 8 :+:

Milestone 5.2: Injection helpers

class (Functor sub, Functor sup) => sub :<: sup where
  inj :: sub a -> sup a

instance Functor f => f :<: f where
  inj = id

instance (Functor f, Functor g) => f :<: (f :+: g) where
  inj = InL

instance (Functor f, Functor g, Functor h, f :<: g) => f :<: (h :+: g) where
  inj = InR . inj

Milestone 5.3: Generic liftF

inject :: (g :<: f) => g a -> Free f a
inject = liftF . inj

Milestone 5.4: Combined interpreter

type AppF = KVStoreF String Int :+: ConsoleF
type App = Free AppF

runApp :: App a -> StateT (Map String Int) IO a
runApp (Pure a) = return a
runApp (Free (InL kv)) = handleKV kv >>= runApp
runApp (Free (InR console)) = handleConsole console >>= runApp

Test: Combined programs use both DSLs correctly.


Testing Strategy

Property-Based Tests

-- Interpreter consistency: same program, same result
prop_interpreterConsistency :: Map String Int -> KVStore String Int Int -> Bool
prop_interpreterConsistency initial prog =
  fst (runPure initial prog) == fst (runState (runLogged prog) initial)

-- Monad laws
prop_leftIdentity :: Int -> (Int -> KVStore String Int Int) -> Bool
prop_leftIdentity a f = runPure Map.empty (return a >>= f) == runPure Map.empty (f a)

prop_rightIdentity :: KVStore String Int Int -> Bool
prop_rightIdentity m = runPure Map.empty (m >>= return) == runPure Map.empty m

Unit Tests

test_transfer :: Assertion
test_transfer = do
  let initial = Map.fromList [("alice", 100), ("bob", 50)]
      prog = transfer "alice" "bob" 30
      (result, final) = runPure initial prog
  result @?= Just "Success"
  Map.lookup "alice" final @?= Just 70
  Map.lookup "bob" final @?= Just 80

test_transferFail :: Assertion
test_transferFail = do
  let initial = Map.fromList [("alice", 20), ("bob", 50)]
      prog = transfer "alice" "bob" 30
      (result, final) = runPure initial prog
  result @?= Nothing
  final @?= initial  -- No change

Mock Testing for Console

test_consoleProgram :: Assertion
test_consoleProgram = do
  let prog = do
        printLine "What's your name?"
        name <- readLine
        printLine ("Hello, " ++ name)
      ((), outputs) = runConsoleMock ["Alice"] prog
  outputs @?= ["What's your name?", "Hello, Alice"]

Common Pitfalls

1. Forgetting Functor Constraint

Problem: Free monad instances require Functor f:

-- WRONG: No Functor constraint
instance Monad (Free f) where ...  -- Won't compile!

Solution: Always include the constraint:

instance Functor f => Monad (Free f) where ...

2. Wrong Continuation in Smart Constructors

Problem: Using wrong continuation type:

-- WRONG: Should use 'id', not '()'
get k = liftF (Get k ())  -- Type error!

Solution: Match the continuation to the return type:

get k = liftF (Get k id)  -- id :: Maybe v -> Maybe v

3. Infinite Loops in Interpreters

Problem: Not recursing properly:

-- WRONG: Doesn't interpret the continuation!
runMemory (Free (Put k v next)) = do
  modify (Map.insert k v)
  return ()  -- Lost the rest of the program!

Solution: Always interpret the continuation:

runMemory (Free (Put k v next)) = do
  modify (Map.insert k v)
  runMemory next  -- Continue!

4. Missing Derive Functor

Problem: Manually implementing wrong Functor:

-- WRONG: Forgot to handle continuation
instance Functor (KVStoreF k v) where
  fmap f (Get k cont) = Get k cont  -- Lost f!

Solution: Use DeriveFunctor:

{-# LANGUAGE DeriveFunctor #-}
data KVStoreF k v next = ... deriving Functor

5. Coproduct Pattern Match Exhaustiveness

Problem: Forgetting to handle all cases:

runApp (Free (InL kv)) = ...
-- Missing InR case!

Solution: Pattern match exhaustively:

runApp (Free (InL kv)) = ...
runApp (Free (InR console)) = ...

Extensions and Challenges

1. Freer Monads

Implement the more efficient Freer representation:

data Freer f a where
  Pure :: a -> Freer f a
  Impure :: f x -> (x -> Freer f a) -> Freer f a

2. Effect Tracking at the Type Level

Use type-level lists to track which effects a program uses:

type Eff (effs :: [* -> *]) a = ...

runState :: Eff (State s ': effs) a -> s -> Eff effs (a, s)

3. Program Optimization

Implement optimizations that transform DSL programs:

optimize :: Free KVStoreF a -> Free KVStoreF a
optimize = batchReads . cacheWrites . eliminateDeadStores

4. Transactional Semantics

Add rollback on error:

transaction :: Free KVStoreF a -> Free KVStoreF (Either Error a)

5. HTTP Client DSL

Build an HTTP DSL and compose with existing DSLs:

data HttpF next
  = HttpGet URL (Response -> next)
  | HttpPost URL Body (Response -> next)

Real-World Connections

Where Free Monads Appear

  1. Testing: Mock external services in tests
  2. Logging/Tracing: Add observability without changing code
  3. DSL Design: Build domain-specific languages
  4. Workflow Engines: Describe complex workflows as data
  5. Game Engines: Separate game logic from rendering

Evolution to Modern Effect Systems

Free monads evolved into modern effect libraries:

  • Polysemy (Haskell): Type-safe, composable effects
  • Eff (Haskell): Effect inference
  • fused-effects (Haskell): Performance-optimized
  • ZIO (Scala): Full effect system with concurrency
  • Effectful (Haskell): High-performance effects

Industry Adoption

  • Stripe: Uses effect patterns for API design
  • Facebook: Effect systems in Haxl
  • Jane Street: OCaml effects for trading systems
  • Various startups: Haskell services using Polysemy/Effectful

Interview Questions

  1. “What is a free monad and why would you use one?”
    • Answer: A free monad separates program description from execution. It represents effectful programs as pure data structures, enabling multiple interpretations (testing, logging, real execution) of the same program.
  2. “What does ‘free’ mean in ‘free monad’?”
    • Answer: “Free” means the minimal/most general structure satisfying the monad laws. Like lists are the free monoid, Free f is the free monad over functor f. It adds no constraints beyond what’s required by the monad laws.
  3. “How does bind work for free monads?”
    • Answer: Pure a >>= f = f a applies f directly. Free fa >>= f = Free (fmap (>>= f) fa) pushes the bind into the structure, deferring execution. This is substitution: every Pure in the tree gets replaced by applying f.
  4. “What are the performance implications of free monads?”
    • Answer: Free monads build a tree structure, leading to O(n^2) bind for deeply nested programs. Solutions include the codensity transformation, Freer monads (type-aligned sequences), and modern effect libraries that optimize away the overhead.
  5. “How do you compose multiple DSLs with free monads?”
    • Answer: Use coproducts of functors: data (f :+: g) a = InL (f a) | InR (g a). Inject each DSL’s operations into the combined type, then pattern match in the interpreter. This is the “Data Types a la Carte” approach.
  6. “How do free monads help with testing?”
    • Answer: Since programs are data, you can write pure interpreters that don’t perform real effects. Test with mock data, verify behavior without databases or I/O, and even inspect what operations a program would perform.
  7. “How do free monads relate to algebraic effects?”
    • Answer: Free monads are the precursor to algebraic effects. Both separate effect definition from handling. Algebraic effects add better composition (effect rows), more ergonomic syntax, and are implemented natively in some languages.

Self-Assessment Checklist

You’ve mastered this project when you can:

  • Explain what “free” means mathematically and why it matters
  • Implement the Free monad type with correct instances
  • Derive Functor for operation types automatically
  • Write smart constructors that hide Free/liftF
  • Build programs using do-notation that are pure data
  • Write multiple interpreters for the same DSL
  • Test effectful code using pure mock interpreters
  • Compose multiple DSLs using coproducts
  • Explain the performance tradeoffs of free monads
  • Connect free monads to modern effect systems
  • Debug interpreter issues (wrong continuation handling)
  • Design new DSLs for different domains

Resources

Primary References

Topic Resource Specific Section
Free monads introduction “Haskell in Depth” by Bragilevsky Chapter 11
Why Free Monads Matter Blog post by Gabriel Gonzalez Full post
Monad fundamentals “Haskell Programming from First Principles” Chapter 18
DSL composition “Data Types a la Carte” by Swierstra Full paper
Functor and higher-order types “Haskell Programming from First Principles” Chapter 16

Academic Papers

Topic Paper
DSL composition “Data Types a la Carte” (Swierstra)
Extensible effects “Extensible Effects” (Kiselyov et al.)
Free monads optimized “Reflection without Remorse”
Algebraic effects “An Introduction to Algebraic Effects and Handlers”

Online Resources

  • Gabriel Gonzalez’s “Why Free Monads Matter” blog post
  • Polysemy documentation (modern effect library)
  • Sandy Maguire’s “Thinking with Types” for advanced type-level programming
  • Matt Parsons’s blog on effect systems

“The goal is not to eliminate effects, but to make them explicit, composable, and testable. Free monads are a stepping stone to that vision.”

After completing this project, you’ll understand why Haskell programmers are obsessed with effects—and why they should be.