module Data.Iteratee.Exception (
IFException (..)
,Exception (..)
,EnumException (..)
,DivergentException (..)
,EnumStringException (..)
,EnumUnhandledIterException (..)
,IException (..)
,IterException (..)
,SeekException (..)
,EofException (..)
,IterStringException (..)
,enStrExc
,iterStrExc
,wrapIterExc
,iterExceptionToException
,iterExceptionFromException
)
where
import Data.Iteratee.IO.Base
import Control.Exception
import Data.Data
data IFException = forall e . Exception e => IFException e
deriving Typeable
instance Show IFException where
show (IFException e) = show e
instance Exception IFException
ifExceptionToException :: Exception e => e -> SomeException
ifExceptionToException = toException . IFException
ifExceptionFromException :: Exception e => SomeException -> Maybe e
ifExceptionFromException x = do
IFException a <- fromException x
cast a
data EnumException = forall e . Exception e => EnumException e
deriving Typeable
instance Show EnumException where
show (EnumException e) = show e
instance Exception EnumException where
toException = ifExceptionToException
fromException = ifExceptionFromException
enumExceptionToException :: Exception e => e -> SomeException
enumExceptionToException = toException . IterException
enumExceptionFromException :: Exception e => SomeException -> Maybe e
enumExceptionFromException x = do
IterException a <- fromException x
cast a
data DivergentException = DivergentException
deriving (Show, Typeable)
instance Exception DivergentException where
toException = enumExceptionToException
fromException = enumExceptionFromException
data EnumStringException = EnumStringException String
deriving (Show, Typeable)
instance Exception EnumStringException where
toException = enumExceptionToException
fromException = enumExceptionFromException
enStrExc :: String -> EnumException
enStrExc = EnumException . EnumStringException
data EnumUnhandledIterException = EnumUnhandledIterException IterException
deriving (Show, Typeable)
instance Exception EnumUnhandledIterException where
toException = enumExceptionToException
fromException = enumExceptionFromException
wrapIterExc :: IterException -> EnumException
wrapIterExc = EnumException . EnumUnhandledIterException
class Exception e => IException e where
toIterException :: e -> IterException
toIterException = IterException
fromIterException :: IterException -> Maybe e
fromIterException = fromException . toException
data IterException = forall e . Exception e => IterException e
deriving Typeable
instance Show IterException where
show (IterException e) = show e
instance Exception IterException where
toException = ifExceptionToException
fromException = ifExceptionFromException
iterExceptionToException :: Exception e => e -> SomeException
iterExceptionToException = toException . IterException
iterExceptionFromException :: Exception e => SomeException -> Maybe e
iterExceptionFromException x = do
IterException a <- fromException x
cast a
instance IException IterException where
toIterException = id
fromIterException = Just
data SeekException = SeekException FileOffset
deriving (Typeable, Show)
instance Exception SeekException where
toException = iterExceptionToException
fromException = iterExceptionFromException
instance IException SeekException where
data EofException = EofException
deriving (Typeable, Show)
instance Exception EofException where
toException = iterExceptionToException
fromException = iterExceptionFromException
instance IException EofException where
data IterStringException = IterStringException String deriving (Typeable, Show)
instance Exception IterStringException where
toException = iterExceptionToException
fromException = iterExceptionFromException
instance IException IterStringException where
iterStrExc :: String -> SomeException
iterStrExc= toException . IterStringException