📜 ⬆️ ⬇️

What are good free monads

I offer the readers of "Habrakhabr" a translation of the article "Why free monads matter" .

Interpreters


Good programmers share the data and interpreters that process this data. An example is the compilers, which represent the source code as an abstract syntax tree, which can later be processed by one of many interpreters. Namely, we can:

The advantages of this separation are obvious. Let's try to build an abstraction that reflects the essence of the syntax tree. It is better to start with a specific example. To do this, we will design our own toy language and try to format it as a data type.

The language will include only three commands:

We will present it in the form of a syntactic tree, in which the following commands will be the leaves of the previous ones:

data Toy b next = Output b next | Bell next | Done 

Please note that the Done command has no list and therefore must be terminal.
Now I could write a program and run it with an interpreter:
')
 -- output 'A' -- done Output 'A' Done :: Toy Char (Toy a next) 

But unfortunately, this is a bad decision that wouldn't work. When adding each new command to the program, the expression will change its type:

 -- bell -- output 'A' -- done Bell (Output 'A' Done) :: Toy a (Toy Char (Toy b next)) 

Fortunately, in order to use any number of instances of Toy and at the same time save the type, we can proceed as follows:

 data Cheat f = Cheat (f (Cheat f)) 

The cheat type defines a sequence of functors, which ends with the Done constructor. To pleasant surprise, Haskell already contains a similar type:

 data Fix f = Fix (f (Fix f)) 

Fix means "the fixed point of a functor" (fixed point of the functor). Armed with Fix, we can rewrite our programs:

 Fix (Output 'A' (Fix Done)) :: Fix (Toy Char) Fix (Bell (Fix (Output 'A' (Fix Done)))) :: Fix (Toy Char) 

Now both expressions have the same type. Fine. However, this solution still has problems: every chain of functors must be completed by the Done constructor. Unfortunately, programmers do not often write programs on their own from beginning to end. More often we just want to write a procedure that could be called from other programs. The Fix type does not allow this.

Let's try to solve this problem. Our procedure ends, but we are not ready to call Done, instead we will throw an exception so that the calling procedure can process it and continue execution:

 data FixE fe = Fix (f (FixE fe)) | Throw e 

The handler function will look like this:

 catch (Fucntor f) => FixE f e1 -> (e1 -> FixE f e2) -> FixE f e2 catch (Fix x) f = Fix (fmap (flip catch f) x) catch (Throw e) f = fe 

To use it, you need to make Toy an instance of the Functor class:

 instance Functor (Toy b) where fmap f (Output x next) = Output x (f next) fmap f (Bell next) = Bell (f next) fmap f Done = Done 

Now we can write the code that will be executed and return control to the calling procedure:

 data IncompleteException = IncompleteException -- output 'A' -- throw IncompleteException subroutine = Fix (Output 'A' (Throw IncompleteException)) :: FixE (Toy Char) IncompleteException -- try {subroutine} -- catch (IncompleteException) { -- bell -- done -- } program = subroutine `catch` (\_ -> Fix (Bell (Fix Done))) :: Fix (Toy Char) e 

Monad Free. Part 1


