Exception: Difference between revisions
(monad transformer) |
(how to escape from Exception monad by handling the exception) |
||
Line 73: | Line 73: | ||
Here are some example signatures for typical IO functions with explicit exceptions. | |||
<haskell> | <haskell> | ||
data IOException = | data IOException = | ||
Line 94: | Line 95: | ||
bracketT (open fileName) close $ \h -> | bracketT (open fileName) close $ \h -> | ||
read h | read h | ||
</haskell> | |||
Finally we can escape from the Exception monad if we handle the exception completely. | |||
<haskell> | |||
main :: IO () | |||
main = | |||
do result <- runExActionT (readText "test") | |||
case result of | |||
Exception e -> putStrLn ("When reading file 'test' we encountered exception " ++ show e) | |||
Success x -> putStrLn ("Content of the file 'test'\n" ++ x) | |||
</haskell> | </haskell> | ||
Revision as of 15:07, 23 January 2008
An exception denotes an unpredictable situation at runtime, like "out of disk storage", "read protected file", "user removed disk while reading", "syntax error in user input".
These are situation which occur relatively seldom and thus their immediate handling would clutter the code which should describe the regular processing.
Since exceptions must be expected at runtime there are also mechanisms for (selectively) handling them.
(Control.Exception,try
, Control.Exception.catch
)
Unfortunately Haskell's standard library names common exceptions of IO actions IOError
and the module Control.Monad.Error
is about exception handling not error handling.
In general you should be very careful, not to mix up exceptions with errors.
Actually, an unhandled exception is an error.
Implementation
The great thing about Haskell is, that it is not necessary to hard-wire the exception handling into the language.
Everything is already there to implement definition and handling of exceptions nicely.
See the implementation in Control.Monad.Error
(and please, excuse the misleading name, for now).
First for non-monadic functions.
data ExAction e a =
Success a
| Exception e
deriving (Show)
instance Monad (ExAction e) where
return = Success
Exception l >>= _ = Exception l
Success r >>= k = k r
throw :: e -> ExAction e a
throw = Exception
catch :: ExAction e a -> (e -> ExAction e a) -> ExAction e a
catch (Exception l) h = h l
catch (Success r) _ = Success r
Now we extend this monadic functions.
This is not restricted to IO, but may also immediately used for non-deterministic algorithms implemented with List
monad.
newtype ExActionT e m a =
ExActionT {runExActionT :: m (ExAction e a)}
instance Monad m => Monad (ExActionT e m) where
return = ExActionT . return . Success
m >>= k = ExActionT $
runExActionT m >>= \ a ->
case a of
Exception e -> return (Exception e)
Success r -> runExActionT (k r)
throwT :: Monad m => e -> ExActionT e m a
throwT = ExActionT . return . Exception
catchT :: Monad m =>
ExActionT e m a -> (e -> ExActionT e m a) -> ExActionT e m a
catchT m h = ExActionT $
runExActionT m >>= \ a ->
case a of
Exception l -> runExActionT (h l)
Success r -> return (Success r)
bracketT :: Monad m =>
ExActionT e m h ->
(h -> ExActionT e m ()) ->
(h -> ExActionT e m a) ->
ExActionT e m a
bracketT open close body =
open >>= (\ h ->
ExActionT $
do a <- runExActionT (body h)
runExActionT (close h)
return a)
Here are some example signatures for typical IO functions with explicit exceptions.
data IOException =
DiskFull
| FileDoesNotExist
| ReadProtected
| WriteProtected
| NoSpaceOnDevice
deriving (Show, Eq, Enum)
open :: FilePath -> ExActionT IOException IO Handle
close :: Handle -> ExActionT IOException IO ()
read :: Handle -> ExActionT IOException IO String
write :: Handle -> String -> ExActionT IOException IO ()
readText :: FilePath -> ExActionT IOException IO String
readText fileName =
bracketT (open fileName) close $ \h ->
read h
Finally we can escape from the Exception monad if we handle the exception completely.
main :: IO ()
main =
do result <- runExActionT (readText "test")
case result of
Exception e -> putStrLn ("When reading file 'test' we encountered exception " ++ show e)
Success x -> putStrLn ("Content of the file 'test'\n" ++ x)