better error expression in IO function

i am working on improving a module for getting Yahoo Finance quote data, hopefully getting it to a point that i can put it on hackage in the quote retrieval function, there are a few places i would like to call out errors. in a trivial case i could return IO (Maybe String) with Nothing signifying any error state, or Just expressing the data but i would like to be able to express some of these error cases in a more structured manner i know the Either type can be used in such a case(?), but i've had some problem locating a satisfactory example (if this is indeed appropriate) could one of the vets here provide a simplistic example expressing error cases, preferrably in the IO Monad (in case there are any gotchas there)? thanks so much! brad

brad clawsie wrote:
i am working on improving a module for getting Yahoo Finance quote data, hopefully getting it to a point that i can put it on hackage
in the quote retrieval function, there are a few places i would like to call out errors. in a trivial case i could return
IO (Maybe String)
with Nothing signifying any error state, or Just expressing the data
but i would like to be able to express some of these error cases in a more structured manner
i know the Either type can be used in such a case(?), but i've had some problem locating a satisfactory example (if this is indeed appropriate)
could one of the vets here provide a simplistic example expressing error cases, preferrably in the IO Monad (in case there are any gotchas there)?
It's fairly common to use the Either type for this. By convention, "Right" means "correct", and by elimination "Left" means an error... foo x = case x of .... return (Right y) .... return (Left "Some error happened") Instead of just returning a text string indicating the error condition, you could devize your own special type for representing the possible errors that can happen. You could also make a kind of a "Result" type that represents both successful *and* failed results, if you prefer. In addition, in the IO monad, I believe you can do fun stuff with exceptions. Specifically, you can *catch* them. However, beware: Haskell has something of a habit of executing stuff at unpredictable times, which means that if you're throwing errors in pure code, it can be hard to register the exception handler(s) at the right time! Probably simpler and clearer to go with Either or something OTOH, if you're throwing errors from within the IO monad itself, timing should be less of an issue. Just my few cents...

On 7/12/07, Andrew Coppin
It's fairly common to use the Either type for this. By convention, "Right" means "correct", and by elimination "Left" means an error...
Presumably, this is because the world is dominated by dull, conventional, right handed people. :-) cheers, Tom Southpaw Conway -- Dr Thomas Conway drtomc@gmail.com Silence is the perfectest herald of joy: I were but little happy, if I could say how much.

At Thu, 12 Jul 2007 09:18:14 +1000, Thomas Conway wrote:
On 7/12/07, Andrew Coppin
wrote: It's fairly common to use the Either type for this. By convention, "Right" means "correct", and by elimination "Left" means an error...
Presumably, this is because the world is dominated by dull, conventional, right handed people. :-)
Personally, I blame it on the Romans. The English word "sinister" comes from the Latin word "sinister,-tra,-trum", which originally meant "left" but took on meanings of "evil" or "unlucky" by the Classical Latin era[1]. j. [1] http://en.wikipedia.org/wiki/Left-handed

On Wed, 2007-07-11 at 17:10 -0700, Jeremy Shaw wrote:
At Thu, 12 Jul 2007 09:18:14 +1000, Thomas Conway wrote:
On 7/12/07, Andrew Coppin
wrote: It's fairly common to use the Either type for this. By convention, "Right" means "correct", and by elimination "Left" means an error...
Presumably, this is because the world is dominated by dull, conventional, right handed people. :-)
Personally, I blame it on the Romans.
Personally, I blame it on biology.

