[Haskell-cafe] Code walking off the right edge of the screen

Claus Reinke claus.reinke at talk21.com
Sun Jun 21 07:03:15 EDT 2009


>I (too) often find myself writing code such as this:
>
> if something
>  then putStrLn "howdy there!"
>  else if somethingElse
>          then putStrLn "howdy ho!"
>          else ...

1. recognize something odd. done.
2. look for improvements. good.
3. define suitable abstractions for your special case
4. look for general abstractions covering the special case

> I recall reading some tutorial about how you can use the Maybe monad
> if your code starts looking like this, but as you can see, that
> doesn't really apply here. "something" and "somethingElse" are simply
> booleans and each of them have different actions to take if either of
> them is True.

Maybe, or MaybeT (a monad transformer adding Maybe-style
functionality to your base monad, in this case IO) can be used here
as well, but may not be the first choice. As has been pointed out,
guards would seem to cover your use case:

e something somethingElse
  | something     = putStrLn "howdy there!"
  | somethingElse = putStrLn "howdy ho!"
  | otherwise     = putStrLn "hmm.. hi?"

If you need something more, you can define your own abstractions
to cover the repeated patterns in your code. Perhaps a function to
select one of a list of (condition,action) pairs:

g something somethingElse = oneOf
  [(something,     putStrLn "howdy there!")
  ,(somethingElse, putStrLn "howdy ho!")
  ,(otherwise,     putStrLn "hmm.. hi?")
  ]
  where oneOf = foldr (\(c,a) r->if c then a else r) (error "no match in oneOf")

or some combinators for alternatives of guarded actions instead

h something somethingElse =
  (something     -:> putStrLn "howdy there!")
  `orElse`
  (somethingElse -:> putStrLn "howdy ho!")
  `orElse`
  (otherwise     -:> putStrLn "hmm.. hi?")
  where
  c -:> a      = when c a >> return c
  a `orElse` b = a >>= \ar-> if ar then return True else b

Now, the former can be quite sufficient for many situations, but it
doesn't quite feel like a general solution, and the latter clearly shows
the dangers of defining your own abstractions: if you overdo it, anyone
reading your code will need a translator!-) Which is where the search
for general abstractions comes in - we're looking for something that
will not only cover this special use case, but will be more generally
useful, in a form that only needs to be understand once (not once per
project).

And that brings us to things like MonadPlus: you don't have to use
the Monad combinator for sequencing, but if you do (as in IO),
then it is natural to ask for a second combinator, for alternatives.
Now, IO itself doesn't have a MonadPlus instance, but we can
use a monad transformer to add such functionality. Using MaybeT,
that will be similar to version 'h' above:

i something somethingElse = runMaybeT $
  (guard something     >> lift (putStrLn "howdy there!"))
  `mplus`
  (guard somethingElse >> lift (putStrLn "howdy ho!"))
  `mplus`
  (                       lift (putStrLn "hmm.. hi?"))

and it can also be used for related patterns, such as running
a sequence of actions until the first failure:

j something somethingElse = runMaybeT $ do
  (guard something     >> lift (putStrLn "howdy there!"))
  (guard somethingElse >> lift (putStrLn "howdy ho!"))
  (                       lift (putStrLn "hmm.. hi?"))

or other combinations of these two patterns.

MaybeT is not the only possibility, and not always the best,
but Maybe is perhaps the best known instance of MonadPlus
(and the only thing that needs to change to use other MonadPlus
instances is the 'runMaybeT').

Hth,
Claus

PS. for a more extensive example of MaybeT vs indentation creep, see 
http://www.haskell.org/haskellwiki/Equational_reasoning_examples#Coding_style:_indentation_creep_with_nested_Maybe

---------------------------
data MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }

instance Monad m => Monad (MaybeT m) where
  return  = MaybeT . return . Just
  a >>= b = MaybeT $ runMaybeT a >>= maybe (return Nothing) (runMaybeT . b)
  fail msg= mzero

instance Monad m => MonadPlus (MaybeT m) where
  mzero       = MaybeT $ return Nothing
  a `mplus` b = MaybeT $ runMaybeT a >>= maybe (runMaybeT b) (return . Just)

instance MonadTrans MaybeT where
  lift m = MaybeT $ m >>= return . Just


main = do
  putStrLn "e:" >> mapM_ (uncurry e) args
  putStrLn "f:" >> mapM_ (uncurry f) args
  putStrLn "g:" >> mapM_ (uncurry g) args
  putStrLn "h:" >> mapM_ (uncurry h) args
  putStrLn "i:" >> mapM_ (uncurry i) args
  putStrLn "j:" >> mapM_ (uncurry j) args
  where args = [(x,y)|x<-[True,False],y<-[True,False]]







More information about the Haskell-Cafe mailing list