servant-exceptions-0.1.1

Safe HaskellNone
LanguageHaskell2010

Servant.Exception

Synopsis

Documentation

data Throws (e :: *) Source #

Instances

HasServer * ((:<|>) ((:>) * * (Throws e) api1) ((:>) * * (Throws e) api2)) context => HasServer * ((:>) * * (Throws e) ((:<|>) api1 api2)) context Source #

Transitive application of Throws on (:|).

Associated Types

type ServerT ((* :> *) (Throws e) (api1 :<|> api2)) (context :: (* :> *) (Throws e) (api1 :<|> api2)) (m :: * -> *) :: * #

Methods

route :: Proxy ((* :> *) (Throws e) (api1 :<|> api2)) context -> Context context -> Delayed env (Server ((* :> *) (Throws e) (api1 :<|> api2)) context) -> Router env #

hoistServerWithContext :: Proxy ((* :> *) (Throws e) (api1 :<|> api2)) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> *) (Throws e) (api1 :<|> api2)) context m -> ServerT ((* :> *) (Throws e) (api1 :<|> api2)) context n #

HasServer * ((:>) k * api ((:>) * k1 (Throws e) upstream)) context => HasServer * ((:>) * * (Throws e) ((:>) k k1 api upstream)) context Source #

Push Throws further "upstream".

Associated Types

type ServerT ((* :> *) (Throws e) ((k :> k1) api upstream)) (context :: (* :> *) (Throws e) ((k :> k1) api upstream)) (m :: * -> *) :: * #

Methods

route :: Proxy ((* :> *) (Throws e) ((k :> k1) api upstream)) context -> Context context -> Delayed env (Server ((* :> *) (Throws e) ((k :> k1) api upstream)) context) -> Router env #

hoistServerWithContext :: Proxy ((* :> *) (Throws e) ((k :> k1) api upstream)) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> *) (Throws e) ((k :> k1) api upstream)) context m -> ServerT ((* :> *) (Throws e) ((k :> k1) api upstream)) context n #

(Exception e, ToServantErr e, AllMimeRender ct e, HasServer * (Verb k * mt st ct a) context) => HasServer * ((:>) * * (Throws e) (Verb k * mt st ct a)) context Source #

Main HasServer instance for Throws e. Catches exceptions of type e in the upstream server and encodes them using ToServantErr and MimeRender.

Associated Types

type ServerT ((* :> *) (Throws e) (Verb k * mt st ct a)) (context :: (* :> *) (Throws e) (Verb k * mt st ct a)) (m :: * -> *) :: * #

Methods

route :: Proxy ((* :> *) (Throws e) (Verb k * mt st ct a)) context -> Context context -> Delayed env (Server ((* :> *) (Throws e) (Verb k * mt st ct a)) context) -> Router env #

hoistServerWithContext :: Proxy ((* :> *) (Throws e) (Verb k * mt st ct a)) context -> Proxy [*] context -> (forall x. m x -> n x) -> ServerT ((* :> *) (Throws e) (Verb k * mt st ct a)) context m -> ServerT ((* :> *) (Throws e) (Verb k * mt st ct a)) context n #

type ServerT * ((:>) * * (Throws e) ((:<|>) api1 api2)) m Source # 
type ServerT * ((:>) * * (Throws e) ((:<|>) api1 api2)) m = ServerT * ((:<|>) ((:>) * * (Throws e) api1) ((:>) * * (Throws e) api2)) m
type ServerT * ((:>) * * (Throws e) ((:>) k k1 api upstream)) m Source # 
type ServerT * ((:>) * * (Throws e) ((:>) k k1 api upstream)) m = ServerT * ((:>) k * api ((:>) * k1 (Throws e) upstream)) m
type ServerT * ((:>) * * (Throws e) (Verb k * mt st ct a)) m Source # 
type ServerT * ((:>) * * (Throws e) (Verb k * mt st ct a)) m = ServerT * (Verb k * mt st ct a) m

class (Typeable * e, Show e) => Exception e where #

Any type that you wish to throw or catch as an exception must be an instance of the Exception class. The simplest case is a new exception type directly below the root:

data MyException = ThisException | ThatException
    deriving Show

