21

Given a free monad DSL such as:

data FooF x = Foo String x
            | Bar Int    x
  deriving (Functor)

type Foo = Free FooF

And a random interpreter for Foo:

printFoo :: Foo -> IO ()
printFoo (Free (Foo s n)) = print s >> printFoo n
printFoo (Free (Bar i n)) = print i >> printFoo n

It appears to me that it should be possible to intersperse something into each iteration of printFoo without resorting to doing it manually:

printFoo' :: Foo -> IO ()
printFoo' (Free (Foo s n)) = print s >> print "extra info" >> printFoo' n
printFoo' (Free (Bar i n)) = print i >> print "extra info" >> printFoo' n

Is this somehow possible by 'wrapping' the original printFoo?


Motivation: I am writing a small DSL that 'compiles' down to a binary format. The binary format contains some extra information after each user command. It has to be there, but is totally irrelevant in my usecase.

fho
  • 6,787
  • 26
  • 71

5 Answers5

15

The other answers have missed how simplefree makes this! :) Currently you have

{-# LANGUAGE DeriveFunctor #-}

import Control.Monad.Free

data FooF x = Foo String x
            | Bar Int    x
  deriving (Functor)

type Foo = Free FooF

program :: Free FooF ()
program = do
  liftF (Foo "Hello" ())
  liftF (Bar 1 ())
  liftF (Foo "Bye" ())

printFoo :: Foo () -> IO ()
printFoo (Free (Foo s n)) = print s >> printFoo n
printFoo (Free (Bar i n)) = print i >> printFoo n
printFoo (Pure a) = return a

which gives

*Main> printFoo program 
"Hello"
1
"Bye"

That's fine, but iterM can do the requisite plumbing for you

printFooF :: FooF (IO a) -> IO a
printFooF (Foo s x) = print s >> x
printFooF (Bar i x) = print i >> x

printFooBetter :: Foo () -> IO ()
printFooBetter = iterM printFooF

Then we get

*Main> printFooBetter program
"Hello"
1
"Bye"

OK great, it's the same as before. But printFooF gives us more flexibility to augment the translator along the lines you want

printFooFExtra :: FooF (IO a) -> IO a
printFooFExtra = (print "stuff before IO action" >>)
                 . printFooF
                 . fmap (print "stuff after IO action" >>)

printFooExtra :: Foo () -> IO ()
printFooExtra = iterM printFooFExtra

then we get

*Main> printFooExtra program
"stuff before IO action"
"Hello"
"stuff after IO action"
"stuff before IO action"
1
"stuff after IO action"
"stuff before IO action"
"Bye"
"stuff after IO action"

Thanks Gabriel Gonzalez for popularizing free monads and Edward Kmett for writing the library! :)

Tom Ellis
  • 9,224
  • 1
  • 29
  • 54
  • That is exactly what I was looking for! I was sure that this is somehow possible, but didn't knew how. Thanks! – fho Dec 14 '13 at 16:06
  • Could you maybe elaborate on why this strange function combination stuff in `printFooFExtra` is necessary? – fho Dec 14 '13 at 16:36
  • I'm not sure what you mean exactly, but you could write it as `printFooFExtra x = print "stuff before IO action" >> (printFooF (fmap (print "stuff after IO action" >>) x))`. You basically make an "augmented" interpreter that instead of just doing the `printFooF` interpretation you do some stuff before hand and do some stuff afterwards. The `fmap` is there to do the stuff before the continuation of `printFooF`. Does that help? If feel free to ask further. – Tom Ellis Dec 14 '13 at 19:02
  • @TomEllis I think you are missing the point that annotation is the same sort of traversal as is done by interpreter. I haven't tried, but I am pretty sure the following will work: `iter annotate $ (program >>= return . return)` will turn `Foo ()` into `Foo (Foo ())`, which then can be annotated with `annotate (Foo x y) = ...$ Foo x y; annotate (Bar x y) = ... $ Bar x y` – Sassa NF Dec 15 '13 at 18:22
  • @SassaNF: I'm afraid I don't understand. Could you give me a concrete implementation of what you are talking about? – Tom Ellis Dec 15 '13 at 18:59
  • Actually I think I understand what you're saying now. Yes, you can indeed do the annotation by interpreting `Foo` in itself, taking advantage of the fact that the `Foo` action contains a string that is printed. However, this is not a general solution. What would you do if the "annotation" was to ring a bell before every action? You can't do that by adding an extra action in the `Foo` monad, because there is no such action corresponding to ringing a bell. It *has* to be done in `IO`. Thus to keep the solution general I prefer to do it the way I presented. – Tom Ellis Dec 15 '13 at 20:57
  • Actuall @TomEllis is right. My 'interpreter' uses `cereal` to output a binary format so the type is `putMacroF :: MacroF (PutM b) -> PutM b`. Again thanks for this great answer. It is working like a charm for me. – fho Dec 16 '13 at 20:40
