How to read safely?

Hi, Read often throws runtime errors, which breaks the robust of the problem. How to deal with it? Without lost too much proformance (so reads is a no). At least, if its error could be catched, that'd be better. -- 竹密岂妨流水过 山高哪阻野云飞

2009/6/24 Magicloud Magiclouds
Hi, Read often throws runtime errors, which breaks the robust of the problem. How to deal with it? Without lost too much proformance (so reads is a no).
Hi, You might be interested in http://hackage.haskell.org/packages/archive/safe/0.2/doc/html/Safe.html#v%3A.... Also, I think a similar question was asked not too long ago, so you might want to get a look at the archive : http://www.haskell.org/pipermail/haskell-cafe/ Cheers, Thu

On Wednesday 24 June 2009 5:40:28 am Magicloud Magiclouds wrote:
Hi, Read often throws runtime errors, which breaks the robust of the problem. How to deal with it? Without lost too much proformance (so reads is a no). At least, if its error could be catched, that'd be better.
There was talk of adding a readMaybe a while ago, but apparently it never happened. As it is, you can use reads, "read s" becomes: case reads s of [(a, rest)] | all isSpace rest -> <code using a> _ -> <error case> which ensures that you have an unambiguous parse with only trailing whitespace. You can, of course, modify that if you don't care about ambiguity or trailing characters. Also, technically, if you're reading things in conjunction with IO code, you can use readIO, which throws a catchable IO exception on failure. But that obviously doesn't work in the general case. -- Dan

