[Haskell-cafe] Re: Monads aren't evil? I think they are.

Apfelmus, Heinrich apfelmus at quantentunnel.de
Thu Jan 15 09:06:03 EST 2009


Ertugrul Soeylemez wrote:
> [...]

Thank you for your reply, I think I can refine my thoughts. And make
them much longer... ;)


The elegance I have in mind comes from abstraction, that is when a type
takes a meaning on its own, independent of its implementation. Let's
take the example of vector graphics again

  data Graphic

  empty   :: Graphic
  polygon :: [Point] -> Graphic
  over    :: Graphic -> Graphic -> Graphic

All primitives can be explained in terms of our intuition on pictures
alone; it is completely unnecessary to know that  Graphic  is implemented as

  type Graphics = Window -> IO ()

  empty          = \w -> return ()
  polygon (p:ps) = \w -> moveTo p w >> mapM_ (\p -> lineTo p w) ps
  over g1 g2     = \w -> g1 w >> g2 w

Furthermore, this independence is often exemplified by the existence of
many different implementations. For instance,  Graphics  can as well be
written as

  type Graphics = Pixel -> Color

  empty          = const Transparent
  polygon (p:ps) = foldr over empty $ zipWith line (p:ps) ps
  over g1 g2     = \p -> if g1 p == Transparent then g2 p else g1 p

Incidentally, this representation also makes a nice formalization of the
intuitive notion of pictures, making it possible to verify the
correctness of other implementations. Of course, taking it as definition
for  Graphic  would still fall short of the original goal of creating
meaning independent of any implementation. But this can be achieved by
stating the laws that relate the available operations. For instance, we have

     g = empty `over` g = g `over` empty          (identity element)
  g `over` (h `over` j) = (g `over` h) `over` j   (associativity)
             g `over` g = g                       (idempotence)

The first two equations say that  Graphics  is a monoid. Abstraction and
equational laws are the cornerstones of functional programming. For
more, see also the following classics

  John Hughes. The Design of a Pretty-printing Library.
  http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.38.8777

  Philip Wadler. A prettier printer.
  http://homepages.inf.ed.ac.uk/wadler/topics/
    language-design.html#prettier

  Richard Bird. A program to solve Sudoku
  Slides: http://icfp06.cs.uchicago.edu/bird-talk.pdf


(From this point of view, the feature of non-pure languages to allow
side effects in every function is useless and distracting. Why on earth
would I want  over  to potentially have side effects? That would just
invalidate the laws while offering nothing in return.)

> Often, the monadic solution _is_ the elegant solution.  Please don't
> confuse monads with impure operations.  I use the monadic properties of
> lists, often together with monad transformers, to find elegant
> solutions.  As long as you're not abusing monads to program
> imperatively, I think, they are an excellent and elegant structure.
>
> I do use state monads where there is no more elegant solution than passing
> state around.  It's simply that:  you have a structure, which you modify
> continuously in a complex fashion, such as a neural network or an
> automaton.  Monads are the way to go here, unless you want to do
> research and find a better way to express this.

In the light of the discussion above, the state monad for a particular
state is an implementation, not an abstraction. There is no independent
meaning in "stateful computation with an automaton as state", it is
defined by its sole implementation. Sure, it does reduce boilerplate and
simplifies the implementation, but it doesn't offer any insights.

In other words, "passing state" is not an abstraction and it's a good
idea to consciously exclude it from the design space when searching for
a good abstraction. Similar for the other monads, maybe except the
nondeterminism monad to some extend.

Of course, a good abstraction depends on the problem domain. For
automata, in particular finite state automata, I can imagine that the
operations on corresponding regular expressions like concatenation,
alternation and Kleene star are viable candidates. I have no clue about
neural networks.


On a side note, not every function that involves "state" does need the
state monad. For instance, an imperative language might accumulate a
value with a while-loop and updating a state variable, but in Haskell we
simply pass a parameter to the recursive call

   foldl f z []     = z
   foldl f z (x:xs) = foldl f (f z x) xs

Another example is "modifying" a value where a simple function of type
s -> s  like

   insert 1 'a' :: Map k v -> Map k v

will do the trick.

> Personally I prefer this:
> 
>   somethingWithRandomsM :: (Monad m, Random a) => m a -> Something a
> 
> over these:
> 
>   somethingWithRandoms1 :: [a] -> Something a
>   somethingWithRandoms2 :: RandomGen g => g -> Something a
>
>> Consciously excluding monads and restricting the design space to pure
>> functions is the basic tool of thought for finding such elegant
>> abstractions. [...]
> 
> You don't need to exclude monads to restrict the design space to pure
> functions.  Everything except IO and ST (and some related monads) is
> pure.  As said, often monads _are_ the elegant solutions.  Just look at
> parser monads.

Thanks for the reminder, there is indeed a portion of designs that
I overlooked in my previous post, namely when the abstraction involves a
parameter. For instance,

   data Parser a

   parse :: Parser a -> String -> Maybe a

is a thing that can parse values of some type  a . Here, the abstraction
solves a whole class of problems, one for every type. Similarly

   data Random a

denotes a value that "wiggles randomly". For instance, we can sample
them with a random seed

   sample :: RandomGen g => Random a -> g -> [a]

or inspect its distribution

   distribution :: Eq a => Random a -> [(a,Probability)]

The former can be implemented with a state monad, for the latter see also

   Martin Erwig, Steve Kollmansberger.
   Probabilistic functional programming in Haskell.
   http://web.engr.oregonstate.edu/~erwig/papers/PFP_JFP06.pdf

In these cases, it is a good idea to check whether the abstraction can
be made a monad, just like it is good to realize that  Graphic  is a
monoid. The same goes for applicative functors. These "abstractions
about abstractions" are useful design guides, but this is very different
from using a particular monad like the state monad and hoping that using
it somehow gives an insight into the problem domain.


Regards,
H. Apfelmus



More information about the Haskell-Cafe mailing list