Readline read_history and write_history addition

Hello all, I'd like to propose the addition of read_history and write_history bindings to the readline library. I believe I've followed the instructions on the Haskell wiki appropriately and I've set up a ticket (with a patch) at http://hackage.haskell.org/trac/ghc/ticket/2053. Essentially, the patch adds simple bindings so that Haskell programs can use Readline's read_history and write_history functions. This will be useful for the implementation of http://hackage.haskell.org/trac/ghc/ticket/2050 (add persistent history to GHCi) and potentially other applications. Thanks for your time and consideration. Alex

On Jan 18, 2008 11:10 PM, Alexander Dunlap
Hello all,
I'd like to propose the addition of read_history and write_history bindings to the readline library. I believe I've followed the instructions on the Haskell wiki appropriately and I've set up a ticket (with a patch) at http://hackage.haskell.org/trac/ghc/ticket/2053.
Essentially, the patch adds simple bindings so that Haskell programs can use Readline's read_history and write_history functions. This will be useful for the implementation of http://hackage.haskell.org/trac/ghc/ticket/2050 (add persistent history to GHCi) and potentially other applications.
Thanks for your time and consideration.
Alex
That patch looks good to me. While we're at it, can we also add the following related functions, which are used to control the maximum size of the history file? (They're also provided by editline.) void clear_history(void); void stifle_history(int); int unstifle_history(void); int history_is_stifled(void); Thanks, -Judah

I don't see why not. I've attached a patch to add bindings for all six
functions.
Alex
On Jan 19, 2008 11:09 AM, Judah Jacobson
On Jan 18, 2008 11:10 PM, Alexander Dunlap
wrote: Hello all,
I'd like to propose the addition of read_history and write_history bindings to the readline library. I believe I've followed the instructions on the Haskell wiki appropriately and I've set up a ticket (with a patch) at http://hackage.haskell.org/trac/ghc/ticket/2053.
Essentially, the patch adds simple bindings so that Haskell programs can use Readline's read_history and write_history functions. This will be useful for the implementation of http://hackage.haskell.org/trac/ghc/ticket/2050 (add persistent history to GHCi) and potentially other applications.
Thanks for your time and consideration.
Alex
That patch looks good to me. While we're at it, can we also add the following related functions, which are used to control the maximum size of the history file? (They're also provided by editline.)
void clear_history(void); void stifle_history(int); int unstifle_history(void); int history_is_stifled(void);
Thanks, -Judah

On Jan 19, 2008 11:09 AM, Judah Jacobson
wrote: On Jan 18, 2008 11:10 PM, Alexander Dunlap
wrote: Hello all,
I'd like to propose the addition of read_history and write_history bindings to the readline library. I believe I've followed the instructions on the Haskell wiki appropriately and I've set up a ticket (with a patch) at http://hackage.haskell.org/trac/ghc/ticket/2053.
Essentially, the patch adds simple bindings so that Haskell programs can use Readline's read_history and write_history functions. This will be useful for the implementation of http://hackage.haskell.org/trac/ghc/ticket/2050 (add persistent history to GHCi) and potentially other applications.
Thanks for your time and consideration.
Alex
That patch looks good to me. While we're at it, can we also add the following related functions, which are used to control the maximum size of the history file? (They're also provided by editline.)
void clear_history(void); void stifle_history(int); int unstifle_history(void); int history_is_stifled(void);
One more suggestion, from Robert Dockins (author of the Shellac and Shellac-readline packages):
The only concern I have is that this patch doesn't seem to be handling errors properly. read_history and write_history should return errno, but this binding has them returning (). These functions do file operations and therefore can fail; we want (be able) to know when that happens.
I think we should just throw an error if those functions return a nonzero value; for example, we already do that in the functions readInitFile and parseAndBind. Thanks, -Judah

On Monday 21 January 2008 01:27:35 pm Judah Jacobson wrote:
On Jan 19, 2008 11:09 AM, Judah Jacobson
wrote: On Jan 18, 2008 11:10 PM, Alexander Dunlap
wrote: Hello all,
I'd like to propose the addition of read_history and write_history bindings to the readline library. I believe I've followed the instructions on the Haskell wiki appropriately and I've set up a ticket (with a patch) at http://hackage.haskell.org/trac/ghc/ticket/2053.
Essentially, the patch adds simple bindings so that Haskell programs can use Readline's read_history and write_history functions. This will be useful for the implementation of http://hackage.haskell.org/trac/ghc/ticket/2050 (add persistent history to GHCi) and potentially other applications.
Thanks for your time and consideration.
Alex
That patch looks good to me. While we're at it, can we also add the following related functions, which are used to control the maximum size of the history file? (They're also provided by editline.)
void clear_history(void); void stifle_history(int); int unstifle_history(void); int history_is_stifled(void);
One more suggestion, from Robert Dockins (author of the Shellac and
Shellac-readline packages):
The only concern I have is that this patch doesn't seem to be handling errors properly. read_history and write_history should return errno, but this binding has them returning (). These functions do file operations and therefore can fail; we want (be able) to know when that happens.
I think we should just throw an error if those functions return a nonzero value; for example, we already do that in the functions readInitFile and parseAndBind.
Ha, I was just now composing an email to this effect. In addition, it would be nice for me if you could include: history_max_entries :: IO Int You can get this from readline by peeking this variable: foreign import ccall "readline/history.h &history_max_entries" history_max_entries :: Ptr CInt Then I could completely remove direct FFI bindings from my packages.
Thanks, -Judah

