[Haskell-cafe] haskell programming guidelines

Cale Gibbard cgibbard at gmail.com
Tue Feb 28 04:52:40 EST 2006


On 28/02/06, John Meacham <john at repetae.net> wrote:
> On Tue, Feb 28, 2006 at 01:09:03AM -0500, Cale Gibbard wrote:
> > > Well, the benefit of the Identity monad is so that the user of a routine
> > > can choose to recover gracefully by using a different monad, you only
> > > use the Identity monad when you are making a choice to bottom out on
> > > errors. using 'error' directly is not an option in said cases because it
> > > would take away the ability of the user of a routine to catch errors
> > > properly. error should only be used for reporting bugs that should never
> > > happen, not user visible failure.
> >
> > I'd argue that it would be better for the user to simply catch the
> > value returned which indicates error explicitly, and throw the error
> > themselves. This indicates that they have put thought into the fact
> > that the function may fail.
>
> so does using runIdentity, that is the point of it. You are saying I
> want failure to bottom out, just like using it as a 'Maybe' means you
> only care about whether it has a result or using it as a 'Either' means
> you want the result string or using it as a WriterT Foo IO means you
> want to possibly collect some results and have fail throw an IO
> exception.
>
> I consider it bad style to spend code on cases you never expect to
> happen, if it takes too much work to write code that fails properly on
> bugs, people arn't (and definitly should not have to) do the extra work,
> they will just write code that fails poorly. Monadic failure is
> absolutely great for writing robust, concise, code.
>
> > > be handled, the user of it should.
> >
> > Right, which is why minimal types for expressing the failure should be
> > used, and the user should convert from those types to whatever larger
> > environment they have in mind. If your function is simply partial, use
> > Maybe, if you want to report error strings, use Either String. These
> > types easily lift into any monad which support similar functionality.
> > It also gives the users of your library more information about the
> > exact way in which your functions may fail, just by looking at the
> > type signatures, and gets them thinking about handling that failure.
> > An arbitrary monad m doesn't indicate anything about the failure modes
> > present.
>
> ack! The user of a library is who should get to choose how to deal with
> the error case, not the library writer.
>
> I'd hate to give up such very common idioms as
>
> -- collect error messages from all failing parsers
> [ err | Left err <- map parse xs]

I don't see how you lose this one at all.

>
> -- 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

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

If we had a bigger monadic context, it would be just as easy to lift
the error up into that.

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

Or finally, if Map.lookup uses the MonadError class, like it probably should:
do vs <- mapM (`Map.lookup` m) xs
   Map.lookup vs sm

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.

Also, if Map.lookup was equipped to give us symbolic information about
the error, we could extend this to that. With fail, all we get is a
string. We'd know what's actually available from Map.lookup before we
write any of this.

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.

What I'm advocating is not the use of non-monadic case-style failure handling.

I'm advocating the use of specific classes and types which indicate
that failure is a reasonably expected option.

> 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.

> monadic failure means they don't have to. not only can they let the use
> decide how failure should be handled, but Monads provide exactly th
> compositional tools needed to combine code in a such a way that
> preserves that property.

I agree.

>
> imagine if Map.lookup returned Maybe Int, but writeInt returned (Either
> String Foo).
>
> now suddenly you couldn't do
> > Map.lookup x map >>= writeInt

Right, you couldn't. If the inconvenience of applying lifting
functions is just too great, the solution to this is typeclasses.
Monad is not the right typeclass. (It's not enough.)

>
> By prematurely deciding on an algebraic type, you seriously limit the
> usability of your code.

Not quite. Those types are universal with respect to the features that
they provide. There's always an embedding from them into anything
suitable, so you're not stuck at all.
>
> you say
>
> "If your function is simply partial, use Maybe, if you want to report
> error strings, use Either String."
>
> which is exactly precicely what monadic failure lets you do. use the
> routine in the way that makes sense. but more importantly it lets you write
> monadic combinators that preserve said property.

Yeah, those are monads.

> > Well, that means that Reader, Writer and State, and any monad based
> > upon them or their transformers does not have a meaningful fail. IO
> > also does not have an interesting fail. It also means that all custom
> > monads based on state transformers, say, don't have interesting fails.
> > This is a very large chunk of the monads which people use in everyday
> > code! The List monad and Maybe monad have nice fails, and that's why
> > they should be in MonadZero.
>
> 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.
>
> Reader,Writer, and State are stacked on top of Identity, which has error
> as fail on purpose. if you don't like that you have the freedom to
> either stack the transformer version on to another monad. Or there are
> various transformers that give you an interesting 'fail' if you want it.
> When you use Identity, you are saying 'error' is what you want.
>
>
> but in any case, you just stated the power of monadic fail right there.
>
> "monads based on Reader, Writer, State won't have an interesting fail"
> but you seem to miss the converse
> "monads based on ones with interesting fails will have an interesting
> fail"
>

Monads which have interesting fails should and do have their own
class, and we should use it.

> 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.

>
> > I disagree that Identity, Reader, Writer, or State should be an
> > instance of MonadError or MonadZero. They should simply not be used
> > for that purpose. I'd like a monad hierarchy where if there is an
> > instance of a class for a monad, then none of the methods of that
> > class are identically bottom. It seems disingenuous to me to say that
> > some type constructor implements certain functionality, and then
> > implement it in a way which crashes the program. If you need failure
> > in your monad, add it explicitly via a transformer, and if you use
> > failure, you should express that via a class. Types and classes should
> > be meaningful and informative about this sort of thing.
>
>
> 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.

 - Cale


More information about the Haskell-Cafe mailing list