3

I have the following type:

data S req rsp = Done rsp | Next req (rsp -> S req rsp)

The idea is to use it as a pure representation for network communication, i.e:

... Next GetUser $ \uid -> Next (Login uid) $ \success -> Done success

Which would then be evaluated by some impure function eval.

Now, what is this (if anything?) It's not a monad, neither an arrow, as far as I can see. It seems to be something between a stream/pipe/automaton/fsm and the continuation monad. This makes me think that there might be a better representation for this type of thing, but what?

Benjamin Hodgson
  • 42,952
  • 15
  • 108
  • 157
Philip Kamenarsky
  • 2,757
  • 2
  • 24
  • 30
  • 2
    This can be viewed as a free monad if it is rewritten `data S req rsp r = Done r | Next req (rsp -> S req rsp r)` Then it's effectively the free monad on the functor `Compose ((,) req) ((->) resp)` or `data Request req resp r = Request req (resp -> r`. It is very common to use a constructor of this type in writing a functor for a free monad, as you can see from some of the examples in http://degoes.net/articles/modern-fp Note that all four constructors of his `HttpF` functor, `GET`, `POST` etc, are effectively of this shape. – Michael Oct 24 '16 at 03:20
  • 1
    In `pipes`, the `Server` (or equivalently `Client`) type is a (monad transformer) version of it. Then we can write say ` let mkRequest :: Monad m => req -> Client req resp m resp; mkRequest = request` (Here an underlying monad is presupposed, as if you had applied `FreeT` rather than `Free` to the request functor). – Michael Oct 24 '16 at 03:20

2 Answers2

6

It's Free Monad. The idea is that you have a description of instructions for which you can have multiple interpreters like your eval function. Free Monad abstracts over the pattern that this task has. For details I recommend this great post.

To adapt your type to Free we can do the following:

{-# LANGUAGE DeriveFunctor #-}

import Control.Monad.Free

data Instruction req rsp next =
  Respond rsp |
  Interact req (rsp -> next)
  deriving (Functor)

type S req rsp =
  Free (Instruction req rsp)

respond :: rsp -> S req rsp ()
respond rsp =
  liftF (Respond rsp)

interact :: req -> S req rsp rsp
interact req =
  liftF (Interact req id)

Now, thanks to Free, S req rsp is a monad, which means that you can now compose your respond and interact functions using Monad API.

There's more to it. The respond and interact functions could be generated using Template Haskell with the following extra code:

{-# LANGUAGE TemplateHaskell #-}

import Control.Monad.Free.TH

makeFree ''Instruction
Nikita Volkov
  • 42,792
  • 11
  • 94
  • 169
5

Your type looks a little bit like Apfelmus's operational monad, also known as the Freer monad:

data Program inst a where
    Return :: a -> Program inst a
    Bind :: inst a -> (a -> Program inst b) -> Program inst b

instance Monad (Program inst) where
    return = Return
    Return x >>= f = f x
    Bind i next >>= f = Bind i (fmap (>>= f) next)

-- plus the usual Functor and Applicative boilerplate

Program :: (* -> *) -> * -> * represents a sequence of instructions inst, which use their type parameter to indicate the "return type" of running that instruction in an interpreter. The Bind constructor takes an instruction and a continuation which can be run after the result of the instruction has been received from the interpreter. Note how a is existentially quantified, reflecting the fact that the types of all the intermediate steps in a computation are not relevant to the overall type.

The important difference between Program and your type is that the type of the response is determined by the instruction, rather than being fixed over the whole computation. This allows us to make more fine-grained guarantees about the response that each request expects to provoke.

For example, here's the state monad written as a Program:

data StateI s r where
    Get :: StateI s s
    Put :: s -> StateI s ()

type State s = Program (StateI s)

get :: State s s
get = Bind Get Return
put :: s -> State s ()
put s = Bind (Put s) Return

modify :: (s -> s) -> State s ()
modify f = do
    x <- get
    put (f x)

runState :: State s a -> s -> (s, a)
runState (Return x) s = (s, x)
runState (Bind Get next) s = runState (next s) s
runState (Bind (Put s) next) _ = runState (next ()) s

The co-Yoneda lemma tells us that Program is isomorphic to Free. Intuitively, it's a free monad based on ->'s Functor instance. For certain operations like left-associative binds, Program can be more efficient than Free, because its >>= is based on function composition, rather than possibly-expensively fmapping an arbitrary Functor.

Benjamin Hodgson
  • 42,952
  • 15
  • 108
  • 157