haskell programming guidelines

Hi, haskell admits many programming styles and I find it important that several developers of a prject agree on a certain style to ease code review. I've set up guidelines (still as plain text) for our (hets) project in http://www.informatik.uni-bremen.de/agbkb/forschung/formal_methods/CoFI/hets... These were inspired by C programming guidelines, http://haskell.org/hawiki/ThingsToAvoid and the problems I came across myself. It like to get comments or proposals for our or other haskell grogramming guidelines. Thanks Christian

On Mon, 20 Feb 2006, Christian Maeder wrote:
I've set up guidelines (still as plain text) for our (hets) project in
http://www.informatik.uni-bremen.de/agbkb/forschung/formal_methods/CoFI/hets...
It seems we share the preference for 'case', 'let', 'map', 'filter' and 'fold'. :-) I prefer a definite choice between all_lower_case_with_underscore and camelCase identifier style. 'you should probably"' -- should probably what? Is the function size restriction still sensible for Haskell? I think Haskell functions should be at most a few lines, but not "one or two screenfuls of text". formJust -> fromJust
These were inspired by C programming guidelines, http://haskell.org/hawiki/ThingsToAvoid and the problems I came across myself.
It like to get comments or proposals for our or other haskell grogramming guidelines.
http://www.haskell.org/hawiki/UsingQualifiedNames http://www.haskell.org/hawiki/PairsOfIdentifiers

Henning Thielemann wrote:
I prefer a definite choice between all_lower_case_with_underscore and camelCase identifier style.
me too and I prefer camlCase (but it was too late already, when I wrote these guidelines)
'you should probably"' -- should probably what?
you should look into the section "Good Programming Practice" (i.e. decompose your stuff, but I'll rephrase that)
Is the function size restriction still sensible for Haskell? I think Haskell functions should be at most a few lines, but not "one or two screenfuls of text".
good point.
When reading (compilable) code unqualified names can be looked up using the haddock index.
What about the pair (insert, delete) from Data.Set and Map? Thanks for your comments Christian

On Feb 20, 2006, at 12:48 PM, Christian Maeder wrote:
Hi,
haskell admits many programming styles and I find it important that several developers of a prject agree on a certain style to ease code review.
I've set up guidelines (still as plain text) for our (hets) project in
http://www.informatik.uni-bremen.de/agbkb/forschung/formal_methods/ CoFI/hets/src-distribution/versions/HetCATS/docs/Programming- Guidelines.txt
These were inspired by C programming guidelines, http://haskell.org/ hawiki/ThingsToAvoid and the problems I came across myself.
It like to get comments or proposals for our or other haskell grogramming guidelines.
I personally disagree with your preference for custom datatypes with a value representing failure to lifting types with Maybe. I tend to like using the Maybe monad for composing large partial functions from smaller ones, but your suggestion makes that impossible. Also, if you bake in your failure case into your datatype, you can't use the type system to differentiate explicitly partial functions (which use Maybe X), from ones that are not expected to be partial (which just use X). Final point, using Maybe gives you an easy route to go to "Either String X" or some other richer monad to represent failure. Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

On Feb 20, 2006, at 2:26 PM, Henning Thielemann wrote:
On Mon, 20 Feb 2006, Robert Dockins wrote:
I personally disagree with your preference for custom datatypes with a value representing failure to lifting types with Maybe.
I understood that part of the guidelines as a pleading for Maybe.
Humm. Well clearly I read it the opposite way. I suppose that means that whatever technique is being recommended should be put forth with more clarity ;-) Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

G'day.
Quoting Christian Maeder
http://www.informatik.uni-bremen.de/agbkb/forschung/formal_methods/CoFI/hets... As mentioned in an earlier discussion, I strongly disapprove of the use of multiple ($) applications in the same expression. Or, for that matter, most uses of ($). I also disapprove of avoiding parentheses for the hell of it. The guideline that I use is: If what you are expressing is a chain of function applications, the correct operator to express this is function composition. Low-priority application may then be used to apply this composed function to an argument. So, for example, f (g (h x)) can be expressed well as: f . g $ h x -- only use if you need to distinguish h f . g . h $ x -- better And poorly as: f $ g $ h x f $ g $ h $ x (f . g . h) $ x -- except as an intermediate step in refactoring Cheers, Andrew Bromage