instance Exception MyException

The default method definitions in the Exception class do what we need in this case. You can now throw and catch ThisException and ThatException as exceptions:

*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException))
Caught ThisException

In more complicated examples, you may wish to define a whole hierarchy of exceptions:

---------------------------------------------------------------------
-- Make the root exception type for all the exceptions in a compiler

data SomeCompilerException = forall e . Exception e => SomeCompilerException e

instance Show SomeCompilerException where
    show (SomeCompilerException e) = show e

instance Exception SomeCompilerException

compilerExceptionToException :: Exception e => e -> SomeException
compilerExceptionToException = toException . SomeCompilerException

compilerExceptionFromException :: Exception e => SomeException -> Maybe e
compilerExceptionFromException x = do
    SomeCompilerException a <- fromException x
    cast a

---------------------------------------------------------------------
-- Make a subhierarchy for exceptions in the frontend of the compiler

data SomeFrontendException = forall e . Exception e => SomeFrontendException e

instance Show SomeFrontendException where
    show (SomeFrontendException e) = show e

instance Exception SomeFrontendException where
    toException = compilerExceptionToException
    fromException = compilerExceptionFromException

frontendExceptionToException :: Exception e => e -> SomeException
frontendExceptionToException = toException . SomeFrontendException

frontendExceptionFromException :: Exception e => SomeException -> Maybe e
frontendExceptionFromException x = do
    SomeFrontendException a <- fromException x
    cast a

---------------------------------------------------------------------
-- Make an exception type for a particular frontend compiler exception

data MismatchedParentheses = MismatchedParentheses
    deriving Show

instance Exception MismatchedParentheses where
    toException   = frontendExceptionToException
    fromException = frontendExceptionFromException

We can now catch a MismatchedParentheses exception as MismatchedParentheses, SomeFrontendException or SomeCompilerException, but not other types, e.g. IOException:

*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: IOException))
*** Exception: MismatchedParentheses

Methods

toException :: e -> SomeException #

fromException :: SomeException -> Maybe e #

displayException :: e -> String #

Render this exception value in a human-friendly manner.

Default implementation: show.

Since: 4.8.0.0

Instances

Exception Void

Since: 4.8.0.0

Exception BlockedIndefinitelyOnMVar

Since: 4.1.0.0

Exception BlockedIndefinitelyOnSTM

Since: 4.1.0.0

Exception Deadlock

Since: 4.1.0.0

Exception AllocationLimitExceeded

Since: 4.8.0.0

Exception CompactionFailed

Since: 4.10.0.0

Exception AssertionFailed

Since: 4.1.0.0

Exception SomeAsyncException

Since: 4.7.0.0

Exception AsyncException

Since: 4.7.0.0

Exception ArrayException

Since: 4.1.0.0

Exception ExitCode

Since: 4.1.0.0

Exception IOException

Since: 4.1.0.0

Exception ErrorCall

Since: 4.0.0.0

Exception ArithException

Since: 4.0.0.0

Exception SomeException

Since: 3.0

Exception ASCII7_Invalid 

Methods

toException :: ASCII7_Invalid -> SomeException #

fromException :: SomeException -> Maybe ASCII7_Invalid #

displayException :: ASCII7_Invalid -> String #

Exception ISO_8859_1_Invalid 

Methods

toException :: ISO_8859_1_Invalid -> SomeException #

fromException :: SomeException -> Maybe ISO_8859_1_Invalid #

displayException :: ISO_8859_1_Invalid -> String #

Exception UTF16_Invalid 

Methods

toException :: UTF16_Invalid -> SomeException #

fromException :: SomeException -> Maybe UTF16_Invalid #

displayException :: UTF16_Invalid -> String #

Exception UTF32_Invalid 

Methods

toException :: UTF32_Invalid -> SomeException #

fromException :: SomeException -> Maybe UTF32_Invalid #

displayException :: UTF32_Invalid -> String #

Exception InvalidAccess 
Exception ResourceCleanupException 
Exception ServantErr 
Exception ServantException # 

mapException :: (Exception e1, Exception e2, MonadCatch m) => (e1 -> e2) -> m a -> m a Source #

Catch and rethrow using mapping function f.