5

Here a very simple solution using the operational package -- the reasonable alternative to free monads.

You can just factor the printFoo function into a part that prints the instruction proper and a part that adds the additional information, the standard treatment for code duplication like this.

{-# LANGUAGE GADTs #-}

import Control.Monad.Operational

data FooI a where
    Foo :: String -> FooI ()
    Bar :: Int    -> FooI ()

type Foo = Program FooI

printFoo :: Foo a -> IO a
printFoo = interpretWithMonad printExtra
    where
    printExtra :: FooI a -> IO a
    printExtra instr = do { a <- execFooI instr; print "extra info"; return a; }

execFooI :: FooI a -> IO a
execFooI (Foo s) = print s
execFooI (Bar i) = print i
Heinrich Apfelmus
  • 11,034
  • 1
  • 39
  • 67
3

Are you looking for something like this?

Your original code would be

{-# LANGUAGE DeriveFunctor #-}

import Control.Monad.Free

data FooF a = Foo String a | Bar Int a deriving (Functor)

type Foo = Free FooF

printFoo :: Show a => Foo a -> IO ()
printFoo (Free (Foo s n)) = print s >> printFoo n
printFoo (Free (Bar i n)) = print i >> printFoo n
printFoo (Pure a)         = print a

You can then define a simple wrapper function, and a recursive annotater that adds the extra info to each layer of Foo (obviously these can be as complicated as you like).

annotate :: Foo a -> Foo a
annotate (Free (Foo s n)) = wrapper (Free (Foo s (annotate n)))
annotate (Free (Bar i n)) = wrapper (Free (Bar i (annotate n)))
annotate (Pure a)         = wrapper (Pure a)

wrapper :: Foo a -> Foo a
wrapper n = Free (Foo "Extra info" n)

Now define some convenience constructors that define your DSL

foo :: String -> a -> Foo a
foo s a = Free (Foo s (Pure a))

bar :: Int -> a -> Foo a
bar i a = Free (Bar i (Pure a))

Which means that you can create Foo a objects just using the monad interface and your DSL

example = do
    i <- return 1
    a <- foo "Created A" i
    b <- bar 123 a
    c <- foo "Created C" b
    return c

Now if you load up GHCI, you can work with either the original example or with the annotated version

>> printFoo example
"Created A"
123
"Created C"
1
>> printFoo (annotate example)
"Extra info"
"Created A"
"Extra info"
123
"Extra info"
"Created C"
"Extra info"
1
Chris Taylor
  • 46,912
  • 15
  • 110
  • 154
  • That looks like it should work for me. I have to try it (ie refactor my code). – fho Dec 13 '13 at 13:27
  • Two quick questions: a) is there a way to write `annotate` without having to write everything out? Possibly via `uniplate` or something? b) This requires me to add a `ExtraInfo` constructor to `FooF`, is there a way around that? – fho Dec 13 '13 at 13:38
  • @Florian re. `uniplate` I'm not sure, I've never used that library. Possibly you can search around `Data.Typeable` and `Data.Generics` to get an answer, but I'm not very familiar with them. re. extra constructor, I don't see an obvious way to avoid the additional constructor, but I'd argue that you probably should have it - clearly your application needs it at some point, or you wouldn't be asking the question! – Chris Taylor Dec 13 '13 at 13:43
  • Think of it as an *package footer* (as opposed to header). Just without any additional useful information. Come to think of it I probably should just write some `addFooter :: Foo a -> FooWithFooter a` function and then write that to the file. – fho Dec 13 '13 at 14:07
  • @Florian these two things are just catamorphisms. – Sassa NF Dec 13 '13 at 14:25
  • 1
    @SassaNF how does that help me? – fho Dec 13 '13 at 14:52
  • @Florian depending what you mean by "having to write everything out" – Sassa NF Dec 13 '13 at 14:54
1

Both things just traverse the structure and accumulate the result of inductive processing. This calls for generalizing the iteration through catamorphism.

