Jump to content
Main menu
Main menu
move to sidebar
hide
Navigation
Haskell
Wiki community
Recent changes
Random page
HaskellWiki
Search
Search
Create account
Log in
Personal tools
Create account
Log in
Pages for logged out editors
learn more
Contributions
Talk
Editing
All About Monads
(section)
Page
Discussion
English
Read
Edit
View history
Tools
Tools
move to sidebar
hide
Actions
Read
Edit
View history
General
What links here
Related changes
Special pages
Page information
Warning:
You are not logged in. Your IP address will be publicly visible if you make any edits. If you
log in
or
create an account
, your edits will be attributed to your username, along with other benefits.
Anti-spam check. Do
not
fill this in!
== Monad support in Haskell == Haskell's built in support for monads is split among the standard prelude, which exports the most common monad functions, and the Monad module, which contains less-commonly used monad functions. The individual monad types are each in their own libraries and are the subject of [[introII.html|Part II]] of this tutorial. === In the standard prelude === The Haskell 2010 [https://www.haskell.org/onlinereport/haskell2010/haskellch5.html#x11-1110005.6 standard prelude] includes the definition of the <code>Monad</code> class as well as a few auxilliary functions for working with monadic data types. ==== The <code>Monad</code> class ==== We have seen the <code>Monad</code> class before: <haskell> class Monad m where (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b return :: a -> m a -- Minimal complete definition: -- (>>=), return m >> k = m >>= \_ -> k </haskell> ==== The sequencing functions ==== The <code>sequence</code> function takes a list of monadic computations, executes each one in turn and returns a list of the results. If any of the computations fail, then the whole function fails: <haskell> sequence :: Monad m => [m a] -> m [a] sequence = foldr mcons (return []) where mcons p q = p >>= \x -> q >>= \y -> return (x:y) </haskell> The <code>sequence_</code> function (notice the underscore) has the same behavior as <code>sequence</code> but does not return a list of results. It is useful when only the side-effects of the monadic computations are important. <haskell> sequence_ :: Monad m => [m a] -> m () sequence_ = foldr (>>) (return ()) </haskell> ==== The mapping functions ==== The <code>mapM</code> function maps a monadic computation over a list of values and returns a list of the results. It is defined in terms of the list <code>map</code> function and the <code>sequence</code> function above: <haskell> mapM :: Monad m => (a -> m b) -> [a] -> m [b] mapM f as = sequence (map f as) </haskell> There is also a version with an underscore, <code>mapM_</code> which is defined using sequence_. <code>mapM_</code> operates the same as <code>mapM</code>, but it doesn't return the list of values. It is useful when only the side-effects of the monadic computation are important. <haskell> mapM_ :: Monad m => (a -> m b) -> [a] -> m () mapM_ f as = sequence_ (map f as) </haskell> As a simple example of the use the mapping functions, a <code>putString</code> function for the <code>IO</code> monad could be defined as: <haskell> putString :: [Char] -> IO () putString s = mapM_ putChar s </haskell> <code>mapM</code> can be used within a do block in a manner similar to the way the <code>map</code> function is normally used on lists. This is a common pattern with monads β a version of a function for use within a monad (i.e., intended for binding) will have a signature similar to the non-monadic version but the function outputs will be within the monad: <haskell> -- compare the non-monadic and monadic signatures map :: (a -> b) -> [a] -> [b] mapM :: Monad m => (a -> m b) -> [a] -> m [b] </haskell> ==== The reverse binder function (<code>=<<</code>) ==== The prelude also defines a binding function that takes its arguments in the opposite order to the standard binding function. Since the standard binding function is called "<code>>>=</code>", the reverse binding function is called "<code>=<<</code>". It is useful in circumstances where the binding operator is used as a higher-order term and it is more convenient to have the arguments in the reversed order. Its definition is simply: <haskell> (=<<) :: Monad m => (a -> m b) -> m a -> m b f =<< x = x >>= f </haskell> === In the Monad module === The <code>Monad</code> module in the standard Haskell 2010 libraries exports a number of facilities for more advanced monadic operations. To access these facilities, simply <code>import Monad</code> in your Haskell program. Not all of the function in the <code>Monad</code> module are discussed here, but you are encouraged to [https://www.haskell.org/onlinereport/haskell2010/haskellch13.html#x21-19300013 explore the module for yourself] when you feel you are ready to see some of the more esoteric monad functions. ==== The <code>MonadPlus</code> class ==== The <code>Monad</code> module defines the <code>MonadPlus</code> class for monads with a zero element and a plus operator: <haskell> class Monad m => MonadPlus m where mzero :: m a mplus :: m a -> m a -> m a </haskell> ==== Monadic versions of list functions ==== Several functions are provided which generalize standard list-processing functions to monads. The <code>mapM</code> functions are exported in the standard prelude and were described above. <code>foldM</code> is a monadic version of <code>foldl</code> in which monadic computations built from a list are bound left-to-right. The definition is: <haskell> foldM :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a foldM f a [] = return a foldM f a (x:xs) = f a x >>= \y -> foldM f y xs </haskell> but it is easier to understand the operation of <code>foldM</code> if you consider its effect in terms of a do block: <haskell> -- this is not valid Haskell code, it is just for illustration foldM f a1 [x1,x2,...,xn] = do a2 <- f a1 x1 a3 <- f a2 x2 ... f an xn </haskell> Right-to-left binding is achieved by reversing the input list before calling <code>foldM</code>. We can use <code>foldM</code> to create a more poweful query function in our sheep cloning example: === Example 3 === <haskell> -- traceFamily is a generic function to find an ancestor traceFamily :: Sheep -> [ (Sheep -> Maybe Sheep) ] -> Maybe Sheep traceFamily s l = foldM getParent s l where getParent s f = f s -- we can define complex queries using traceFamily in an easy, clear way mothersPaternalGrandfather s = traceFamily s [mother, father, father] paternalGrandmother s = traceFamily s [father, mother] </haskell> The <code>traceFamily</code> function uses <code>foldM</code> to create a simple way to trace back in the family tree to any depth and in any pattern. In fact, it is probably clearer to write "<code>traceFamily s [father, mother]</code>" than it is to use the <code>paternalGrandmother</code> function! A more typical use of <code>foldM</code> is within a do block: === Example 4 === <haskell> -- a Dict is just a finite map from strings to strings type Dict = FiniteMap String String -- this an auxilliary function used with foldl addEntry :: Dict -> Entry -> Dict addEntry d e = addToFM d (key e) (value e) -- this is an auxiliiary function used with foldM inside the IO monad addDataFromFile :: Dict -> Handle -> IO Dict addDataFromFile dict hdl = do contents <- hGetContents hdl let entries = map read (lines contents) return (foldl (addEntry) dict entries) -- this program builds a dictionary from the entries in all files named on the -- command line and then prints it out as an association list main :: IO () main = do files <- getArgs handles <- mapM openForReading files dict <- foldM addDataFromFile emptyFM handles print (fmToList dict) </haskell> The <code>filterM</code> function works like the list <code>filter</code> function inside of a monad. It takes a predicate function which returns a Boolean value in the monad and a list of values. It returns, inside the monad, a list of those values for which the predicate was True. <haskell> filterM :: Monad m => (a -> m Bool) -> [a] -> m [a] filterM p [] = return [] filterM p (x:xs) = do b <- p x ys <- filterM p xs return (if b then (x:ys) else ys) </haskell> Here is an example showing how <code>filterM</code> can be used within the <code>IO</code> monad to select only the directories from a list: === Example 5 === <haskell> import Monad import Directory import System -- NOTE: doesDirectoryExist has type FilePath -> IO Bool -- this program prints only the directories named on the command line main :: IO () main = do names <- getArgs dirs <- filterM doesDirectoryExist names mapM_ putStrLn dirs </haskell> <code>zipWithM</code> is a monadic version of the <code>zipWith</code> function on lists. <code>zipWithM_</code> behaves the same but discards the output of the function. It is useful when only the side-effects of the monadic computation matter. <haskell> zipWithM ::(Monad m) => (a -> b -> m c) -> [a] -> [b] -> m [c] zipWithM f xs ys = sequence (zipWith f xs ys) zipWithM_ ::(Monad m) => (a -> b -> m c) -> [a] -> [b] -> m () zipWithM_ f xs ys = sequence_ (zipWith f xs ys) </haskell> ==== Conditional monadic computations ==== There are two functions provided for conditionally executing monadic computations. The <code>when</code> function takes a boolean argument and a monadic computation with unit "()" type and performs the computation only when the boolean argument is <code>True</code>. The <code>unless</code> function does the same, except that it performs the computation ''unless'' the boolean argument is <code>True</code>. <haskell> when :: (Monad m) => Bool -> m () -> m () when p s = if p then s else return () unless :: (Monad m) => Bool -> m () -> m () unless p s = when (not p) s </haskell> ==== <code>ap</code> and the lifting functions ==== ''Lifting'' is a monadic operation that converts a non-monadic function into an equivalent function that operates on monadic values. We say that a function is "lifted into the monad" by the lifting operators. A lifted function is useful for operating on monad values outside of a do block and can also allow for cleaner code within a do block. The simplest lifting operator is <code>liftM</code>, which lifts a function of a single argument into a monad. <haskell> liftM :: (Monad m) => (a -> b) -> (m a -> m b) liftM f = \a -> do { a' <- a; return (f a') } </haskell> Lifting operators are also provided for functions with more arguments. <code>liftM2</code> lifts functions of two arguments: <haskell> liftM2 :: (Monad m) => (a -> b -> c) -> (m a -> m b -> m c) liftM2 f = \a b -> do { a' <- a; b' <- b; return (f a' b') } </haskell> The same pattern is applied to give the definitions to lift functions of more arguments. Functions up to <code>liftM5</code> are defined in the <code>Monad</code> module. To see how the lifting operators allow more concise code, consider a computation in the <code>Maybe</code> monad in which you want to use a function <code>swapNames::String -> String</code>. You could do: <haskell> getName :: String -> Maybe String getName name = do let db = [("John", "Smith, John"), ("Mike", "Caine, Michael")] tempName <- lookup name db return (swapNames tempName) </haskell> But making use of the <code>liftM</code> function, we can use <code>liftM swapNames</code> as a function of type <code>Maybe String -> Maybe String</code>: === Example 6 === <haskell> getName :: String -> Maybe String getName name = do let db = [("John", "Smith, John"), ("Mike", "Caine, Michael")] liftM swapNames (lookup name db) </haskell> The difference is even greater when lifting functions with more arguments. The lifting functions also enable very concise constructions using higher-order functions. To understand this example code, you might need to review the definition of the monad functions for the [[listmonad.html#definition|List monad]] (particularly <code>>>=</code>). Imagine how you might implement this function without lifting the operator: === Example 7 === <haskell> -- allCombinations returns a list containing the result of -- folding the binary operator through all combinations -- of elements of the given lists -- For example, allCombinations (+) [[0,1],[1,2,3]] would be -- [0+1,0+2,0+3,1+1,1+2,1+3], or [1,2,3,2,3,4] -- and allCombinations (*) [[0,1],[1,2],[3,5]] would be -- [0*1*3,0*1*5,0*2*3,0*2*5,1*1*3,1*1*5,1*2*3,1*2*5], or [0,0,0,0,3,5,6,10] allCombinations :: (a -> a -> a) -> [[a]] -> [a] allCombinations fn [] = [] allCombinations fn (l:ls) = foldl (liftM2 fn) l ls </haskell> There is a related function called <code>ap</code> that is sometimes more convenient to use than the lifting functions. <code>ap</code> is simply the function application operator (<code>$</code>) lifted into the monad: <haskell> ap :: (Monad m) => m (a -> b) -> m a -> m b ap = liftM2 ($) </haskell> Note that <code>liftM2 f x y</code> is equivalent to <code>return f `ap` x `ap` y</code>, and so on for functions of more arguments. <code>ap</code> is useful when working with higher-order functions and monads. The effect of <code>ap</code> depends on the strategy of the monad in which it is used. So for example <code>[(*2),(+3)] `ap` [0,1,2]</code> is equal to <code>[0,2,4,3,4,5]</code> and <code>(Just (*2)) `ap` (Just 3)</code> is <code>Just 6</code>. Here is a simple example that shows how <code>ap</code> can be useful when doing higher-order computations: === Example 8 === <haskell> -- lookup the commands and fold ap into the command list to -- compute a result. main :: IO () main = do let fns = [("double",(2*)), ("halve",(`div`2)), ("square",(\x->x*x)), ("negate", negate), ("incr",(+1)), ("decr",(+(-1))) ] args <- getArgs let val = read (args!!0) cmds = map ((flip lookup) fns) (words (args!!1)) print $ foldl (flip ap) (Just val) cmds </haskell> ==== Functions for use with <code>MonadPlus</code> ==== There are two functions in the <code>Monad</code> module that are used with monads that have a zero and a plus. The first function is <code>msum</code>, which is analogous to the <code>sum</code> function on lists of integers. <code>msum</code> operates on lists of monadic values and folds the <code>mplus</code> operator into the list using the <code>mzero</code> element as the initial value: <haskell> msum :: MonadPlus m => [m a] -> m a msum xs = foldr mplus mzero xs </haskell> In the List monad, <code>msum</code> is equivalent to <code>concat</code>. In the <code>Maybe</code> monad, <code>msum</code> returns the first non-<code>Nothing</code> value from a list. Likewise, the behavior in other monads will depend on the exact nature of their <code>mzero</code> and <code>mplus</code> definitions. <code>msum</code> allows many recursive functions and folds to be expressed more concisely. In the <code>Maybe</code> monad, for example, we can write: === Example 9 === <haskell> type Variable = String type Value = String type EnvironmentStack = [[(Variable,Value)]] -- lookupVar retrieves a variable's value from the environment stack -- It uses msum in the Maybe monad to return the first non-Nothing value. lookupVar :: Variable -> EnvironmentStack -> Maybe Value lookupVar var stack = msum $ map (lookup var) stack </haskell> instead of: <haskell> lookupVar :: Variable -> EnvironmentStack -> Maybe Value lookupVar var [] = Nothing lookupVar var (e:es) = let val = lookup var e in maybe (lookupVar var es) Just val </haskell> The second function for use with monads with a zero and a plus is the <code>guard</code> function: <haskell> guard :: MonadPlus m => Bool -> m () guard p = if p then return () else mzero </haskell> The trick to understanding this function is to recall the law for monads with zero and plus that states <code>mzero >>= f ==== mzero</code>. So, placing a <code>guard</code> function in a sequence of monadic operations will force any execution in which the guard is <code>False</code> to be <code>mzero</code>. This is similar to the way that guard predicates in a list comprehension cause values that fail the predicate to become <code>[]</code>. Here is an example demonstrating the use of the <code>guard</code> function in the <code>Maybe</code> monad. === Example 10 === <haskell> data Record = Rec {name::String, age::Int} deriving Show type DB = [Record] -- getYoungerThan returns all records for people younger than a specified age. -- It uses the guard function to eliminate records for ages at or over the limit. -- This is just for demonstration purposes. In real life, it would be -- clearer to simply use filter. When the filter criteria are more complex, -- guard becomes more useful. getYoungerThan :: Int -> DB -> [Record] getYoungerThan limit db = mapMaybe (\r -> do { guard (age r < limit); return r }) db </haskell> === Summary === Haskell provides a number of functions which are useful for working with monads in the standard libraries. The <code>Monad</code> class and most common monad functions are in the standard prelude. The <code>MonadPlus</code> class and less commonly-used (but still very useful!) functions are defined in the <code>Monad</code> module. Many other types in the Haskell libraries are declared as instances of <code>Monad</code> and <code>MonadPlus</code> in their respective modules.
Summary:
Please note that all contributions to HaskellWiki are considered to be released under simple permissive license (see
HaskellWiki:Copyrights
for details). If you don't want your writing to be edited mercilessly and redistributed at will, then don't submit it here.
You are also promising us that you wrote this yourself, or copied it from a public domain or similar free resource.
DO NOT SUBMIT COPYRIGHTED WORK WITHOUT PERMISSION!
Cancel
Editing help
(opens in new window)
Toggle limited content width