servant-checked-exceptions-core-2.1.0.0: Checked exceptions for Servant APIs.

Safe HaskellNone
LanguageHaskell2010

Servant.Checked.Exceptions.Envelope

Contents

Synopsis

Envelope

data Envelope es a Source #

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 Either e a, but where the e is specialized to OpenUnion es. The most important difference from Either is the the FromJSON and ToJSON instances.

Given an Envelope '[String, Double] (), we know that the envelope could be a 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 # 
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

Methods

(>>=) :: Envelope es a -> (a -> Envelope es b) -> Envelope es b #

(>>) :: Envelope es a -> Envelope es b -> Envelope es b #

return :: a -> Envelope es a #

fail :: String -> Envelope es a #

Functor (Envelope es) Source # 
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

Methods

fmap :: (a -> b) -> Envelope es a -> Envelope es b #

(<$) :: a -> Envelope es b -> Envelope es a #

MonadFix (Envelope es) Source # 
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

Methods

mfix :: (a -> Envelope es a) -> Envelope es a #

Applicative (Envelope es) Source # 
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

Methods

pure :: a -> Envelope es a #

(<*>) :: Envelope es (a -> b) -> Envelope es a -> Envelope es b #

liftA2 :: (a -> b -> c) -> Envelope es a -> Envelope es b -> Envelope es c #

(*>) :: Envelope es a -> Envelope es b -> Envelope es b #

(<*) :: Envelope es a -> Envelope es b -> Envelope es a #

Foldable (Envelope es) Source # 
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

Methods

fold :: Monoid m => Envelope es m -> m #

foldMap :: Monoid m => (a -> m) -> Envelope es a -> m #

foldr :: (a -> b -> b) -> b -> Envelope es a -> b #

foldr' :: (a -> b -> b) -> b -> Envelope es a -> b #

foldl :: (b -> a -> b) -> b -> Envelope es a -> b #

foldl' :: (b -> a -> b) -> b -> Envelope es a -> b #

foldr1 :: (a -> a -> a) -> Envelope es a -> a #

foldl1 :: (a -> a -> a) -> Envelope es a -> a #

toList :: Envelope es a -> [a] #

null :: Envelope es a -> Bool #

length :: Envelope es a -> Int #

elem :: Eq a => a -> Envelope es a -> Bool #

maximum :: Ord a => Envelope es a -> a #

minimum :: Ord a => Envelope es a -> a #

sum :: Num a => Envelope es a -> a #

product :: Num a => Envelope es a -> a #

Traversable (Envelope es) Source # 
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

Methods

traverse :: Applicative f => (a -> f b) -> Envelope es a -> f (Envelope es b) #

sequenceA :: Applicative f => Envelope es (f a) -> f (Envelope es a) #

mapM :: Monad m => (a -> m b) -> Envelope es a -> m (Envelope es b) #

sequence :: Monad m => Envelope es (m a) -> m (Envelope es a) #

(Eq (OpenUnion es), Eq a) => Eq (Envelope es a) Source # 
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

Methods

(==) :: Envelope es a -> Envelope es a -> Bool #

(/=) :: Envelope es a -> Envelope es a -> Bool #

(Data (OpenUnion es), Data a, Typeable es) => Data (Envelope es a) Source # 
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Envelope es a -> c (Envelope es a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Envelope es a) #

toConstr :: Envelope es a -> Constr #

dataTypeOf :: Envelope es a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Envelope es a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Envelope es a)) #