maeder:
Hi,
haskell admits many programming styles and I find it important that several developers of a prject agree on a certain style to ease code review.
I've set up guidelines (still as plain text) for our (hets) project in
Perhas you'd like to put up a Style page on thew new Haskell wiki, perhaps under the Idioms category? You could take some hints from the old style page, http://www.haskell.org/hawiki/HaskellStyle -- Don

Donald Bruce Stewart wrote:
Perhas you'd like to put up a Style page on thew new Haskell wiki, perhaps under the Idioms category?
I cannot promise it, but I'll try. If someone else is willing to do it, I would support this. Rob Dockins wrote:
I understood that part of the guidelines as a pleading for Maybe.
Humm. Well clearly I read it the opposite way. I suppose that means that whatever technique is being recommended should be put forth with more clarity ;-)
done (use Maybe or another Monad) Andrew Bromage wrote:
So, for example, f (g (h x)) can be expressed well as:
f . g $ h x -- only use if you need to distinguish h f . g . h $ x -- better
I see this differently. Expressions may be succinct! I find "$" and "." similar enough for non-obfuscation. But I collect cases where "$" does not work (i.e. for the kind #). Bad would be cases where "$" works differently than (reasonably) expected. John Meacham wrote:
f x = ... y ... where Just y = Map.lookup x theMap
now if the lookup fails you automatically get an error message pointing to the exact line number of the failure. or if the failure message of the routine is more important than the source location you can do
f x = ... y ... where Identity y = Map.lookup x theMap
These are potential runtime errors, that may be not so obvious to see in the source (ie. for user defined types) and even the compiler (ghc) does not emit a warning. Thanks for all your comments Christian

On Wed, Feb 22, 2006 at 01:14:41PM +0100, Christian Maeder wrote:
John Meacham wrote:
f x = ... y ... where Just y = Map.lookup x theMap
now if the lookup fails you automatically get an error message pointing to the exact line number of the failure. or if the failure message of the routine is more important than the source location you can do
f x = ... y ... where Identity y = Map.lookup x theMap
These are potential runtime errors, that may be not so obvious to see in the source (ie. for user defined types) and even the compiler (ghc) does not emit a warning.
Indeed, that is the entire point of the construct. ghc definitly should not emit a warning in this case as it is what lazy pattern matching is for. John -- John Meacham - ⑆repetae.net⑆john⑈

John Meacham wrote:
Identity y = Map.lookup x theMap
These are potential runtime errors, that may be not so obvious to see in the source (ie. for user defined types) and even the compiler (ghc) does not emit a warning.
Indeed, that is the entire point of the construct. ghc definitly should not emit a warning in this case as it is what lazy pattern matching is for.
I prefer to be explicit about this kind of partiality (by using 'error "<qualified function name>"') Christian

On Thu, Feb 23, 2006 at 11:16:11AM +0100, Christian Maeder wrote:
John Meacham wrote:
Identity y = Map.lookup x theMap
These are potential runtime errors, that may be not so obvious to see in the source (ie. for user defined types) and even the compiler (ghc) does not emit a warning.
Indeed, that is the entire point of the construct. ghc definitly should not emit a warning in this case as it is what lazy pattern matching is for.
I prefer to be explicit about this kind of partiality (by using 'error "<qualified function name>"')
I prefer the exact opposite :) John -- John Meacham - ⑆repetae.net⑆john⑈

G'day all.
Quoting Christian Maeder
I see this differently. Expressions may be succinct! I find "$" and "." similar enough for non-obfuscation.
But they're _not_ similar! Compare this notation: f . g . h $ x with the one you suggested: f $ g $ h $ x Advantages of the first one: - Encourages the idea that there is function composition going on. Function composition is one of the features of functional programming, so this should be highly encouraged. - Protects your code against the day when the committee realises that ($) has the wrong associativity. (It's the opposite of what you'd expect, since normal function application is left-associative.) Disadvantages: - None whatsoever. It's just as succinct and uses just as many parentheses. Cheers, Andrew Bromage

G'day all.
Quoting Christian Maeder
I suggested:
f . g $ h x
or f $ g $ h x
Of these, the first version only makes sense if you want to single out h for some reason. I'm known to do this, for example, if h is a record accessor. The second is just plain wrong. My reasoning is here for those who care: http://permalink.gmane.org/gmane.comp.lang.haskell.cafe/11256 Cheers, Andrew Bromage

