| 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.Internal.Envelope
Description
- data Envelope es a
- = ErrEnvelope (OpenUnion es)
- | SuccEnvelope a
- toErrEnvelope :: IsMember e es => e -> Envelope es a
- toSuccEnvelope :: a -> Envelope es a
- pureErrEnvelope :: (Applicative m, IsMember e es) => e -> m (Envelope es a)
- pureSuccEnvelope :: Applicative m => a -> 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
- fromEnvelopeM :: Applicative m => (OpenUnion es -> m a) -> Envelope es a -> m a
- fromEnvelopeOr :: Envelope es a -> (OpenUnion es -> a) -> a
- fromEnvelopeOrM :: Applicative m => Envelope es a -> (OpenUnion es -> m a) -> m a
- 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)
- _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
- 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
Documentation
>>>:set -XDataKinds>>>:set -XTypeOperators>>>import Data.Aeson (encode)>>>import Data.ByteString.Lazy.Char8 (hPutStrLn)>>>import Data.Text (Text)>>>import System.IO (stdout)>>>import Text.Read (readMaybe)>>>import Servant.Checked.Exceptions.Internal.Prism (review)>>>let putByteStrLn = hPutStrLn stdout
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 # | |
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)
toSuccEnvelope :: a -> Envelope es a Source #
This is a function to create a SuccEnvelope.
>>>toSuccEnvelope "hello" :: Envelope '[Double] StringSuccEnvelope "hello"
pureErrEnvelope :: (Applicative m, IsMember e es) => e -> m (Envelope es a) Source #
pureErrEnvelope is toErrEnvelope lifted up to an Applicative.
pureSuccEnvelope :: Applicative m => a -> m (Envelope es a) Source #
pureSuccEnvelope is toSuccEnvelope lifted up to an Applicative.
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"
fromEnvelopeM :: Applicative m => (OpenUnion es -> m a) -> Envelope es a -> m a Source #
Lifted version of fromEnvelope.
fromEnvelopeOr :: Envelope es a -> (OpenUnion es -> a) -> a Source #
Flipped version of fromEnvelope.
fromEnvelopeOrM :: Applicative m => Envelope es a -> (OpenUnion es -> m a) -> m a Source #
Flipped version of fromEnvelopeM.
isoEnvelopeEither :: Iso (Envelope es a) (Envelope fs b) (Either (OpenUnion es) a) (Either (OpenUnion fs) b) Source #
_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
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