Exception: Difference between revisions
("mix up" links to Error vs. Exception) |
(handling individual exceptions) |
||
Line 118: | Line 118: | ||
{{PackageInfoBox|name=explicit-exception|darcs-code=explicit-exception/}} | {{PackageInfoBox|name=explicit-exception|darcs-code=explicit-exception/}} | ||
=== Processing individual exceptions === | |||
So far I used the sum type <hask>IOException</hask> that subsumes a bunch of exceptions. | |||
However, not all of these exceptions can be thrown by all of the IO functions. E.g. a read function cannot throw <hask>WriteProtected</hask> or <hask>NoSpaceOnDevice</hask>. | |||
Thus when handling exceptions we do not want to handle <hask>WriteProtected</hask> if we know that it cannot occur in the real world. | |||
We like to express this in the type and actually we can express this in the type. | |||
<haskell> | |||
import Prelude hiding (readFile, writeFile, ) | |||
import Control.Monad.Exception.Synchronous | |||
(ExceptionalT, Exceptional(Success,Exception)) | |||
class ThrowsRead e where throwRead :: e | |||
class ThrowsWrite e where throwWrite :: e | |||
readFile :: ThrowsRead e => FilePath -> ExceptionalT e IO String | |||
writeFile :: ThrowsWrite e => FilePath -> String -> ExceptionalT e IO () | |||
readFile = undefined | |||
writeFile = undefined | |||
copyFile :: | |||
(ThrowsWrite e, ThrowsRead e) => | |||
FilePath -> FilePath -> ExceptionalT e IO () | |||
copyFile src dst = | |||
writeFile dst =<< readFile src | |||
data ApplicationException = | |||
ReadException | |||
| WriteException | |||
instance ThrowsRead ApplicationException where | |||
throwRead = ReadException | |||
instance ThrowsWrite ApplicationException where | |||
throwWrite = WriteException | |||
data ReadException e = | |||
ReadException | |||
| NoReadException e | |||
instance ThrowsRead (ReadException e) where | |||
throwRead = ReadException | |||
instance ThrowsWrite e => ThrowsWrite (ReadException e) where | |||
throwWrite = NoReadException throwWrite | |||
data WriteException e = | |||
WriteException | |||
| NoWriteException e | |||
instance ThrowsRead e => ThrowsRead (WriteException e) where | |||
throwRead = NoWriteException throwRead | |||
instance ThrowsWrite (WriteException e) where | |||
throwWrite = WriteException | |||
catchRead :: ReadException e -> Exceptional e String | |||
catchRead ReadException = Success "catched a read exception" | |||
catchRead (NoReadException e) = Exception e | |||
throwReadWrite :: (ThrowsRead e, ThrowsWrite e) => e | |||
throwReadWrite = | |||
asTypeOf throwRead throwWrite | |||
exampleCatchRead :: (ThrowsWrite e) => Exceptional e String | |||
exampleCatchRead = | |||
catchRead throwReadWrite | |||
</haskell> | |||
== See also == | == See also == | ||
Line 123: | Line 201: | ||
* [[Error]] | * [[Error]] | ||
* [[Error vs. Exception]] | * [[Error vs. Exception]] | ||
* {{HackagePackage|id=control-monad-exception}} | * {{HackagePackage|id=control-monad-exception}} (reduces the number of type class instances by some type extensions) | ||
[[Category:Glossary]] | [[Category:Glossary]] |
Revision as of 13:07, 5 January 2012
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
Exception monad
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 the definition and handling of exceptions nicely.
See the implementation in Control.Monad.Error
(and please, excuse the misleading name for now).
There is an old dispute between C++ programmers on whether exceptions or error return codes are the right way. Also Niklaus Wirth considered exceptions to be the reincarnation of GOTO and thus omitted them in his languages. Haskell solves the problem a diplomatic way: Functions return error codes, but the handling of error codes does not uglify the calling code.
First we implement exception handling for non-monadic functions. Since no IO functions are involved, we still cannot handle exceptional situations induced from outside the world, but we can handle situations where it is unacceptable for the caller to check a priori whether the call can succeed.
data Exceptional e a =
Success a
| Exception e
deriving (Show)
instance Monad (Exceptional e) where
return = Success
Exception l >>= _ = Exception l
Success r >>= k = k r
throw :: e -> Exceptional e a
throw = Exception
catch :: Exceptional e a -> (e -> Exceptional e a) -> Exceptional e a
catch (Exception l) h = h l
catch (Success r) _ = Success r
Now we extend this to monadic functions.
This is not restricted to IO, but may be used immediately also for non-deterministic algorithms implemented with the List
monad.
newtype ExceptionalT e m a =
ExceptionalT {runExceptionalT :: m (Exceptional e a)}
instance Monad m => Monad (ExceptionalT e m) where
return = ExceptionalT . return . Success
m >>= k = ExceptionalT $
runExceptionalT m >>= \ a ->
case a of
Exception e -> return (Exception e)
Success r -> runExceptionalT (k r)
throwT :: Monad m => e -> ExceptionalT e m a
throwT = ExceptionalT . return . Exception
catchT :: Monad m =>
ExceptionalT e m a -> (e -> ExceptionalT e m a) -> ExceptionalT e m a
catchT m h = ExceptionalT $
runExceptionalT m >>= \ a ->
case a of
Exception l -> runExceptionalT (h l)
Success r -> return (Success r)
bracketT :: Monad m =>
ExceptionalT e m h ->
(h -> ExceptionalT e m ()) ->
(h -> ExceptionalT e m a) ->
ExceptionalT e m a
bracketT open close body =
open >>= (\ h ->
ExceptionalT $
do a <- runExceptionalT (body h)
runExceptionalT (close h)
return a)
Here are some examples for typical IO functions with explicit exceptions.
data IOException =
DiskFull
| FileDoesNotExist
| ReadProtected
| WriteProtected
| NoSpaceOnDevice
deriving (Show, Eq, Enum)
open :: FilePath -> ExceptionalT IOException IO Handle
close :: Handle -> ExceptionalT IOException IO ()
read :: Handle -> ExceptionalT IOException IO String
write :: Handle -> String -> ExceptionalT IOException IO ()
readText :: FilePath -> ExceptionalT IOException IO String
readText fileName =
bracketT (open fileName) close $ \h ->
read h
Finally we can escape from the Exception monad if we handle the exceptions completely.
main :: IO ()
main =
do result <- runExceptionalT (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)
Hackage | http://hackage.haskell.org/package/explicit-exception |
Repository | darcs get http://code.haskell.org/explicit-exception/
|
Processing individual exceptions
So far I used the sum type IOException
that subsumes a bunch of exceptions.
However, not all of these exceptions can be thrown by all of the IO functions. E.g. a read function cannot throw WriteProtected
or NoSpaceOnDevice
.
Thus when handling exceptions we do not want to handle WriteProtected
if we know that it cannot occur in the real world.
We like to express this in the type and actually we can express this in the type.
import Prelude hiding (readFile, writeFile, )
import Control.Monad.Exception.Synchronous
(ExceptionalT, Exceptional(Success,Exception))
class ThrowsRead e where throwRead :: e
class ThrowsWrite e where throwWrite :: e
readFile :: ThrowsRead e => FilePath -> ExceptionalT e IO String
writeFile :: ThrowsWrite e => FilePath -> String -> ExceptionalT e IO ()
readFile = undefined
writeFile = undefined
copyFile ::
(ThrowsWrite e, ThrowsRead e) =>
FilePath -> FilePath -> ExceptionalT e IO ()
copyFile src dst =
writeFile dst =<< readFile src
data ApplicationException =
ReadException
| WriteException
instance ThrowsRead ApplicationException where
throwRead = ReadException
instance ThrowsWrite ApplicationException where
throwWrite = WriteException
data ReadException e =
ReadException
| NoReadException e
instance ThrowsRead (ReadException e) where
throwRead = ReadException
instance ThrowsWrite e => ThrowsWrite (ReadException e) where
throwWrite = NoReadException throwWrite
data WriteException e =
WriteException
| NoWriteException e
instance ThrowsRead e => ThrowsRead (WriteException e) where
throwRead = NoWriteException throwRead
instance ThrowsWrite (WriteException e) where
throwWrite = WriteException
catchRead :: ReadException e -> Exceptional e String
catchRead ReadException = Success "catched a read exception"
catchRead (NoReadException e) = Exception e
throwReadWrite :: (ThrowsRead e, ThrowsWrite e) => e
throwReadWrite =
asTypeOf throwRead throwWrite
exampleCatchRead :: (ThrowsWrite e) => Exceptional e String
exampleCatchRead =
catchRead throwReadWrite
See also
- Error
- Error vs. Exception
- control-monad-exception (reduces the number of type class instances by some type extensions)