ajb@spamcop.net wrote:
I suggested:
f . g $ h x
or f $ g $ h x
[..]
The second is just plain wrong. My reasoning is here for those who care:
http://permalink.gmane.org/gmane.comp.lang.haskell.cafe/11256
If you want a left-associative operator, you're free to define it (though single ascii symbols are rare). In a more realistic example, the current dollars help to improve readability, I think, and that is my argument why "$" should be right- associative: map (+ 1) $ filter (/= 0) $ Set.toList l An additional $ before the final argument (" $ l") looks stupid to me. I also find additional parentheses instead of the dollars more confusing, because of the other parts in parentheses. For a function definition, I recommend to simply change the dollars into dots and omit the last argument (if that is possible): myfun = map (+ 1) . filter (/= 0) . Set.toList That should correspond to your taste as well, although someone (ie. S.M.) proposed to disallow the dot as operator in haskell'. So, I don't know if either "." or "$" may be changed in the future and what other symbols may be used instead of these user-definable functions. However, if the argument cannot be omitted, I suggest to only change the last dot back into a dollar: myfun l = map (+ sum l) . filter (/= 0) $ Set.toList l I've no solution (ie. operator) for omitting two elements in: f x y = g $ h $ i x y apart from omitting only the first: f x = g . h . i x HTH Christian

Christian Maeder
That should correspond to your taste as well, although someone (ie. S.M.) proposed to disallow the dot as operator in haskell'.
From http://hackage.haskell.org/trac/haskell-prime/wiki/CompositionAsDot:
| We lose . as composition. Mostly this doesn't matter as $ is | probably more common in reality anyway. While I don't agree, this has been left standing for a long time and has survived several edits. -k -- If I haven't seen further, it is by standing in the footprints of giants

On 01/03/06, Christian Maeder
In a more realistic example, the current dollars help to improve readability, I think, and that is my argument why "$" should be right- associative:
map (+ 1) $ filter (/= 0) $ Set.toList l
An additional $ before the final argument (" $ l") looks stupid to me. I also find additional parentheses instead of the dollars more confusing, because of the other parts in parentheses.
If you don't like map (+ 1) . filter (/= 0) . Set.toList $ l then map (+ 1) . filter (/= 0) $ Set.toList l works just as well. In this case it's also a fairly natural way to break up the thought process. Your main computation is solely a composition of list functions, and the conversion is part of how you get the input to it. - Cale

There is a more straightforward way to get localized error messages rather than using 'maybe' and hand-writing an appropriate error, and that is to rely on irrefutable bindings. f x = ... y ... where Just y = Map.lookup x theMap now if the lookup fails you automatically get an error message pointing to the exact line number of the failure. or if the failure message of the routine is more important than the source location you can do f x = ... y ... where Identity y = Map.lookup x theMap it is anoying you have to make a choice between these two possibilities, but this can be mitigated with CPP magic or the SRCLOC_ANNOTATE pragma. John -- John Meacham - ⑆repetae.net⑆john⑈

On 20/02/06, John Meacham
There is a more straightforward way to get localized error messages rather than using 'maybe' and hand-writing an appropriate error, and that is to rely on irrefutable bindings.
f x = ... y ... where Just y = Map.lookup x theMap
now if the lookup fails you automatically get an error message pointing to the exact line number of the failure. or if the failure message of the routine is more important than the source location you can do
f x = ... y ... where Identity y = Map.lookup x theMap
it is anoying you have to make a choice between these two possibilities, but this can be mitigated with CPP magic or the SRCLOC_ANNOTATE pragma.
John
I look at the above as generating a proof obligation for me as the programmer that the lookup will never fail, or at least the ability to convince myself. :) If you want to handle errors, you should actually handle them, not let your users get "Irrefutable pattern failed" messages. Also, if someone else later comes along and wants to catch that error, they have to either do it in IO, which can be fiddly if the error occurs deep in the evaluation of some structure, or they refactor your code so that it returns the error explicitly. Sure, irrefutable pattern matches are useful, but they shouldn't be used if you expect they'll ever fail. - Cale