On Jan 21, 2008 10:27 AM, Judah Jacobson
On Jan 19, 2008 11:09 AM, Judah Jacobson
wrote: On Jan 18, 2008 11:10 PM, Alexander Dunlap
wrote: Hello all,
I'd like to propose the addition of read_history and write_history bindings to the readline library. I believe I've followed the instructions on the Haskell wiki appropriately and I've set up a ticket (with a patch) at http://hackage.haskell.org/trac/ghc/ticket/2053.
Essentially, the patch adds simple bindings so that Haskell programs can use Readline's read_history and write_history functions. This will be useful for the implementation of http://hackage.haskell.org/trac/ghc/ticket/2050 (add persistent history to GHCi) and potentially other applications.
Thanks for your time and consideration.
Alex
That patch looks good to me. While we're at it, can we also add the following related functions, which are used to control the maximum size of the history file? (They're also provided by editline.)
void clear_history(void); void stifle_history(int); int unstifle_history(void); int history_is_stifled(void);
One more suggestion, from Robert Dockins (author of the Shellac and Shellac-readline packages):
The only concern I have is that this patch doesn't seem to be handling errors properly. read_history and write_history should return errno, but this binding has them returning (). These functions do file operations and therefore can fail; we want (be able) to know when that happens.
I think we should just throw an error if those functions return a nonzero value; for example, we already do that in the functions readInitFile and parseAndBind.
Thanks, -Judah
I'm reluctant to use the throw an error solution because these functions failing does not have to be the end of the world (or even necessarily handled by the application). If the history file can't be found, the user just doesn't get their history restored (in fact, this may not even be a problem: if the user hasn't used the application before, readHistory will fail silently on the first run and then work fine after the history has been saved at the end of the first session). Similarly, writing or appending to the history file is generally not an essential task and can fail without terminating the program. (I know there's catch, but I don't think the programmer even has to worry about it that much.) I think that just returning a value for success and a value for failure would be appropriate. However, I'm not sure how we would implement it without using error. The usual Haskell solution would be to use Maybe, but what would we have Just of, since the functions don't return real values? Is Just () an accepted idiom? (I've never seen it, but I haven't seen all the Haskell there is to see, either.) Thanks. Alex

It seems to me that the proper solution would be to throw the proper exception for the errno, warning of such an exception clearly in the documentation. If the user of the library wants to swallow the exception themselves and continue with a catch or bracket statement, they should have that option, but they should also have the flexibility to handle exceptions in a particular way, should they need that functionality. There's no reason a library binding should conceal any potentially useful functionality of the underlying library. If the errors that were returned were unique, Either String Bool might be an option, but as we've got a built-in standard for handling precisely the sorts of IO errors that are returned, it seems silly not to use it. --S On Jan 21, 2008, at 11:34 PM, Alexander Dunlap wrote:
On Jan 21, 2008 10:27 AM, Judah Jacobson
wrote: One more suggestion, from Robert Dockins (author of the Shellac and Shellac-readline packages):
The only concern I have is that this patch doesn't seem to be handling errors properly. read_history and write_history should return errno, but this binding has them returning (). These functions do file operations and therefore can fail; we want (be able) to know when that happens.
I think we should just throw an error if those functions return a nonzero value; for example, we already do that in the functions readInitFile and parseAndBind.
Thanks, -Judah
I'm reluctant to use the throw an error solution because these functions failing does not have to be the end of the world (or even necessarily handled by the application). If the history file can't be found, the user just doesn't get their history restored (in fact, this may not even be a problem: if the user hasn't used the application before, readHistory will fail silently on the first run and then work fine after the history has been saved at the end of the first session). Similarly, writing or appending to the history file is generally not an essential task and can fail without terminating the program. (I know there's catch, but I don't think the programmer even has to worry about it that much.) I think that just returning a value for success and a value for failure would be appropriate.
However, I'm not sure how we would implement it without using error. The usual Haskell solution would be to use Maybe, but what would we have Just of, since the functions don't return real values? Is Just () an accepted idiom? (I've never seen it, but I haven't seen all the Haskell there is to see, either.)
Thanks. Alex _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Tuesday 22 January 2008 12:00:51 am Sterling Clover wrote:
It seems to me that the proper solution would be to throw the proper exception for the errno, warning of such an exception clearly in the documentation. If the user of the library wants to swallow the exception themselves and continue with a catch or bracket statement, they should have that option, but they should also have the flexibility to handle exceptions in a particular way, should they need that functionality. There's no reason a library binding should conceal any potentially useful functionality of the underlying library. If the errors that were returned were unique, Either String Bool might be an option, but as we've got a built-in standard for handling precisely the sorts of IO errors that are returned, it seems silly not to use it.
I agree. For reference, the way I have handled this myself up to now is: foreign import ccall "readline/history.h read_history" read_history :: CString -> IO Errno doReadHistory :: FilePath -> IO () doReadHistory path = do err <- withCString path read_history if err == eOK then return () else ioError $ errnoToIOError "System.Console.Shell.Backend.Readline.doReadHistory" err Nothing (Just path) I think it's a pretty good solution.
--S
On Jan 21, 2008, at 11:34 PM, Alexander Dunlap wrote:
On Jan 21, 2008 10:27 AM, Judah Jacobson
wrote:
One more suggestion, from Robert Dockins (author of the Shellac and
Shellac-readline packages):
The only concern I have is that this patch doesn't seem to be handling errors properly. read_history and write_history should return errno, but this binding has them returning (). These functions do file operations and therefore can fail; we want (be able) to know when that happens.
I think we should just throw an error if those functions return a nonzero value; for example, we already do that in the functions readInitFile and parseAndBind.
Thanks, -Judah
I'm reluctant to use the throw an error solution because these functions failing does not have to be the end of the world (or even necessarily handled by the application). If the history file can't be found, the user just doesn't get their history restored (in fact, this may not even be a problem: if the user hasn't used the application before, readHistory will fail silently on the first run and then work fine after the history has been saved at the end of the first session). Similarly, writing or appending to the history file is generally not an essential task and can fail without terminating the program. (I know there's catch, but I don't think the programmer even has to worry about it that much.) I think that just returning a value for success and a value for failure would be appropriate.
However, I'm not sure how we would implement it without using error. The usual Haskell solution would be to use Maybe, but what would we have Just of, since the functions don't return real values? Is Just () an accepted idiom? (I've never seen it, but I haven't seen all the Haskell there is to see, either.)
Thanks. Alex _______________________________________________ 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