> newtype Fix f = Fix {unFix :: f (Fix f)}
> data N a b x = Z a | S b x deriving (Functor)
> type Nat a b = Fix (N a b)
> let z = Fix . Z
> let s x = Fix . S x
> let x = s "blah" $ s "doo" $ s "duh" $ z 0
> let annotate (Z x) = s "annotate" $ z x;
      annotate (S x y) = s "annotate" $ s x y
> let exec (Z x) = print x; exec (S x y) = print x >> y
> let cata phi = phi . fmap (cata phi) . unFix
>
> cata exec x
"blah"
"doo"
"duh"
0
>
> cata exec $ cata annotate x
"annotate"
"blah"
"annotate"
"doo"
"annotate"
"duh"
"annotate"
0

Now let me explain in more depth what is going on, since there were some requests in the comments, and concerns that it won't be a monad anymore, if I use Fix.

Consider functor G:

G(X) = A + F(G(X))

Here F is a arbitrary functor. Then for any A we can find a fixed point (F and G are clearly polynomial - we are in Hask). Since we map every object A of the category to a object of the category, we are talking about a functor of fixed points, T(A). It turns out that it is a Monad. Since it is a monad for any functor F, T(A) is a Free Monad. (You will see it is obviously a Monad from the code below)

{-# LANGUAGE DeriveFunctor
           , TypeSynonymInstances #-}

newtype Fix f = Fix {unFix :: f (Fix f)} -- the type of Fixed point of a functor
newtype Compo f g x = Compo {unCompo :: f (g x)} -- composition of functors

instance (Functor f, Functor g) => Functor (Compo f g) where -- composition of functors is a functor
  fmap f = Compo . fmap (fmap f) . unCompo

data FreeF a x = Pure a | Free x deriving (Functor) -- it is a bi-functor, really;
                -- this derives functor in x

-- a special case of fmap - the fmap with unwrapping; useful to eliminate pattern matching
ffmap :: (a -> b) -> FreeF b a -> b
ffmap f x = case fmap f x of -- unwrapping, since now distinction between Pure and Free is not important
              Pure a -> a
              Free a -> a

-- Free Monad is a functor of fixed points of functor G(X)
-- G(X) = A + F(G(X))
type Free f a = Fix (Compo (FreeF a) f) -- fixed point of composition F . (FreeF a)


-- unfortunately, when defined as type, (Free f a) cannot be declared
-- as a Monad (Free f) - Haskell wants Free f to be with `a`
-- instance Monad (Free f) where -- this derives a functor in a at the same time;
--                          note that fmap will work in x, and is not meant
--                          to be equal to (m >>= return . f), which is in `a`
--   return a = Fix $ Compo $ Pure a
--   (Fix (Compo (Pure a))) >>= f  = f a
--   (Fix (Compo (Free fx))) >>= f = Fix $ Compo $ Free $ fmap (>>= f) fx

ret :: (Functor f) => a -> Free f a -- yet it is a monad: this is return
ret = Fix . Compo . Pure

-- and this is >>= of the monad
bind :: (Functor f) => Free f a -> (a -> Free f b) -> Free f b
bind (Fix (Compo (Pure a))) f = f a
bind (Fix (Compo (Free fx))) f = Fix $ Compo $ Free $ fmap (`bind` f) fx

-- Free is done

-- here is your functor FooF
data FooF x = Z Int x | S String x deriving (Functor)

type Foo x = Free FooF x

-- catamorphism for an algebra phi "folds" any F(X) (represented by fixed point of F)
-- into X
cata :: (Functor f) => (f x -> x) -> Fix f -> x
cata phi = phi . fmap (cata phi) . unFix

-- helper functions to construct "Foo a"
z :: Int -> Foo a -> Foo a
z x = Fix . Compo . Free . Z x

s :: String -> Foo a -> Foo a
s x = Fix . Compo . Free . S x

tip :: a -> Foo a
tip = ret

program :: Foo (IO ())
program = s "blah" $ s "doo" $ s "duh" $ z 0 $ tip $ return ()

-- This is essentially a catamorphism; I only added a bit of unwrapping
cata' :: (Functor f) => (f a -> a) -> Free f a -> a
cata' phi = ffmap (phi . fmap (cata' phi)) . unCompo . unFix

exec (Z x y) = print x >> y
exec (S x y) = print x >> y

annotate (Z x y) = s "annotated Z" $ z x y
annotate (S x y) = s "met S" $ s x y

main = do
         cata' exec program
         cata' exec $ cata' annotate (program `bind` (ret . ret))
           -- cata' annotate (program >>= return . return)
           -- or rather cata' annotate $ fmap return program

