Difference between revisions of "Do notation considered harmful"

From HaskellWiki
Jump to navigation Jump to search
(alternative Applicative syntax)
(counter with Reader monad, but without monad)
Line 51: Line 51:
 
thus many types are instances of <hask>Monad</hask> and <hask>Arrow</hask> classes,
 
thus many types are instances of <hask>Monad</hask> and <hask>Arrow</hask> classes,
 
but not as much are instances of <hask>Applicative</hask>.
 
but not as much are instances of <hask>Applicative</hask>.
There is not special syntax for applicative functors because it is hardly necessary.
+
There is no special syntax for applicative functors because it is hardly necessary.
 
You just write
 
You just write
 
<haskell>
 
<haskell>
Line 85: Line 85:
 
</haskell>
 
</haskell>
   
  +
<!-- to be continued -->
 
  +
If you are confident, that you will not need the counter state at the end and
  +
that you will not combine blocks of code using the counter
  +
(where the second block needs the state at the end of the first block),
  +
you can enforce a more strict scheme of usage.
  +
The following is like a <hask>Reader</hask> monad,
  +
where we call <hask>local</hask> on an incremented counter for each generated identifier.
  +
  +
<haskell>
  +
newtype T a = T (Int -> a)
  +
  +
run :: T a -> a
  +
run (T f) = f 0
  +
  +
newId :: (Int -> T a) -> T a
  +
newId f = T $ \i -> case f i of T g -> g (succ i)
  +
  +
example :: (Int -> Int -> T a) -> a
  +
example f =
  +
run $
  +
newId $ \a ->
  +
newId $ \b ->
  +
f a b
  +
</haskell>
  +
  +
This way users cannot accidentally place a <hask>return</hask>
  +
somewhere in a <hask>do</hask> block where it has no effect.
  +
   
 
=== Safety ===
 
=== Safety ===

Revision as of 14:04, 5 November 2007

Criticism

Haskell's do notation is popular and ubiquitous. However we shall not ignore that there are several problems. Here we like to shed some light on aspects you may not have thought about, so far.

Didactics

The do notation hides functional details. This is wanted in order to simplify writing imperative style code fragments. The downsides are

  • that, since do notation is used almost everywhere, where IO takes place, newcomers quickly believe that the do notation is necessary for doing IO,
  • and that newcomers think, that IO is somehow special and non-functional, in contrast to the advertisement for Haskell being purely functional.

These misunderstandings let people write clumsy code like

do putStrLn "text"

instead of

putStrLn "text"

or

do text <- getLine
   return text

instead of

getLine

or

do
  text <- readFile "foo"
  writeFile "bar" text

instead of

readFile "foo" >>= writeFile "bar"

.

Library design

Unfortunately, the do notation is so popular that people write more things with monads than necessary. See for instance the Binary package. It contains the Put monad, which has in principle nothing to do with a monad. Even more unfortunate, the applicative functors were introduced to Haskell's standard libraries only after monads and arrows, thus many types are instances of Monad and Arrow classes, but not as much are instances of Applicative. There is no special syntax for applicative functors because it is hardly necessary. You just write

data Header = Header Char Int Bool

readHeader :: Get Header
readHeader = liftA3 Header get get get

or

readHeader = Header <$> get <*> get <*> get

Not using monads and thus do notation can have advantages. Consider a generator of unique identifiers. First you might think of a State monad which increments a counter each time an identifier is requested.

run :: State Int a -> a
run m = evalState m 0

newId :: State Int Int
newId =
   do n <- get
      modify succ
      return n

example :: (Int -> Int -> a) -> a
example f =
   run $
      do x <- newId
         y <- newId
         return (f x y)


If you are confident, that you will not need the counter state at the end and that you will not combine blocks of code using the counter (where the second block needs the state at the end of the first block), you can enforce a more strict scheme of usage. The following is like a Reader monad, where we call local on an incremented counter for each generated identifier.

newtype T a = T (Int -> a)

run :: T a -> a
run (T f) = f 0

newId :: (Int -> T a) -> T a
newId f = T $ \i -> case f i of T g -> g (succ i)

example :: (Int -> Int -> T a) -> a
example f =
   run $
   newId $ \a ->
   newId $ \b ->
   f a b

This way users cannot accidentally place a return somewhere in a do block where it has no effect.


Safety

With do notation we have kept alive a dark side of the C programming language: The silent neglect of return values of functions. In an imperative language it is common to return an error code and provide the real work by side effects. In Haskell this cannot happen, because functions have no side effects. If you ignore the result of a Haskell function the function will even not be evaluated. The situation is different for IO: While processing the IO you might still ignore the contained return value.

You can write

do getLine
   putStrLn "text"

and thus silently ignore the result of getLine. The same applies to

do System.cmd.system "echo foo >bar"

where you ignore the ExitCode. Is this behaviour wanted?

In safety oriented languages there are possibilities to explicitly ignore return values (e.g. EVAL in Modula-3). Haskell does not need this, because you can already write

do _ <- System.cmd.system "echo foo >bar"
   return ()

Writing _ <- should always make you cautious whether ignoring the result is the right thing to do. The possibility for silently ignoring monadic return values is not entirely the fault of the do notation. It would suffice to restrict the type of the (>>) combinator to

(>>) :: m () -> m a -> m a

This way, you can omit _ <- only if the monadic return value has type ().


Useful applications

It shall be mentioned that the do sometimes takes the burden from you to write boring things. E.g. in

getRight :: Either a b -> Maybe b
getRight y =
   do Right x <- y
      return x

a case on y is included, which calls fail if y is not a Right (i.e. Left), and thus returns Nothing in this case.

Also the mdo notation proves useful, since it maintains a set of variables for you in a safe manner. Compare

mdo x <- f x y z
    y <- g x y z
    z <- h x y z
    return (x+y+z)

and

mfix
   (\ ~( ~(x,y,z), _) ->
      do x <- f x y z
         y <- g x y z
         z <- h x y z
         return ((x,y,z),x+y+z))


See also