Difference between revisions of "Monad"

From HaskellWiki
Jump to navigation Jump to search
(Initial sections swapped)
(Relocation of "introdutorial" to 'Merely monadic')
Line 1: Line 1:
 
{{Standard class|Monad|module=Control.Monad|module-doc=Control-Monad|package=base}}
 
{{Standard class|Monad|module=Control.Monad|module-doc=Control-Monad|package=base}}
 
'''''Monads''''' in Haskell can be thought of as ''composable'' computation descriptions. The essence of monad is thus ''separation'' of ''composition timeline'' from the composed computation's ''execution timeline'', as well as the ability of ''computation'' to implicitly carry extra data, as pertaining to the computation itself, in addition to its ''one'' (hence the name) output, that it '''''will produce''''' when run (or queried, or called upon). This lends monads to supplementing ''pure'' calculations with features like I/O, common environment, updatable state, etc.
 
 
Each monad, or computation type, provides means, subject to '''''Monad Laws''''', to
 
 
* '''''(a)''''' ''create'' a description of a computation that will produce (a.k.a. "return") a given Haskell value, and
 
 
* '''''(b)''''' ''combine'' (a.k.a. "bind") a computation description with a ''reaction'' to it, – a pure Haskell function that is set to receive a computation-produced value (when and if ''that'' happens) and return another computation description, using or dependent on that value if need be, – creating a description of a combined computation that will feed the original computation's output through the reaction while automatically taking care of the particulars of the computational process itself.
 
 
''Reactions'' are thus computation description ''constructors''. A monad might also define additional primitives to provide access to and/or enable manipulation of data it implicitly carries, specific to its nature; cause some specific side-effects; etc..
 
 
Sometimes the specific monadic type also provides the ability to somehow '''''(c)''''' ''run'' a computation description, getting its result back into Haskell if computations described by the monad are pure, but this is expressly '''''not''''' a part of the Monad interface. Officially, <i>you can't get the <hask>a</hask> out of <hask>M a</hask></i> directly, only arrange for it to be "fed" into the next computation's constructor, the "reaction", indirectly. In case of an <hask>IO</hask> monad value, a computation it describes runs implicitly as a part of the chain of I/O computation descriptions composed together into the value <hask>main</hask> (of type <hask>IO ()</hask>) in a given Haskell program, by convention. <!-- Put simply, it runs when the compiled program runs (but then, everything does). -->
 
 
<haskell style="background-color:#f8f1ab;border-radius:15px;border:2px solid #000000;padding:15px">
 
# Monad interactions:
 
 
(a) reaction $ value ==> computation_description
 
 
(b) reaction =<< computation_description ==> computation_description
 
 
(c) reaction $ computation_description ==> ***type_mismatch***
 
 
(d) reaction <$> computation_description ==> computation_description_description
 
 
(e) join $ computation_description_description ==> computation_description
 
</haskell>
 
 
(<i><hask>join</hask></i> is another function expressing the essence of monad; where <hask>m >>= k = k =<< m = join (k <$> m) = join (fmap k m)</hask>; it is prefered in mathematics, over the ''bind''; both express the same concept).
 
 
Thus in Haskell, though it is a purely-functional language, side effects that '''''will be performed''''' by a computation can be dealt with and combined ''purely'' at the monad's composition time. Monads thus resemble programs in a particular [[EDSL]] (''embedded'' domain-specific language, "embedded" because the values denoting these computations are legal Haskell values, not some extraneous annotations).
 
 
While programs may describe impure effects and actions ''outside'' Haskell, they can still be combined and processed (''"assembled"'') purely, ''inside'' Haskell, creating a pure Haskell value - a computation action description that describes an impure calculation. That is how Monads in Haskell help keep the ''pure'' and the ''impure'' apart.
 
 
The computation doesn't have to be impure and can be pure itself as well. Then monads serve to provide the benefits of separation of concerns, and automatic creation of a computational "pipeline". Because they are very useful in practice but rather mind-twisting for the beginners, numerous tutorials that deal exclusively with monads were created (see [[Monad#Monad tutorials|monad tutorials]]).
 
   
 