Derek Elkins wrote:
On Wed, 2007-07-11 at 17:10 -0700, Jeremy Shaw wrote:
At Thu, 12 Jul 2007 09:18:14 +1000, Thomas Conway wrote:
On 7/12/07, Andrew Coppin
wrote: It's fairly common to use the Either type for this. By convention, "Right" means "correct", and by elimination "Left" means an error... Presumably, this is because the world is dominated by dull, conventional, right handed people. :-) Personally, I blame it on the Romans.
Personally, I blame it on biology.
I blame it on partial application at the type level. "instance Monad (Either x)" and "instance MonadError (Either x)" determine that x has no hope of being the normal return type and is stuck as the exception type. But I guess you can still blame the Romans for writing everything from left to right, writing "Either x y" rather than "y x rehtiE", thus designating the first argument x as Left. Actually, it predates the Romans too: they learned that from the Greeks, and the Greeks got that from God-knows-who. (Actually, God knows, just that I don't know.)

On Jul 11, 2007, at 20:10 , Jeremy Shaw wrote:
At Thu, 12 Jul 2007 09:18:14 +1000, Thomas Conway wrote:
On 7/12/07, Andrew Coppin
wrote: It's fairly common to use the Either type for this. By convention, "Right" means "correct", and by elimination "Left" means an error...
Presumably, this is because the world is dominated by dull, conventional, right handed people. :-)
Personally, I blame it on the Romans.
The English word "sinister" comes from the Latin word "sinister,-tra,-trum", which originally meant "left" but took on meanings of "evil" or "unlucky" by the Classical Latin era[1].
Dig deeper; it far predates the Romans. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Jul 11, 2007, at 15:57 , brad clawsie wrote:
i know the Either type can be used in such a case(?), but i've had some problem locating a satisfactory example (if this is indeed appropriate)
You might want to look at MonadError (Control.Monad.Error), more specifically ErrorT layered on top of IO. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Brandon S. Allbery KF8NH wrote:
On Jul 11, 2007, at 15:57 , brad clawsie wrote:
i know the Either type can be used in such a case(?), but i've had some problem locating a satisfactory example (if this is indeed appropriate)
You might want to look at MonadError (Control.Monad.Error), more specifically ErrorT layered on top of IO.
I think *I* might want to spend some time reading about that... (Throwing and catching exceptions is just fiddly.)

On Wed, Jul 11, 2007 at 12:57:53PM -0700, brad clawsie wrote:
but i would like to be able to express some of these error cases in a more structured manner
okay, i'm going to answer my own question for the sake of documenting it for others who might be interested. thanks to andrew and brandon for clues module Main (main) where data ErrorTestType = ErrorA | ErrorB Int | ErrorC String instance Show ErrorTestType where show ErrorA = "Error A" show (ErrorB n) = "Error B:" ++ (show n) show (ErrorC s) = "Error C:" ++ (show s) type ErrorTestT = Either ErrorTestType f :: IO (ErrorTestT String) f = do print "type something:" s <- getLine case length s of 1 -> return (Left ErrorA) 2 -> return (Left (ErrorB (length s))) 3 -> return (Left (ErrorC "error c")) _ -> return (Right s) main = do r <- f case r of (Left e) -> print e (Right a) -> print a return ()

I have written up the beginnings of some code to get Yahoo Finance quotes, too. Perhaps we should compare notes, and try to put something together that uses the best ideas from each attempt? Aaron On Jul 11, 2007, at 12:57 PM, brad clawsie wrote:
i am working on improving a module for getting Yahoo Finance quote data, hopefully getting it to a point that i can put it on hackage
in the quote retrieval function, there are a few places i would like to call out errors. in a trivial case i could return
IO (Maybe String)
with Nothing signifying any error state, or Just expressing the data
but i would like to be able to express some of these error cases in a more structured manner
i know the Either type can be used in such a case(?), but i've had some problem locating a satisfactory example (if this is indeed appropriate)
could one of the vets here provide a simplistic example expressing error cases, preferrably in the IO Monad (in case there are any gotchas there)?
thanks so much! brad _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (8)
-
Aaron Tomb
-
Albert Y. C. Lai
-
Andrew Coppin
-
brad clawsie
-
Brandon S. Allbery KF8NH
-
Derek Elkins
-
Jeremy Shaw
-
Thomas Conway