Sterling Clover wrote:
...as we've got a built-in standard for handling precisely the sorts of IO errors that are returned, it seems silly not to use it.
IO exceptions wreak havoc on programs using any instance of MonadIO other than IO itself. At best, you need a major reorganization of your entire program. At worst, it can make it completely impossible to write a library. The built-in standard that you are referring to is fine for when something happens that makes it impossible for the program to continue - out of memory, hard disk failure, etc. But in cases where it is possible to return a meaningful value and continue, why be so disruptive? As Robert Dockins pointed out, it is very easy for those who prefer an IO exception to throw one themselves. The opposite can be difficult or impossible. Thanks, Yitz

On Mon, 21 Jan 2008, Alexander Dunlap wrote:
I'm reluctant to use the throw an error solution because these functions failing does not have to be the end of the world (or even necessarily handled by the application).
http://www.haskell.org/haskellwiki/Exception http://www.haskell.org/haskellwiki/Error

On Mon, Jan 21, 2008 at 08:34:50PM -0800, Alexander Dunlap wrote:
However, I'm not sure how we would implement it without using error. The usual Haskell solution would be to use Maybe, but what would we have Just of, since the functions don't return real values? Is Just () an accepted idiom?
Bool would be nicer than that, but presumably these functions can fail in a number of ways, so better still would be Maybe Exception or Maybe IOError. I think in my opinion throwing an exception is best, though. People using MonadIO can convert this into the variant that doesn't throw an exception by replacing readlineFunction args with something like (try $ readlineFunction args) >> return () Thanks Ian