gmapT :: (forall b. Data b => b -> b) -> Envelope es a -> Envelope es a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Envelope es a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Envelope es a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Envelope es a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Envelope es a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Envelope es a -> m (Envelope es a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Envelope es a -> m (Envelope es a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Envelope es a -> m (Envelope es a) #

(Ord (OpenUnion es), Ord a) => Ord (Envelope es a) Source # 
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

Methods

compare :: Envelope es a -> Envelope es a -> Ordering #

(<) :: Envelope es a -> Envelope es a -> Bool #

(<=) :: Envelope es a -> Envelope es a -> Bool #

(>) :: Envelope es a -> Envelope es a -> Bool #

(>=) :: Envelope es a -> Envelope es a -> Bool #

max :: Envelope es a -> Envelope es a -> Envelope es a #

min :: Envelope es a -> Envelope es a -> Envelope es a #

(Read (OpenUnion es), Read a) => Read (Envelope es a) Source # 
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

(Show (OpenUnion es), Show a) => Show (Envelope es a) Source # 
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

Methods

showsPrec :: Int -> Envelope es a -> ShowS #

show :: Envelope es a -> String #

showList :: [Envelope es a] -> ShowS #

Generic (Envelope es a) Source # 
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

Associated Types

type Rep (Envelope es a) :: Type -> Type #

Methods

from :: Envelope es a -> Rep (Envelope es a) x #

to :: Rep (Envelope es a) x -> Envelope es a #

Semigroup (Envelope es a) Source # 
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

Methods

(<>) :: Envelope es a -> Envelope es a -> Envelope es a #

sconcat :: NonEmpty (Envelope es a) -> Envelope es a #

stimes :: Integral b => b -> Envelope es a -> Envelope es a #

(ToJSON (OpenUnion es), ToJSON a) => ToJSON (Envelope es a) Source #

This ToJSON instance encodes an Envelope as an object with one of two keys depending on whether it is a SuccEnvelope or an ErrEnvelope.

Here is an example of a SuccEnvelope:

>>> let string = "hello" :: String
>>> let env = toSuccEnvelope string :: Envelope '[Double] String
>>> putByteStrLn $ encode env
{"data":"hello"}

Here is an example of a ErrEnvelope:

>>> let double = 3.5 :: Double
>>> let env' = toErrEnvelope double :: Envelope '[Double] String
>>> putByteStrLn $ encode env'
{"err":3.5}
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

(FromJSON (OpenUnion es), FromJSON a) => FromJSON (Envelope es a) Source #

This is only a valid instance when the FromJSON instances for the es don't overlap.

For an explanation, see the documentation on the FromJSON instance for Union.

Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

ToSample a => ToSample (Envelope es a) Source #

We can generate a sample of an Envelope es a as long as there is a way to generate a sample of the a.

This doesn't need to worry about generating a sample of es, because that is taken care of in the HasDocs instance for Throwing es.

Instance details

Defined in Servant.Checked.Exceptions.Internal.Servant.Docs

Methods

toSamples :: Proxy (Envelope es a) -> [(Text, Envelope es a)] #

type Rep (Envelope es a) Source # 
Instance details

Defined in Servant.Checked.Exceptions.Internal.Envelope

type Rep (Envelope es a) = D1 (MetaData "Envelope" "Servant.Checked.Exceptions.Internal.Envelope" "servant-checked-exceptions-core-2.1.0.0-C4VEfWrdzm54Jj67xD84kn" False) (C1 (MetaCons "ErrEnvelope" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (OpenUnion es))) :+: C1 (MetaCons "SuccEnvelope" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

Helper functions

Envelope Constructors

toSuccEnvelope :: a -> Envelope es a Source #

This is a function to create a SuccEnvelope.

>>> toSuccEnvelope "hello" :: Envelope '[Double] String
SuccEnvelope "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)

Envelope Destructors

envelope :: (OpenUnion es -> c) -> (a -> c) -> Envelope es a -> c Source #

Case analysis for Envelopes.

Examples

Expand

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

Expand
>>> 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

Expand

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

Expand

Successfully pull out an e:

>>> let double = 3.5 :: Double
>>> let env = toErrEnvelope double :: Envelope '[Double] ()
>>> errEnvelopeMatch env :: Maybe Double
Just 3.5

Unsuccessfully pull out an e:

>>> let env' = toSuccEnvelope () :: Envelope '[Double] ()
>>> errEnvelopeMatch env' :: Maybe Double
Nothing
>>> let env'' = toErrEnvelope 'c' :: Envelope '[Double, Char] ()
>>> errEnvelopeMatch env'' :: Maybe Double
Nothing

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

Expand

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 Envelope '[Int, String] Double, the type of catchesEnvelope 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 Envelope '[Int, String, Char] Double, the type of catchesEnvelope 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 Envelope '[Int] Double, the type of catchesEnvelope becomes the following:

  catchesEnvelope
    :: (Int -> x)
    -> (Double -> x)
    -> Envelope '[Int] Double
    -> x

Optics

_SuccEnvelope :: Prism (Envelope es a) (Envelope es b) a b Source #

Lens-compatible Prism to pull out an a from a SuccEnvelope.

Examples

Expand

Use _SuccEnvelope to construct an Envelope:

>>> review _SuccEnvelope "hello" :: Envelope '[Double] String
SuccEnvelope "hello"

Use _SuccEnvelope to try to destruct an Envelope into an a:

>>> let env = toSuccEnvelope "hello" :: Envelope '[Double] String
>>> preview _SuccEnvelope env :: Maybe String
Just "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 String
Nothing

_ErrEnvelope :: Prism (Envelope es a) (Envelope es' a) (OpenUnion es) (OpenUnion es') Source #

Lens-compatible Prism to pull out an OpenUnion es from a ErrEnvelope.

Most users will not use _ErrEnvelope, but instead _ErrEnvelopeErr.

Examples

Expand

Use _ErrEnvelope to construct an Envelope:

>>> let string = "hello" :: String
>>> review _ErrEnvelope (openUnionLift string) :: Envelope '[String] Double
ErrEnvelope (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 OpenUnion es (unsuccessfully):

>>> 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

Expand

Use _ErrEnvelopeErr to construct an Envelope:

>>> let string = "hello" :: String
>>> review _ErrEnvelopeErr string :: Envelope '[String] Double
ErrEnvelope (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 Double
Just 3.5

Use _ErrEnvelopeErr to try to destruct a 'Envelope into an e (unsuccessfully):

>>> let env' = toSuccEnvelope () :: Envelope '[Double] ()
>>> preview _ErrEnvelopeErr env' :: Maybe Double
Nothing
>>> let env'' = toErrEnvelope 'c' :: Envelope '[Double, Char] ()
>>> preview _ErrEnvelopeErr env'' :: Maybe Double
Nothing

Either

envelopeToEither :: Envelope es a -> Either (OpenUnion es) a Source #

Convert an Envelope to an Either.

eitherToEnvelope :: Either (OpenUnion es) a -> Envelope es a Source #

Convert an Either to an Envelope.

isoEnvelopeEither :: Iso (Envelope es a) (Envelope fs b) (Either (OpenUnion es) a) (Either (OpenUnion fs) b) Source #

Lens-compatible Iso from Envelope to Either.

Setup code for doctests