At 2002-05-13 22:07, Ashley Yakeley wrote:
>I've noticed something a bit unusual about Exception.catch.
Curiously, the definition of Exception.evaluate given in the GHC
Libraries documentation sec. 5.12.3 is not that actually implemented by
GHC.
evaluate' :: a -> IO a;
evaluate' a = a `seq` return a;
"evaluate' undefined" is bottom, whereas "Expression.evaluate undefined"
is an IO action that "fails" when executed. But both will be caught by
Exception.catch.
--
Ashley Yakeley, Seattle WA
-- 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);
};
}