| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Haxl.Core.Exception
Description
An exception hierarchy that can be used with the Haxl monad.
The Haxl framework may throw exceptions from this hierarchy: for
example, a misbehaving data source causes dataFetch to throw a
DataSourceError. The combinator withDefault from
Haxl.Core.Prelude uses this hierarchy to provide default values
for expressions that raise TransientError or LogicError
exceptions.
You are under no obligations to use this hierarchy for your own
exceptions, but you might find it useful nonetheless; for
withDefault to be useful, for example, you'll want your
exceptions to be children of LogicError or TransientError as
appropriate.
Most users should import Haxl.Core instead of importing this module directly.
Synopsis
- data HaxlException = forall e.MiddleException e => HaxlException (Maybe Stack) e
- data InternalError = forall e.Exception e => InternalError e
- internalErrorToException :: Exception e => e -> SomeException
- internalErrorFromException :: Exception e => SomeException -> Maybe e
- data LogicError = forall e.Exception e => LogicError e
- logicErrorToException :: Exception e => e -> SomeException
- logicErrorFromException :: Exception e => SomeException -> Maybe e
- data LogicBug = forall e.Exception e => LogicBug e
- logicBugToException :: Exception e => e -> SomeException
- logicBugFromException :: Exception e => SomeException -> Maybe e
- data TransientError = forall e.Exception e => TransientError e
- transientErrorToException :: Exception e => e -> SomeException
- transientErrorFromException :: Exception e => SomeException -> Maybe e
- newtype CriticalError = CriticalError Text
- newtype DataSourceError = DataSourceError Text
- newtype NonHaxlException = NonHaxlException Text
- newtype NotFound = NotFound Text
- newtype UnexpectedType = UnexpectedType Text
- newtype EmptyList = EmptyList Text
- newtype JSONError = JSONError Text
- newtype InvalidParameter = InvalidParameter Text
- newtype MonadFail = MonadFail Text
- newtype FetchError = FetchError Text
- asHaxlException :: SomeException -> HaxlException
- class Exception a => MiddleException a where
- rethrowAsyncExceptions :: SomeException -> IO ()
- tryWithRethrow :: IO a -> IO (Either SomeException a)
Documentation
data HaxlException Source #
We have a 3-tiered hierarchy of exceptions, with HaxlException at
the top, and all Haxl exceptions as children of this. Users should
never deal directly with HaxlExceptions.
The main types of exceptions are:
InternalError- Something is wrong with Haxl core.
LogicBug- Something is wrong with Haxl client code.
LogicError- Things that really should be return values, e.g. NotFound.
TransientError- Something is temporarily failing (usually in a fetch).
These are not meant to be thrown (but likely be caught). Thrown
exceptions should be a subclass of one of these. There are some
generic leaf exceptions defined below this, such as FetchError
(generic transient failure) or CriticalError (internal failure).
Constructors
| forall e.MiddleException e => HaxlException (Maybe Stack) e |
Instances
| ToJSON HaxlException Source # | These need to be serializable to JSON to cross FFI boundaries. |
Defined in Haxl.Core.Exception Methods toJSON :: HaxlException -> Value # toEncoding :: HaxlException -> Encoding # toJSONList :: [HaxlException] -> Value # toEncodingList :: [HaxlException] -> Encoding # omitField :: HaxlException -> Bool # | |
| Exception HaxlException Source # | |
Defined in Haxl.Core.Exception Methods toException :: HaxlException -> SomeException # fromException :: SomeException -> Maybe HaxlException # displayException :: HaxlException -> String # | |
| Show HaxlException Source # | |
Defined in Haxl.Core.Exception Methods showsPrec :: Int -> HaxlException -> ShowS # show :: HaxlException -> String # showList :: [HaxlException] -> ShowS # | |
Exception categories
data InternalError Source #
For errors in Haxl core code.
Constructors
| forall e.Exception e => InternalError e |
Instances
| Exception InternalError Source # | |
Defined in Haxl.Core.Exception Methods toException :: InternalError -> SomeException # fromException :: SomeException -> Maybe InternalError # displayException :: InternalError -> String # | |
| Show InternalError Source # | |
Defined in Haxl.Core.Exception Methods showsPrec :: Int -> InternalError -> ShowS # show :: InternalError -> String # showList :: [InternalError] -> ShowS # | |
| MiddleException InternalError Source # | |
Defined in Haxl.Core.Exception Methods eName :: InternalError -> String Source # | |
internalErrorToException :: Exception e => e -> SomeException Source #
internalErrorFromException :: Exception e => SomeException -> Maybe e Source #
data LogicError Source #
For errors in Haxl client code.
Constructors
| forall e.Exception e => LogicError e |
Instances
| Exception LogicError Source # | |
Defined in Haxl.Core.Exception Methods toException :: LogicError -> SomeException # fromException :: SomeException -> Maybe LogicError # displayException :: LogicError -> String # | |
| Show LogicError Source # | |
Defined in Haxl.Core.Exception Methods showsPrec :: Int -> LogicError -> ShowS # show :: LogicError -> String # showList :: [LogicError] -> ShowS # | |
| MiddleException LogicError Source # | |
Defined in Haxl.Core.Exception Methods eName :: LogicError -> String Source # | |
logicErrorToException :: Exception e => e -> SomeException Source #
logicErrorFromException :: Exception e => SomeException -> Maybe e Source #
Instances
| Exception LogicBug Source # | |
Defined in Haxl.Core.Exception Methods toException :: LogicBug -> SomeException # fromException :: SomeException -> Maybe LogicBug # displayException :: LogicBug -> String # | |
| Show LogicBug Source # | |
| MiddleException LogicBug Source # | |
logicBugToException :: Exception e => e -> SomeException Source #
logicBugFromException :: Exception e => SomeException -> Maybe e Source #
data TransientError Source #
For transient failures.
Constructors
| forall e.Exception e => TransientError e |
Instances
| Exception TransientError Source # | |
Defined in Haxl.Core.Exception Methods toException :: TransientError -> SomeException # | |
| Show TransientError Source # | |
Defined in Haxl.Core.Exception Methods showsPrec :: Int -> TransientError -> ShowS # show :: TransientError -> String # showList :: [TransientError] -> ShowS # | |
| MiddleException TransientError Source # | |
Defined in Haxl.Core.Exception Methods eName :: TransientError -> String Source # | |
transientErrorToException :: Exception e => e -> SomeException Source #
transientErrorFromException :: Exception e => SomeException -> Maybe e Source #
Internal exceptions
newtype CriticalError Source #
Generic "critical" exception. Something internal is borked. Panic.
Constructors
| CriticalError Text |
Instances
| Exception CriticalError Source # | |
Defined in Haxl.Core.Exception Methods toException :: CriticalError -> SomeException # fromException :: SomeException -> Maybe CriticalError # displayException :: CriticalError -> String # | |
| Show CriticalError Source # | |
Defined in Haxl.Core.Exception Methods showsPrec :: Int -> CriticalError -> ShowS # show :: CriticalError -> String # showList :: [CriticalError] -> ShowS # | |
| Binary CriticalError Source # | |
Defined in Haxl.Core.Exception | |
| Eq CriticalError Source # | |
Defined in Haxl.Core.Exception Methods (==) :: CriticalError -> CriticalError -> Bool # (/=) :: CriticalError -> CriticalError -> Bool # | |
newtype DataSourceError Source #
A data source did something wrong
Constructors
| DataSourceError Text |
Instances
| Exception DataSourceError Source # | |
Defined in Haxl.Core.Exception Methods toException :: DataSourceError -> SomeException # | |
| Show DataSourceError Source # | |
Defined in Haxl.Core.Exception Methods showsPrec :: Int -> DataSourceError -> ShowS # show :: DataSourceError -> String # showList :: [DataSourceError] -> ShowS # | |
| Eq DataSourceError Source # | |
Defined in Haxl.Core.Exception Methods (==) :: DataSourceError -> DataSourceError -> Bool # (/=) :: DataSourceError -> DataSourceError -> Bool # | |
newtype NonHaxlException Source #
Exceptions that are converted to HaxlException by
asHaxlException. Typically these will be pure exceptions,
e.g., the error function in pure code, or a pattern-match
failure.
Constructors
| NonHaxlException Text |
Instances
| Exception NonHaxlException Source # | |
Defined in Haxl.Core.Exception Methods toException :: NonHaxlException -> SomeException # | |
| Show NonHaxlException Source # | |
Defined in Haxl.Core.Exception Methods showsPrec :: Int -> NonHaxlException -> ShowS # show :: NonHaxlException -> String # showList :: [NonHaxlException] -> ShowS # | |
| Binary NonHaxlException Source # | |
Defined in Haxl.Core.Exception Methods put :: NonHaxlException -> Put # get :: Get NonHaxlException # putList :: [NonHaxlException] -> Put # | |
| Eq NonHaxlException Source # | |
Defined in Haxl.Core.Exception Methods (==) :: NonHaxlException -> NonHaxlException -> Bool # (/=) :: NonHaxlException -> NonHaxlException -> Bool # | |
Logic exceptions
Generic "something was not found" exception.
Instances
| Exception NotFound Source # | |
Defined in Haxl.Core.Exception Methods toException :: NotFound -> SomeException # fromException :: SomeException -> Maybe NotFound # displayException :: NotFound -> String # | |
| Show NotFound Source # | |
| Binary NotFound Source # | |
| Eq NotFound Source # | |
newtype UnexpectedType Source #
Generic "something had the wrong type" exception.
Constructors
| UnexpectedType Text |
Instances
| Exception UnexpectedType Source # | |
Defined in Haxl.Core.Exception Methods toException :: UnexpectedType -> SomeException # | |
| Show UnexpectedType Source # | |
Defined in Haxl.Core.Exception Methods showsPrec :: Int -> UnexpectedType -> ShowS # show :: UnexpectedType -> String # showList :: [UnexpectedType] -> ShowS # | |
| Eq UnexpectedType Source # | |
Defined in Haxl.Core.Exception Methods (==) :: UnexpectedType -> UnexpectedType -> Bool # (/=) :: UnexpectedType -> UnexpectedType -> Bool # | |
Generic "input list was empty" exception.
Instances
| Exception EmptyList Source # | |
Defined in Haxl.Core.Exception Methods toException :: EmptyList -> SomeException # fromException :: SomeException -> Maybe EmptyList # displayException :: EmptyList -> String # | |
| Show EmptyList Source # | |
| Eq EmptyList Source # | |
Generic "Incorrect assumptions about JSON data" exception.
Instances
| Exception JSONError Source # | |
Defined in Haxl.Core.Exception Methods toException :: JSONError -> SomeException # fromException :: SomeException -> Maybe JSONError # displayException :: JSONError -> String # | |
| Show JSONError Source # | |
| Eq JSONError Source # | |
newtype InvalidParameter Source #
Generic "passing some invalid parameter" exception.
Constructors
| InvalidParameter Text |
Instances
| Exception InvalidParameter Source # | |
Defined in Haxl.Core.Exception Methods toException :: InvalidParameter -> SomeException # | |
| Show InvalidParameter Source # | |
Defined in Haxl.Core.Exception Methods showsPrec :: Int -> InvalidParameter -> ShowS # show :: InvalidParameter -> String # showList :: [InvalidParameter] -> ShowS # | |
| Eq InvalidParameter Source # | |
Defined in Haxl.Core.Exception Methods (==) :: InvalidParameter -> InvalidParameter -> Bool # (/=) :: InvalidParameter -> InvalidParameter -> Bool # | |
Generic "fail was called" exception.
Instances
| Exception MonadFail Source # | |
Defined in Haxl.Core.Exception Methods toException :: MonadFail -> SomeException # fromException :: SomeException -> Maybe MonadFail # displayException :: MonadFail -> String # | |
| Show MonadFail Source # | |
| Eq MonadFail Source # | |
Transient exceptions
newtype FetchError Source #
Generic transient fetching exceptions.
Constructors
| FetchError Text |
Instances
| Exception FetchError Source # | |
Defined in Haxl.Core.Exception Methods toException :: FetchError -> SomeException # fromException :: SomeException -> Maybe FetchError # displayException :: FetchError -> String # | |
| Show FetchError Source # | |
Defined in Haxl.Core.Exception Methods showsPrec :: Int -> FetchError -> ShowS # show :: FetchError -> String # showList :: [FetchError] -> ShowS # | |
| Eq FetchError Source # | |
Defined in Haxl.Core.Exception | |
Exception utilities
asHaxlException :: SomeException -> HaxlException Source #
Converts all exceptions that are not derived from HaxlException
into NonHaxlException, using show.
class Exception a => MiddleException a where Source #
Instances
| MiddleException InternalError Source # | |
Defined in Haxl.Core.Exception Methods eName :: InternalError -> String Source # | |
| MiddleException LogicBug Source # | |
| MiddleException LogicError Source # | |
Defined in Haxl.Core.Exception Methods eName :: LogicError -> String Source # | |
| MiddleException TransientError Source # | |
Defined in Haxl.Core.Exception Methods eName :: TransientError -> String Source # | |
rethrowAsyncExceptions :: SomeException -> IO () Source #
tryWithRethrow :: IO a -> IO (Either SomeException a) Source #