Proposal: Add Text.Read.maybeRead :: Read a => String -> Maybe a

This function is typically defined once per project. So its about time this safe variant of 'read' made it into the base. maybeRead :: Read a => String -> Maybe a maybeRead s = case reads s of [(x, "")] -> Just x _ -> Nothing Consideration period: 1 week. Patch to Text.Read attached.

On Thu, 7 Feb 2008, Don Stewart wrote:
This function is typically defined once per project. So its about time this safe variant of 'read' made it into the base.
maybeRead :: Read a => String -> Maybe a maybeRead s = case reads s of [(x, "")] -> Just x _ -> Nothing
Consideration period: 1 week.
Patch to Text.Read attached.
Seems to be useful. May prevent people from using just 'read' while hoping that parsing will always succeed.

Hello, Why not allow an arbitrary monad? readM :: (Monad m, Read a) => String -> String -> m a readM errMsg s = case reads s of [(x, "")] -> return x _ -> fail errMsg -Jeff libraries-bounces@haskell.org wrote on 02/07/2008 01:46:48 PM:
This function is typically defined once per project. So its about time this safe variant of 'read' made it into the base.
maybeRead :: Read a => String -> Maybe a maybeRead s = case reads s of [(x, "")] -> Just x _ -> Nothing
Consideration period: 1 week.
Patch to Text.Read attached.
[attachment "maybeRead.patch" deleted by Jeff Polakow/db/dbcom] _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
--- This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden.

Hello,
I don't think that the function should be in an arbitrary monad
because not all monads support failure, and the purpose of using this
function is to take an action when a parse error occurs (if parse
errors were not an issue, then we could just use 'read' instead). If
we really wanted to generalize the function, then we should use the
'MonadPlus' (or 'Alternative') classes to restrict the result to types
that have meaningful "default" values. Having said this, I have used
this function on many occasions, and the Maybe type has always been
sufficient, so my preference would be to keep the original type that
was proposed by Don.
-Iavor
2008/2/7 Jeff Polakow
Hello,
Why not allow an arbitrary monad?
readM :: (Monad m, Read a) => String -> String -> m a readM errMsg s = case reads s of [(x, "")] -> return x _ -> fail errMsg
-Jeff
libraries-bounces@haskell.org wrote on 02/07/2008 01:46:48 PM:
This function is typically defined once per project. So its about time this safe variant of 'read' made it into the base.
maybeRead :: Read a => String -> Maybe a maybeRead s = case reads s of [(x, "")] -> Just x _ -> Nothing
Consideration period: 1 week.
Patch to Text.Read attached.
[attachment "maybeRead.patch" deleted by Jeff Polakow/db/dbcom]
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
---
This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Thu, 7 Feb 2008, Iavor Diatchki wrote:
Hello, I don't think that the function should be in an arbitrary monad because not all monads support failure, and the purpose of using this function is to take an action when a parse error occurs
I'm for the fixed Maybe type. I also think that 'maybeRead' is better than 'readMaybe' since the latter one suggests that it is about reading a value of type 'Maybe'. (Though you can also argue the opposite way.)

Hello. I like the functionality, but I generally don't like type information in a name. Isn't there a way to express this with the module system or the type system. Best regards, Johannes.

On Feb 8, 2008 9:05 AM, Johannes Waldmann
Hello. I like the functionality, but I generally don't like type information in a name. Isn't there a way to express this with the module system or the type system. Best regards, Johannes.
I have to agree here. We should try to make more use of the module system and qualified imports. All this type information in function names is distracting. And no fail please. -- Johan

On Thu, Feb 07, 2008 at 03:20:31PM -0500, Jeff Polakow wrote:
Why not allow an arbitrary monad?
readM :: (Monad m, Read a) => String -> String -> m a readM errMsg s = case reads s of [(x, "")] -> return x _ -> fail errMsg
Yes. I strongly support this, this routine has been in my GenUtil for a long time as is hella useful. Though, I wouldn't give it an error message argument and just let it have something descriptive like "readM: no parse" as in my other reply. John -- John Meacham - ⑆repetae.net⑆john⑈