== Monad class ==
 
== Monad class ==

Revision as of 02:03, 16 March 2021

Monad class (base)
import Control.Monad

Monad class

Monads can be viewed as a standard programming interface to various data or control structures, which is captured by the Monad class. All common monads are members of it:

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

In addition to implementing the class functions, all instances of Monad should obey the following equations, or Monad Laws:

return a >>= k                  =  k a
m        >>= return             =  m
m        >>= (\x -> k x >>= h)  =  (m >>= k) >>= h

For more information, including an intuitive explanation of why they should be obeyed, see Monad laws.

As of GHC 7.10, the Applicative typeclass is a superclass of Monad, and the Functor typeclass is a superclass of Applicative. This means that all monads are applicatives, all applicatives are functors, and, therefore, all monads are also functors. See Functor hierarchy proposal.

If the Monad definitions are preferred, Functor and Applicative instances can be defined from them with

fmap fab ma  =  do { a <- ma ; return (fab a) }
            --  ma >>= (return . fab)
pure a       =  do { return a }
            --  return a
mfab <*> ma  =  do { fab <- mfab ; a <- ma ; return (fab a) }
            --  mfab >>= (\ fab -> ma >>= (return . fab)) 
            --  mfab `ap` ma

although the recommended order is to define `return` as `pure`, if the two are the same.

Common monads

Most common applications of monads include:

  • Representing failure using Maybe monad
  • Nondeterminism using List monad to represent carrying multiple values
  • State using State monad
  • Read-only environment using Reader monad
  • I/O using IO monad

do-notation

In order to improve the look of code that uses monads Haskell provides a special syntactic sugar called do-notation. For example, the following expression:

thing1 >>= (\x -> func1 x >>= (\y -> thing2 
       >>= (\_ -> func2 y >>= (\z -> return z))))

which can be written more clearly by breaking it into several lines and omitting parentheses:

thing1  >>= \x ->
func1 x >>= \y ->
thing2  >>= \_ ->
func2 y >>= \z ->
return z

This can also be written using the do-notation as follows:

do {
  x <- thing1 ;
  y <- func1 x ;
  thing2 ;
  z <- func2 y ;
  return z
  }

(the curly braces and the semicolons are optional, when the indentation rules are observed).

Code written using do-notation is transformed by the compiler to ordinary expressions that use the functions from the Monad class (i.e. the two varieties of bind, >>= and >>).

When using do-notation and a monad like State or IO programs look very much like programs written in an imperative language as each line contains a statement that can change the simulated global state of the program and optionally binds a (local) variable that can be used by the statements later in the code block.

It is possible to intermix the do-notation with regular notation.

More on do-notation can be found in a section of Monads as computation and in other tutorials.

Commutative monads

Commutative monads are monads for which the order of actions makes no difference (they commute), that is when following code:

do
  a <- actA
  b <- actB
  m a b

is the same as:

do
  b <- actB
  a <- actA
  m a b

Examples of commutative include:

  • Reader monad
  • Maybe monad

Monad tutorials

Monads are known for being deeply confusing to lots of people, so there are plenty of tutorials specifically related to monads. Each takes a different approach to Monads, and hopefully everyone will find something useful.

See the Monad tutorials timeline for a comprehensive list of monad tutorials.

Monad reference guides

An explanation of the basic Monad functions, with examples, can be found in the reference guide A tour of the Haskell Monad functions, by Henk-Jan van Tuyl.

Monad research

A collection of research papers about monads.

Monads in other languages

Implementations of monads in other languages.

Unfinished:

And possibly there exist:

  • Standard ML (via modules?)

Please add them if you know of other implementations.

Collection of links to monad implementations in various languages. on Lambda The Ultimate.

Interesting monads

A list of monads for various evaluation strategies and games:

There are many more interesting instance of the monad abstraction out there. Please add them as you come across each species.

Fun

Help

Because they are very useful in practice but rather mind-twisting for beginners, there are some tutorials about monads which are available for those new to Haskell:

See also