On Fri, Feb 24, 2006 at 12:39:27PM -0500, Cale Gibbard wrote:
I look at the above as generating a proof obligation for me as the programmer that the lookup will never fail, or at least the ability to convince myself. :) If you want to handle errors, you should actually handle them, not let your users get "Irrefutable pattern failed" messages. Also, if someone else later comes along and wants to catch that error, they have to either do it in IO, which can be fiddly if the error occurs deep in the evaluation of some structure, or they refactor your code so that it returns the error explicitly. Sure, irrefutable pattern matches are useful, but they shouldn't be used if you expect they'll ever fail.
Ah, perhaps I wasn't clear. I don't ever expect these to fail. The reason I prefer irrefutable pattern matches to handwritten 'error' messages (at first) is so many months later when I introduce a subtle heisenbug I don't get a error: This shouldn't happen or worse error: Prelude.undefined but rather a nice error pointing right to the line number. anything I ever expect to fail for any reason other than a bug I put in a failing Monad with a suitably user digestable error message. So, I was comparing them to handwritten 'error' messages for announcing programming bugs. not handwritten 'error' messages for users to see (which really should be using 'fail' in a monad anyway). John -- John Meacham - ⑆repetae.net⑆john⑈

On 24/02/06, John Meacham
On Fri, Feb 24, 2006 at 12:39:27PM -0500, Cale Gibbard wrote:
I look at the above as generating a proof obligation for me as the programmer that the lookup will never fail, or at least the ability to convince myself. :) If you want to handle errors, you should actually handle them, not let your users get "Irrefutable pattern failed" messages. Also, if someone else later comes along and wants to catch that error, they have to either do it in IO, which can be fiddly if the error occurs deep in the evaluation of some structure, or they refactor your code so that it returns the error explicitly. Sure, irrefutable pattern matches are useful, but they shouldn't be used if you expect they'll ever fail.
Ah, perhaps I wasn't clear. I don't ever expect these to fail. The reason I prefer irrefutable pattern matches to handwritten 'error' messages (at first) is so many months later when I introduce a subtle heisenbug I don't get a
error: This shouldn't happen or worse error: Prelude.undefined
but rather a nice error pointing right to the line number.
anything I ever expect to fail for any reason other than a bug I put in a failing Monad with a suitably user digestable error message. So, I was comparing them to handwritten 'error' messages for announcing programming bugs. not handwritten 'error' messages for users to see (which really should be using 'fail' in a monad anyway).
John
Well, this is an issue. Perhaps a version of error which makes the line/column number available to its parameter would help... something along the lines of type SourcePos = (Integer, Integer) -- possibly a data/newtype with a nicer Show instance errorPos :: (SourcePos -> String) -> a This would give all the benefits normally acquired from the expansion of the syntax sugar while allowing you to additionally add any extra messages you'd like. Further, you'd not be required to work in, say the identity monad, in order to get line number messages for failures (though in GHC at least, irrefutable pattern match failures in lambdas and let also get line numbered). I'm actually really against the inclusion of fail in the Monad class, so finding a reasonable replacement for any constructive uses it might have had is important to me. - Cale

On Mon, Feb 27, 2006 at 10:57:17PM -0500, Cale Gibbard wrote:
Well, this is an issue. Perhaps a version of error which makes the line/column number available to its parameter would help... something along the lines of
type SourcePos = (Integer, Integer) -- possibly a data/newtype with a nicer Show instance errorPos :: (SourcePos -> String) -> a
Yes, this is what jhc's SRCLOC_ANNOTATE addreses, more or less.
This would give all the benefits normally acquired from the expansion of the syntax sugar while allowing you to additionally add any extra messages you'd like. Further, you'd not be required to work in, say the identity monad, in order to get line number messages for failures (though in GHC at least, irrefutable pattern match failures in lambdas and let also get line numbered).
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. The writer of a library shouldn't decide how (non-buggy) failure should be handled, the user of it should.
I'm actually really against the inclusion of fail in the Monad class, so finding a reasonable replacement for any constructive uses it might have had is important to me.
I know you keep saying this, We start with the exact same premises and goals, yet somehow come to the exact opposite conclusion. I have not quite figured out why. However, a quick survey shows that _every single_ monad defined in the standard and fptools libraries has an interesting non-error 'fail' method other than Identity, whose sole purpose is to turn 'fail's into errors. Separating out a MonadError with 'fail' seems rather odd as every monad will be an instance of it! (including Identity, since turning fails into errors is its main purpose) (the monads like 'Reader' and 'Writer' are actually just shorthand for ReaderT a Identity, the inner monad determines the failure mode) John -- John Meacham - ⑆repetae.net⑆john⑈

On 27/02/06, John Meacham
On Mon, Feb 27, 2006 at 10:57:17PM -0500, Cale Gibbard wrote:
Well, this is an issue. Perhaps a version of error which makes the line/column number available to its parameter would help... something along the lines of
type SourcePos = (Integer, Integer) -- possibly a data/newtype with a nicer Show instance errorPos :: (SourcePos -> String) -> a
Yes, this is what jhc's SRCLOC_ANNOTATE addreses, more or less.
This would give all the benefits normally acquired from the expansion of the syntax sugar while allowing you to additionally add any extra messages you'd like. Further, you'd not be required to work in, say the identity monad, in order to get line number messages for failures (though in GHC at least, irrefutable pattern match failures in lambdas and let also get line numbered).
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.
The writer of a library shouldn't decide how (non-buggy) failure should 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.
I'm actually really against the inclusion of fail in the Monad class, so finding a reasonable replacement for any constructive uses it might have had is important to me.
I know you keep saying this, We start with the exact same premises and goals, yet somehow come to the exact opposite conclusion. I have not quite figured out why.
However, a quick survey shows that _every single_ monad defined in the standard and fptools libraries has an interesting non-error 'fail' method other than Identity, whose sole purpose is to turn 'fail's into errors. Separating out a MonadError with 'fail' seems rather odd as every monad will be an instance of it! (including Identity, since turning fails into errors is its main purpose)
(the monads like 'Reader' and 'Writer' are actually just shorthand for ReaderT a Identity, the inner monad determines the failure mode)
John
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. 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. - Cale

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] -- 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 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 really don't like it when things fail via 'error'. monadic failure means they don't have to. not only can they let the user decide how failure should be handled, but Monads provide exactly the compositional tools needed to combine code in a such a way that preserves that property. imagine if Map.lookup returned Maybe Int, but writeInt returned (Either String Foo). now suddenly you couldn't do
Map.lookup x map >>= writeInt
By prematurely deciding on an algebraic type, you seriously limit the usability of your code. 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.
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) 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" 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.
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. John -- John Meacham - ⑆repetae.net⑆john⑈

On 28/02/06, John Meacham
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

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⑈

Is there a consensus on how anticipatable failure situations should be handled? There was a thread, "haskell programming guidelines", from 2006-02-25 where John Meacham and Cale Gibbard had a bit of back-and-forth about using Monad.fail or a purpose specific MonadFail class. I believe a consensus was reached that using error should only be for 'impossible' situations and signaling buggy code. [Apologies if I've put words in anyones mouth.] Using fail certainly seems quick and easy, but I find it a bit distasteful for a few different reasons: users of a library can't discriminate between a failure indicating they've supplied bad input and a failure indicating that teh library writer has got a bad pattern match somewhere, it doesn't seem to force the potential for failure to be explicit in the api of a library, it doesn't seem to allow distinct, and rich, failure constructs at system layer boundaries, or the containment of them. Maybe the last two aren't a problem when programming in Haskell, but by itself the first seems pretty nasty. Apparently the advantage of fail is that user of the library can choose to receive failures as eg Maybes, Eithers, [], or whatever they like. But surely a MonadFail could allow the best of both worlds, letting the library throw as detailed an error construct as it can, and letting the library user choose MonadFail instance such that error constructs are turned into Maybes, Eithers, a new construct appropriate for a higher system layer, etc? MonadError is not up to this task as far as I can tell. Has anybody whipped up an alternative, or can explain why it can't be done? Cheers Daniel

On Mon, Mar 27, 2006 at 02:53:58PM +1200, Daniel McAllansmith wrote:
Is there a consensus on how anticipatable failure situations should be handled?
There was a thread, "haskell programming guidelines", from 2006-02-25 where John Meacham and Cale Gibbard had a bit of back-and-forth about using Monad.fail or a purpose specific MonadFail class.
Using fail certainly seems quick and easy, but I find it a bit distasteful for a few different reasons:
All of your reasons are good, but I recently tripped over an even better one: While fail must be defined in all monads, it has no sensible definition in many, and so throws an exception. I got burned because I wrote a function to run some monad of mine, which might result in an answer or an error, and I used fail for the error case: run :: Monad m => MyMonad a -> m a run m = ... if ... then return x else fail e Then, I accidentally (this was spread across two functions) ran my monad twice: run (run m) This typechecked and crashed. The inner run was given type MyMonad a -> MyMonad a and you can guess what fail does in MyMonad. Ugh. If I had used MonadError for the return value of run, run would only typecheck in a monad that can sensibly handle errors, catching my bug.
Apparently the advantage of fail is that user of the library can choose to receive failures as eg Maybes, Eithers, [], or whatever they like. ... MonadError is not up to this task as far as I can tell.
Why not? All that needs to be done is write the missing instances, eg instance MonadError () Maybe where throwError x = Nothing Nothing `catchError` f = f () Just x `catchError` f = Just x instance Error () where noMsg = () strMsg s = () As you might tell, I would like to see this instance in MonadError. An instance for [] is however questionable, IMO. BTW, I've posted about these issues several times, eg http://www.haskell.org/pipermail/haskell-cafe/2005-June/010361.html Andrew

On Tuesday 28 March 2006 07:29, Andrew Pimlott wrote:
MonadError is not up to this task as far as I can tell.
Why not? All that needs to be done is write the missing instances, eg
instance MonadError () Maybe where throwError x = Nothing Nothing `catchError` f = f () Just x `catchError` f = Just x
instance Error () where noMsg = () strMsg s = ()
How would you go about writing the Maybe based analogue of ErrorT? What do you give to the handler in the instance of MonadError? newtype ErrMaybeT e m a = ErrMaybeT { runErrMaybeT :: m (Maybe a) } instance (Monad m, Error e) => Monad (ErrMaybeT e m) where return a = ErrMaybeT $ return (Just a) m >>= k = ErrMaybeT $ do a <- runErrMaybeT m case a of Nothing -> return Nothing Just r -> runErrMaybeT (k r) fail msg = ErrMaybeT $ return Nothing instance (Monad m, Error e) => MonadError e (ErrMaybeT e m) where throwError l = ErrMaybeT $ return Nothing m `catchError` h = ErrMaybeT $ do a <- runErrMaybeT m case a of Nothing -> runErrMaybeT (h ???) --what to do here? Just r -> return (Just r) f :: (MonadError String m) => Bool -> m Int f b = if b then return 42 else throwError "The boolean was false." test1 b = do r <- runErrorT $ f b putStrLn (show r) --Left "..." or Right 42 return () test2 b = do r <- runErrMaybeT $ f b putStrLn (show r) --Nothing or Just 42 return () Daniel

On Wed, Mar 29, 2006 at 08:57:00AM +1200, Daniel McAllansmith wrote:
On Tuesday 28 March 2006 07:29, Andrew Pimlott wrote:
MonadError is not up to this task as far as I can tell.
Why not? All that needs to be done is write the missing instances, eg
instance MonadError () Maybe where throwError x = Nothing Nothing `catchError` f = f () Just x `catchError` f = Just x
instance Error () where noMsg = () strMsg s = ()
How would you go about writing the Maybe based analogue of ErrorT?
Maybe is a MonadError only with a dummy error type, which is why I used () above. Same with your ErrMaybeT: newtype ErrMaybeT m a = ErrMaybeT { runErrMaybeT :: m (Maybe a) } instance Monad m => MonadError () (ErrMaybeT m) where throwError l = ErrMaybeT $ return Nothing m `catchError` h = ErrMaybeT $ do a <- runErrMaybeT m case a of Nothing -> runErrMaybeT (h ()) Just r -> return (Just r) If you want to write a MonadError operation that can be used with Maybe or Either, it would look like f :: (MonadError e m, Error e) => Bool -> m Int f b = if b then return 42 else throwError (strMsg "The boolean was false.") But I see your point now about MonadFail (having throw but not catch) being perhaps preferable for this use. Andrew

On Wednesday 29 March 2006 09:49, Andrew Pimlott wrote:
If you want to write a MonadError operation that can be used with Maybe or Either, it would look like
f :: (MonadError e m, Error e) => Bool -> m Int f b = if b then return 42 else throwError (strMsg "The boolean was false.")
As long as you're happy only using Strings for your error constructs. Or you're willing to write a global construct<->String codec across all error constructs. Doesn't sound very pleasant to me.
But I see your point now about MonadFail (having throw but not catch) being perhaps preferable for this use.
My intuition is that you'd want three error related monads, Fail, Catch and Convert, to achieve what I'm after... don't know if that's a good intuition or not. :) Daniel
participants (10)
-
ajb@spamcop.net
-
Andrew Pimlott
-
Cale Gibbard
-
Christian Maeder
-
Daniel McAllansmith
-
dons@cse.unsw.edu.au
-
Henning Thielemann
-
John Meacham
-
Ketil Malde
-
Robert Dockins