We proudly pack an “improved” Fix and publish it on Hackage as fix-impoved, and then we find out that it is not quite used as we assumed: users send normal values ​​instead of exceptions. How dare they! Exceptions only for exceptional situations! What a boob!
... although it is not known who is who, because our FixE is already implemented and is called Free:

 data Free fr = Free (f (Free fr) instance (Functor f) => Monad (Free f) where return = Pure (Free x) >>= f = Free (fmap (>>= f) x) (Pure r) >>= f = fr 

return - our Throw and (>> =) - catch. Users intelligently applied exceptions to pass normal values.
The remarkable aspect of haskell is the free option to use do-notation for any monads. But in order to use do-notation with the commands of our language, we need to change their types from Toy b to Free (Toy b). It will look like this:

 output :: a -> Free (Toy a) () output x = Free (Output x (Pure ())) bell :: Free (Toy a) () bell = Free (Bell (Pure ())) done :: Free (Toy a) r done = Free Done 

Noticed the general pattern?

 liftF :: (Functor f) => fr -> Free fr liftF command = Free (fmap Pure command) output x = liftF (Output x ()) bell = liftF (Bell ()) done = liftF Done 

Now we can consistently execute commands using do-notation. Let's rewrite our previous example, getting rid of unnecessary exceptions:

 subroutine :: Free (Toy Char) () subroutine = output 'A' program :: Free (Toy Char) r program = do subroutine bell done 

This is where the magic begins. Our program in do-notation is pure data that we can interpret. Beginners often associate monads with external effects, but the code above only generates data. We can show this by writing a function that will translate them into a string representation:

 showProgram :: (Show a, Show r) => Free (Toy a) r -> String showProgram (Free (Output ax)) = "output " ++ show a ++ "\n" ++ showProgram x showProgram (Free (Bell x)) = "bell\n" ++ showProgram x showProgram (Free Done) = "done\n" showProgram (Pure r) = "return " ++ show r ++ "\n" 

and run it
 >>> putStr (showProgram program) output 'A' bell done 

Looks like we just wrote our first interpreter. We can use it to verify that our monad obeys certain laws:

 pretty :: (Show a, Show r) => Free (Toy a) r -> IO () pretty = putStr . showProgram >>> pretty (output 'A') output 'A' return () >>> pretty (return 'A' >>= output) output 'A' return () >>> pretty (output 'A' >>= return) output 'A' return () >>> pretty ((output 'A' >> done) >> output 'C') output 'A' done >>> pretty (output 'A' >> (done >> output 'C')) output 'A' done 

Notice how Done "swallows" all the commands following it. I included Done in Toy for illustration purposes only. In most cases, we do not need such a constructor, but rather the behavior provided by Pure, that is, the possibility of continuing execution, but there may be exceptions.

We can also write an interpreter in its traditional meaning:

 ringBell :: IO () -- ,  ,   interpret :: (Show b) => Free (Toy b) r -> IO () interpret (Free (Output bx)) = print b >> interpret x interpret (Free (Bell x)) = ringBell >> interpret x interpret (Free Done ) = return () interpret (Pure r) = throwIO (userError "Improper termination") 

Monad Free no matter how you use it.

Multitasking


Suppose that we have two monadic "streams" and we want to alternate the steps of their implementation. In the case of IO monads, we could use forkIO just by running them in parallel, however, that if we need to do the same for State or even Cont monads. You can try to present the stream as a list of monadic actions:

 type Thread m = [m ()] 

... but there is no guarantee that the interpreter will call them in the specified order, as there is no possibility to transfer the results of calculations between actions. However, we can guarantee the order of execution by investing each subsequent action in the previous one and use a separate constructor to indicate the end of the stream:

 data Thread mr = Atomic (m (Thread mr)) | Return r 

This structure allows you to get the next action only after the completion of the current one. Now we can wrap each individual monad call into an atomic step Thread:

 atomic :: (Monad m) => ma -> Thread ma atomic m = Atomic $ liftM Return m 

Now we need to make Thread a monad: we “pretend” that we glue the two streams, but at the same time preserving the atomicity of each step, in order to be able to alternate them with the steps of other streams:

 instance (Monad m) => Monad (Thread m) where return = Return (Atomic m) >>= f = Atomic (liftM (>>= f) m) (Return r) >>= f = fr 

Using this, we can create threads consisting of atomic steps:

 thread1 :: Thread IO () thread1 = do atomic $ print 1 atomic $ print 2 thread2 :: Thread IO () thread2 = do str <- atomic $ getLine atomic $ putStrLn str 

All that remains to be done is to implement the alternation of two streams, while maintaining the atomicity of the individual steps. Let's write the simplest implementation:

 interleave :: (Monad m) => Thread mr -> Thread mr -> Thread mr interleave (Atomic m1) (Atomic m2) = do next1 <- atomic m1 next2 <- atomic m2 interleave next1 next2 interleave t1 (Return _) = t1 interleave (Return _) t2 = t2 

Now we need to learn how to run the resultant streams:

 runThread :: (Monad m) => Thread mr -> mr runThread (Atomic m) = m >>= runThread runThread (Return r) = return r >>> runThread (interleave thread1 thread2) 1 [[Input: "Hello, world!"]] 2 Hello, world! 

Magic! We just implemented the simplest flow control system. Try using it with the pure state monad now.

Monad Free. Part 2


If you were careful, you might have noticed that Thread is a veiled Free and atomic - liftF. This example well demonstrates how close free monads and lists are. Indeed, compare the definitions of Free and List:

 data Free fr = Free (f (Free fr)) | Pure r data List a = Cons a (List a ) | Nil 

In other words, we can think of a free monad as a list of functors. The Free constructor behaves like Cons, adding a functor to the list and Pure as Nil, symbolizing an empty list (lack of functors).

If List is a list of values ​​and a free monad is a list of functors, what happens if these functors themselves are values:

 type List' a = Free ((,) a) () List' a = Free ((,) a) () = Free (a, List' a) | Pure () = Free a (List' a) | Pure () 

It turns out an ordinary list.

Thus, the list is a special case of the monad Free. However, [] as an instance of the Monad class is different from List 'a (i.e. Free ((,) a)). In the List 'a monad, join (note bind) apparently behaves like (++) and return like []. You can think of the List 'a monad as an unusual way of concatenating values ​​using do-notation.

When you think of a free monad as a list, many things become more obvious. For example, liftF is represented by a list with a single element creating a free monad containing one functor:

 singleton x = Cons x Nii -- x:[]  [x] liftF x = Free (fmap Pure x) 

Similarly, the interleave function is the merging of lists:

 merge (x1:xs1) (x2:xs2) = x1:x2:merge xs1 xs2 merge xs1 [] = xs1 merge [] xs2 = xs2 --     : -- [x1] ++ [x2] ++ interleave xs1 xs2 interleave (Atomic m1) (Atomic m2) = do next1 <- liftF m1 next2 <- liftF m2 interleave next1 next2 interleave a1 (Return _) = a1 interleave (Return _) a2 = a2 

Indeed, multitasking looks like the usual merging of action lists, if you look at free monads in this way. In the next post, I will look at an excellent article that demonstrates how you can build elegant flow control systems and planners using free monads.

It is not a coincidence that Free monads are similar to lists. When considering the category theory, it can be understood that both of them are free objects, where lists are free monoids, and Free monads are free monads.

Interpreters. Continuation


In the first part, I introduced the concept of using free monads in interpreters, but the potential of this idea is much more than it might seem - it is not limited to compilers and formatted output. As an example, suppose you decide to beat Notch with his idea of ​​the game 0x10c by writing a game with the possibility of programming in it on haskell. You want to allow players to run their programs, but at the same time restrict full access to the IO monad. What are your actions?

You could use the original haskell design, in which the output would be presented as a list of requests to the outside world and input - as a list of answers received from it:

 main :: [Response] -> [Request] 

The Request type is an enumeration of all the actions that you can perform, and Response - the results obtained. For our game, the query set could be as follows:

 data Request = Look Direction | ReadLine | Fire Direction | WriteLine String 

... and a set of answers:

 data Response= Image Picture --   Look | ChartLine String --   Read | Succeed Bool --   Write 

It is safe to say that this approach will not work. We have no explicit correspondence between requests and responses (Fire has no answer at all), and it is completely unclear what will happen if we try to get an answer before we send the request.

Let's try to establish this by combining these types into one:

 data Interaction next = | Look Direction (Image -> next) | Fire Direction next | ReadLine (String -> next | WriteLine String (Bool -> next) 

Each constructor has fields that the player needs to fill out (parameters requests). The player can also transfer functions that the interpreter will apply to the received answers. You can think of the Interaction type as a contract between the programmer and the interpreter for each individual step.

You can easily make Interaction an instance of the class Functor:

 instance Functor Interaction where: fmap f (Look dir g) = Look dir (f . g) fmap f (Fire dir x) = Fire dir (fx) fmap f (ReadLine g) = ReadLine (f . g) fmap f (WriteLine sg) = WriteLine s (f . g) 

In fact, there is no need to do it yourself. GHC provides the DeriveFunctor extension, which allows you to simply write:

 data Interaction ... deriving (Functor) 

And achieve the desired result.
As before, we can create a list of actions using the Free monad:

 type Program = Free Interaction 

With this type, the player can write a simple program:

 easyToAnger = Free $ ReadLine $ \s -> case s of "No" -> Free $ Fire Forward $ Free $ WriteLine "Take that!" (\_ -> easyToAnger) - -> easyToAnger 

Now this program can be launched, possibly by converting it into the hypothetical monad Game:

 interpret :: Program r -> Game r interpret prog = case prog of Free (Look dir g) -> do img <- collectImage dir interpret (g img) Free (Fire dir next) -> do sendBullet dir interpret next Free (ReadLine g) -> do str <- getChatLine interpret (g str) Free (WriteLine sg) -> putChatLine s interpret (g True) Pure r -> return r 

Since we use the Free monad, we can treat the player with syntactic sugar, allowing him to write programs in do-notation:

 look :: Direction -> Program Image look dir = liftF (Look dir id) fire :: Direction -> Program () fire dir = liftF (Fire dir ()) readLine :: Program String readLine = liftF (ReadLine id) writeLine :: String -> Program Bool writeLine s = liftF (WriteLine s id) 

Now it will be more convenient for the player to write programs:

 easyToAnger :: Program a easyToAnger = forever $ do str <- readLine when (str == "No") $ do fire Forward _ <- writeLine "Take that!" return () 

In a nutshell, we provided the player with an interaction language that limits his possible actions, and at the same time saved syntax sugar and haskell buns. Behind us remained the complete freedom of interpretation of the players' programs. For example, if I were going to release a patch tomorrow that would change the game world (and haskell had hot-swapping mechanisms), I could change the interpreter without interrupting the execution of the players' programs.

Free monads. Part 3


The free monad is the interpreter's best friend. It “frees the interpreter” as much as possible and at the same time keeps the necessary minimum to remain a monad.

Every time when we want the interpreter to provide the programmer with only the possibility of using monads, free monads come to the rescue. If you present yourself as an interpreter, and me as a programmer, then you reserve the right to choose alternatives, forcing me to write my programs using only the free monads that you give me.

The expression “free interpreter” as far as possible “sounds like an optimization problem, which can be rephrased as:

Which monad is the most flexible to interpret, provided it is still a monad

In fact, a detailed consideration of the concept of "freedom", given the restrictions, leads to the definition of a free object in the category theory, where this concept is formalized. The free monad is the “most free” object, which is a monad.

Source: https://habr.com/ru/post/254715/


All Articles