| Copyright | Dennis Gosnell 2017 |
|---|---|
| License | BSD3 |
| Maintainer | Dennis Gosnell (cdep.illabout@gmail.com) |
| Stability | experimental |
| Portability | unknown |
| Safe Haskell | None |
| Language | Haskell2010 |
Servant.Checked.Exceptions
Contents
Description
This module gives you the ability to specify which errors are thrown by a
Servant api. This is done with the Throws data type. Here is an example of
creating an api that uses Throws:
type Api =
"author" :>
Capture "author-id" AuthorId :>
Throws CouldNotConnectToDbError :>
Throws AuthorNotFoundError :>
Get '[JSON] Author
This api will return an Author for a given AuthorId. Throws is used
to indicate that this api will potentially return two different errors:
CouldNotConnectToDbError and AuthorNotFoundError.
These two errors might be defined like this:
data CouldNotConnectToDbError = CouldNotConnectToDbError
deriving (Eq, Read, Show)
data AuthorNotFoundError = AuthorNotFoundError
deriving (Eq, Read, Show)
Writing the server handler for this api will look like the following. Notice
how the Envelope type is used:
getAuthorHandler
:: AuthorId
-> Handler (Envelope '[DatabaseError, AuthorNotFoundError] Author)
getAuthorHandler authorId = do
eitherAuthor <- getAuthorFromDb authorId
case eitherAuthor of
Left NoDb -> pure $ toErrEnvelope CouldNotConnectToDbError
Left NoAuthor -> pure $ toErrEnvelope AuthorNotFoundError
Right author -> pure $ toSuccEnvelope author
getAuthorFromDb :: AuthorId -> Handler (Either DbErr Author)
getAuthorFromDb = ...
data DbErr = NoDb | NoAuthor
represents a
response that will contain an Envelope '[DatabaseError, AuthorNotFoundError] AuthorAuthor on success, or contain either a
DatabaseError or a AuthorNotFoundError on error.
Under the hood, Envelope is using an extensible sum-type (OpenUnion) to
represent possible errors. Working with an api that returns two possible
errors is just as easy as working with an api that returns three possible
errors.
Clients will also use the Envelope type:
getAuthor
:: AuthorId
-> ClientM (Envelope '[DatabaseError, AuthorNotFoundError] Author)
getAuthor = client (Proxy :: Proxy Api)
It is easy to do case analysis (similar to pattern matching) on the Envelope
type with the catchesEnvelope function.
Checkout the example in the repository on Github. It includes a fleshed-out example of an api, server, client, and documentation. The README.md shows how to compile and run the examples.
- data Throws (e :: *)
- data NoThrow
- class ErrStatus e where
- data Status :: *
- data VerbWithErr (method :: k1) (successStatusCode :: Nat) (contentTypes :: [*]) (es :: [*]) a
- type GetWithErr = VerbWithErr GET 200
- type PostWithErr = VerbWithErr POST 200
- type PutWithErr = VerbWithErr PUT 200
- type DeleteWithErr = VerbWithErr DELETE 200
- type PatchWithErr = VerbWithErr PATCH 200
- type PostCreatedWithErr = VerbWithErr POST 201
- type GetAcceptedWithErr = VerbWithErr GET 202
- type PostAcceptedWithErr = VerbWithErr POST 202
- type DeleteAcceptedWithErr = VerbWithErr DELETE 202
- type PatchAcceptedWithErr = VerbWithErr PATCH 202
- type PutAcceptedWithErr = VerbWithErr PUT 202
- type GetNonAuthoritativeWithErr = VerbWithErr GET 203
- type PostNonAuthoritativeWithErr = VerbWithErr POST 203
- type DeleteNonAuthoritativeWithErr = VerbWithErr DELETE 203
- type PatchNonAuthoritativeWithErr = VerbWithErr PATCH 203
- type PutNonAuthoritativeWithErr = VerbWithErr PUT 203
- type GetNoContentWithErr = VerbWithErr GET 204
- type PostNoContentWithErr = VerbWithErr POST 204
- type DeleteNoContentWithErr = VerbWithErr DELETE 204
- type PatchNoContentWithErr = VerbWithErr PATCH 204
- type PutNoContentWithErr = VerbWithErr PUT 204
- type GetResetContentWithErr = VerbWithErr GET 205
- type PostResetContentWithErr = VerbWithErr POST 205
- type DeleteResetContentWithErr = VerbWithErr DELETE 205
- type PatchResetContentWithErr = VerbWithErr PATCH 205
- type PutResetContentWithErr = VerbWithErr PUT 205
- type GetPartialContentWithErr = VerbWithErr GET 206
- data Envelope es a
- = ErrEnvelope (OpenUnion es)
- | SuccEnvelope a
- toSuccEnvelope :: a -> Envelope es a
- toErrEnvelope :: IsMember e es => e -> Envelope es a
- pureSuccEnvelope :: Applicative m => a -> m (Envelope es a)
- pureErrEnvelope :: (Applicative m, IsMember e es) => e -> m (Envelope es a)
- envelope :: (OpenUnion es -> c) -> (a -> c) -> Envelope es a -> c
- emptyEnvelope :: Envelope '[] a -> a
- fromEnvelope :: (OpenUnion es -> a) -> Envelope es a -> a
- fromEnvelopeOr :: Envelope es a -> (OpenUnion es -> a) -> a
- fromEnvelopeM :: Applicative m => (OpenUnion es -> m a) -> Envelope es a -> m a
- fromEnvelopeOrM :: Applicative m => Envelope es a -> (OpenUnion es -> m a) -> m a
- errEnvelopeMatch :: forall e es a. IsMember e es => Envelope es a -> Maybe e
- catchesEnvelope :: forall tuple es a x. ToOpenProduct tuple (ReturnX x es) => tuple -> (a -> x) -> Envelope es a -> x
- _SuccEnvelope :: Prism (Envelope es a) (Envelope es b) a b
- _ErrEnvelope :: Prism (Envelope es a) (Envelope es' a) (OpenUnion es) (OpenUnion es')
- _ErrEnvelopeErr :: forall e es a. IsMember e es => Prism' (Envelope es a) e
- envelopeToEither :: Envelope es a -> Either (OpenUnion es) a
- eitherToEnvelope :: Either (OpenUnion es) a -> Envelope es a
- isoEnvelopeEither :: Iso (Envelope es a) (Envelope fs b) (Either (OpenUnion es) a) (Either (OpenUnion fs) b)
- module Data.WorldPeace
- module Servant.Checked.Exceptions.Internal.Servant.Docs
Servant Types
Throws API parameter
NoThrow API parameter
NoThrow is used to indicate that an API will not throw an error, but
that it will still return a response wrapped in a
Envelope.
Examples
Create an API using NoThrow:
>>>import Servant.API (Get, JSON, (:>))>>>type API = NoThrow :> Get '[JSON] Int
A servant-server handler for this type would look like the following:
apiHandler ::Handler(Envelope'[] Int) apiHandler =pureSuccEnvelope3
HTTP Error Status Code
class ErrStatus e where Source #
Minimal complete definition
Methods
toErrStatus :: e -> Status Source #
HTTP Status.
Only the statusCode is used for comparisons.
Please use mkStatus to create status codes from code and message, or the Enum instance or the
status code constants (like ok200). There might be additional record members in the future.
Note that the Show instance is only for debugging.
Verbs
data VerbWithErr (method :: k1) (successStatusCode :: Nat) (contentTypes :: [*]) (es :: [*]) a Source #
Instances
| Generic (VerbWithErr k1 k method successStatusCode contentTypes es a) Source # | |
| type Rep (VerbWithErr k1 k method successStatusCode contentTypes es a) Source # | |
Specialized Verbs
HTTP 200
type GetWithErr = VerbWithErr GET 200 Source #
type PostWithErr = VerbWithErr POST 200 Source #
type PutWithErr = VerbWithErr PUT 200 Source #
type DeleteWithErr = VerbWithErr DELETE 200 Source #
type PatchWithErr = VerbWithErr PATCH 200 Source #
HTTP 201
type PostCreatedWithErr = VerbWithErr POST 201 Source #
HTTP 202
type GetAcceptedWithErr = VerbWithErr GET 202 Source #
type PostAcceptedWithErr = VerbWithErr POST 202 Source #
type DeleteAcceptedWithErr = VerbWithErr DELETE 202 Source #
type PatchAcceptedWithErr = VerbWithErr PATCH 202 Source #
type PutAcceptedWithErr = VerbWithErr PUT 202 Source #
HTTP 203
type GetNonAuthoritativeWithErr = VerbWithErr GET 203 Source #
type PostNonAuthoritativeWithErr = VerbWithErr POST 203 Source #
type DeleteNonAuthoritativeWithErr = VerbWithErr DELETE 203 Source #
type PatchNonAuthoritativeWithErr = VerbWithErr PATCH 203 Source #
type PutNonAuthoritativeWithErr = VerbWithErr PUT 203 Source #
HTTP 204
type GetNoContentWithErr = VerbWithErr GET 204 Source #
type PostNoContentWithErr = VerbWithErr POST 204 Source #
type DeleteNoContentWithErr = VerbWithErr DELETE 204 Source #
type PatchNoContentWithErr = VerbWithErr PATCH 204 Source #
type PutNoContentWithErr = VerbWithErr PUT 204 Source #
HTTP 205
type GetResetContentWithErr = VerbWithErr GET 205 Source #
type PostResetContentWithErr = VerbWithErr POST 205 Source #
type DeleteResetContentWithErr = VerbWithErr DELETE 205 Source #
type PatchResetContentWithErr = VerbWithErr PATCH 205 Source #
type PutResetContentWithErr = VerbWithErr PUT 205 Source #
HTTP 206
type GetPartialContentWithErr = VerbWithErr GET 206 Source #
Envelope response wrapper
This Envelope type is a used as a wrapper around either an OpenUnion
with an error or a successful value. It is similar to an ,
but where the Either e ae is specialized to . The most important
difference from OpenUnion esEither is the the FromJSON and ToJSON instances.
Given an , we know that the envelope
could be a Envelope '[String, Double] ()SuccEnvelope and contain (). Or it could be a ErrEnvelope
that contains either a String or a Double. It might be simpler to
think of it as a type like .Either String (Either Double ())
An Envelope can be created with the toErrEnvelope and toSuccEnvelope
functions. The Prisms _SuccEnvelope, _ErrEnvelope, and
_ErrEnvelopeErr can be used to get values out of an Envelope.
Constructors
| ErrEnvelope (OpenUnion es) | |
| SuccEnvelope a |
Instances
| Monad (Envelope es) Source # | |
| Functor (Envelope es) Source # | |
| MonadFix (Envelope es) Source # | |
| Applicative (Envelope es) Source # | |
| Foldable (Envelope es) Source # | |
| Traversable (Envelope es) Source # | |
| (Eq (OpenUnion es), Eq a) => Eq (Envelope es a) Source # | |
| (Data (OpenUnion es), Data a, Typeable [*] es) => Data (Envelope es a) Source # | |
| (Ord (OpenUnion es), Ord a) => Ord (Envelope es a) Source # | |
| (Read (OpenUnion es), Read a) => Read (Envelope es a) Source # | |
| (Show (OpenUnion es), Show a) => Show (Envelope es a) Source # | |
| Generic (Envelope es a) Source # | |
| Semigroup (Envelope es a) Source # | |
| (ToJSON (OpenUnion es), ToJSON a) => ToJSON (Envelope es a) Source # | This Here is an example of a
Here is an example of a
|
| (FromJSON (OpenUnion es), FromJSON a) => FromJSON (Envelope es a) Source # | This is only a valid instance when the For an explanation, see the documentation on the |
| type Rep (Envelope es a) Source # | |
Envelope helper functions
Envelope constructors
toSuccEnvelope :: a -> Envelope es a Source #
This is a function to create a SuccEnvelope.
>>>toSuccEnvelope "hello" :: Envelope '[Double] StringSuccEnvelope "hello"
toErrEnvelope :: IsMember e es => e -> Envelope es a Source #
Create an ErrEnvelope from a member of the OpenUnion.
For instance, here is how to create an ErrEnvelope that contains a
Double:
>>>let double = 3.5 :: Double>>>toErrEnvelope double :: Envelope '[String, Double, Int] ()ErrEnvelope (Identity 3.5)
pureSuccEnvelope :: Applicative m => a -> m (Envelope es a) Source #
pureSuccEnvelope is toSuccEnvelope lifted up to an Applicative.
pureErrEnvelope :: (Applicative m, IsMember e es) => e -> m (Envelope es a) Source #
pureErrEnvelope is toErrEnvelope lifted up to an Applicative.
Envelope destructors
envelope :: (OpenUnion es -> c) -> (a -> c) -> Envelope es a -> c Source #
Case analysis for Envelopes.
Examples
Here is an example of matching on a SuccEnvelope:
>>>let env = toSuccEnvelope "hello" :: Envelope '[Double, Int] String>>>envelope (const "not a String") id env"hello"
Here is an example of matching on a ErrEnvelope:
>>>let double = 3.5 :: Double>>>let env' = toErrEnvelope double :: Envelope '[Double, Int] String>>>envelope (const "not a String") id env'"not a String"
emptyEnvelope :: Envelope '[] a -> a Source #
Unwrap an Envelope that cannot contain an error.
Examples
>>>let env = toSuccEnvelope "hello" :: Envelope '[] String>>>emptyEnvelope env"hello"
fromEnvelope :: (OpenUnion es -> a) -> Envelope es a -> a Source #
Just like fromEither but for Envelope.
Examples
Here is an example of successfully matching:
>>>let env = toSuccEnvelope "hello" :: Envelope '[Double, Int] String>>>fromEnvelope (const "not a String") env"hello"
Here is an example of unsuccessfully matching:
>>>let double = 3.5 :: Double>>>let env' = toErrEnvelope double :: Envelope '[Double, Int] String>>>fromEnvelope (const "not a String") env'"not a String"
fromEnvelopeOr :: Envelope es a -> (OpenUnion es -> a) -> a Source #
Flipped version of fromEnvelope.
fromEnvelopeM :: Applicative m => (OpenUnion es -> m a) -> Envelope es a -> m a Source #
Lifted version of fromEnvelope.
fromEnvelopeOrM :: Applicative m => Envelope es a -> (OpenUnion es -> m a) -> m a Source #
Flipped version of fromEnvelopeM.
errEnvelopeMatch :: forall e es a. IsMember e es => Envelope es a -> Maybe e Source #
Pull out a specific e from an ErrEnvelope.
Examples
Successfully pull out an e:
>>>let double = 3.5 :: Double>>>let env = toErrEnvelope double :: Envelope '[Double] ()>>>errEnvelopeMatch env :: Maybe DoubleJust 3.5
Unsuccessfully pull out an e:
>>>let env' = toSuccEnvelope () :: Envelope '[Double] ()>>>errEnvelopeMatch env' :: Maybe DoubleNothing>>>let env'' = toErrEnvelope 'c' :: Envelope '[Double, Char] ()>>>errEnvelopeMatch env'' :: Maybe DoubleNothing
catchesEnvelope :: forall tuple es a x. ToOpenProduct tuple (ReturnX x es) => tuple -> (a -> x) -> Envelope es a -> x Source #
An alternate case anaylsis for an Envelope. This method uses a tuple
containing handlers for each potential value of the Envelope. This is
somewhat similar to the catches function.
When working with an Envelope with a large number of possible error types,
it can be easier to use catchesEnvelope than envelope.
Examples
Here is an example of handling an SuccEnvelope with two possible error values.
Notice that a normal tuple is used:
>>>let env = toSuccEnvelope 2.0 :: Envelope '[Int, String] Double>>>let intHandler = (\int -> show int) :: Int -> String>>>let strHandler = (\str -> str) :: String -> String>>>let succHandler = (\dbl -> "got a double") :: Double -> String>>>catchesEnvelope (intHandler, strHandler) succHandler env :: String"got a double"
Here is an example of handling an ErrEnvelope with two possible error values.
Notice that a normal tuple is used to hold the handlers:
>>>let env = toErrEnvelope (3 :: Int) :: Envelope '[Int, String] Double>>>let intHandler = (\int -> show int) :: Int -> String>>>let strHandler = (\str -> str) :: String -> String>>>let succHandler = (\dbl -> "got a double") :: Double -> String>>>catchesEnvelope (intHandler, strHandler) succHandler env :: String"3"
Given an Envelope like , the type of
Envelope '[Int, String] DoublecatchesEnvelope becomes the following:
catchesEnvelope:: (Int-> x,String-> x) -> (Double-> x) ->Envelope'[Int,String]Double-> x
Here is an example of handling an ErrEnvelope with three possible values.
Notice how a 3-tuple is used to hold the handlers:
>>>let env = toErrEnvelope ("hi" :: String) :: Envelope '[Int, String, Char] Double>>>let intHandler = (\int -> show int) :: Int -> String>>>let strHandler = (\str -> str) :: String -> String>>>let chrHandler = (\chr -> [chr]) :: Char -> String>>>let succHandler = (\dbl -> "got a double") :: Double -> String>>>catchesEnvelope (intHandler, strHandler, chrHandler) succHandler env :: String"hi"
Given an Envelope like ,
the type of Envelope '[Int, String, Char] DoublecatchesEnvelope becomes the following:
catchesEnvelope:: (Int-> x,String-> x,Char-> x) -> (Double-> x) ->Envelope'[Int,String,Char]Double-> x
Here is an example of handling an ErrEnvelope with only one possible error value.
Notice that a normal handler is used (not a tuple):
>>>let env = toErrEnvelope (3 :: Int) :: Envelope '[Int] Double>>>let intHandler = (\int -> show int) :: Int -> String>>>let succHandler = (\dbl -> "got a double") :: Double -> String>>>catchesEnvelope intHandler succHandler env :: String"3"
Given an Envelope like , the type of
Envelope '[Int] DoublecatchesEnvelope becomes the following:
catchesEnvelope:: (Int-> x) -> (Double-> x) ->Envelope'[Int]Double-> x
Envelope optics
_SuccEnvelope :: Prism (Envelope es a) (Envelope es b) a b Source #
Lens-compatible Prism to pull out an a from a SuccEnvelope.
Examples
Use _SuccEnvelope to construct an Envelope:
>>>review _SuccEnvelope "hello" :: Envelope '[Double] StringSuccEnvelope "hello"
Use _SuccEnvelope to try to destruct an Envelope into an a:
>>>let env = toSuccEnvelope "hello" :: Envelope '[Double] String>>>preview _SuccEnvelope env :: Maybe StringJust "hello"
Use _SuccEnvelope to try to destruct a 'Envelope into an a
(unsuccessfully):
>>>let double = 3.5 :: Double>>>let env' = toErrEnvelope double :: Envelope '[Double] String>>>preview _SuccEnvelope env' :: Maybe StringNothing
_ErrEnvelope :: Prism (Envelope es a) (Envelope es' a) (OpenUnion es) (OpenUnion es') Source #
Lens-compatible Prism to pull out an from a
OpenUnion esErrEnvelope.
Most users will not use _ErrEnvelope, but instead _ErrEnvelopeErr.
Examples
Use _ErrEnvelope to construct an Envelope:
>>>let string = "hello" :: String>>>review _ErrEnvelope (openUnionLift string) :: Envelope '[String] DoubleErrEnvelope (Identity "hello")
Use _ErrEnvelope to try to destruct an Envelope into an
:OpenUnion es
>>>let double = 3.5 :: Double>>>let env = toErrEnvelope double :: Envelope '[Double] ()>>>preview _ErrEnvelope env :: Maybe (OpenUnion '[Double])Just (Identity 3.5)
Use _ErrEnvelope to try to destruct a 'Envelope into an
(unsuccessfully):OpenUnion es
>>>let env' = toSuccEnvelope () :: Envelope '[Double] ()>>>preview _ErrEnvelope env' :: Maybe (OpenUnion '[Double])Nothing
_ErrEnvelopeErr :: forall e es a. IsMember e es => Prism' (Envelope es a) e Source #
Lens-compatible Prism to pull out a specific e from an ErrEnvelope.
Most users will use _ErrEnvelopeErr instead of _ErrEnvelope.
Examples
Use _ErrEnvelopeErr to construct an Envelope:
>>>let string = "hello" :: String>>>review _ErrEnvelopeErr string :: Envelope '[String] DoubleErrEnvelope (Identity "hello")
Use _ErrEnvelopeErr to try to destruct an Envelope into an e:
>>>let double = 3.5 :: Double>>>let env = toErrEnvelope double :: Envelope '[Double] ()>>>preview _ErrEnvelopeErr env :: Maybe DoubleJust 3.5
Use _ErrEnvelopeErr to try to destruct a 'Envelope into an
e (unsuccessfully):
>>>let env' = toSuccEnvelope () :: Envelope '[Double] ()>>>preview _ErrEnvelopeErr env' :: Maybe DoubleNothing>>>let env'' = toErrEnvelope 'c' :: Envelope '[Double, Char] ()>>>preview _ErrEnvelopeErr env'' :: Maybe DoubleNothing
Envelope and Either
isoEnvelopeEither :: Iso (Envelope es a) (Envelope fs b) (Either (OpenUnion es) a) (Either (OpenUnion fs) b) Source #
Re-exported modules
Data.WorldPeace exports the OpenUnion type as well as other
combinators. It also exports the OpenProduct type and ToProduct type
class used by some of the functions above.
module Data.WorldPeace