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 ()


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to