readM for an arbitrary monad with a standard error message++. not necessarily because I believe this is the right or even the one true way to do this per se., but rather because this is how Data.Map etc. handle failure on lookups, etc. Given that read apparently trims trailing whitespace, I also approve of adding that to this function. My argument here is that uniform and expected behavior should be a stronger goal of libraries than the ugly rails notion of "configuration by convention." As such, generalizing to an arbitrary monad is more uniform and common than simply using a Maybe instance (and provides a strict superset of functionality to boot). Furthermore, I agree with the dislike of fail, and agree that it should be moved to MonadFail or MonadZero or such. However, I also think that even if this were to happen in a major revamp (Haskell' or whatever) that it would be more appropriate to have a generalized readM than not. in fact, as a whole, there's really no reason the libraries should err on the size of giving less generality rather than more. --Sterl. p.s. Actually, the fact that read doesn't act like readM by default strikes me as a bug, but not one that can reasonably be resolved with the libraries as they stand. As the general sentiment seems to go, total base libraries ftw. The more direct the path for haskell newcomers to come over the benefits of strong type-safety in all instances, the better. On Feb 7, 2008, at 10:52 PM, John Meacham wrote:
On Thu, Feb 07, 2008 at 03:20:31PM -0500, Jeff Polakow wrote:
Why not allow an arbitrary monad?
readM :: (Monad m, Read a) => String -> String -> m a readM errMsg s = case reads s of [(x, "")] -> return x _ -> fail errMsg
Yes. I strongly support this, this routine has been in my GenUtil for a long time as is hella useful. Though, I wouldn't give it an error message argument and just let it have something descriptive like "readM: no parse" as in my other reply.
John
-- John Meacham - ⑆repetae.net⑆john⑈ _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hi Don:
This function is typically defined once per project. So its about time this safe variant of 'read' made it into the base.
maybeRead :: Read a => String -> Maybe a maybeRead s = case reads s of [(x, "")] -> Just x _ -> Nothing
Jeff:
Why not allow an arbitrary monad?
readM :: (Monad m, Read a) => String -> String -> m a readM errMsg s = case reads s of [(x, "")] -> return x _ -> fail errMsg
My instinct here is to follow James McKinna's observation (which give rise to views in Epigram): you don't need to produce elements of an *arbitrary* whatever-it-is when you can produce elements of the *initial* whatever-it-is. It makes the construction a bit easier to implement, because you're working at a concrete type, but no harder to use. I'd suggest going with the Maybe version, but then add the relevant initiality principles for Maybe (if they're not already there). This thing mayA :: Alternative a => Maybe x -> a x mayA (Just x) = pure x mayA Nothing = empty is a useful little piece of glue, and it has a few friends which might also help, including, for the moment, mayM :: Monadplus m => Maybe x -> m x mayM (Just x) = return x mayM Nothing = mzero and (oh all right then) mayhem :: Monad m => Maybe x -> m x mayhem (Just x) = return x mayhem Nothing = fail "I told you so!" These things are common factors in quite a lot of unnecessarily abstract operations. I suggest factoring out the final appeals to initiality, keeping the actual machinery simple and specific. All the best Conor

Because the fail method is an abomination that should never have been
included in the Monad class.
2008/2/7 Jeff Polakow
Hello,
Why not allow an arbitrary monad?
readM :: (Monad m, Read a) => String -> String -> m a readM errMsg s = case reads s of [(x, "")] -> return x _ -> fail errMsg
-Jeff
libraries-bounces@haskell.org wrote on 02/07/2008 01:46:48 PM:
This function is typically defined once per project. So its about time this safe variant of 'read' made it into the base.
maybeRead :: Read a => String -> Maybe a maybeRead s = case reads s of [(x, "")] -> Just x _ -> Nothing
Consideration period: 1 week.
Patch to Text.Read attached.
[attachment "maybeRead.patch" deleted by Jeff Polakow/db/dbcom] _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
---
This e-mail may contain confidential and/or privileged information. If you
are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hi
This function is typically defined once per project. So its about time this safe variant of 'read' made it into the base.
It's also in the Safe library as readMay: http://www-users.cs.york.ac.uk/~ndm/safe/ and has been useful. Not 100% certain that maybe read is the right name as opposed to readMaybe - given read/reads both have a read prefix. (+0.7) agreement. Thanks Neil

On Thu, Feb 07, 2008 at 10:46:48AM -0800, Don Stewart wrote:
This function is typically defined once per project. So its about time this safe variant of 'read' made it into the base.
maybeRead :: Read a => String -> Maybe a maybeRead s = case reads s of [(x, "")] -> Just x _ -> Nothing
I think this is a good idea, though I normally write the equivalent of maybeRead :: Read a => String -> Maybe a maybeRead s = case reads s of [(x, rest)] | all isSpace rest -> Just x _ -> Nothing and would prefer not to generalize it to any monad. fail is a wart, not a design pattern.
Consideration period: 1 week.
I think that's too short, and the recent fashion of 2 weeks is too short, even for an uncontroversial change. Some people aren't here continuously, but I'd still like to get their input.

On Feb 7, 2008 6:12 PM, Ross Paterson
I think this is a good idea, though I normally write the equivalent of
maybeRead :: Read a => String -> Maybe a maybeRead s = case reads s of [(x, rest)] | all isSpace rest -> Just x _ -> Nothing
and would prefer not to generalize it to any monad. fail is a wart, not a design pattern.
I also prefer Maybe to fail. Error strings are only useful if you're
ignoring them or passing them to the user without interpretation.
--
Dave Menendez

On Fri, Feb 08, 2008 at 12:17:31AM -0500, David Menendez wrote:
On Feb 7, 2008 6:12 PM, Ross Paterson
wrote: I think this is a good idea, though I normally write the equivalent of
maybeRead :: Read a => String -> Maybe a maybeRead s = case reads s of [(x, rest)] | all isSpace rest -> Just x _ -> Nothing
and would prefer not to generalize it to any monad. fail is a wart, not a design pattern.
I also prefer Maybe to fail. Error strings are only useful if you're ignoring them or passing them to the user without interpretation.
say that next time you get a mysterious "fromJust: Nothing" error with no context, error messages in haskell are quite an issue as is, _any_ useful information is good, passing them on to the user without interpretation is loads better than not having any clue what went wrong. It is what you want to do because the fact that it was a 'readM' that failed is extremely useful for figuring out what went wrong. It is a straightforward generalization that is very useful pragmatically. John -- John Meacham - ⑆repetae.net⑆john⑈

On Fri, 8 Feb 2008, John Meacham wrote:
On Fri, Feb 08, 2008 at 12:17:31AM -0500, David Menendez wrote:
I also prefer Maybe to fail. Error strings are only useful if you're ignoring them or passing them to the user without interpretation.
say that next time you get a mysterious "fromJust: Nothing" error with no context, error messages in haskell are quite an issue as is, _any_ useful information is good, passing them on to the user without interpretation is loads better than not having any clue what went wrong.
Since 'error' denotes a programming error, not an exception, there is no need that the user understands the error message. It is entirely the task of the programmer to understand the message or its absence and it would be completely ok if the program aborts with "the programmer made a mistake, please complain to him". http://www.haskell.org/haskellwiki/Error http://www.haskell.org/haskellwiki/Exception

On Fri, Feb 08, 2008 at 11:39:18AM +0100, Henning Thielemann wrote:
say that next time you get a mysterious "fromJust: Nothing" error with no context, error messages in haskell are quite an issue as is, _any_ useful information is good, passing them on to the user without interpretation is loads better than not having any clue what went wrong.
Since 'error' denotes a programming error, not an exception, there is no need that the user understands the error message. It is entirely the task of the programmer to understand the message or its absence and it would be completely ok if the program aborts with "the programmer made a mistake, please complain to him". http://www.haskell.org/haskellwiki/Error http://www.haskell.org/haskellwiki/Exception
I am not sure what distinction you are making between the user and the developer. I don't believe errors should be catchable at all and find the ability to catch 'error' rather unaethetic. But I do believe they should be absolutely as informative as possible in order to track down bugs and the string argument is invaluable for that. I am not saying that "users" will be happier seeing "readM: no parse" than "fromJust: Nothing" as they both indicate bugs in your code, but getting a bug report with the first is much more useful and more precise. Haskell is hard enough to debug as is, we should take help wherever we can get it. John -- John Meacham - ⑆repetae.net⑆john⑈

On Fri, Feb 08, 2008 at 01:56:27AM -0800, John Meacham wrote:
On Fri, Feb 08, 2008 at 12:17:31AM -0500, David Menendez wrote:
I also prefer Maybe to fail. Error strings are only useful if you're ignoring them or passing them to the user without interpretation.
say that next time you get a mysterious "fromJust: Nothing" error with no context,
And that is why people recommend against using functions that throw errors, like fromJust. But in some monads (and which monad is involved isn't immediately obvious), readM would be another such function (as is read, of course). In contrast, the proposed maybeRead wraps up a solution to a common problem in a safe way, and requires the caller (who has more information about the context) to handle failed parses.

ross:
On Fri, Feb 08, 2008 at 01:56:27AM -0800, John Meacham wrote:
On Fri, Feb 08, 2008 at 12:17:31AM -0500, David Menendez wrote:
I also prefer Maybe to fail. Error strings are only useful if you're ignoring them or passing them to the user without interpretation.
say that next time you get a mysterious "fromJust: Nothing" error with no context,
And that is why people recommend against using functions that throw errors, like fromJust. But in some monads (and which monad is involved isn't immediately obvious), readM would be another such function (as is read, of course).
In contrast, the proposed maybeRead wraps up a solution to a common problem in a safe way, and requires the caller (who has more information about the context) to handle failed parses.
Quite so. The whole point of this exercise was to get a version of read that was safe, and where an unintential <- or other slip up wouldn't bring down the system. readM with fail defaults to ioError for almost all Monads, and so admits many dangerous programs, which is against the intent of the proposal in the first place. It seems with Conor's suggestion of a maybeReturn :: MonadPlus m => Maybe a -> m a maybeReturn = maybe mzero return we can still have the by-default-safe maybeRead, that doesn't admit exception throwing opportunities. -- Don

Hello,
readM with fail defaults to ioError for almost all Monads, and so admits many dangerous programs, which is against the intent of the proposal in the first place.
ioError is only in the IO monad and is catchable. I think the problem is when fail defaults to error which can be anywhere and is not catchable.
It seems with Conor's suggestion of a
maybeReturn :: MonadPlus m => Maybe a -> m a maybeReturn = maybe mzero return
we can still have the by-default-safe maybeRead, that doesn't admit exception throwing opportunities.
Isn't the MonadPlus approach also by-default-safe? -Jeff --- This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden.

2008/2/8 Jeff Polakow
readM with fail defaults to ioError for almost all Monads, and so admits many dangerous programs, which is against the intent of the proposal in the first place.
ioError is only in the IO monad and is catchable. I think the problem is when fail defaults to error which can be anywhere and is not catchable.
I think Don meant "error". The default definition of fail in the Monad class is "error".
It seems with Conor's suggestion of a
maybeReturn :: MonadPlus m => Maybe a -> m a maybeReturn = maybe mzero return
we can still have the by-default-safe maybeRead, that doesn't admit exception throwing opportunities.
Isn't the MonadPlus approach also by-default-safe?
Safe, yes, but is it more useful? (I'm tempted to argue that the way
MTL conflates mzero/mplus with throwError/catchError is unfortunate,
but that's another discussion.)
--
Dave Menendez

David Menendez wrote:
Isn't the MonadPlus approach also by-default-safe?
Safe, yes, but is it more useful?
Yes. In this case, take a parsing monad for example. You could write: parseInt :: CharParser () Int parseInt = do ds <- many digit readM ds And it would work automatically. A reading error would be propagated to the parser monad, and it would backtrack/report the error/whatever. Twan

On Fri, Feb 08, 2008 at 09:35:34PM +0100, Twan van Laarhoven wrote:
David Menendez wrote:
Isn't the MonadPlus approach also by-default-safe?
Safe, yes, but is it more useful?
Yes. In this case, take a parsing monad for example. You could write:
parseInt :: CharParser () Int parseInt = do ds <- many digit readM ds
And it would work automatically. A reading error would be propagated to the parser monad, and it would backtrack/report the error/whatever.
Yes. this is exactly the sort of thing I use this for. (I have had readM in my standard toolkit for a while). John -- John Meacham - ⑆repetae.net⑆john⑈

On Fri, Feb 08, 2008 at 09:35:34PM +0100, Twan van Laarhoven wrote:
David Menendez wrote:
Isn't the MonadPlus approach also by-default-safe?
Safe, yes, but is it more useful?
Yes. In this case, take a parsing monad for example. You could write:
parseInt :: CharParser () Int parseInt = do ds <- many digit readM ds
And it would work automatically. A reading error would be propagated to the parser monad, and it would backtrack/report the error/whatever.
In this example a read error indicates a bug, which you'd want to treat differently from a syntax error in the input. If one were using read as part of the parsing process, one could give better messages with something like parseInt :: CharParser () Int parseInt = do ds <- many alphaNum fromMaybe (fail "integer expected") $ maybeRead ds

On Feb 8, 2008 4:56 AM, John Meacham
On Fri, Feb 08, 2008 at 12:17:31AM -0500, David Menendez wrote:
On Feb 7, 2008 6:12 PM, Ross Paterson
wrote: I think this is a good idea, though I normally write the equivalent of
maybeRead :: Read a => String -> Maybe a maybeRead s = case reads s of [(x, rest)] | all isSpace rest -> Just x _ -> Nothing
and would prefer not to generalize it to any monad. fail is a wart, not a design pattern.
I also prefer Maybe to fail. Error strings are only useful if you're ignoring them or passing them to the user without interpretation.
say that next time you get a mysterious "fromJust: Nothing" error with no context, error messages in haskell are quite an issue as is, _any_ useful information is good, passing them on to the user without interpretation is loads better than not having any clue what went wrong.
That's why I use "fromMaybe" (or "maybe"). Why narrow it down to a call to some function when you can narrow it down to a specific call to a function? It's a pity there isn't something like __LINE__ in Haskell itself.
It is what you want to do because the fact that it was a 'readM' that failed is extremely useful for figuring out what went wrong. It is a straightforward generalization that is very useful pragmatically.
We already have a function that produces an opaque error string to
pass to the user: read.
--
Dave Menendez

I vote mildly in favor of maybeRead, strongly against readM. "fail" refers only to failure of pattern matching. The wart is that its name should have been more specific, like "patternFail". Using "fail" for a non-pattern-matching error is a bug, not just a wart, in my opinion. My preferences for the type of this function, from best to worst, would be: 1. (Error e, MonadError e m, Read a) => String -> m a 2. (MonadZero m, Read a) => String -> m a 3. (MonanPlus m, Read a) => String -> m a 4. Read a => String -> Maybe a But (1) depends on mtl, and MonadZero is not even part of the libraries, so (2) is also out. That leaves (3) and (4) as the only possibilities. They're still useful sometimes. Thanks, Yitz

On 2008-02-08, Yitzchak Gale
I vote mildly in favor of maybeRead, strongly against readM.
"fail" refers only to failure of pattern matching. The wart is that its name should have been more specific, like "patternFail". Using "fail" for a non-pattern-matching error is a bug, not just a wart, in my opinion.
Even if you do consider it a bug, it's an extremely useful bug. I don't see the point in deprecating it until a truly usable alternative is actually in the standard. -- Aaron Denney -><-

On Fri, 8 Feb 2008, Aaron Denney wrote:
On 2008-02-08, Yitzchak Gale
wrote: I vote mildly in favor of maybeRead, strongly against readM.
"fail" refers only to failure of pattern matching. The wart is that its name should have been more specific, like "patternFail". Using "fail" for a non-pattern-matching error is a bug, not just a wart, in my opinion.
Even if you do consider it a bug, it's an extremely useful bug. I don't see the point in deprecating it until a truly usable alternative is actually in the standard.
If an alternative is added to the standard libraries, readM would have to remain. I think the generalization is not useful enough to introduce the monad version that we will regret later. readM can be added with the right type, when the alternative appears. Until then maybeRead is fine.

This discussion has pretty much convinced me as well that readM would be a mistake at this point. As to whether maybeRead trims trailing whitespace though...? --S On Feb 8, 2008, at 8:20 AM, Henning Thielemann wrote:
On Fri, 8 Feb 2008, Aaron Denney wrote:
On 2008-02-08, Yitzchak Gale
wrote: I vote mildly in favor of maybeRead, strongly against readM.
"fail" refers only to failure of pattern matching. The wart is that its name should have been more specific, like "patternFail". Using "fail" for a non-pattern-matching error is a bug, not just a wart, in my opinion.
Even if you do consider it a bug, it's an extremely useful bug. I don't see the point in deprecating it until a truly usable alternative is actually in the standard.
If an alternative is added to the standard libraries, readM would have to remain. I think the generalization is not useful enough to introduce the monad version that we will regret later. readM can be added with the right type, when the alternative appears. Until then maybeRead is fine. _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Thu, Feb 07, 2008 at 10:46:48AM -0800, Don Stewart wrote:
This function is typically defined once per project. So its about time this safe variant of 'read' made it into the base.
maybeRead :: Read a => String -> Maybe a maybeRead s = case reads s of [(x, "")] -> Just x _ -> Nothing
Consideration period: 1 week.
May I suggest 'readM'? It is just the obvious generalization of the 'readIO' that is in the Prelude, that it isn't generalized is a bug in the prelude IMHO. (and it is signifigantly more useful)
readM :: (Monad m,Read a) => String -> m a readM s = case reads s of [(x, "")] -> return x _ -> fail "readM: no parse"
John -- John Meacham - ⑆repetae.net⑆john⑈

On Thursday 07 February 2008, Don Stewart wrote:
This function is typically defined once per project. So its about time this safe variant of 'read' made it into the base.
maybeRead :: Read a => String -> Maybe a maybeRead s = case reads s of [(x, "")] -> Just x _ -> Nothing
Consideration period: 1 week.
Patch to Text.Read attached.
I was poking around the GHC sources, and it seems like you'd be closer to 'read' if you went with: maybeRead s = case reads s of [(x, s')] | all isSpace s' -> Just x _ -> Nothing I'd also, personally, vote in favor of readM. fail is a wart, but that's a problem with the Monad class, not with the idea of failing in an arbitrary, appropriate monad. In fact, if you use fail, you can also make a distinction between "no parse" and "ambiguous parse", as read does. In fact, GHC has an internal 'readEither' it uses to define 'read': readEither s = case [ x | (x,"") <- readPrec_to_S read' minPrec s ] of [x] -> Right x [] -> Left "Prelude.read: no parse" _ -> Left "Prelude.read: ambiguous parse" where read' = do x <- readPrec lift P.skipSpaces return x Using this auxiliary function, you have: read s = either error id (readEither s) maybeRead s = either (const Nothing) Just (readEither s) readIO s = either fail return (readEither s) -- [1] readM s = either fail return (readEither s) readM is the generalization of readIO, maybeRead, and even readEither, so one could simply define it instead of readEither, read in terms of readM, and export both (although I don't know how that'd gel with non-GHC compilers; the importing/exporting in base is somewhat convoluted :)). -- Dan 1: readIO apparently uses 'lex' instead of 'skipSpaces', which is the same if there are actually just spaces left, but does extra work if not.

Dan Doel wrote:
readEither s = case [ x | (x,"") <- readPrec_to_S read' minPrec s ] of [x] -> Right x [] -> Left "Prelude.read: no parse" _ -> Left "Prelude.read: ambiguous parse"
Because there are multiple error cases, I support the Monad version. I agree with everyone who has said that fail is a wart, but since we don't have a haskell98 'MonadStringError', and 'MonadError' requires fundeps and MPTCs, I think fail is the best we have at the moment. If we were prepared to endorse fundeps and MPTCs then I might support a (Error e, MonadError e m,Read a) => String -> m a type. If there was only one error case, then Maybe would contain enough information, and I would support the simpler version. As there are three (no parse, ambiguous parse, and incomplete parse), it is losing information just to product Nothing. +1 for Text.Read.readM from me. Dan points out in conversation that a MonadPlus constraint might be considered a 'valid hint' that fail is a sensible operation. Without wishing to derail the conversation, common combinators to promote and demote error types might be good thigns to document and possibly even include in the standard lib. One example which springs to mind is maybe (fail "it went wrong") return which the combinator to "promote" from unlabelled errors (Maybe) to labelled errors (presumably in an error monad). Or with a custom error type, something like maybe (throwError ThereWasAProblem) return which could be set up as an infix like this: possiblyFailingOperation `withError` ThereWasAProblem There are a whole bunch of tricks like this for embedding one error strategy inside another which are 'obvious' and even 'folklore' but not written down. Jules
participants (18)
-
Aaron Denney
-
Conor McBride
-
Dan Doel
-
David Menendez
-
Don Stewart
-
Henning Thielemann
-
Iavor Diatchki
-
Jeff Polakow
-
Johan Tibell
-
Johannes Waldmann
-
John Meacham
-
Jules Bean
-
Lennart Augustsson
-
Neil Mitchell
-
Ross Paterson
-
Sterling Clover
-
Twan van Laarhoven
-
Yitzchak Gale