[Haskell-cafe] haskell programming guidelines

John Meacham john at repetae.net
Tue Feb 28 06:14:23 EST 2006


On Tue, Feb 28, 2006 at 04:52:40AM -0500, Cale Gibbard wrote:
> > -- collect error messages from all failing parsers
> > [ err | Left err <- map parse xs]
> 
> I don't see how you lose this one at all.

because somewhere else, you might want to use 'parse' as a maybe.
somewhere else, you might want it to throw an IO exception, somewhere
else you might want to compose it with some other arbitrary monad and
not loose the ability to override the return type.

> > -- look up a string transformed by a map in another map, failing if it
> > -- is not in said other map.
> > runIdentity $ Map.lookup (concatMap (`Map.lookup` map) xs) smap
> 
> Suppose Map.lookup returns something in the Maybe monad.
> 
> let lookup k m = fromJust $ Map.lookup k m
> in lookup (map (`lookup` m) xs) sm

and then in 2 months you get a 
"Predule.error: fromJust"

but moreso, you may define a value like so 
> z = Map.lookup (concatMap (`Map.lookup` map) xs) smap

now z can be used for any sort of monad. very handy.

The need for partial functions like fromJust are exactly what I don't
want to see used anywhere.

> Not so hard. How about if Map.lookup is prepared to give us a string
> via the Either String monad and we want to throw an error:
> let lookup k m = either error id $ Map.lookup k m
> in lookup (map (`lookup` m) xs) sm

exactly, if it is in a monad then you don't have to make this decision,
the user of lookup does.


> let lookup k m = either (throwError . strMsg) return $ Map.lookup k m
> in do vs <- mapM (`lookup` m) xs
>       lookup vs sm

now compare that to:

> mapM (`lookup` m) xs >>= (`lookup` sm)

and that is a relatively simple one.


> But note that this is *not* the Identity monad we're working in here.
> It's some MonadError, and as far as I'm concerned, that's quite
> different.

I was never working in the Identity monad either, the routines should
work in an _arbitrary_ monad, of which Identity is one of.

> It's important to note here that  either (throwError . strMsg) return 
> is a useful lifter in its own right, and should probably be extracted
> and put in the library.
> 
> > but the real power is when you combine monadic failure with combinators
> > and monad transformers
> 
> > -- imagine some complicated function
> > f x xs = runWriterT $ mapM (\x -> foofunc x >>= tell) xs
> >
> > the great thing about this is it is transparent to failure! so you can
> > build arbitrarily complicated transformers while still letting the user
> > of 'f' decide what to do with failure. this is a great feature, if
> > foofunc returned a data type, the writer of 'f' would be forced to deal
> > with failure, and might (likely will) do something silly like call
> > 'error'.
> 
> I'm not sure I understand your point here. Why would the writer of f
> be any more forced to deal with failure if foofunc returned a specific
> type here? In fact, it must be at least typed in WriterT, so I'm not
> sure what you mean. The code would be identical regardless of whether
> the transformed monad was fixed or not, and the writer of f doesn't
> have to do anything.

indeed. it is identical only because the inner monad can be an arbitrary
one. if foofunc returned an error in an algebraic type, then the monad
becomes fixed and your function is no longer general.

> > I really don't like it when things fail via 'error'.
> 
> Then why do you advocate the use of 'fail' which is implemented with
> error in half of all monads that people use? Why do you advocate the
> use of runIdentity on a possibly failing computation? That's the same
> as failing via error.

Yup. except for the fact that I am advocating making functions work
in an arbitrary monad. Think about lambda patterns, they cause 'errors'
but arn't indicated as special in the type system, at least with the
'do' notation you can recover and do something interesting when the
pattern doesn't match. bottom is a member of every type in haskell
whether we like it or not. People already use 'error' way to much, we
should be making it easier for them to use recoverable things like
'fail', not harder. Dealing with errors sanely should not take more
effort, but should be the default.

bottoming out is a perfectly valid thing to do on some errors, but such
a thing should _never_ be forced. the choice of Monad is what lets you
do that. The difference is non-trivial and deals with more than just
error handling. A space leaking deterministic parser written correctly
will become constant space when run in the 'Identity' Monad (but might
fill in some values with bottom) while using Either or Just would cause
it to hold onto its entire input until the information can be verified.

