I'm releasing the mvc
library for model-view-controller (MVC) programming in Haskell. I initially designed this library with games and user interfaces in mind, but the larger goal of this library is to provide a mathematically inspired framework for general-purpose component sharing in Haskell.
This library differs in a significant way from other MVC libraries: this API statically enforces in the types that the Model
is pure, but with very little loss in power. Using mvc
you can refactor many types of concurrent applications into a substantial and pure Model
that interfaces with carefully constrained View
s and Controller
s.
When you purify your Model
this way, you can:
record and replay bugs reproducibly,
do property-based testing (ala
QuickCheck
) to uncover corner cases, and:prove formal properties about your
Model
using equational reasoning.
The first half of this post walks through two examples reproduced from the mvc
documentation and the second half of this post describes the architecture that enables you to embed large and non-trivial business logic in an entirely pure Model
. This post will use a side-by-side mix of theoretical terminology alongside plain English. Even if you don't understand the theoretical half of this post you should still derive benefit from the non-technical half and use that as a bridge towards understanding the underlying theory.
Examples
The mvc
library uses four types to represent everything:
The
Model
is a pure streaming transformation from inputs to outputsThe
View
handles all outputs from theModel
The
Controller
supplies all inputs to theModel
The
Managed
type extends other types with logic for acquiring or releasing resources
There are no other concepts you have to learn. The API is extraordinarily small (4 types, and 8 primitive functions associated with those types).
However, as we extend our application the types will never grow more complex. In fact, the mvc
library statically forbids you from increasing the complexity of your types, because the library only provides a single run function of the following type:
runMVC
:: s -- Initial state
-> Model s a b -- Program logic
-> Managed (View b, Controller a) -- Impure output and input
-> IO s -- Returns final state
There is no other way to consume Model
s, View
s, and Controller
s, so runMVC
forces you to consolidate all your View
s into a single View
and consolidate all your Controller
s into a single Controller
. This creates a single entry point and a single exit point for your Model
. Equally important, you cannot mix your Model
logic with your View
or Controller
logic. The mvc
library enforces MVC best practices using the type system.
This first minimal example illustrates these basic concepts:
import MVC
import qualified MVC.Prelude as MVC
import qualified Pipes.Prelude as Pipes
external :: Managed (View String, Controller String)
external = do
c1 <- MVC.stdinLines
c2 <- MVC.tick 1
return (MVC.stdoutLines, c1 <> fmap show c2)
model :: Model () String String
model = asPipe (Pipes.takeWhile (/= "quit"))
main :: IO ()
main = runMVC () model external
The key components are:
A
Controller
that interleaves lines from standard input with periodic ticksA
View
that writes lines to standard outputA pure
Model
, which forwards lines until it detects the string"quit"
A
Managed
type, which abstracts over resource acquisition and release
The Model
only has a single streaming entry point (the Controller
) and a single streaming exit point (the View
).
However, this interface is deceptively simple and can model very complex logic. For example, here's a more elaborate example using the sdl
library that displays a white rectangle between every two mouse clicks:
import Control.Monad (join)
import Graphics.UI.SDL as SDL
import Lens.Family.Stock (_Left, _Right) -- `lens-family-core`
import MVC
import MVC.Prelude
import qualified Pipes.Prelude as Pipes
data Done = Done deriving (Eq, Show)
sdl :: Managed (View (Either Rect Done), Controller Event)
sdl = join $ managed $ \k ->
withInit [InitVideo, InitEventthread] $ do
surface <- setVideoMode 640 480 32 [SWSurface]
white <- mapRGB (surfaceGetPixelFormat surface) 255 255 255
let done :: View Done
done = asSink (\Done -> SDL.quit)
drawRect :: View Rect
drawRect = asSink $ \rect -> do
_ <- fillRect surface (Just rect) white
SDL.flip surface
totalOut :: View (Either Rect Done)
totalOut = handles _Left drawRect <> handles _Right done
k $ do
totalIn <- producer Single (lift waitEvent >~ cat)
return (totalOut, totalIn)
pipe :: Monad m => Pipe Event (Either Rect Done) m ()
pipe = do
Pipes.takeWhile (/= Quit)
>-> (click >~ rectangle >~ Pipes.map Left)
yield (Right Done)
rectangle :: Monad m => Consumer' (Int, Int) m Rect
rectangle = do
(x1, y1) <- await
(x2, y2) <- await
let x = min x1 x2
y = min y1 y2
w = abs (x1 - x2)
h = abs (y1 - y2)
return (Rect x y w h)
click :: Monad m => Consumer' Event m (Int, Int)
click = do
e <- await
case e of
MouseButtonDown x y ButtonLeft ->
return (fromIntegral x, fromIntegral y)
_ -> click
main :: IO ()
main = runMVC () (asPipe pipe) sdl
Compile and run this program, which will open up a window, and begin clicking to paint white rectangles to the screen:
Here we package the effectful and concurrent components that we need from the sdl
into a self-contained package containing a single View
and Controller
. Our pure logic is contained entirely within a pure Pipe
, meaning that we can feed synthetic input to our program:
>>> let leftClick (x, y) = MouseButtonDown x y ButtonLeft
>>> Pipes.toList $
... each [leftClick (10, 10), leftClick (15, 16), Quit]
... >-> pipe
[Left (Rect {rectX = 10, rectY = 10, rectW = 5, rectH = 6}),Right
Done]
... or even QuickCheck our program logic! We can verify that our program generates exactly one rectangle for every two clicks:
>>> import Test.QuickCheck
>>> quickCheck $ \xs ->
... length (Pipes.toList (each (map leftClick xs) >-> pipe))
... == length xs `div` 2
+++ OK, passed 100 tests.
These kinds of tests would be impossible to run if we settled for anything less than complete separation of impurity and concurrency from our program's logic.
However, this total separation might seem unrealistic. What happens if we don't have exactly one View
or exactly one Controller
?
Monoids - Part 1
View
s and Controller
s are Monoid
s, meaning that we can combine any number of View
s into a single View
, and likewise combine any number of Controller
s into a single Controller
, by using mconcat
(short for "Monoid concatenation") from Data.Monoid
:
-- Combine a list of `Monoid`s into a single `Monoid`
mconcat :: Monoid m => [m] -> m
When we specialize the type of mconcat
to View
or Controller
we get the following two specialized functions:
-- Combining `View`s sequences their effects
mconcat :: [View a] -> View a
-- Combining `Controller`s interleaves their events
mconcat :: [Controller a] -> Controller a
In other words, we can can combine a list of any number of View
s into a single View
and combine a list of any number of Controller
s into a single Controller
. We get several benefits for free as a result of this design.
First, combinability centralizes our View
logic and Controller
logic into a single expression that we feed to runMVC
. We can therefore identify all inputs and outputs to our system simply by tracing all sub-expressions that feed into this larger expression. Contrast this with a typical mature code base where locating all relevant inputs and outputs for the system is non-trivial because they are typically not packaged into a single self-contained term.
Second, combinability promotes reuse. If we find ourselves repeatedly using the same set of inputs or outputs we can bundle them into a new derived component that we can share with others.
Third, combinable inputs and outputs are the reason our Model
can afford to have a single entry point and a single exit point. This beats having to write callback spaghetti code where we cannot easily reason about our application's control flow.
This is an example of a scalable architecture. The Monoid
type class lets us indefinitely grow our inputs and outputs without ever increasing the number of concepts, abstractions or types.
To be more specific, this scalable architecture is a special case of the category design pattern. When combinable components are morphisms in a category, we can connect as many components as we please yet still end up back where we started. In this case the operative category is a monoid, where View
s or Controller
s are morphisms, (<>)
is the composition operator and mempty
is the identity morphism.
Functors - Part 1
However, the Monoid
type class only lets us combine View
s and Controller
s that have the same type. For example, suppose we have a Controller
for key presses, and a separate Controller
for mouse events:
keys :: Controller KeyEvent
clicks :: Controller MouseEvent
If we try to combine these using (<>)
(an infix operator for mappend
), we will get a type error because their types do not match:
keys <> clicks -- TYPE ERROR!
keys
and clicks
don't stream the same event type, so how do we reconcile their different types? We use functors!
fmap Left keys
:: Controller (Either KeyEvent MouseEvent)
fmap Right clicks
:: Controller (Either KeyEvent MouseEvent)
fmap Left keys <> fmap Right clicks
:: Controller (Either KeyEvent MouseEvent)
The functor design pattern specifies that when we have an impedance mismatch between components, we unify them to agree on a common component framework. Here, we unify both of our Controller
output types using Either
.
Using theoretical terminology, when we have morphisms in diverse categories, we use functors to transform these morphisms to agree on a common category. In this case keys
is a morphism in the Controller KeyEvent
monoid and clicks
is a morphism in the Controller MouseEvent
monoid. We use fmap
to transform both monoids to agree on the Controller (Either KeyEvent MouseEvent)
monoid.
However, in this case fmap
is behaving as a functor in a different sense than we are normally accustomed to. We're already familiar with the following functor laws for fmap
:
fmap (f . g) = fmap f . fmap g
fmap id = id
However, right now we're not interested in transformations from functions to functions. Instead, we're interested in transformations from monoids to monoids, so we're going to invoke a different set of functor laws for our Controller
s:
fmap f (c1 <> c2) = fmap f c1 <> fmap f c2
fmap f mempty = mempty
In other words, fmap f
correctly translates monoid operations from one type of Controller
to another. This functor between monoids is the operative functor when we transform Controller
s to agree on a common type.
Functors - Part 2
We can use the same functor design pattern to unify different types of View
s as well. For example, let's assume that we have two separate View
s, one that logs String
s to a file, and another that displays video Frame
s to a screen:
logLines :: View String
frames :: View Frame
Again, we cannot naively combine these using mappend
/(<>)
because the types don't match:
logLines <> frames -- TYPE ERROR!
However, View
does not implement Functor
, so how do we unify the types this time?
We still use functors! However, this time we will be using the handles
function from mvc
, which has the following type:
handles :: Traversal' a b -> View b -> View a
This lets us use Traversal
s to specify which outgoing values each View
should handle:
import Lens.Family.Stock (_Left, _Right)
-- _Left :: Traversal' (Either a b) a
-- _Right :: Traversal' (Either a b) b
handles _Left logLines
:: View (Either String Frames)
handles _Right frames
:: View (Either String Frames)
handles _Left logLines <> handles _Right frames
:: view (Either String Frames)
This reads a little like English: logLines
handles
_Left
values, and frames
handles
_Right
values.
Like the previous example, handles
is a functor in two ways. The first functor maps traversal composition to function composition:
handles (t1 . t2) = handles t1 . handles t2
handles id = id
The second functor maps monoid operations from one View
to another:
handles t (v1 <> v2) = handles t v1 <> handles t v2
handles t mempty = mempty
This latter functor between View
monoids is the operative functor when we are unifying View
s to agree on a common type.
Applicatives
Alright, but we don't typically work with unadorned View
s or Controller
s. If you look at the utility section of mvc
you will see that most View
s or Controller
s are Managed
, meaning that they must acquire or release some sort of resource before they can begin streaming values in or out. For example, any View
or Controller
that interacts with a file must initially acquire the file and release the file when done:
fromFile :: FilePath -> Managed (Controller String)
toFile :: FilePath -> Managed (View String)
Uh oh... We have a problem! runMVC
doesn't accept separate Managed
View
s and Managed
Controller
s. runMVC
only accepts a combined View
and Controller
that share the same Managed
logic:
runMVC
:: s
-> Model s a b
-> Managed (View b, Controller a) -- What do we do?
-> IO s
runMVC
is written this way because some View
s and Controller
s must acquire and release the same resource. Does this mean that I need to provide a new run function that accepts separate Managed
View
s and Managed
Controller
s?
No! Fortunately, Managed
implements the Applicative
type class and we can use Applicative
s to combined two Managed
resources into a single Managed
resource:
import Control.Applicative (liftA2)
liftA2 (,)
:: Applicative f => f a -> f b -> f (a, b)
-- Specialize `liftA2` to `Managed`
liftA2 (,)
:: Managed a -> Managed b -> Managed (a, b)
toFile "output.txt"
:: Managed (View String)
fromFile "input.txt"
:: Managed (Controller String)
liftA2 (,) (toFile "output.txt") (fromFile "input.txt")
:: Managed (View String, Controller String)
I can fuse my two Managed
resources into a single Managed
resource! This is another example of scalable design. We don't complicate our run function by adding special cases for every permutation of Managed
View
s and Controller
s. Instead, we make Managed
layers laterally combinable, which prevents proliferation of functions, types, and concepts.
Monoids - Part 2
Managed
implements the Monoid
type class, too! Specifically, we can wrap any type that implements Monoid
with Managed
and we will get back a new derived Monoid
:
instance Monoid r => Monoid (Managed r) where
mempty = pure mempty
mappend = liftA2 mappend
This means that if I have two Managed
View
s, I can combine them into a single Managed
View
using the same Monoid
operations as before:
view1 :: Managed (View A)
view2 :: Managed (View A)
viewBoth :: Managed (View A)
viewBoth = view1 <> view2
The same is true for Controller
s:
controller1 :: Managed (Controller A)
controller2 :: Managed (Controller A)
controllerBoth :: Managed (Controller A)
controllerBoth = controller1 <> controller2
In fact, this trick works for any Applicative
, not just Managed
. Applicative
s let you extend arbitrary Monoid
s with new features while still preserving their Monoid
interface. There is no limit to how many Applicative
extensions you can layer this way.
Conclusion
The documentation for the mvc
library is full of theoretical examples like these showing how to architect applications using scalable abstractions inspired by category theory.
The mvc
library has certain limitations. Specifically, I did not design the library to handle changing numbers of inputs and outputs over time. This is not because of a deficiency in category theory. Rather, I wanted to introduce this simpler API as a stepping stone towards understanding more general abstractions later on that I will release as separate libraries.
The other reason I'm releasing the mvc
library is to test the waters for an upcoming book I will write about architecting programs using category theory. I plan to write one section of the book around an application structured using this mvc
style.
Links: