Proposal: die to System.Exit (and/or Prelude)

Hi! I propose to add die :: String -> IO () die err = hPutStrLn stderr err >> exitFailure to System.Exit. Reasoning: (1) It's a frequently required functionality. Almost every command-line program has code similar to this. (2) The definition is relatively short, but in addition to the definition, you need two import statements. (3) It's frequently done wrong (e.g. writing to stdout instead of stderr, or not using exitFailure, or both). I haven't done any extensive research on Hackage, but I quickly looked at Haddock. Here we have a definition of die [1], but we also print to stdout at a couple of place and then call exitFailure [2]. Personally, I think it should be re-exported from Prelude. But this may be controversial. So let's have two separate votes: Add System.Exit.die: +1 Re-export it from Prelude: +1 (discussion until December, 28th) Cheers, Simon [1] https://github.com/ghc/haddock/blob/8d4c94ca5a969a5ebbb791939fb0195dc672429e... [2] https://github.com/ghc/haddock/blob/c6faeae064668125721b0d5e60f067f90c538933...

On Sat, Dec 14, 2013 at 11:56:11AM +0100, Simon Hengel wrote:
I propose to add
die :: String -> IO () die err = hPutStrLn stderr err >> exitFailure
to System.Exit.
An alternative implementation would be: die :: String -> IO () die err = do name <- getProgramName hPutStrLn stderr (name ++ ": " ++ err) >> exitFailure (not sure what's preferable) Cheers.

2013/12/14 Simon Hengel
Hi! I propose to add
die :: String -> IO () die err = hPutStrLn stderr err >> exitFailure
to System.Exit.
Reasoning:
(1) It's a frequently required functionality. Almost every command-line program has code similar to this.
(2) The definition is relatively short, but in addition to the definition, you need two import statements.
(3) It's frequently done wrong (e.g. writing to stdout instead of stderr, or not using exitFailure, or both).
I haven't done any extensive research on Hackage, but I quickly looked at Haddock. Here we have a definition of die [1], but we also print to stdout at a couple of place and then call exitFailure [2].
Personally, I think it should be re-exported from Prelude. But this may be controversial. So let's have two separate votes:
Isn't your `die` function a special case of `error :: String -> a`, which is in the Prelude ? I think variants of what you propose are often used: different exit codes, not exiting and flushing stderr, displaying an arbitrary `Show a` instead of `String`, using `Text`, and so on. Actually I think some (all ?) `IO` things from the Prelude should not be in the Prelude. For instance I may want to use the `bytestring` `readFile`. - 1 (for both) Thu

* Vo Minh Thu
Isn't your `die` function a special case of `error :: String -> a`, which is in the Prelude ?
There are two differences: * die throws an exception in the IO monad (i.e. it uses `throwIO`, whereas `error` uses `throw`). * error adds "*** Exception: " to the message Roman

On Sat, Dec 14, 2013 at 12:09:20PM +0100, Vo Minh Thu wrote:
Isn't your `die` function a special case of `error :: String -> a`, which is in the Prelude ?
No, it's not. I'm not going into the details of imprecise exceptions (and GHC's interpretation of them + all the bugs that various versions of GHC have when it comes to that topic), but `error` indicates a programmer error and should not be part of a valid path in your program. In contrast, `die` is meant to be used when a user e.g. passes wrong input to a program (which is a user error, not a programmer error).
I think variants of what you propose are often used: different exit codes, not exiting and flushing stderr
You can just use hPutStrLn here, stderr is unbuffered by default.
displaying an arbitrary `Show a` instead of `String`
Yes, that is actually a good point. But die (show x) is still much more concise than using hPrint + exitFailure.
using `Text`
Valid point. Still, I think for the particular case of error messages it's ok to stick with String. Cheers.

On 2013-12-14 at 12:09:20 +0100, Vo Minh Thu wrote: [...]
I propose to add
die :: String -> IO () die err = hPutStrLn stderr err >> exitFailure
to System.Exit.
[...]
Isn't your `die` function a special case of `error :: String -> a`, which is in the Prelude ?
Imho, it'd be more comparable to the effect of `fail :: Monad m =>
String -> m a` for 'm == IO' (which throws an 'userError' exception).
E.g.:
$ cat > foo.hs <

I agree that this function would be useful for quick&dirty prototyping.
However, I'm not sure we should encourage its use. What looks to me like
a superior approach is to throw proper exceptions.
Here's an example in my own code:
https://github.com/haskell-suite/haskell-names/blob/master/hs-gen-iface/src/...
The main advantage of this is that it's much easier to turn the 'main'
code into library code, which is not supposed to write to stderr
anymore. Exceptions carry important semantic information about what
actually happened, and can be caught and handled if needed. (The
ExitCode exception can also be caught, but it doesn't tell us anything,
and the output would have already gone to stderr.)
As a bonus, this approach forces you to separate (in code) message
strings from places where you die, which in my experience leads to much
cleaner code.
There's a caveat that the standard doesn't specify what happens to
uncaught exceptions, so we have to rely on the runtime doing the right
thing for us. Well, GHC's one does.
Roman
* Simon Hengel
Hi! I propose to add
die :: String -> IO () die err = hPutStrLn stderr err >> exitFailure
to System.Exit.
Reasoning:
(1) It's a frequently required functionality. Almost every command-line program has code similar to this.
(2) The definition is relatively short, but in addition to the definition, you need two import statements.
(3) It's frequently done wrong (e.g. writing to stdout instead of stderr, or not using exitFailure, or both).
I haven't done any extensive research on Hackage, but I quickly looked at Haddock. Here we have a definition of die [1], but we also print to stdout at a couple of place and then call exitFailure [2].
Personally, I think it should be re-exported from Prelude. But this may be controversial. So let's have two separate votes:
Add System.Exit.die: +1 Re-export it from Prelude: +1
(discussion until December, 28th)
Cheers, Simon
[1] https://github.com/ghc/haddock/blob/8d4c94ca5a969a5ebbb791939fb0195dc672429e... [2] https://github.com/ghc/haddock/blob/c6faeae064668125721b0d5e60f067f90c538933... _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I agree that this function would be useful for quick&dirty prototyping.
However, I'm not sure we should encourage its use. What looks to me like a superior approach is to throw proper exceptions.
Here's an example in my own code: https://github.com/haskell-suite/haskell-names/blob/master/hs-gen-iface/src/...
The main advantage of this is that it's much easier to turn the 'main' code into library code, which is not supposed to write to stderr anymore. Exceptions carry important semantic information about what actually happened, and can be caught and handled if needed. (The ExitCode exception can also be caught, but it doesn't tell us anything, and the output would have already gone to stderr.)
As a bonus, this approach forces you to separate (in code) message strings from places where you die, which in my experience leads to much cleaner code.
There's a caveat that the standard doesn't specify what happens to uncaught exceptions, so we have to rely on the runtime doing the right thing for us. Well, GHC's one does.
For my own code, I actually prefer to stick with Maybe/Either instead of exceptions when ever possible. I'd use `die` only in a top-level wrapper, e.g. like so: import Acme.Omitted main :: IO () main = getContents >>= either die run . parseInput run :: UserInput -> IO () run = (...) parseInput :: String -> Either String UserInput parseInput = (...) Cheers.

I also think that people should generally use exceptions which I can catch by names (as opposed to error), especially in libraries, but in simple top-level cases as you described, your `die` makes a lot of sense to me. "Easy things should be easy", and removing another case for `error` sounds like a good thing. Add System.Exit.die: +1 I'd prefer your simple, first version though, since `getProgramName` might not always print the thing you would like. Glad to be convinced otherwise though (how do unix tools do this? Is it hardcoded or do they check their program name)? Re-export it from Prelude: -1 (At least for now, let's have it around firstr.) On 14/12/13 11:54, Simon Hengel wrote:
I agree that this function would be useful for quick&dirty prototyping.
However, I'm not sure we should encourage its use. What looks to me like a superior approach is to throw proper exceptions.
Here's an example in my own code: https://github.com/haskell-suite/haskell-names/blob/master/hs-gen-iface/src/...
The main advantage of this is that it's much easier to turn the 'main' code into library code, which is not supposed to write to stderr anymore. Exceptions carry important semantic information about what actually happened, and can be caught and handled if needed. (The ExitCode exception can also be caught, but it doesn't tell us anything, and the output would have already gone to stderr.)
As a bonus, this approach forces you to separate (in code) message strings from places where you die, which in my experience leads to much cleaner code.
There's a caveat that the standard doesn't specify what happens to uncaught exceptions, so we have to rely on the runtime doing the right thing for us. Well, GHC's one does.
For my own code, I actually prefer to stick with Maybe/Either instead of exceptions when ever possible. I'd use `die` only in a top-level wrapper, e.g. like so:
import Acme.Omitted
main :: IO () main = getContents >>= either die run . parseInput
run :: UserInput -> IO () run = (...)
parseInput :: String -> Either String UserInput parseInput = (...)
Cheers. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 14.12.2013 12:54, Simon Hengel wrote:
main :: IO () main = getContents >>= either die run . parseInput
Funny way to write a pipeline. Its neither left-to-right, which would be getContents >>= (parseInput >>> either die run) nor right-to-left: either die run . parseInput =<< getContents A case for hlint. So much for my smart-ass comments. About "(to) die or not (to) die" I am rather agnostic. -1 for adding it to the Prelude. -- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

On Mon, 16 Dec 2013, Andreas Abel wrote:
On 14.12.2013 12:54, Simon Hengel wrote:
main :: IO () main = getContents >>= either die run . parseInput
Funny way to write a pipeline. Its neither left-to-right, which would be
getContents >>= (parseInput >>> either die run)
nor right-to-left:
either die run . parseInput =<< getContents
A case for hlint.

On 14 December 2013 22:19, Roman Cheplyaka
I agree that this function would be useful for quick&dirty prototyping.
However, I'm not sure we should encourage its use. What looks to me like a superior approach is to throw proper exceptions.
I've written something similar to this die function specifically to deal with these exceptions (or to exit early out of main if I know nothing more can proceed) rather than relying upon GHC to deal with them. That said, I'm not sure if it's worth adding; +0.5 to having it in System.Exit.
Here's an example in my own code: https://github.com/haskell-suite/haskell-names/blob/master/hs-gen-iface/src/...
The main advantage of this is that it's much easier to turn the 'main' code into library code, which is not supposed to write to stderr anymore. Exceptions carry important semantic information about what actually happened, and can be caught and handled if needed. (The ExitCode exception can also be caught, but it doesn't tell us anything, and the output would have already gone to stderr.)
As a bonus, this approach forces you to separate (in code) message strings from places where you die, which in my experience leads to much cleaner code.
There's a caveat that the standard doesn't specify what happens to uncaught exceptions, so we have to rely on the runtime doing the right thing for us. Well, GHC's one does.
Roman
* Simon Hengel
[2013-12-14 11:56:11+0100] Hi! I propose to add
die :: String -> IO () die err = hPutStrLn stderr err >> exitFailure
to System.Exit.
Reasoning:
(1) It's a frequently required functionality. Almost every command-line program has code similar to this.
(2) The definition is relatively short, but in addition to the definition, you need two import statements.
(3) It's frequently done wrong (e.g. writing to stdout instead of stderr, or not using exitFailure, or both).
I haven't done any extensive research on Hackage, but I quickly looked at Haddock. Here we have a definition of die [1], but we also print to stdout at a couple of place and then call exitFailure [2].
Personally, I think it should be re-exported from Prelude. But this may be controversial. So let's have two separate votes:
Add System.Exit.die: +1 Re-export it from Prelude: +1
(discussion until December, 28th)
Cheers, Simon
[1] https://github.com/ghc/haddock/blob/8d4c94ca5a969a5ebbb791939fb0195dc672429e... [2] https://github.com/ghc/haddock/blob/c6faeae064668125721b0d5e60f067f90c538933... _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

On Sat, 14 Dec 2013, Simon Hengel wrote:
Hi! I propose to add
die :: String -> IO () die err = hPutStrLn stderr err >> exitFailure
to System.Exit.
I have written this definition several times and called it exitFailureMsg. I used it only for the argument handling in shell programs. I agree with Roman that the proper way are exceptions. However, the implicit nature of IO exceptions is the wrong way, too. This is confirmed by Roman's observation that it is not clear how uncaught IO exceptions are handled. In an explicit ErrorT way you cannot accidentally ignore exceptions. Thus, I think neither 'die'/exit nor IO exceptions are the right way to go. Consequently I hesitate to add further steps in wrong directions to 'base'. Maybe it would be better to add an exception handler containing "hPutStrLn stderr" to ErrorT module.
Add System.Exit.die:
0
Re-export it from Prelude:
-1

+1 to adding 'die' to System.Exit
-1 to adding to Prelude
I've pretty much only wanted this in command-line type programs, but as the
proposal notes, it's very frequently required in that situation.
John L.
On Sat, Dec 14, 2013 at 2:56 AM, Simon Hengel
Hi! I propose to add
die :: String -> IO () die err = hPutStrLn stderr err >> exitFailure
to System.Exit.
Reasoning:
(1) It's a frequently required functionality. Almost every command-line program has code similar to this.
(2) The definition is relatively short, but in addition to the definition, you need two import statements.
(3) It's frequently done wrong (e.g. writing to stdout instead of stderr, or not using exitFailure, or both).
I haven't done any extensive research on Hackage, but I quickly looked at Haddock. Here we have a definition of die [1], but we also print to stdout at a couple of place and then call exitFailure [2].
Personally, I think it should be re-exported from Prelude. But this may be controversial. So let's have two separate votes:
Add System.Exit.die: +1 Re-export it from Prelude: +1
(discussion until December, 28th)
Cheers, Simon
[1] https://github.com/ghc/haddock/blob/8d4c94ca5a969a5ebbb791939fb0195dc672429e... [2] https://github.com/ghc/haddock/blob/c6faeae064668125721b0d5e60f067f90c538933... _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

+1 adding to System.Exit
-0.5 adding to Prelude
Tom
El Dec 15, 2013, a las 18:50, John Lato
+1 to adding 'die' to System.Exit -1 to adding to Prelude
I've pretty much only wanted this in command-line type programs, but as the proposal notes, it's very frequently required in that situation.
John L.
On Sat, Dec 14, 2013 at 2:56 AM, Simon Hengel
wrote: Hi! I propose to add
die :: String -> IO () die err = hPutStrLn stderr err >> exitFailure
to System.Exit.
Reasoning:
(1) It's a frequently required functionality. Almost every command-line program has code similar to this.
(2) The definition is relatively short, but in addition to the definition, you need two import statements.
(3) It's frequently done wrong (e.g. writing to stdout instead of stderr, or not using exitFailure, or both).
I haven't done any extensive research on Hackage, but I quickly looked at Haddock. Here we have a definition of die [1], but we also print to stdout at a couple of place and then call exitFailure [2].
Personally, I think it should be re-exported from Prelude. But this may be controversial. So let's have two separate votes:
Add System.Exit.die: +1 Re-export it from Prelude: +1
(discussion until December, 28th)
Cheers, Simon
[1] https://github.com/ghc/haddock/blob/8d4c94ca5a969a5ebbb791939fb0195dc672429e... [2] https://github.com/ghc/haddock/blob/c6faeae064668125721b0d5e60f067f90c538933... _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I'm neutral on adding or removing it to System.Exit in the first place.
On one hand it incurs the extra clutter of another name for a simple
composition, but on the other it is exiled to a fairly appropriate place
and I can see that there is a worldview in which would be the right way to
deal with exceptional situations that have no recovery mechanism.
That said, I'm pretty strongly -1 on adding it to the Prelude.
-Edward
On Sun, Dec 15, 2013 at 7:40 PM,
+1 adding to System.Exit -0.5 adding to Prelude
Tom
El Dec 15, 2013, a las 18:50, John Lato
escribió: +1 to adding 'die' to System.Exit -1 to adding to Prelude
I've pretty much only wanted this in command-line type programs, but as the proposal notes, it's very frequently required in that situation.
John L.
On Sat, Dec 14, 2013 at 2:56 AM, Simon Hengel
wrote: Hi! I propose to add
die :: String -> IO () die err = hPutStrLn stderr err >> exitFailure
to System.Exit.
Reasoning:
(1) It's a frequently required functionality. Almost every command-line program has code similar to this.
(2) The definition is relatively short, but in addition to the definition, you need two import statements.
(3) It's frequently done wrong (e.g. writing to stdout instead of stderr, or not using exitFailure, or both).
I haven't done any extensive research on Hackage, but I quickly looked at Haddock. Here we have a definition of die [1], but we also print to stdout at a couple of place and then call exitFailure [2].
Personally, I think it should be re-exported from Prelude. But this may be controversial. So let's have two separate votes:
Add System.Exit.die: +1 Re-export it from Prelude: +1
(discussion until December, 28th)
Cheers, Simon
[1] https://github.com/ghc/haddock/blob/8d4c94ca5a969a5ebbb791939fb0195dc672429e... [2] https://github.com/ghc/haddock/blob/c6faeae064668125721b0d5e60f067f90c538933... _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I always thought it was kind of bizarre how other languages (even wordy old java) have "exit :: Int -> IO ()", but haskell has "System.Exit.exitSuccess" and "System.Exit.exitWith (ExitFailure 42)". Yes it's higher level to say "success" and "failure" than "0" and ">0", but wow that's a lot of bureaucracy for something trivial. And it still lets you write (ExitFailure 0). Anyway, +1 for System.Exit, -1 for Prelude, because I sometimes define my own 'die'.

* Evan Laforge
I always thought it was kind of bizarre how other languages (even wordy old java) have "exit :: Int -> IO ()", but haskell has "System.Exit.exitSuccess" and "System.Exit.exitWith (ExitFailure 42)". Yes it's higher level to say "success" and "failure" than "0" and ">0", but wow that's a lot of bureaucracy for something trivial. And it still lets you write (ExitFailure 0).
System.Exit.exitFailure :: IO a has existed for a long time, FWIW. Roman

On Sun, Dec 15, 2013 at 6:16 PM, Roman Cheplyaka
* Evan Laforge
[2013-12-15 17:54:14-0800] I always thought it was kind of bizarre how other languages (even wordy old java) have "exit :: Int -> IO ()", but haskell has "System.Exit.exitSuccess" and "System.Exit.exitWith (ExitFailure 42)". Yes it's higher level to say "success" and "failure" than "0" and ">0", but wow that's a lot of bureaucracy for something trivial. And it still lets you write (ExitFailure 0).
System.Exit.exitFailure :: IO a has existed for a long time, FWIW.
Yeah, that's what I was saying. One module, one type, two constructors, and three functions, just to do what everyone else does with one 'exit' function. It's the windows vista shutdown menu of exit functions. It's almost as if haskell doesn't want to let us out. Um. Anyway. Ignore me and carry on.

Hello Simon, On 2013-12-14 at 11:56:11 +0100, Simon Hengel wrote:
I propose to add
die :: String -> IO () die err = hPutStrLn stderr err >> exitFailure
to System.Exit.
Why not simply use the existing `fail :: String -> IO a` method instead? The differences & similiarities I see wrt `fail`: - `die` throws an `ExitCode` exception, whereas `fail` throws an `IOError` exception - Both result in the message written to stderr and a non-zero exit code - As both use exceptions, `die` does guarantee termination (as it can be caught) - `die` writes to stderr at invocation time, whereas `fail` attaches the message to the exception, which is then output by the top exception handler. Due to that, catching a `die`-caused exception will print the termination message even though the process-exit was cancelled. Whereas attaching the message to the exception allows for more flexibility as well as for atomicity wrt message-output and termination. - `fail` is available from Prelude (and part of Haskell98/2010), whereas `System.Exit.die` would require an import of "System.Exit" (with the small risk of breaking code that expects only Haskell2010-known entities exported by "System.Exit") Therefore I'm not convinced (yet), that the suggested `die` implementation has sensible semantics in the context of exceptions, and that it offers enough benefits over the already existing `fail` method. Cheers, hvr

On 16 December 2013 22:15, Roman Cheplyaka
* Herbert Valerio Riedel
[2013-12-16 10:53:21+0100] Why not simply use the existing `fail :: String -> IO a` method instead?
The purpose of 'fail' is to handle monadic pattern-match failures. I consider explicit use of 'fail' in user code a hack.
Or for use with parser-combinator libraries (though I suppose this could be seen as a pattern-match failure...)?
Roman
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

* Ivan Lazar Miljenovic
On 16 December 2013 22:15, Roman Cheplyaka
wrote: * Herbert Valerio Riedel
[2013-12-16 10:53:21+0100] Why not simply use the existing `fail :: String -> IO a` method instead?
The purpose of 'fail' is to handle monadic pattern-match failures. I consider explicit use of 'fail' in user code a hack.
Or for use with parser-combinator libraries (though I suppose this could be seen as a pattern-match failure...)?
I'd consider that an abuse, too. E.g. Parsec provides a parserFail function that you can call instead. I treat 'fail' as a semi-private method of the Monad class. I may override it, but I should never call it. It only exists for the compiler. Roman

On 16.12.2013 14:12, Roman Cheplyaka wrote:
The purpose of 'fail' is to handle monadic pattern-match failures. I consider explicit use of 'fail' in user code a hack.
I treat 'fail' as a semi-private method of the Monad class. I may override it, but I should never call it. It only exists for the compiler.
This is useful information. Please add it to the documentation. That would definitely help newcomers to get some orientation in the design space of exceptions... http://hackage.haskell.org/package/base-4.6.0.1/docs/Control-Monad.html#t:Mo... fail :: String -> m a Fail with a message. This operation is not part of the mathematical definition of a monad, but is invoked on pattern-match failure in a do expression. -- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

On 2013-12-16 at 14:54:53 +0100, Andreas Abel wrote:
On 16.12.2013 14:12, Roman Cheplyaka wrote:
The purpose of 'fail' is to handle monadic pattern-match failures. I consider explicit use of 'fail' in user code a hack.
I treat 'fail' as a semi-private method of the Monad class. I may override it, but I should never call it. It only exists for the compiler.
This is useful information. Please add it to the documentation. That would definitely help newcomers to get some orientation in the design space of exceptions...
[...] If this is really the intent of `fail`, shouldn't we then also attach a {-# WARNING fail "Monad(fail) is not supposed to be called directly" #-} to the `fail` method definition to help catch illegal uses of `fail` in user code? (Fwiw, I've tested attaching such a warning to `fail` in GHC HEAD's libraries/base/GHC/Base.lhs and it seems to work just fine so far... so if there's consensus, we could add that for GHC 7.8) Cheers, hvr

(Fwiw, I've tested attaching such a warning to `fail` in GHC HEAD's libraries/base/GHC/Base.lhs and it seems to work just fine so far... so if there's consensus, we could add that for GHC 7.8)
That sounds great! And as far as I remember, we will have MonadFail, as Malcolm mentioned, soon. On 16/12/13 13:54, Andreas Abel wrote
fail :: String -> m a
Fail with a message. This operation is not part of the mathematical definition of a monad, but is invoked on pattern-match failure in a do expression.
This seems to go well with your change.

On 16.12.2013 18:37, Niklas Hambüchen wrote:
(Fwiw, I've tested attaching such a warning to `fail` in GHC HEAD's libraries/base/GHC/Base.lhs and it seems to work just fine so far... so if there's consensus, we could add that for GHC 7.8)
That sounds great!
And as far as I remember, we will have MonadFail, as Malcolm mentioned, soon.
On 16/12/13 13:54, Andreas Abel wrote
fail :: String -> m a
Fail with a message. This operation is not part of the mathematical definition of a monad, but is invoked on pattern-match failure in a do expression.
This seems to go well with your change.
Above I was just quoting the current documentation. It should be formulated sharper, to say explicitly "do not use `fail' to throw your own errors!" -- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

On Mon, Dec 16, 2013 at 5:50 PM, Herbert Valerio Riedel
On 2013-12-16 at 14:54:53 +0100, Andreas Abel wrote:
On 16.12.2013 14:12, Roman Cheplyaka wrote:
The purpose of 'fail' is to handle monadic pattern-match failures. I consider explicit use of 'fail' in user code a hack.
I treat 'fail' as a semi-private method of the Monad class. I may override it, but I should never call it. It only exists for the compiler.
This is useful information. Please add it to the documentation. That would definitely help newcomers to get some orientation in the design space of exceptions...
[...]
If this is really the intent of `fail`, shouldn't we then also attach a
{-# WARNING fail "Monad(fail) is not supposed to be called directly" #-}
to the `fail` method definition to help catch illegal uses of `fail` in user code?
(Fwiw, I've tested attaching such a warning to `fail` in GHC HEAD's libraries/base/GHC/Base.lhs and it seems to work just fine so far... so if there's consensus, we could add that for GHC 7.8)
Cheers, hvr _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
+1! I think `fail` is a huge wart anyway. I'm still partial to the Haskell 1.4 solution to this problem, where the translation of refutable patterns in do-notation would involve `mzero` rather than `fail "Here, have some debugging info."`. :), Stijn

On 16/12/2013 16:50, Herbert Valerio Riedel wrote:
On 2013-12-16 at 14:54:53 +0100, Andreas Abel wrote:
On 16.12.2013 14:12, Roman Cheplyaka wrote:
The purpose of 'fail' is to handle monadic pattern-match failures. I consider explicit use of 'fail' in user code a hack.
I treat 'fail' as a semi-private method of the Monad class. I may override it, but I should never call it. It only exists for the compiler.
This is useful information. Please add it to the documentation. That would definitely help newcomers to get some orientation in the design space of exceptions...
[...]
If this is really the intent of `fail`, shouldn't we then also attach a
{-# WARNING fail "Monad(fail) is not supposed to be called directly" #-}
to the `fail` method definition to help catch illegal uses of `fail` in user code?
(Fwiw, I've tested attaching such a warning to `fail` in GHC HEAD's libraries/base/GHC/Base.lhs and it seems to work just fine so far... so if there's consensus, we could add that for GHC 7.8)
I'm not sure I follow the logic of this. If it does continue to exist, what are the arguments against using it explicitly? Cheers, Ganesh

On Fri, Dec 20, 2013 at 6:27 PM, Ganesh Sittampalam
On 16/12/2013 16:50, Herbert Valerio Riedel wrote:
On 2013-12-16 at 14:54:53 +0100, Andreas Abel wrote:
On 16.12.2013 14:12, Roman Cheplyaka wrote:
The purpose of 'fail' is to handle monadic pattern-match failures. I consider explicit use of 'fail' in user code a hack.
I treat 'fail' as a semi-private method of the Monad class. I may override it, but I should never call it. It only exists for the compiler.
This is useful information. Please add it to the documentation. That would definitely help newcomers to get some orientation in the design space of exceptions...
[...]
If this is really the intent of `fail`, shouldn't we then also attach a
{-# WARNING fail "Monad(fail) is not supposed to be called directly" #-}
to the `fail` method definition to help catch illegal uses of `fail` in user code?
(Fwiw, I've tested attaching such a warning to `fail` in GHC HEAD's libraries/base/GHC/Base.lhs and it seems to work just fine so far... so if there's consensus, we could add that for GHC 7.8)
I'm not sure I follow the logic of this. If it does continue to exist, what are the arguments against using it explicitly?
Cheers,
Ganesh
Some monads have no sensible implementation for fail, so therefore, `fail` can't be bound by any laws besides what's in the type. So when you're writing common functions involving error handling, the type of `fail` gives you some requirements on how to use it, but you get no promise that it does something useful (note: `fail = error` is not useful). However, when you use something like MonadError, you're guaranteed (by the type) that you can use throwError, and promised (by those who create instances for MonadError) that it will have a useful meaning. (And this is just one of the reasons.) Regards, Stijn

I'm personally -1 on making explicit calls to fail into a warning.
That said I'd be more than happy to consider where we should put it if we
wanted to move it to another class on a sufficiently long time horizon to
moderate the community impact of that change.
-Edward
On Fri, Dec 20, 2013 at 6:14 PM, Stijn van Drongelen
On Fri, Dec 20, 2013 at 6:27 PM, Ganesh Sittampalam
wrote: On 16/12/2013 16:50, Herbert Valerio Riedel wrote:
On 2013-12-16 at 14:54:53 +0100, Andreas Abel wrote:
On 16.12.2013 14:12, Roman Cheplyaka wrote:
> The purpose of 'fail' is to handle monadic pattern-match failures. > I consider explicit use of 'fail' in user code a hack.
I treat 'fail' as a semi-private method of the Monad class. I may override it, but I should never call it. It only exists for the compiler.
This is useful information. Please add it to the documentation. That would definitely help newcomers to get some orientation in the design space of exceptions...
[...]
If this is really the intent of `fail`, shouldn't we then also attach a
{-# WARNING fail "Monad(fail) is not supposed to be called directly" #-}
to the `fail` method definition to help catch illegal uses of `fail` in user code?
(Fwiw, I've tested attaching such a warning to `fail` in GHC HEAD's libraries/base/GHC/Base.lhs and it seems to work just fine so far... so if there's consensus, we could add that for GHC 7.8)
I'm not sure I follow the logic of this. If it does continue to exist, what are the arguments against using it explicitly?
Cheers,
Ganesh
Some monads have no sensible implementation for fail, so therefore, `fail` can't be bound by any laws besides what's in the type. So when you're writing common functions involving error handling, the type of `fail` gives you some requirements on how to use it, but you get no promise that it does something useful (note: `fail = error` is not useful).
However, when you use something like MonadError, you're guaranteed (by the type) that you can use throwError, and promised (by those who create instances for MonadError) that it will have a useful meaning.
(And this is just one of the reasons.)
Regards, Stijn
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Fri, Dec 20, 2013 at 4:58 PM, Edward Kmett
I'm personally -1 on making explicit calls to fail into a warning.
I think it really depends on how the warning is enabled. I don't think it should be part of -Wall, but I could see it being there for people that want such things. And if you're going that route, shouldn't it be part of hlint instead of ghc? So, I think I just convinced myself that I'm -1 on this too :) Jason

On 20/12/2013 23:14, Stijn van Drongelen wrote:
Some monads have no sensible implementation for fail, so therefore, `fail` can't be bound by any laws besides what's in the type. So when you're writing common functions involving error handling, the type of `fail` gives you some requirements on how to use it, but you get no promise that it does something useful (note: `fail = error` is not useful).
However, when you use something like MonadError, you're guaranteed (by the type) that you can use throwError, and promised (by those who create instances for MonadError) that it will have a useful meaning.
(And this is just one of the reasons.)
But as long as it used for pattern match failures, those problems will exist anyway - is using it explicitly any worse than writing incomplete patterns in a do block? Ganesh

On Dec 21, 2013 11:13 AM, "Ganesh Sittampalam"
On 20/12/2013 23:14, Stijn van Drongelen wrote:
Some monads have no sensible implementation for fail, so therefore, `fail` can't be bound by any laws besides what's in the type. So when you're writing common functions involving error handling, the type of `fail` gives you some requirements on how to use it, but you get no promise that it does something useful (note: `fail = error` is not
useful).
However, when you use something like MonadError, you're guaranteed (by the type) that you can use throwError, and promised (by those who create instances for MonadError) that it will have a useful meaning.
(And this is just one of the reasons.)
But as long as it used for pattern match failures, those problems will exist anyway - is using it explicitly any worse than writing incomplete patterns in a do block?
Ganesh
You're right that fail can be used sensibly when there'd be a pattern match failure otherwise. I was going to write that people use fail for other things as well, but I just realize that the distinction between a pattern match failure and any other failure 'based on a value' is very vague. Warning about fail but allowing it implicitly is then a pretty unfounded solution. So I change my +1 into a -1. Let's split fail off of Monad instead. Thanks, Stijn

On 16 Dec 2013, at 13:12, Roman Cheplyaka wrote:
* Ivan Lazar Miljenovic
[2013-12-17 00:00:16+1100] On 16 December 2013 22:15, Roman Cheplyaka
wrote: * Herbert Valerio Riedel
[2013-12-16 10:53:21+0100] Why not simply use the existing `fail :: String -> IO a` method instead?
The purpose of 'fail' is to handle monadic pattern-match failures. I consider explicit use of 'fail' in user code a hack.
Or for use with parser-combinator libraries (though I suppose this could be seen as a pattern-match failure...)?
I'd consider that an abuse, too. E.g. Parsec provides a parserFail function that you can call instead.
I respectfully disagree. Whilst it was probably a mistake originally to include "fail" as a method of the Monad class, it has always been a useful additional method. Personally, I would have it in a separate class (called MonadFail, or similar). But wherever it lives, we would always have had it. I see no good reason to distinguish between runtime pattern-match failure, and a direct user call of "fail". It is quite common to write parsers using pattern-matching, and why should one kind of backtracking be privileged over another? Their effects are of exactly the same kind. e.g. keyword = ( do "let" <- word -- fails if the string does not match b <- binding return (LET b) ) `onFail` ( do "case" <- word exp <- expression "of" <- word `onFail` fail "missing keyword 'of'" alts <- many1 alternative return (CASE exp alts) ) etc.

* Malcolm Wallace
I see no good reason to distinguish between runtime pattern-match failure, and a direct user call of "fail".
One reason to distinguish them is that there's no good reason for fail to have type String -> m a. Perhaps a better type would be PatternFailureInfo -> m a, where PatternFailureInfo would include the SrcLoc of where the failure happened, the pattern itself, maybe something else. So, it is possible to use fail in parsers, but only because it incidentally has such a loose type. That's why it looks like a hack to me. Roman

At ICFP, Simon mentioned a willingness to revisit the placement of fail in
Monad for GHC, offering to defer to the core libraries committee on the
issue.
I'm somewhat loathe to do anything about this for 7.10, as I'd like to
focus on changes that can be made without requiring #ifdef's in user code
for the next major release, and just focus on making progress on things
that are near universally accepted to be good ideas, and which can be
"defended against" without CPP. e.g. finally bringing in Applicative as a
superclass of Monad.
That said, for say, 7.12 a well-reasoned proposal for what to do with fail
would have a very high likelihood of getting through! (for example, exiling
it to a MonadFail class or to the existing MonadPlus) Especially as if the
split-base proposal goes through for 7.12 a lot of breaking changes would
already be in the air.
-Edward
On Mon, Dec 16, 2013 at 9:17 AM, Malcolm Wallace
On 16 Dec 2013, at 13:12, Roman Cheplyaka wrote:
* Ivan Lazar Miljenovic
[2013-12-17 00:00:16+1100] On 16 December 2013 22:15, Roman Cheplyaka
wrote: * Herbert Valerio Riedel
[2013-12-16 10:53:21+0100] Why not simply use the existing `fail :: String -> IO a` method instead?
The purpose of 'fail' is to handle monadic pattern-match failures. I consider explicit use of 'fail' in user code a hack.
Or for use with parser-combinator libraries (though I suppose this could be seen as a pattern-match failure...)?
I'd consider that an abuse, too. E.g. Parsec provides a parserFail function that you can call instead.
I respectfully disagree. Whilst it was probably a mistake originally to include "fail" as a method of the Monad class, it has always been a useful additional method. Personally, I would have it in a separate class (called MonadFail, or similar). But wherever it lives, we would always have had it.
I see no good reason to distinguish between runtime pattern-match failure, and a direct user call of "fail". It is quite common to write parsers using pattern-matching, and why should one kind of backtracking be privileged over another? Their effects are of exactly the same kind.
e.g.
keyword = ( do "let" <- word -- fails if the string does not match b <- binding return (LET b) ) `onFail` ( do "case" <- word exp <- expression "of" <- word `onFail` fail "missing keyword 'of'" alts <- many1 alternative return (CASE exp alts) )
etc.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hi,
On Mon, Dec 16, 2013 at 6:53 PM, Herbert Valerio Riedel
Why not simply use the existing `fail :: String -> IO a` method instead?
The differences & similiarities I see wrt `fail`:
- `die` throws an `ExitCode` exception, whereas `fail` throws an `IOError` exception
- Both result in the message written to stderr and a non-zero exit code
One problem with 'fail' is that the error message is surrounded by "user error (" and ")". This is ok for debugging, but it can be confusing for the end user. Add System.Exit.die: +1 Re-export it from Prelude: +0 Takano Akio
participants (18)
-
Akio Takano
-
amindfv@gmail.com
-
Andreas Abel
-
David Luposchainsky
-
Edward Kmett
-
Evan Laforge
-
Ganesh Sittampalam
-
Henning Thielemann
-
Herbert Valerio Riedel
-
Ivan Lazar Miljenovic
-
Jason Dagit
-
John Lato
-
Malcolm Wallace
-
Niklas Hambüchen
-
Roman Cheplyaka
-
Simon Hengel
-
Stijn van Drongelen
-
Vo Minh Thu