Sometimes you want fail to bottom, sometimes you don't, but best of all
in all cases is to defer the decision to an outer monad.


if people can't do 

> "foo" <- getString

without changing all their type signatures, then they are going to do
something like

> x <- getString 
> if x == "foo" then ... else error "expecting foo!"

being able to use 'fail' without changing your signatures is a very nice
thing and encourages good program practice.


> > IO definitly has an interesting fail, it throws a catchable IO
> > exception. (note, this is not the same as imprecise exceptions)
> 
> Hm? Exceptions thrown by error are catchable too, in the exact same
> way. If the error is thrown by pure evaluation, you sometimes have to
> use Control.Exception.evaluate to ensure that the evaluation actually
> occurs in the context of the catch, but otherwise, it's the same
> thing, and certainly if the error is typed in IO.

not at all. They are extremely differint types of exceptions. imprecise
exceptions are thrown by 'error' and are non-deterministic hacky things.
The only thing they have to do with IO exceptions is that they are
reported via the IO exception mechanism, but are a fundamentally
different beast.

IO is a true error monad and proper IOErrors are completely
deterministic and specified fully by the haskell 98 report.
IO is defined in jhc as (roughly)

data IOResult a = JustIO World a | ErrorIO World IOError
newtype IO a = IO (World -> IOResult a)  

it is a true error monad just like Maybe or Either and obeys all the
same nice properties.


I would advocate making the imprecise exception catching routine
separate from the IO exception catching routine as confusion between
them is bad as they are quite different.

(and imprecise exceptions in general should never be used except in
extreme or system-level programming IMHO)


In jhc 'error' will never be catchable as a design choice. error should
never be recoverable, if you want to recover from something, use 'fail'
or some other mechanism to propagate errors properly. (that and
optimizations are much simpler if you know branches will abort
unrecoverably)

Not to say I won't do imprecise exceptions, (though, I may not, I am
iffy about them) I just won't make 'error' one of the catchable ones.


> > but who determines what monad code runs in? the _user_ of the code. not
> > the code itself. if you want to handle failure, just use it in a monad
> > that has failure. it is completly up to the user of a routine how to
> > deal with failure and that is the great power of monadic failure and
> > typeclasses.
> >
> 
> There are many cases where the fact that the result of an operation is
> typed in an arbitrary monad is not enough to indicate the potential
> need for error handling. (In fact, I'd tend not to read it as such.)
> If I accidentally pick a monad which can't handle that error
> gracefully, I get an exception and my program dies. Put the contract
> in the type, so that just by looking at the type, I know what I'm up
> against.

Perhaps you are using the wrong monads then? I never use ones that die
on error except when I explicitly and obviously use the Identity monad.
I tend to always build my monads using a stack of transformers and the
newtype deriving trick, I always leave the bottom spot free (unless I
need IO) just so that whoever uses my Monad (often me) can stack in
whatever error handler they want (often different ones depending on the
use). 

> > I really don't want programs to bottom out, which is why I like monadic
> > failure, it lets me write code that does not do so and use other peoples
> > code in such a way that it doesn't. bottom is bad! we should avoid it,
> > not encourage it! Monadic failure lets us avoid it in a very nice, clean
> > way. not having it would encourage people to write code that bottoms out
> > on failure with no good recovery path.
> >
> 
> I agree on all of those points. Let's put failure in its own class
> where it's guaranteed, at least in the libraries, not to be
> implemented with bottom, and let's use that class instead of Monad,
> where we have no choice but to give broken implementations in many
> important cases.


Well that is the thing. bottom is a perfectly valid 'fail'
implementation for a Monad, indeed it inhabits every Monad in haskell
(*cough* jhc unboxed monads *cough*). However, using it should always be
a choice. People will use 'error' if fail is not available and you loose
that choice.  (I don't consider 'error' catchable). I would want
Identity to be a member of MonadError because it is darn useful to be
able to turn 'fail' into 'error' precicely where you want and nowhere
else. not to mention its useful time/space properties. Not being in
MonadError is no guarentee your code won't bottom out, it just means you
can't catch (many instances) of it if you want to.

        John



-- 
John Meacham - ⑆repetae.net⑆john⑈


More information about the Haskell-Cafe mailing list