{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
module Haxl.Core.Exception (
HaxlException(..),
InternalError(..),
internalErrorToException,
internalErrorFromException,
LogicError(..),
logicErrorToException,
logicErrorFromException,
LogicBug(..),
logicBugToException,
logicBugFromException,
TransientError(..),
transientErrorToException,
transientErrorFromException,
CriticalError(..),
DataSourceError(..),
NonHaxlException(..),
NotFound(..),
UnexpectedType(..),
EmptyList(..),
JSONError(..),
InvalidParameter(..),
MonadFail(..),
FetchError(..),
asHaxlException,
MiddleException(..),
rethrowAsyncExceptions,
tryWithRethrow,
) where
#if __GLASGOW_HASKELL__ >= 808
import Prelude hiding (MonadFail)
#endif
import Control.Exception as Exception
import Data.Aeson
import Data.Binary (Binary)
import Data.Typeable
import Data.Text (Text)
import Haxl.Core.Util
import GHC.Stack
data HaxlException
= forall e. (MiddleException e)
=> HaxlException
(Maybe Stack)
e
deriving (Typeable)
type Stack = [String]
instance Show HaxlException where
show (HaxlException (Just stk@(_:_)) e) = show e ++ '\n' : renderStack stk
show (HaxlException _ e) = show e
instance Exception HaxlException
instance ToJSON HaxlException where
toJSON (HaxlException stk e) = object fields
where
fields | Just s@(_:_) <- stk = ("stack" .= reverse s) : rest
| otherwise = rest
rest =
[ "type" .= show (typeOf e)
, "name" .= eName e
, "txt" .= show e
]
haxlExceptionToException
:: (MiddleException e) => e -> SomeException
haxlExceptionToException = toException . HaxlException Nothing
haxlExceptionFromException
:: (MiddleException e) => SomeException -> Maybe e
haxlExceptionFromException x = do
HaxlException _ a <- fromException x
cast a
class (Exception a) => MiddleException a where
eName :: a -> String
data TransientError = forall e . (Exception e) => TransientError e
deriving (Typeable)
deriving instance Show TransientError
instance Exception TransientError where
toException = haxlExceptionToException
fromException = haxlExceptionFromException
instance MiddleException TransientError where
eName (TransientError e) = show $ typeOf e
transientErrorToException :: (Exception e) => e -> SomeException
transientErrorToException = toException . TransientError
transientErrorFromException
:: (Exception e) => SomeException -> Maybe e
transientErrorFromException x = do
TransientError a <- fromException x
cast a
data InternalError = forall e . (Exception e) => InternalError e
deriving (Typeable)
deriving instance Show InternalError
instance Exception InternalError where
toException = haxlExceptionToException
fromException = haxlExceptionFromException
instance MiddleException InternalError where
eName (InternalError e) = show $ typeOf e
internalErrorToException :: (Exception e) => e -> SomeException
internalErrorToException = toException . InternalError
internalErrorFromException
:: (Exception e) => SomeException -> Maybe e
internalErrorFromException x = do
InternalError a <- fromException x
cast a
data LogicError = forall e . (Exception e) => LogicError e
deriving (Typeable)
deriving instance Show LogicError
instance Exception LogicError where
toException = haxlExceptionToException
fromException = haxlExceptionFromException
instance MiddleException LogicError where
eName (LogicError e) = show $ typeOf e
logicErrorToException :: (Exception e) => e -> SomeException
logicErrorToException = toException . LogicError
logicErrorFromException
:: (Exception e) => SomeException -> Maybe e
logicErrorFromException x = do
LogicError a <- fromException x
cast a
data LogicBug = forall e . (Exception e) => LogicBug e
deriving (Typeable)
deriving instance Show LogicBug
instance Exception LogicBug where
toException = haxlExceptionToException
fromException = haxlExceptionFromException
instance MiddleException LogicBug where
eName (LogicBug e) = show $ typeOf e
logicBugToException :: (Exception e) => e -> SomeException
logicBugToException = toException . LogicBug
logicBugFromException
:: (Exception e) => SomeException -> Maybe e
logicBugFromException x = do
LogicBug a <- fromException x
cast a
newtype CriticalError = CriticalError Text
deriving (Typeable, Binary, Eq, Show)
instance Exception CriticalError where
toException = internalErrorToException
fromException = internalErrorFromException
newtype NonHaxlException = NonHaxlException Text
deriving (Typeable, Binary, Eq, Show)
instance Exception NonHaxlException where
toException = internalErrorToException
fromException = internalErrorFromException
newtype NotFound = NotFound Text
deriving (Typeable, Binary, Eq, Show)
instance Exception NotFound where
toException = logicErrorToException
fromException = logicErrorFromException
newtype UnexpectedType = UnexpectedType Text
deriving (Typeable, Eq, Show)
instance Exception UnexpectedType where
toException = logicErrorToException
fromException = logicErrorFromException
newtype EmptyList = EmptyList Text
deriving (Typeable, Eq, Show)
instance Exception EmptyList where
toException = logicErrorToException
fromException = logicErrorFromException
newtype JSONError = JSONError Text
deriving (Typeable, Eq, Show)
instance Exception JSONError where
toException = logicErrorToException
fromException = logicErrorFromException
newtype InvalidParameter = InvalidParameter Text
deriving (Typeable, Eq, Show)
instance Exception InvalidParameter where
toException = logicErrorToException
fromException = logicErrorFromException
newtype MonadFail = MonadFail Text
deriving (Typeable, Eq, Show)
instance Exception MonadFail where
toException = logicErrorToException
fromException = logicErrorFromException
newtype FetchError = FetchError Text
deriving (Typeable, Eq, Show)
instance Exception FetchError where
toException = transientErrorToException
fromException = transientErrorFromException
newtype DataSourceError = DataSourceError Text
deriving (Typeable, Eq, Show)
instance Exception DataSourceError where
toException = internalErrorToException
fromException = internalErrorFromException
asHaxlException :: SomeException -> HaxlException
asHaxlException e
| Just haxl_exception <- fromException e =
haxl_exception
| otherwise =
HaxlException Nothing (InternalError (NonHaxlException (textShow e)))
rethrowAsyncExceptions :: SomeException -> IO ()
rethrowAsyncExceptions e
| Just SomeAsyncException{} <- fromException e = Exception.throw e
| Just AllocationLimitExceeded{} <- fromException e = Exception.throw e
| otherwise = return ()
tryWithRethrow :: IO a -> IO (Either SomeException a)
tryWithRethrow io =
(Right <$> io) `catch` \e -> do rethrowAsyncExceptions e ; return (Left e)