program is Foo (IO ()). fmap in a (remember FreeF is a bi-functor - we need the fmap in a) can turn program into Foo (Foo (IO ())) - now catamorphism for annotate can construct a new Foo (IO ()).

Note that cata' is iter from Control.Monad.Free.

Sassa NF
  • 5,306
  • 15
  • 22
  • If you add some types and give a bit more of an explanation of `cata` (types are a good start) than this would be a great answer. – daniel gratzer Dec 13 '13 at 15:06
  • 3
    Also writing this as normal Haskell code vs for GHCi is probably a good idea – daniel gratzer Dec 13 '13 at 15:07
  • @Sassa By using `Fix` you would lose the ability to perform monadic bind, which could be a problem depending on the use case. – danidiaz Dec 13 '13 at 16:45
  • @DanielDíazCarrete I am not sure that is the case. Fix is another way to write Free, the free monad. You can observe that `Nat a b` is no different from `Free f a b = Pure a | Free b (f (Free f a b))` – Sassa NF Dec 13 '13 at 18:18
  • @jozefg how about now? (i don't compete for knowledge of Haskell packages :) TomEllis already won that prize) – Sassa NF Dec 15 '13 at 18:09
  • @SassaNF Am I right, that your (updated) answer is basically the same the one from TomEllis? When I first saw your (pre update) answer I was like "how is that supposed to help me". – fho Dec 16 '13 at 20:46
  • @Florian I think the end result is the same: use iter; although I took detour investigating how Free Monad is related to Fix, and how annotation can be done using the same mechanism without printing the annotations. – Sassa NF Dec 16 '13 at 21:38
  • @SassaNF so basically you reinvented Free Monads in your first attempt? ;) – fho Dec 16 '13 at 22:05
  • @Florian I don't pretend to have reinvented them :) But I had to wrangle with the type-system to be able to show the link between Free Monads and Fixed points - and catamorphisms. If you knew all of that, then take it as a learning exercise for me :) – Sassa NF Dec 16 '13 at 22:13
  • @SassaNF I didn't know about the catamorphims, but I was pretty sure `free` was implemented with `fix`. In the end I am just happy that I can no run around and show others that something strangesounding as `free monads` can be used to great effect in a real world application ;) – fho Dec 16 '13 at 22:20
1

If you are willing to slightly modify the original interpreter (by changing how the terminal case is handled)

{-# LANGUAGE DeriveFunctor #-}

import Control.Monad.Free
import Control.Monad.Morph
import Pipes

data FooF a = Foo String a | Bar Int a deriving (Functor)

printFoo :: Free FooF a -> IO a
printFoo (Free (Foo s n)) = print s >> printFoo n
printFoo (Free (Bar i n)) = print i >> printFoo n
printFoo (Pure a)         = return a

...then there's a way to add extra actions without modifying the functor or having to repurpose its constructors, while still being able to reuse the interpreter.

The solution uses the pipes and mmorph packages.

First you have to define a sort of "pre-interpeter" that lifts the free monad into a Producer from pipes. The yield () statements in the producer signify the points at which an extra action is inserted.

pre :: Free FooF a -> Producer () (Free FooF) a
pre (Free (Foo s n)) = lift (Free . Foo s $ return ()) >> yield () >> pre n
pre (Free (Bar i n)) = lift (Free . Bar i $ return ()) >> yield () >> pre n
pre (Pure a)         = lift . Pure $ a 

(In a more complex example the yield statements could carry extra information, like log messages.)

Then you write a function that applies the printFoo interpreter underneath the Producer, using hoist from mmorph:

printFooUnder :: Producer () (Free FooF) a -> Producer () IO a
printFooUnder = hoist printFoo

So, we have a function that "interprets" the free monad into IO, but at some points emits () values that we must decide how to handle.

Now we can define an extended interpreter that reuses the old interpreter:

printFooWithReuse :: Show a => Free FooF a -> IO () 
printFooWithReuse foo = do
    finalv <- runEffect $ for (printFooUnder . pre $ foo) 
                              (\_ -> lift (print "extra info"))
    print finalv

After testing it, it seems to work:

printFooWithReuse $ Free (Foo "nah" (Pure 4))
-- > "nah"
-- > "extra info"
-- > 4

If you happen to want to insert the extra actions manually, then your can eschew writing the "pre-interpreter" and work directly in the Producer () (Free FooF) monad.

(This solution could also be achieved by layering a free monad transformer instead of a Producer. But I think using a Producer is a bit easier.)

danidiaz
  • 26,936
  • 4
  • 45
  • 95