[Haskell-cafe] Lists vs. Monads

Jonathan Cast jcast at ou.edu
Sat Jul 16 21:09:16 EDT 2005


Greg Buchholz <haskell at sleepingsquirrel.org> wrote:
>     Here's  a  question  for  the  Haskell community  that  I've  been
> wrestling with lately.  When we  say "lists are monads" what does that
> mean?  I can see one of two things.  First the slightly superficial...
> 
>   A.)  Lists  can be  made members  of the Monads  class, and  you can
>       define a couple of functions,  "bind" and "return" that obey the
>       Three Laws.
> 
> ...or the more fundamental...
> 
>   B.) Monads  somehow define lists.

Bingo.   More  precisely,  the  MonadPlus class  (with  some  frequently
violated laws  intact) defines  lists; i.e., []  is what  we intuitively
think we  are specifying by the  specification (I use `instance  C t' to
mean that t is an instance of C satisfying the usual laws):

> instance Monad []
> instance MonadPlus []
> a >> mzero = mzero
> (a `mplus` b) >>= f = (a >>= f) `mplus` (b >>= f)

While  the above doesn't  completely specify  [] (any  true backtracking
monad  and many parallelism  monads satisfy  all of  these laws),  [] is
isomorphic to  what most  programmers would produce  given specification
(see    e.g.     /The   Design    of    a   Pretty-Printing    Library/,
<http://www.cs.chalmers.se/~rjmh/Papers/pretty.ps>, section 6.1).

Mathematically,  we say that  [] is  an initial  model (`model'  is what
logicians  call an  implementation)  of the  above specification,  which
means that  there is precisely  one function f  from [alpha] to  m alpha
(for m as above) which satisfies the properties

> f (return x) = return x
> f (a >>= g) = f a >>= f . g
> f mzero = mzero
> f (a `mplus` b) = f a `mplus` f b

(This function is (foldr (mplus  . return) mzero), or (foldr mplus mzero
. map  return), btw.).   This fact, called  an initiality  condition, is
sufficient to guarantee the existence of head and tail.

> If  you had  a version  of Haskell  without recursive  data  types you
> wouldn't be at a loss, because you could always use monads to recreate
> lists.   Maybe "bind"  would replace  the job  of "cons"  and "return"
> would replace "head" or somesuch.

No.   You  can't  define  most  initial  models  without  recursive  (or
inductive)  data types in  general, because  initial models  are defined
inductively.

In any case, you got the definition of the functions wrong :)

> (:) = mplus . return
> [] = mzero
> concatMap = flip (>>=)

You can't define head, tail, or foldr using the MonadPlus signature (how
would you  define them for e.g.   a backtracking parser?),  which is why
you  do need  recursive types  for  [] (or  [] itself,  the approach  of
e.g. python).

<snip>

Jon Cast


More information about the Haskell-Cafe mailing list