Ian Lynagh wrote:
People using MonadIO can convert this into the variant that doesn't throw an exception by replacing readlineFunction args with something like (try $ readlineFunction args) >> return ()
That's in the IO monad, so not always available. Here's an example: In a library, you have a function that starts up an external system, runs a calculation, then shuts down the external system. Like this: bracketSystem :: MonadIO m => m a -> m a bracketSystem x = do startUpSystem ret <- x shutDownSystem return ret Now you would really like to wrap that in bracket to make sure that "shutDownSystem" is called even when an IO exception is thrown. But unfortunately, bracket is currently not available for MonadIO, nor is there any way to emulate it AFIK. (This is a "maybe" for HaskellPrime: http://hackage.haskell.org/trac/haskell-prime/ticket/110) So the best you can do is make sure not to do anything inside "x" that is likely to throw an IO exception. That way, you'll only be left with zombies and other mess when the hard disk fills up, or other rare and serious conditions. If we start throwing IO exceptions for common and minor occurrences like no readline history available, libraries like this become impossible to write in Haskell. And code that has already been written becomes unusable. Thanks, Yitz

On Wed, Jan 23, 2008 at 01:49:34AM +0200, Yitzchak Gale wrote:
Ian Lynagh wrote:
People using MonadIO can convert this into the variant that doesn't throw an exception by replacing readlineFunction args with something like (try $ readlineFunction args) >> return ()
That's in the IO monad, so not always available.
Everywhere you can write readlineFunction args you can write (try $ readlineFunction args) >> return () The only way you can have problems is if there is a library (that you don't control), which exports a (MonadIO m => m a) that internally calls readlineFunction args and doesn't catch exceptions. Personally I'd say that that is a bug in that other library, and it ought to be catching the exception and either ignoring it, returning some sort of sum type, or also constraining m to be in some sort of MonadError monad.
If we start throwing IO exceptions for common and minor occurrences like no readline history available
Pretty much any actual IO you do has this problem, e.g. readFile on a non-existent file. Thanks Ian

Ian Lynagh wrote:
The only way you can have problems is if there is a library (that you don't control), which exports a (MonadIO m => m a) that internally calls readlineFunction args and doesn't catch exceptions. Personally I'd say that that is a bug in that other library, and it ought to be catching the exception and either ignoring it, returning some sort of sum type, or also constraining m to be in some sort of MonadError monad.
Agreed. I think that in this situation our function should have a type that allows the type system to check that.
If we start throwing IO exceptions for common and minor occurrences like no readline history available
Pretty much any actual IO you do has this problem, e.g. readFile on a non-existent file.
Those are asynchronous phenomena. It is reasonable for some programs to ignore them completely, assuming that they are being taken care of on the outside, and allowing the program to fail when they are not. So an IO exception is appropriate. Regards, Yitz

On Wed, Jan 23, 2008 at 02:35:27PM +0200, Yitzchak Gale wrote:
Ian Lynagh wrote:
If we start throwing IO exceptions for common and minor occurrences like no readline history available
Pretty much any actual IO you do has this problem, e.g. readFile on a non-existent file.
Those are asynchronous phenomena.
I'm not sure what you mean by that? It's a synchronous exception. Thanks Ian

Those are asynchronous phenomena.
I'm not sure what you mean by that? It's a synchronous exception.
Sorry. I meant external. In the following sense: The semantics of the program explicitly involve it in a larger external system, in a way that it might make sense to allow exceptions to propagate out to the external system. With readline history, it is clear that we must handle all conditions internally, so this condition is not met. Since E1-3 are also not met, we should not throw IO exceptions. -Yitz

On Jan 23, 2008 5:19 AM, Yitzchak Gale
Those are asynchronous phenomena.
I'm not sure what you mean by that? It's a synchronous exception.
Sorry. I meant external. In the following sense:
The semantics of the program explicitly involve it in a larger external system, in a way that it might make sense to allow exceptions to propagate out to the external system.
With readline history, it is clear that we must handle all conditions internally, so this condition is not met. Since E1-3 are also not met, we should not throw IO exceptions.
-Yitz
The deadline for comments has passed and it seems like there isn't any opposition to adding this to the library. The only thing that remains is to make a decision on the exceptions vs. IO Bool thing. It seems like most are in favor of throwing an exception. For instances where an exception would be too intrusive, I don't see how it would be too hard to write a wrapper function that would have exactly the same monad requirements as the original function but return an IO Bool instead of an error, e.g.
tryReadHistory = catch readHistory (\e -> ...
So where do we go from here? Alex

Alexander Dunlap wrote:
For instances where an exception would be too intrusive, I don't see how it would be too hard to write a wrapper function
In a library that does not have direct access to the IO monad, it would be not just hard - it would be impossible. That is because of type restrictions in the current versions of catch, block, and friends. For example, if you are writing a library that exports something like: class MonadIO m => MyMonad m where... you can't block or catch exceptions, so you have to limit yourself as much as possible to operations that are unlikely to throw IO exceptions. Otherwise, you have to pass on responsibility to users of the library, which makes the library much less useful. That, in turn, would make the use of readline very awkward and complex - or in some cases even impossible - in programs based on monad transformers, one of the most beautiful and powerful idioms in Haskell. What a shame. (The other case is the one Ian mentioned, but as he points out, that could be considered a bug in the library.) On the other hand, it would never be too intrusive to write a wrapper providing an exception if that is really required. So that would be more general. The question becomes: given all of the other bindings in this readline library, is there any conceivable simple usage of readline that would usually not raise exceptions? If not, we should try to fix that. Otherwise, the situation is hopeless anyway, so then it would sadly not make any difference what we do with this particular binding. Regards, Yitz

On Sat, Feb 2, 2008 at 11:30 AM, Yitzchak Gale
Alexander Dunlap wrote:
For instances where an exception would be too intrusive, I don't see how it would be too hard to write a wrapper function
In a library that does not have direct access to the IO monad, it would be not just hard - it would be impossible. That is because of type restrictions in the current versions of catch, block, and friends.
You haven't said why something like the following would not be sufficient: readHistoryM :: MonadIO m => String -> m Bool readHistoryM file = liftIO $ do result <- try (readHistory file) return (result == Right ()) -Judah

Alexander Dunlap wrote:
For instances where an exception would be too intrusive, I don't see how it would be too hard to write a wrapper function
I wrote:
In a library that does not have direct access to the IO monad, it would be not just hard - it would be impossible. That is because of type restrictions in the current versions of catch, block, and friends.
Judah Jacobson wrote:
You haven't said why something like the following would not be sufficient:
readHistoryM :: MonadIO m => String -> m Bool readHistoryM file = liftIO $ do result <- try (readHistory file) return (result == Right ())
Because a library - other than readline itself - can't force its users to do that. OK. Here's a simplified real-world example. Say you want to write a simple library that interfaces the text-to-speech facilities available on multiple platforms. To play nicely with programs written in a monadic style, the interface might be something like: class MonadIO m => Speech m where sayText :: String -> m () runSpeech :: m a -> IO a instance Speech SomeSpeechSystem where sayText t = ... runSpeech x = do liftIO startSomeSpeechSystem ret <- x liftIO stopSomeSpeechSystem return ret Unfortunately, bracket is not available. So if x throws an uncaught IO exception, you may leave around zombies, database corruption, missiles armed for launch, etc. Well, if your speech system doesn't arm any missiles, you may consider it a reasonable risk to use this library in programs that could throw an IO exception on some rare error condition. But the proposal here is to raise the exception in a common situation that will definitely occur in regular usage. That may be fine in Java or Python, but it is a bad idea for IO exceptions in Haskell. Alexander Dunlap wrote:
So why couldn't you have a Utils.hs file that imports System.IO and provides the wrapper around readHistory? Then you can use the tryReadHistory function in your MonadIO-exporting module _exactly_ the same way as the original readHistory function.
You can. But if you are writing a library, your users might not. Regards, Yitz

On Sat, Feb 2, 2008 at 1:14 PM, Yitzchak Gale
Alexander Dunlap wrote:
For instances where an exception would be too intrusive, I don't see how it would be too hard to write a wrapper function
I wrote:
In a library that does not have direct access to the IO monad, it would be not just hard - it would be impossible. That is because of type restrictions in the current versions of catch, block, and friends.
Judah Jacobson wrote:
You haven't said why something like the following would not be sufficient:
readHistoryM :: MonadIO m => String -> m Bool readHistoryM file = liftIO $ do result <- try (readHistory file) return (result == Right ())
Because a library - other than readline itself - can't force its users to do that.
OK. Here's a simplified real-world example. Say you want to write a simple library that interfaces the text-to-speech facilities available on multiple platforms. To play nicely with programs written in a monadic style, the interface might be something like:
class MonadIO m => Speech m where sayText :: String -> m () runSpeech :: m a -> IO a
instance Speech SomeSpeechSystem where sayText t = ... runSpeech x = do liftIO startSomeSpeechSystem ret <- x liftIO stopSomeSpeechSystem return ret
Unfortunately, bracket is not available. So if x throws an uncaught IO exception, you may leave around zombies, database corruption, missiles armed for launch, etc.
I've already demonstrated how a library writer can solve that problem in: http://www.haskell.org/pipermail/libraries/2008-January/009034.html -Judah

Judah Jacobson wrote:
I've already demonstrated how a library writer can solve that problem in: http://www.haskell.org/pipermail/libraries/2008-January/009034.html
Yes, that is indeed very nice. But I don't think it is a practical solution right now. I'll explain why I think that under a different subject. Regards, Yitz

Yitzchak Gale wrote:
OK. Here's a simplified real-world example. Say you want to write a simple library that interfaces the text-to-speech facilities available on multiple platforms. To play nicely with programs written in a monadic style, the interface might be something like:
class MonadIO m => Speech m where sayText :: String -> m () runSpeech :: m a -> IO a
You meant ma -> m a here, right?
instance Speech SomeSpeechSystem where sayText t = ... runSpeech x = do liftIO startSomeSpeechSystem ret <- x liftIO stopSomeSpeechSystem return ret
I think MonadIO is the wrong type class here. For example, ListT IO is an instance of MonadIO, and may cause stopSomeSpeechSystem to be never called, or several times, per startSomeSpeechSytem call, which is clearly not what you wanted (this is still true for the 'ListT done right' versions of ListT). ContT should also be interesting.
But the proposal here is to raise the exception in a common situation that will definitely occur in regular usage. That may be fine in Java or Python, but it is a bad idea for IO exceptions in Haskell.
I agree with that though. regards, Bertram

Yitzchak Gale wrote:
Alexander Dunlap wrote:
For instances where an exception would be too intrusive, I don't see how it would be too hard to write a wrapper function
I wrote:
In a library that does not have direct access to the IO monad, it would be not just hard - it would be impossible. That is because of type restrictions in the current versions of catch, block, and friends.
Judah Jacobson wrote:
You haven't said why something like the following would not be sufficient:
readHistoryM :: MonadIO m => String -> m Bool readHistoryM file = liftIO $ do result <- try (readHistory file) return (result == Right ())
Because a library - other than readline itself - can't force its users to do that.
OK. Here's a simplified real-world example. Say you want to write a simple library that interfaces the text-to-speech facilities available on multiple platforms. To play nicely with programs written in a monadic style, the interface might be something like:
class MonadIO m => Speech m where sayText :: String -> m () runSpeech :: m a -> IO a
Here's my (slightly provocative) take on this: a MonadIO instance is not a complete wrapper around the IO monad, because it doesn't provide catch. It is not the responsibility of a library that provides IO functions to account for defficient wrappers of IO with no way to catch exceptions. The problem is in the IO wrapper, not the library that throws exceptions. However, I do agree that exceptions should generally be used for exceptional conditions, rather than for general control-flow. This is an example of a *good* reason to avoid an exception: because to use an exception for a non-exceptional condition is poor style. Avoiding exceptions because MonadIO has trouble with them is not a good enough reason, IMO. We should fix MonadIO instead. Cheers, Simon

Simon Marlow wrote:
Here's my (slightly provocative) take on this: a MonadIO instance is not a complete wrapper around the IO monad, because it doesn't provide catch.
That's true.
It is not the responsibility of a library that provides IO functions to account for defficient wrappers of IO with no way to catch exceptions. The problem is in the IO wrapper, not the library that throws exceptions.
Makes sense.
However, I do agree that exceptions should generally be used for exceptional conditions, rather than for general control-flow. This is an example of a *good* reason to avoid an exception: because to use an exception for a non-exceptional condition is poor style.
That is also my opinion. Some people have disagreed. So this should be the focus of the decision then. Thanks, Yitz

On Mon, Feb 4, 2008 at 6:06 AM, Yitzchak Gale
Simon Marlow wrote:
However, I do agree that exceptions should generally be used for exceptional conditions, rather than for general control-flow. This is an example of a *good* reason to avoid an exception: because to use an exception for a non-exceptional condition is poor style.
That is also my opinion. Some people have disagreed. So this should be the focus of the decision then.
I also agree that exceptions should only be used for exceptional conditions; but I do think that this is one of those situations. I'll try to explain why below. (Thanks, Yitzchak, for forking off the thread about fixing limitations of MonadIO.) I assume that the following conditions are already considered exceptional (I haven't ever heard anyone complain that they throw an exception): - readFile : read a nonexistent file - writeFile : write to a file in a nonexistent directory - getEnv: retrieve an unset environmental variable - System.Console.Readline.readInitFile: read a nonexistent .inputrc file I think of readHistory and writeHistory as analogues to the above functions. So calling writeHistory when the directory doesn't exist should produce an exception. And if you call readHistory, either check first that the file exists, or else expect that an exception will sometimes be thrown (just as is already the case for readFile). Packages like shellac-readline can wrap the two steps of "only readHistory if file exists" in a higher-level abstraction; but System.Console.Readline itself should just be a thin binding to the readline APIs. All that being said, this is a relatively minor issue, so if many people are strongly opposed to throwing an exception even after what I've said above, I'll accept the consensus decision. Barring that, however, I'm in favor of the interface already used by other, similar functions in the libraries. Thanks, -Judah

Judah Jacobson wrote:
On Mon, Feb 4, 2008 at 6:06 AM, Yitzchak Gale
wrote: Simon Marlow wrote:
However, I do agree that exceptions should generally be used for exceptional conditions, rather than for general control-flow. This is an example of a *good* reason to avoid an exception: because to use an exception for a non-exceptional condition is poor style.
That is also my opinion. Some people have disagreed. So this should be the focus of the decision then.
I also agree that exceptions should only be used for exceptional conditions; but I do think that this is one of those situations. I'll try to explain why below. (Thanks, Yitzchak, for forking off the thread about fixing limitations of MonadIO.)
I assume that the following conditions are already considered exceptional (I haven't ever heard anyone complain that they throw an exception): - readFile : read a nonexistent file - writeFile : write to a file in a nonexistent directory - getEnv: retrieve an unset environmental variable
FWIW, this was hotly debated at the time, and I do believe we made the wrong decision w.r.t. getEnv, mainly because I always end up writing "try $ getEnv", or I forget the try and have to fix the bug later. Cheers, Simon

Judah Jacobson wrote:
- readFile... writeFile... I think of readHistory and writeHistory as analogues to the above functions.
I don't think so. I don't really care about the file itself - that just happens to be the way readline implements its persistence. Non-existence of the file is the normal way that readline represents the fact that there isn't any history yet. The semantics of the API call are: load history, if any exists yet, and report the result. Nothing exceptional about that.
All that being said, this is a relatively minor issue
Agreed. All the more so with the MonadIO problem now factored out. Regards, Yitz

Hi all,
Discussion over this issue has died down. Yitzchak and others have
made good arguments for the type signatures
readHistory :: String -> IO Bool
writeHistory :: String -> IO Bool
which reflect the non-exceptional nature of failure of those functions.
Does anyone have any problems with implementing the following patch
from Alex (along with the above change)?
http://www.haskell.org/pipermail/libraries/2008-January/009007.html
For reference, this is in relation to the following proposal:
http://hackage.haskell.org/trac/ghc/ticket/2053
If no objections are raised by next week (say, Feb. 27), we should
make the above changes to readline, which will let us implement #2050
(persistent history file in ghci).
Thanks,
-Judah
On Wed, Feb 6, 2008 at 1:09 PM, Yitzchak Gale
Judah Jacobson wrote:
- readFile... writeFile...
I think of readHistory and writeHistory as analogues to the above functions.
I don't think so. I don't really care about the file itself - that just happens to be the way readline implements its persistence. Non-existence of the file is the normal way that readline represents the fact that there isn't any history yet. The semantics of the API call are: load history, if any exists yet, and report the result. Nothing exceptional about that.
All that being said, this is a relatively minor issue
Agreed. All the more so with the MonadIO problem now factored out.
Regards, Yitz

On Jan 22, 2008 3:49 PM, Yitzchak Gale
In a library, you have a function that starts up an external system, runs a calculation, then shuts down the external system. Like this:
bracketSystem :: MonadIO m => m a -> m a bracketSystem x = do startUpSystem ret <- x shutDownSystem return ret
Now you would really like to wrap that in bracket to make sure that "shutDownSystem" is called even when an IO exception is thrown. But unfortunately, bracket is currently not available for MonadIO, nor is there any way to emulate it AFIK. (This is a "maybe" for HaskellPrime: http://hackage.haskell.org/trac/haskell-prime/ticket/110)
Following is what I've been using to solve that problem. I can add it to that HaskellPrime ticket if people think it's useful. ============== module IO1 where import Control.Monad.State import Control.Monad.Error import Control.Exception import System.IO class MonadIO m => MonadIO1 m where liftIO1 :: (forall b . IO b -> IO b) -> m a -> m a instance MonadIO1 IO where liftIO1 = id instance MonadIO1 m => MonadIO1 (StateT s m) where liftIO1 f = mapStateT (liftIO1 f) instance (Error e, MonadIO1 m) => MonadIO1 (ErrorT e m) where liftIO1 f = mapErrorT (liftIO1 f) -- and so on for ReaderT, ListT, etc. block1, unblock1 :: MonadIO1 m => m a -> m a block1 = liftIO1 block unblock1 = liftIO1 unblock bracket1 :: MonadIO1 m => m a -> (a -> IO b) -> (a -> m c) -> m c bracket1 before after thing = block1 $ do a <- before r <- liftIO1 (handle (\e -> do {after a; throw e})) (unblock1 (thing a)) liftIO (after a) return r -- example: bracket file operations in an arbitrary monad withFile1 :: MonadIO1 m => FilePath -> IOMode -> (Handle -> m a) -> m a withFile1 name mode = bracket1 (liftIO (openFile name mode)) hClose ============== Note that in bracket1, the "after" action must run in IO. In practice, that hasn't been a problem for me. In fact, since the "after" clause might run in response to an asynchronous exception, I don't see how it could be sequenced with an arbitrary monad, anyway. Best wishes, -Judah

On Wed, 23 Jan 2008, Yitzchak Gale wrote:
If we start throwing IO exceptions for common and minor occurrences like no readline history available, libraries like this become impossible to write in Haskell. And code that has already been written becomes unusable.
It seems that this discussion has no longer to do with readline but with correct exception handling in Haskell. Did someone follow my links to the Haskell wiki articles Error and Exception? Haskell libraries mix these terms in an unfortunate way. Events like "no history available" are precisely the things that are called "exceptions" (not errors) - situations that cannot be avoided by the programmer but must be handled. An approved method to handle these cases are 'try' constructs. Now if 'bracket' does not work for general MonadIO then it should be generalized.

Henning Thielemann wrote:
http://www.haskell.org/haskellwiki/Exception http://www.haskell.org/haskellwiki/Error
The exact usage of the terms "error" and "exception" varies between programming languages. Your descriptions on the wiki follow Java usage, where Error and Exception are separate subclasses of Throwable. In Python, "exception" means the program flow construct, and "error" means a condition in which an exception is raised due to something going "wrong", so StandardError is a subclass of Exception. There are other conventions. In Haskell, the usage is, let's just say, unusual. :) Perhaps some technolinguist will have a good time studying it some day. I wrote:
If we start throwing IO exceptions for common and minor occurrences like no readline history available, libraries like this become impossible to write in Haskell. And code that has already been written becomes unusable.
...situations that cannot be avoided by the programmer but must be handled. An approved method to handle these cases are 'try' constructs.
Approved? The question is: when is it appropriate to use this technique in Haskell? Every function that can return more than one possible value has "situations that must be handled", but usually we will not throw exceptions.
Now if 'bracket' does not work for general MonadIO then it should be generalized.
'bracket', 'try', and 'catch' do need to be generalized. Realistically, that will not happen for a long time, if ever. The reality is that Haskell's IO exception facilities have some rough edges. They work great for asynchronous errors, which is what they were designed for. In general, whether or not IO exceptions are appropriate in Haskell is heavily dependent upon programming style. The only situation in which they are certainly called for is an asynchronous error. Perhaps also a non-error that satisfies all of the following conditions: E1) The function is strongly in the IO monad. E2) The condition is rare. E3) Sometimes the correct action would be to exit the program with an error message. In any other case, throwing an IO exception is an abuse that might ruin someone's program. If an IO exception is appropriate for the style of a particular program, it is easy for that program to provide one. When writing Haskell bindings for a library written in an imperative language, there is always a tension between providing a more idiomatic Haskell interface and faithfully reproducing the calling semantics of the library. When a C function returns an int to indicate various possible outcomes, that doesn't necessarily mean that it must throw an IO exception in Haskell, even if the author called the int an "error code". E2 and E3 do not hold for in the case of readline history - if were to throw an IO exception in the case of empty history, it would be obligatory for every program using it to wrap the function in a try. There is no way to express that in Haskell; you would have to write that requirement in a comment. That itself is evidence that the semantics of this language construct have been abused. (As contrasted with Java, for example, where ignoring the possible exception would cause the program to be rejected.) Regards, Yitz

On Wed, 23 Jan 2008, Yitzchak Gale wrote:
Henning Thielemann wrote:
http://www.haskell.org/haskellwiki/Exception http://www.haskell.org/haskellwiki/Error
The exact usage of the terms "error" and "exception" varies between programming languages. Your descriptions on the wiki follow Java usage, where Error and Exception are separate subclasses of Throwable.
It's also terminology of Modula-3, from where Java inherits its exception mechanism. And probably its the same terminology in the ancestors of Modula-3.
In Haskell, the usage is, let's just say, unusual. :) Perhaps some technolinguist will have a good time studying it some day.
It would be good if Haskell libraries would separate the two issues, with whatever wording.
I wrote:
If we start throwing IO exceptions for common and minor occurrences like no readline history available, libraries like this become impossible to write in Haskell. And code that has already been written becomes unusable.
...situations that cannot be avoided by the programmer but must be handled. An approved method to handle these cases are 'try' constructs.
Approved? The question is: when is it appropriate to use this technique in Haskell? Every function that can return more than one possible value has "situations that must be handled", but usually we will not throw exceptions.
You know, in Haskell we do not need a built-in exception handling facility because we can handle it with the elements of the language. Returning an exceptional value or throwing an exception is the same. We can only hide the exception propagation by appropriate binding of actions.
Now if 'bracket' does not work for general MonadIO then it should be generalized.
'bracket', 'try', and 'catch' do need to be generalized. Realistically, that will not happen for a long time, if ever.
Why not? We could design standard IO functions with improved API, with exceptions explicitly declared in the type. (One could also get rid of 'hFunction' names and use module name qualification instead.) In the future, when it becomes more usual to install a custom set of packages from Hackage instead of installing a large set of base libraries, people can more easily decide to use this library instead of System.IO. I think ByteString was long awaited and thus was adopted quickly by many programmers. I hope this happens for other solutions, too.
The reality is that Haskell's IO exception facilities have some rough edges.
I remember that I read somewhere that the Haskell veterans regret to having put so much things into IO, whenever they didn't know where to place them correctly. Exceptions are one such thing. Manipulating array in-place is another example. Putting 'fail' method into the Monad class is also acknowledged as a misconception today, and (I hope) most people agree, that there should be a separate class MonadError. Solutions already exist. STArray monad and runST can replace IOArray and unsafePerformIO in a safe way. Control.Monad.Error (which should be called Control.Monad.Exception with a distinct type for exceptions instead of Either) with ErrorT already allows to express in a type safe way what exceptions an action can throw. Maybe one day we succeed keeping exceptions completely out of IO and have them implemented by ErrorT/ExceptionT.

Hi Henning, I am going to make an "exception" here to my usual policy of not top-posting. Because I agree with everything you wrote. :) -Yitz On Jan 23, 2008 1:14 PM, Henning Thielemann wrote:
On Wed, 23 Jan 2008, Yitzchak Gale wrote:
Henning Thielemann wrote:
http://www.haskell.org/haskellwiki/Exception http://www.haskell.org/haskellwiki/Error
The exact usage of the terms "error" and "exception" varies between programming languages. Your descriptions on the wiki follow Java usage, where Error and Exception are separate subclasses of Throwable.
It's also terminology of Modula-3, from where Java inherits its exception mechanism. And probably its the same terminology in the ancestors of Modula-3.
In Haskell, the usage is, let's just say, unusual. :) Perhaps some technolinguist will have a good time studying it some day.
It would be good if Haskell libraries would separate the two issues, with whatever wording.
I wrote:
If we start throwing IO exceptions for common and minor occurrences like no readline history available, libraries like this become impossible to write in Haskell. And code that has already been written becomes unusable.
...situations that cannot be avoided by the programmer but must be handled. An approved method to handle these cases are 'try' constructs.
Approved? The question is: when is it appropriate to use this technique in Haskell? Every function that can return more than one possible value has "situations that must be handled", but usually we will not throw exceptions.
You know, in Haskell we do not need a built-in exception handling facility because we can handle it with the elements of the language. Returning an exceptional value or throwing an exception is the same. We can only hide the exception propagation by appropriate binding of actions.
Now if 'bracket' does not work for general MonadIO then it should be generalized.
'bracket', 'try', and 'catch' do need to be generalized. Realistically, that will not happen for a long time, if ever.
Why not? We could design standard IO functions with improved API, with exceptions explicitly declared in the type. (One could also get rid of 'hFunction' names and use module name qualification instead.) In the future, when it becomes more usual to install a custom set of packages from Hackage instead of installing a large set of base libraries, people can more easily decide to use this library instead of System.IO. I think ByteString was long awaited and thus was adopted quickly by many programmers. I hope this happens for other solutions, too.
The reality is that Haskell's IO exception facilities have some rough edges.
I remember that I read somewhere that the Haskell veterans regret to having put so much things into IO, whenever they didn't know where to place them correctly. Exceptions are one such thing. Manipulating array in-place is another example. Putting 'fail' method into the Monad class is also acknowledged as a misconception today, and (I hope) most people agree, that there should be a separate class MonadError. Solutions already exist. STArray monad and runST can replace IOArray and unsafePerformIO in a safe way. Control.Monad.Error (which should be called Control.Monad.Exception with a distinct type for exceptions instead of Either) with ErrorT already allows to express in a type safe way what exceptions an action can throw. Maybe one day we succeed keeping exceptions completely out of IO and have them implemented by ErrorT/ExceptionT.

Henning Thielemann wrote:
You know, in Haskell we do not need a built-in exception handling facility because we can handle it with the elements of the language. Returning an exceptional value or throwing an exception is the same. We can only hide the exception propagation by appropriate binding of actions.
I don't consider exceptions in the IO monad to be a "built-in" concept. This is because, if we wanted to, we could implement IO exceptions purely in Haskell on top of a primitive IO monad without exceptions (indeed, that's what Hugs and other systems do, and what GHC did in the past). If you are implementing a Haskell system, you don't need to provide any primitive functionality to support exceptions, it can all be done in the implementation of the IO monad. Exceptions are no more built-in than the Either type. In practice, you might want to implement exceptions at a lower level for performance reasons, which is what GHC does. Cheers, Simon

"Yitzchak Gale"
The exact usage of the terms "error" and "exception" varies between programming languages. Your descriptions on the wiki follow Java usage, where Error and Exception are separate subclasses of Throwable. In Python, "exception" means the program flow construct, and "error" means a condition in which an exception is raised due to something going "wrong", so StandardError is a subclass of Exception. There are other conventions.
To me, (what you describe as) the Python terminology seems to be the least confusing. E.g., dividing by zero and failed pattern matches are (run-time!) errors, which raise exceptions. I wouldn't say (like the wiki) that an uncaught exception is an error.
E1) The function is strongly in the IO monad. E2) The condition is rare. E3) Sometimes the correct action would be to exit the program with an error message.
I like these criteria. I'd even suggest replacing "Sometimes" with "Commonly" in E3. And add that there should be no obvious, general way to deal with the error (but then there probably wouldn't be an error in the first place).
E2 and E3 do not hold for in the case of readline history - if were to throw an IO exception in the case of empty history, it would be obligatory for every program using it to wrap the function in a try.
I don't know readline, but it looks like a clear candidate for (Maybe History). -k -- If I haven't seen further, it is by standing in the footprints of giants

