-- ghc -package lang TestException.hs -o TestException module Main where { import IORef; import qualified Exception; getPureException :: a -> IO (Maybe Exception.Exception); getPureException a = (Exception.catch (seq a (return Nothing)) (return . Just)); showIOS :: String -> IO String -> IO (); showIOS s ios = do { putStr (s ++ ": "); mpe <- getPureException ios; case mpe of { Just pe -> putStrLn ("pure exception ("++ (show pe) ++")"); Nothing -> do { result <- Exception.catch (ios) (\_ -> return ""); mrpe <- getPureException result; case mrpe of { Just pe -> putStrLn ("returned pure exception ("++ (show pe) ++")"); Nothing -> do { Exception.catch (do { s <- ios; putStrLn ("value ("++ (show s) ++")"); }) (\e -> putStrLn ("IO exception (" ++ (show e) ++")")); }; }; }; }; }; evaluate' :: a -> IO a; evaluate' a = a `seq` return a; main :: IO (); main = do { showIOS "return text" (return "text"); showIOS "fail text" (fail "text"); showIOS "error text" (error "text"); showIOS "undefined" undefined; showIOS "seq undefined (return text)" (seq undefined (return "text")); showIOS "seq undefined (return undefined)" (seq undefined (return undefined)); showIOS "return (seq undefined text)" (return (seq undefined "text")); showIOS "evaluate undefined" (Exception.evaluate undefined); showIOS "evaluate' undefined" (evaluate' undefined); showIOS "return undefined" (return undefined); }; }