Dan Doel
There was talk of adding a readMaybe a while ago, but apparently it never happened.
As it is, you can use reads, "read s" becomes:
case reads s of [(a, rest)] | all isSpace rest -> <code using a> _ -> <error case>
which ensures that you have an unambiguous parse with only trailing whitespace. You can, of course, modify that if you don't care about ambiguity or trailing characters.
I was wondering about a more algebraic way of writing that; here's a version (that doesn't care about ambiguity) readMaybe :: Read a => String -> Maybe a readMaybe = join . fmap no_trailing_garbage . listToMaybe . reads where no_trailing_garbage = fmap fst . check (all isSpace . snd) check :: (MonadPlus m) => (a -> Bool) -> a -> m a check p a | p a = return a | otherwise = mzero I tried Hoogling for a function like check, but couldn't find it. Surely there's one in a library somewhere? It looks useful to me. (I'm rather taken by way the "check (all isSpace . snd)" part reads) Monad.guard comes close but fails to get the cigar; in fact guard b == check (const b) () So check is more general. Also, I don't see a singletonListToMaybe that one could use in place of listToMaybe to require unambiguity. Could do isSingleton [a] = True isSingleton _ = False and then use "listToMaybe . join . check isSingleton" -- aha! Another use for check! Jón [Footnote: I thought of writing "guard == flip (check . const) ()" but then realised it was pointless] -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On Thu, Jul 2, 2009 at 3:36 AM, Jon Fairbairn
Dan Doel
writes: There was talk of adding a readMaybe a while ago, but apparently it never happened.
As it is, you can use reads, "read s" becomes:
case reads s of [(a, rest)] | all isSpace rest -> <code using a> _ -> <error case>
which ensures that you have an unambiguous parse with only trailing whitespace. You can, of course, modify that if you don't care about ambiguity or trailing characters.
I was wondering about a more algebraic way of writing that; here's a version (that doesn't care about ambiguity)
readMaybe :: Read a => String -> Maybe a readMaybe = join . fmap no_trailing_garbage . listToMaybe . reads where no_trailing_garbage = fmap fst . check (all isSpace . snd)
check :: (MonadPlus m) => (a -> Bool) -> a -> m a check p a | p a = return a | otherwise = mzero
I tried Hoogling for a function like check, but couldn't find it. Surely there's one in a library somewhere? It looks useful to me. (I'm rather taken by way the "check (all isSpace . snd)" part reads)
Monad.guard comes close but fails to get the cigar; in fact
guard b == check (const b) ()
So check is more general.
Also, I don't see a singletonListToMaybe that one could use in place of listToMaybe to require unambiguity. Could do
isSingleton [a] = True isSingleton _ = False
and then use "listToMaybe . join . check isSingleton" -- aha! Another use for check!
Jón
[Footnote: I thought of writing "guard == flip (check . const) ()" but then realised it was pointless]
-- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk
You can use the Kleisli composition operator (<=<) to make it a little nicer. singletonListToMaybe :: [a] -> Maybe a singletonListToMaybe [x] = Just x singletonListToMaybe _ = Nothing check :: MonadPlus m => (a -> Bool) -> a -> m a check p a | p a = return a | otherwise = mzero readMaybe = fmap fst.check (all isSpace.snd) <=< singletonListToMaybe.reads Alex

On Thursday 02 July 2009 6:36:09 am Jon Fairbairn wrote:
check :: (MonadPlus m) => (a -> Bool) -> a -> m a check p a | p a = return a | otherwise = mzero
I tried Hoogling for a function like check, but couldn't find it. Surely there's one in a library somewhere? It looks useful to me. (I'm rather taken by way the "check (all isSpace . snd)" part reads)
Monad.guard comes close but fails to get the cigar; in fact
guard b == check (const b) ()
So check is more general.
I've often noticed the need for a similar function in conjunction with unfoldr: -- This is overly general for unfoldr, but it lines up with check stopAt :: (MonadPlus m) => (a -> Bool) -> (a -> b) -> a -> m b stopAt p f x | p x = mzero | otherwise = return (f x) -- stopAt p f x = guard (not $ p x) >> return (f x) -- stopAt p f = liftM2 (>>) (guard . not . p) (return . f) -- etc. Then you can write: unfoldr (stopAt p $ f) where p is a stopping predicate based on the seed, and f unfolds the seed one step. This lets you use the many functions in the standard library that have types like: s -> (a, s) where unfoldr wants them to instead be: s -> Maybe (a, s) However, I don't really like the name stopAt, and have never come up with anything better. And of course: check = flip stopAt id . not -- Dan

On Mon, Jul 6, 2009 at 8:49 PM, Dan Doel
I've often noticed the need for a similar function in conjunction with unfoldr:
-- This is overly general for unfoldr, but it lines up with check stopAt :: (MonadPlus m) => (a -> Bool) -> (a -> b) -> a -> m b stopAt p f x | p x = mzero | otherwise = return (f x)
-- stopAt p f x = guard (not $ p x) >> return (f x) -- stopAt p f = liftM2 (>>) (guard . not . p) (return . f) -- etc.
Then you can write:
unfoldr (stopAt p $ f)
I have the following function sitting around: unfoldUntil :: (b -> Bool) -> (b -> (a, b)) -> b -> [a] unfoldUntil p f n = unfoldr g n where g m | p m = Nothing | otherwise = Just $ f m But I don't remeber where I picked it up from. It looks like it fills a similar niche. Antoine

Dan Doel
On Thursday 02 July 2009 6:36:09 am Jon Fairbairn wrote:
check :: (MonadPlus m) => (a -> Bool) -> a -> m a check p a | p a = return a | otherwise = mzero
I've often noticed the need for a similar function in conjunction with unfoldr:
-- This is overly general for unfoldr, but it lines up with check stopAt :: (MonadPlus m) => (a -> Bool) -> (a -> b) -> a -> m b stopAt p f x | p x = mzero | otherwise = return (f x)
Yes, I've had occasion to use something like that too, eg things similar to: reverse . unfoldr (stopAt (==0) (swap . flip divMod 10)) where swap (a,b) = (b,a)
And of course: check = flip stopAt id . not
or, equally, "stopAt p f = fmap f . check (not . p)" Granted, reverse . unfoldr (fmap (swap . flip divMod 10) . check (/=0)) isn't /quite/ as nice as the first version, but I imagine one could get used to it. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

Magicloud Magiclouds
Read often throws runtime errors, which breaks the robust of the problem. How to deal with it? Without lost too much proformance (so reads is a no). At least, if its error could be catched, that'd be better.
You might like to try using a real parser instead of read. For instance, the polyparse package provides module Text.Parse which provides parser analogues for all of the Prelude instances of Read. It provides nice-ish error messages, or in the lazy variation, catchable exceptions. It also gives you a nice framework to write your own instances. The DrIFT tool can automatically derive these instances for your own datatypes, if you don't want to do it by hand. (I expect it is easy to teach the 'derive' tool to do it too.) Regards, Malcolm

The package ChristmasTree includes an alternative version of read which catches (and repairs if you want) errors. The package contains the code of the paper @inproceedings{1411296, author = {Marcos Viera and S. Doaitse Swierstra and Eelco Lempsink}, title = {Haskell, do you read me?: constructing and composing efficient top-down parsers at runtime}, booktitle = {Haskell '08: Proceedings of the first ACM SIGPLAN symposium on Haskell}, year = {2008}, isbn = {978-1-60558-064-7}, pages = {63--74}, location = {Victoria, BC, Canada}, doi = {http://doi.acm.org/10.1145/1411286.1411296}, publisher = {ACM}, address = {New York, NY, USA}, } cheers, marcos [1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ChristmasTree Magicloud Magiclouds wrote:
Hi, Read often throws runtime errors, which breaks the robust of the problem. How to deal with it? Without lost too much proformance (so reads is a no). At least, if its error could be catched, that'd be better.
participants (8)
-
Alexander Dunlap
-
Antoine Latter
-
Dan Doel
-
Jon Fairbairn
-
Magicloud Magiclouds
-
Malcolm Wallace
-
Marcos Viera
-
minh thu