I wrote:
unfortunately, bracket is currently not available for MonadIO, nor is there any way to emulate it AFIK. (This is a "maybe" for HaskellPrime: http://hackage.haskell.org/trac/haskell-prime/ticket/110)
Judah Jacobson wrote:
Following is what I've been using to solve that problem. I can add it to that HaskellPrime ticket if people think it's useful.
Very nice! I think you should not only add it to the ticket (if that is still relevant, I am not sure what is going on with Haskell' right now), but you should also submit a patch for the mtl library. We need a better name than IO1, though.
Note that in bracket1, the "after" action must run in IO. In practice, that hasn't been a problem for me. In fact, since the "after" clause might run in response to an asynchronous exception, I don't see how it could be sequenced with an arbitrary monad, anyway.
Agreed. The real fix would be to provide a lower-level primitive for block and unblock. The concurrency paper "Asynchronous exceptions in Haskell" states (sec. 4.2) that the reason for the type block :: IO a -> IO a rather than the more obvious block :: IO () is clumsiness and fragility. That may be so. But that type is too high-level for a primitive. In GHC, the implementation of block is: block (IO io) = IO $ blockAsyncExceptions# io It should really be: block x = do IO blockAsyncExceptions# ret <- x IO unblockAsyncExceptions# return ret in which case we could then supply implementations for other monads as well. Regards, Yitz

Yitzchak Gale wrote:
The real fix would be to provide a lower-level primitive for block and unblock. The concurrency paper "Asynchronous exceptions in Haskell" states (sec. 4.2) that the reason for the type
block :: IO a -> IO a
rather than the more obvious
block :: IO ()
is clumsiness and fragility. That may be so. But that type is too high-level for a primitive. In GHC, the implementation of block is:
block (IO io) = IO $ blockAsyncExceptions# io
It should really be:
block x = do IO blockAsyncExceptions# ret <- x IO unblockAsyncExceptions# return ret
in which case we could then supply implementations for other monads as well.
blockAsyncExceptions# has some tricks to restore tail-recursion in some cases (see the paper). But apart from losing that optimisation, I can't think of any reasons why the above couldn't work - one thing you have to worry about is what happens when x raises an exeption, but I think that is handled by the way we save and restore the blocked state in catch. Cheers, Simon

It should really be:
block x = do IO blockAsyncExceptions# ret <- x IO unblockAsyncExceptions# return ret
in which case we could then supply implementations for other monads as well.
blockAsyncExceptions# has some tricks to restore tail-recursion in some cases (see the paper). But apart from losing that optimisation, I can't think of any reasons why the above couldn't work - one thing you have to worry about is what happens when x raises an exeption, but I think that is handled by the way we save and restore the blocked state in catch.
what about if the monad is a transformed one with its own error handling methods (e.g. ErrorT IO) and so (IO blockAsyncExceptions#) is run but (IO unblockAsyncExceptions#) is not? Is that a problem? ~Isaac

Isaac Dupree wrote:
It should really be:
block x = do IO blockAsyncExceptions# ret <- x IO unblockAsyncExceptions# return ret
in which case we could then supply implementations for other monads as well.
blockAsyncExceptions# has some tricks to restore tail-recursion in some cases (see the paper). But apart from losing that optimisation, I can't think of any reasons why the above couldn't work - one thing you have to worry about is what happens when x raises an exeption, but I think that is handled by the way we save and restore the blocked state in catch.
what about if the monad is a transformed one with its own error handling methods (e.g. ErrorT IO) and so (IO blockAsyncExceptions#) is run but (IO unblockAsyncExceptions#) is not? Is that a problem?
Yes, in that case you'd need an exception handler in the above code to ensure that unblockAsyncExceptions# was called. Cheers, Simon
participants (11)
-
Alexander Dunlap
-
Bertram Felgenhauer
-
Henning Thielemann
-
Ian Lynagh
-
Isaac Dupree
-
Judah Jacobson
-
Ketil Malde
-
Robert Dockins
-
Simon Marlow
-
Sterling Clover
-
Yitzchak Gale