Monad

The Monad type-class inherits from Applicative (from GHC 7.10 onward; see the Monad as applicative section for more on this):

class (Applicative m) => Monad m where
  return :: a -> m a
  (>>=) :: m a -> (a -> m b) -> m b

The return function looks just like the pure function of the Applicative type-class (it lifts a value to Monad).

The bind operator (>>=) combines a Monad (m a) with a function (a -> m b), which we'll call a monadic function. The monadic function acts on type a of the first monad and returns a new monad of type (m b).

Let's make our Maybe' type a Monad:

import Control.Monad
import Control.Applicative

data Maybe' a = Just' a | Nothing'
  deriving (Show)

instance Functor Maybe' where
–- ...

instance Applicative Maybe' where
–- ...

instance Monad Maybe' where
  return x = Just' x
  Nothing'  >>= _   = Nothing'
  (Just' x) >>= f   = (f x)

The bind operator for Maybe' says:

  • Given Nothing', ignore the monadic function and simply return Nothing'
  • Given Just' x, apply the monadic function to the value x ; this will return a Maybe' Monad of possibly different type

Let's use bind with our Maybe' Monad:

–- monad >>= monadic function

Just' 10 >>= x -> Just' (show x)
-- evaluates as
   (x -> Just' (show x)) 10
   Just' "10"

Nothing' >>= x -> Just' (show x)
-- evaluates as 
   Nothing'

At first glance, bind simply allows us to combine monads with monadic functions. However, as every Haskell journey man and -woman has found, things are not quite that simple. We will talk more about bind soon, but let's first explore how Monad relates to Functor and Applicative.

Monad as Functor

We can make Monad an instance of Functor by using the liftM function, the monadic version of fmap:

instance Functor Monad where
    fmap = liftM

where

  liftM :: Monad   m => (a -> b) -> m a -> m b
  fmap  :: Functor m => (a -> b) -> m a -> m b

Now we have three ways of expressing Functor-like behavior:

main = do 
  –- Levels of Functors
  print $ fmap (*2) (Just' 10)     -- FUNCTOR
  print $ pure (*2) <*> (Just' 10) -- APPLICATIVE
  print $ liftM (*2) (Just' 10)    -- MONAD

The liftM function is based on the bind operator:

  liftM f m = m >>= return . f
  
  -- in other words
  liftM f m = do 
      val <- m       -- extract value
      return (f val) -- wrap result in Monad

  –- e.g.   
  liftM (*2) (Just' 10) 
  = (Just' 10) >>= return . (*2)
  = return . (*2) 10
  = return 20
  = Just' 20

In the preceding example, we extract the Monad value, apply f to it and then lift the result into a Monad with return.

Monad as Applicative

With Applicative we can lift functions of many arguments. Monad can also do so, albeit less elegantly, with the liftM functions (liftM, liftM2, liftM3, ...):

main = do 
  print $ (<$>)  (*) (Just' 10) <*> (Just' 20) -- APPLICATIVE
  print $ liftM2 (*) (Just' 10)     (Just' 20) -- MONAD

Any Monad is also an Applicative Functor because we define:

-- ap_ defines <*> for Monads
ap_ mf mx = do 
  f <- mf      -- extract function
  x <- mx      -- extract val
  return (f x) 

that is, extract the function from the first Monad and the value from the second, and do the function application (this method already exists as Control.Monad.ap).

Now we can write monadic code in Applicative style:

  (Just' (*)) 'ap_' (Just' 10) 'ap_' (Just' 20)

We can easily make Monad an instance of Applicative:

instance Applicative Monad where
   pure = return
   (<*>) = ap

The "applicative pattern" was recognized and extracted as Applicative only in 2008, more than ten years after Monad became an established part of Haskell (and 20 years after Eugenio Moggi's Monad paper).

This is why we have several ways of doing the same thing, as shown in the following table:

Functor (1990)

Applicative (2008)

Monad (1990s)

fmap

pure, <*>

liftM

 

<*>

ap

 

pure

return

These discrepancies have been resolved by the "Functor-Applicative-Monad Proposal", implemented in base 4.8.0.0 used by GHC 7.10 and above (https://wiki.haskell.org/Functor-Applicative-Monad_Proposal).

Sequencing actions with Monad and Applicative

With Monad we can sequence actions as follows:

action s = do putStrLn s; return s
main = do
  let actions = map action ["parts", "are", "disconnected"]
  sequence' actions
  return ()

Here sequence' performs the actions one after the other:

sequence' [] = return []
sequence' (x:xs) = do
  x'  <- x             -- action performed
  xs' <- sequence' xs
  return (x':xs')

But we can also sequence actions with Applicative:

sequenceA [] = pure []
sequenceA (x:xs) = (:) <$> x <*> (sequenceA xs)
-- sequenceA actions

(In fact, a part of the Functor-Applicative-Monad Proposal mentioned earlier is to change the prelude's sequence function to require applicative instead of monad.)

An Applicative type-class can sequence actions that happen in isolation, that is, actions that don't depend on the results of previous actions. But when actions in a sequence need to communicate results to subsequent actions, Applicative becomes insufficient and we need Monad.

Monads and the bind chain

The magic of Monad is that we can build a chain of actions such that an action can communicate with subsequent actions. This is not so with Applicative; for example, you cannot express this directly with Applicative:

main = do 
  line <- getLine                -- ACTION 1
  putStrLn $ "You said " ++ line -- ACTION 2
  -– uses result of ACTION 1

The bind operator (>>=) lets us bind outputs to inputs, whereas with Applicative (<*>), each action is performed in isolation (there is no "contact point" between two actions).

An important implication of this is that, with Monad, we can have a dynamic sequence of actions, where the outcome of one action can affect which subsequent actions are performed, for example:

main = mainLoop
mainLoop = do 
  line <- getLine                    -- ACTION 1
  if line == "stop"         
    then putStrLn "Bye"              -- ACTION 2b
    else do 
      putStrLn $ "You said " ++ line -- ACTION 2c
      mainLoop

This cannot be expressed with Applicative, where each action in the sequence is destined to be performed. It is worth saying, however, that Applicative does allow for limited communication between actions, for example:

  (+) <$> Nothing <*> Just 10 <*> Just 20

Here the first instance of Nothing will prevent all subsequent actions from being performed. We have essentially baked the communication between actions directly into the Maybe Applicative type instance.

The bind chain provides a "shared context" between actions in a sequence.

The shared context can be used as a place to do "out of band" processing, that is, processing that is made explicit in the bind chain but remains implicit from the perspective of the chain of monadic actions. As an example, consider a sequence of actions occurring in the context of a Reader Monad: the reader state is out of band, that is, "independent" of the monadic pipeline.

This explains why we can use monads to approximate imperative programming (where out of band processing is so prevalent).

In this sense, we can view the bind chain as a more sophisticated version of an accumulator argument in a tail recursive function (the accumulator allows for a shared context in a nested chain of recursive function calls).

Monad bind in a way that includes an "accumulator". This contrasts with applicatives, which have no accumulator and hence no communication between arguments.

The bind operator composes Monad values with monadic functions (functions that return a value embedded in a Monad class). With Functor and Applicative, the functions were ignorant of the types they were being lifted to. When chaining a Monad class with a monadic function, the function is entwined with the Monad class it is being chained with.

Also, it is worth noting that the Monad type is not "closed under composition" (as is the case for Applicative) because the composition of two Monad does not typically yield another Monad.

Composing with Monads

Let's summarize the ways in which we can compose with Monad:

  • We can compose pure functions with Monad:
      liftM* f m -- returns another Monad m
  • We can compose Monadic functions with monad:
      m >>= fM >>= gM >>= hM
  • We can compose Monadic functions with each other:
      gM <=< fM

    where (<=<) is syntactic sugar for

      gM <=< fM = x -> (fM x) >>= gM

The key composition is binding (>>=) the Monad with a Monadic function, but beyond that Monad does not compose as well as Applicative.

Monad transformers

In this section, we look at combining different types of monads into more powerful combinations. We can do this by creating "monad stacks". Let's start with a simple Reader Monad and then stack some other monads on top of it.

We'll use a Reader Monad to hold some configuration data for an application:

 data Config = Config {discountRate :: Float,
                       currencySym  :: String}
  appCfg = (Config 10 "R") 

The discount function takes a Float value and returns another Float, but in the context of a Reader Config:

discount :: Float -> Reader Config Float
discount amt = do        
    discountRate' <- asks discountRate
    return (amt * (1 - discountRate' / 100))

From within the function, we can ask for the configuration data.

Now we can use the runReader function with specific configuration data:

import Control.Monad.Identity
import Control.Monad.Reader
import Control.Monad.Writer

main = do
  print $ runReader (discount 100) appCfg

Let's add a display function that returns a String in the context of Reader Config:

display :: Float -> Reader Config String
display amt = do
  currencySym' <- asks currencySym
  return (currencySym' ++ " " ++ (show amt))

main = do
  putStrLn $ runReader doDoubleDiscount appCfg
 where doDoubleDiscount 
    = (discount 100 >>= 
        discount >>= 
        display)

We have a chain of Monadic functions (doDoubleDiscount) executing in the context of Reader Config. The result is fed into the putStrLn function, which executes in the IO Monad. To add logging capability to our "Reader functions", we can stack our Reader type on top of a Writer Monad.

Instead of Reader, we'll use the ReaderT type which is a Reader Monad that also takes an inner monad (in this case Writer String). The rest of the function is still valid as is, but now we can access the Writer's tell function from inside our functions:

discountWR :: Float -> ReaderT Config (Writer String) Float
discountWR amt = do
  discountRate' <- asks discountRate
  let discounted = amt * (1 - discountRate' / 100)
  tell $ " > Discount " ++ (show amt) ++ " = " ++ (show discounted)
  return discounted

displayWR :: Float -> ReaderT Config (Writer String) String
displayWR amt = do
  currencySym' <- asks currencySym
  tell " > Displaying..."
  return (currencySym' ++ " " ++ (show amt))

main = do
  print $ runWriter (runReaderT doDoubleDiscount appCfg) 
  where
   doDoubleDiscount = (discountWR 100 >>= 
                       discountWR >>= 
                       displayWR)

Since we have a Reader wrapped around a Writer Monad, we need to first use runReaderT (which unwraps the Reader Monad and gives us the result):

  runReaderT someApp appCfg

The result of the runReaderT function is the inner Writer Monad, which needs to be unwrapped with runWriter:

  runWriter (runReaderT someApp appCfg)

In this way, Monad stacks are unwrapped in the opposite order in which they were stacked.

But this is becoming messy:

discountWR :: Float -> ReaderT Config (Writer String) Float
displayWR  :: Float -> ReaderT Config (Writer String) String
runWriter (runReaderT someApp appCfg)

We can simplify the type signatures with the following type alias:

  type App = ReaderT Config (Writer String)

Note the currying of type parameters. We omit the final ReaderT type argument because we want to vary it:

  discountWR :: Float -> App Float
  displayWR  :: Float -> App String

Now we can also define the doApp function:

  doApp :: App a -> (a, String)
  doApp app = runWriter (runReaderT app appCfg) 

main = do
  print $ doApp doDoubleDiscount
  where doDoubleDiscount = (discountWR 100 >>= 
           discountWR >>= 
           displayWR)

More idiomatically, we can use newtype app instead of type App:

newtype App a = App {runApp :: ReaderT Config (Writer String) a}
  deriving (Monad, Applicative, Functor, MonadReader Config, MonadWriter String)

The deriving clause requires the following LANGUAGE pragma (at the top of the file):

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

We are making App an instance of all the type-classes in the deriving clause. MonadReader is the type-class that implements the Reader functionality: both Reader and ReaderT implement MonadReader. Similarly, Writer and WriterT implement MonadWriter. This allows for code sharing between the monads and their transformer versions.

The effect of this is to "flatten" our nested stack of monads, making all lower­-level functions available on the top level (for example, we can call tell and asks as if they are defined on the top level of the stack).

Without this convenience measure, we would have to lift the nested Monad function once for each level of the stack, until we reached the monad with the function we are after. A "flattened" nest of monads lets us avoid excessive lifting through the stack's layers.

On the downside, this elegant way of simplifying the practicalities of working with stacks is precisely what makes it more tedious to define your own monad transformers. Having said that, there are more recent packages that attempt to solve this problem. See extensible-effects (https://hackage.haskell.org/package/extensible-effects) and layers (https://hackage.haskell.org/package/layers) for more information on this.

Returning to our example, with the newtype App declaration, our function type signatures remain unchanged:

  discountWR :: Float -> App Float
  displayWR :: Float -> App String

Also, by using newtype in this way, we can limit what we export from our code and thereby obfuscate the details of how the stack is constructed. However, in doApp we now need to use the runApp app:

  doApp :: App a -> (a, String)
  doApp app = runWriter (runReaderT (runApp app) appCfg) 

main = do
  print $ doApp doDoubleDiscount
  where doDoubleDiscount= (discountWR 100 >>= 
         discountWR >>= 
         displayWR)

IO in Monad stacks

We can also add the IO Monad to our Monad stack, although we will see that IO is a special case:

newtype AppIO a 
  = AppIO {runAppIO :: ReaderT Config (WriterT String IO) a}
 deriving (Monad, Applicative, Functor, MonadReader Config, 
           MonadWriter String, MonadIO)

Instead of Writer String, we use WriterT String IO, that is, a Writer Monad wrapping IO. Also, we've added a derive clause for MonadIO, which is to IO what MonadReader is to the Reader Monad. The MonadIO type-class adds IO access to all Monad in the stack.

  discountWRIO :: Float -> AppIO Float
  displayWRIO  :: Float -> AppIO String

The doAppIO function returns its result wrapped in an IO action:

  doAppIO :: AppIO a -> IO (a, String)
  -- use runWriterT to extract the writer result
  doAppIO app = runWriterT (runReaderT (runAppIO app) appCfg)

Now we can do IO operations in our Monad stack functions. To expose the IO Monad, we need to use the liftIO function:

discountWRIO :: Float ­> AppIO Float
discountWRIO amt = do
  liftIO $ putStrLn "We're doing IO in discountWRIO"
  discountRate' <- asks discountRate
  let discounted = amt * (1 - discountRate' / 100)
  tell $ " > Discount " ++ (show amt) ++ " = " ++ (show discounted)
  return discounted

displayWRIO amt = do
  liftIO $ putStrLn "More IO!"
  currencySym' <- asks currencySym
  tell " > Displaying..."
  return (currencySym' ++ " " ++ (show amt))

main = print <$> doAppIO doDoubleDiscount
  where
    doDoubleDiscount = (discountWRIO 100 >>=
                        discountWRIO >>=
                        displayWRIO)

Sequence of stack composition

A Monad stack implies a sequence of composition of Monads. In the previous example, we had a Reader Monad wrapping a Writer Monad. We could just as well have swapped the position of Writer and Reader in our stack:

newtype AppIO a = AppIO {runAppIO :: WriterT String (ReaderT Config IO) a}
  deriving (Monad, Applicative, Functor,
            MonadReader Config, MonadWriter String, MonadIO)

This means we would also have to swap around the order of unwrapping the stack:

doAppIO :: AppIO a -> IO (a, String)
doAppIO app = runReaderT (runWriterT (runAppIO app)) appCfg

The order of Reader and Writer is inconsequential, since these monads are unaffected by each other in a Monad stack. This is not true for all combinations of monads, however. If one monad relies on the work of a previous monad being done, the order indeed matters (as with the composition of functions).

Moreover, IO is a special case and must remain at the bottom of the stack.

..................Content has been hidden....................

You can't read the all page of ebook, please click here login for view all page.
Reset