| 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
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 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
- 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)
- type OpenUnion = Union Identity
- openUnion :: (OpenUnion as -> c) -> (a -> c) -> OpenUnion (a ': as) -> c
- fromOpenUnion :: (OpenUnion as -> a) -> OpenUnion (a ': as) -> a
- fromOpenUnionOr :: OpenUnion (a ': as) -> (OpenUnion as -> a) -> a
- openUnionPrism :: forall a as. IsMember a as => Prism' (OpenUnion as) a
- openUnionLift :: forall a as. IsMember a as => a -> OpenUnion as
- openUnionMatch :: forall a as. IsMember a as => OpenUnion as -> Maybe a
- catchesOpenUnion :: ToOpenProduct tuple (ReturnX x as) => tuple -> OpenUnion as -> x
- data Union f as where
- union :: (Union f as -> c) -> (f a -> c) -> Union f (a ': as) -> c
- absurdUnion :: Union f '[] -> a
- umap :: (forall a. f a -> g a) -> Union f as -> Union g as
- catchesUnion :: (Applicative f, ToProduct tuple f (ReturnX x as)) => tuple -> Union f as -> f x
- _This :: Prism (Union f (a ': as)) (Union f (b ': as)) (f a) (f b)
- _That :: Prism (Union f (a ': as)) (Union f (a ': bs)) (Union f as) (Union f bs)
- data Nat
- type family RIndex (r :: k) (rs :: [k]) :: Nat where ...
- class i ~ RIndex a as => UElem a as i where
- type IsMember a as = UElem a as (RIndex a as)
- type OpenProduct = Product Identity
- data Product f as where
- class ToOpenProduct tuple as | as -> tuple
- tupleToOpenProduct :: ToOpenProduct t as => t -> OpenProduct as
- class ToProduct tuple f as | f as -> tuple
- tupleToProduct :: ToProduct t f as => t -> Product f as
- type family ReturnX x as where ...
Throws API parameter
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"
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 #
OpenUnion (used in ErrEnvelope)
OpenUnion Helpers
openUnion :: (OpenUnion as -> c) -> (a -> c) -> OpenUnion (a ': as) -> c Source #
Case analysis for OpenUnion.
Examples
Here is an example of successfully matching:
>>>let string = "hello" :: String>>>let o = openUnionLift string :: OpenUnion '[String, Int]>>>openUnion (const "not a String") id o"hello"
Here is an example of unsuccessfully matching:
>>>let double = 3.3 :: Double>>>let p = openUnionLift double :: OpenUnion '[String, Double, Int]>>>openUnion (const "not a String") id p"not a String"
fromOpenUnion :: (OpenUnion as -> a) -> OpenUnion (a ': as) -> a Source #
This is similar to fromMaybe for an OpenUnion.
Examples
Here is an example of successfully matching:
>>>let string = "hello" :: String>>>let o = openUnionLift string :: OpenUnion '[String, Int]>>>fromOpenUnion (const "not a String") o"hello"
Here is an example of unsuccessfully matching:
>>>let double = 3.3 :: Double>>>let p = openUnionLift double :: OpenUnion '[String, Double, Int]>>>fromOpenUnion (const "not a String") p"not a String"
fromOpenUnionOr :: OpenUnion (a ': as) -> (OpenUnion as -> a) -> a Source #
Flipped version of fromOpenUnion.
openUnionPrism :: forall a as. IsMember a as => Prism' (OpenUnion as) a Source #
Just like unionPrism but for OpenUnion.
openUnionLift :: forall a as. IsMember a as => a -> OpenUnion as Source #
openUnionMatch :: forall a as. IsMember a as => OpenUnion as -> Maybe a Source #
Just like unionMatch but for OpenUnion.
Examples
Successful matching:
>>>let string = "hello" :: String>>>let o = openUnionLift string :: OpenUnion '[Double, String, Int]>>>openUnionMatch o :: Maybe StringJust "hello"
Failure matching:
>>>let double = 3.3 :: Double>>>let p = openUnionLift double :: OpenUnion '[Double, String]>>>openUnionMatch p :: Maybe StringNothing
catchesOpenUnion :: ToOpenProduct tuple (ReturnX x as) => tuple -> OpenUnion as -> x Source #
An alternate case anaylsis for an OpenUnion. This method uses a tuple
containing handlers for each potential value of the OpenUnion. This is
somewhat similar to the catches function.
When working with large OpenUnions, it can be easier to use
catchesOpenUnion than openUnion.
Examples
Here is an example of handling an OpenUnion with two possible values.
Notice that a normal tuple is used:
>>>let u = openUnionLift (3 :: Int) :: OpenUnion '[Int, String]>>>let intHandler = (\int -> show int) :: Int -> String>>>let strHandler = (\str -> str) :: String -> String>>>catchesOpenUnion (intHandler, strHandler) u :: String"3"
Given an OpenUnion like , the type of
OpenUnion '[Int, String]catchesOpenUnion becomes the following:
catchesOpenUnion:: (Int-> x,String-> x) ->OpenUnion'[Int,String] -> x
Here is an example of handling an OpenUnion with three possible values:
>>>let u = openUnionLift ("hello" :: String) :: OpenUnion '[Int, String, Double]>>>let intHandler = (\int -> show int) :: Int -> String>>>let strHandler = (\str -> str) :: String -> String>>>let dblHandler = (\dbl -> "got a double") :: Double -> String>>>catchesOpenUnion (intHandler, strHandler, dblHandler) u :: String"hello"
Here is an example of handling an OpenUnion with only one possible value.
Notice how a tuple is not used, just a single value:
>>>let u = openUnionLift (2.2 :: Double) :: OpenUnion '[Double]>>>let dblHandler = (\dbl -> "got a double") :: Double -> String>>>catchesOpenUnion dblHandler u :: String"got a double"
Union (used by OpenUnion)
OpenUnion is a type synonym around Union. Most users will be able to
work directly with OpenUnion and ignore this Union type.
data Union f as where Source #
A Union is parameterized by a universe u, an interpretation f
and a list of labels as. The labels of the union are given by
inhabitants of the kind u; the type of values at any label a ::
u is given by its interpretation f a :: *.
Instances
| (Eq (f a1), Eq (Union a f as)) => Eq (Union a f ((:) a a1 as)) Source # | |
| Eq (Union u f ([] u)) Source # | |
| (Ord (f a1), Ord (Union a f as)) => Ord (Union a f ((:) a a1 as)) Source # | |
| Ord (Union u f ([] u)) Source # | |
| (Read (f a1), Read (Union a f as)) => Read (Union a f ((:) a a1 as)) Source # | This is only a valid instance when the For instance, imagine we are working with a
However, imagine are we working with a
If the order of the types is flipped around, we are are able to read
|
| Read (Union u f ([] u)) Source # | This will always fail, since |
| (Show (f a1), Show (Union a f as)) => Show (Union a f ((:) a a1 as)) Source # | |
| Show (Union u f ([] u)) Source # | |
| (ToJSON (f a1), ToJSON (Union a f as)) => ToJSON (Union a f ((:) a a1 as)) Source # | |
| ToJSON (Union u f ([] u)) Source # | |
| (FromJSON (f a1), FromJSON (Union a f as)) => FromJSON (Union a f ((:) a a1 as)) Source # | This is only a valid instance when the This is similar to the |
| FromJSON (Union u f ([] u)) Source # | This will always fail, since |
| (NFData (f a1), NFData (Union a f as)) => NFData (Union a f ((:) a a1 as)) Source # | |
| NFData (Union u f ([] u)) Source # | |
Union helpers
union :: (Union f as -> c) -> (f a -> c) -> Union f (a ': as) -> c Source #
Case analysis for Union.
Examples
Here is an example of matching on a This:
>>>let u = This (Identity "hello") :: Union Identity '[String, Int]>>>let runIdent = runIdentity :: Identity String -> String>>>union (const "not a String") runIdent u"hello"
Here is an example of matching on a That:
>>>let v = That (This (Identity 3.3)) :: Union Identity '[String, Double, Int]>>>union (const "not a String") runIdent v"not a String"
absurdUnion :: Union f '[] -> a Source #
Since a union with an empty list of labels is uninhabited, we can recover any type from it.
catchesUnion :: (Applicative f, ToProduct tuple f (ReturnX x as)) => tuple -> Union f as -> f x Source #
An alternate case anaylsis for a Union. This method uses a tuple
containing handlers for each potential value of the Union. This is
somewhat similar to the catches function.
Examples
Here is an example of handling a Union with two possible values. Notice
that a normal tuple is used:
>>>let u = This $ Identity 3 :: Union Identity '[Int, String]>>>let intHandler = (Identity $ \int -> show int) :: Identity (Int -> String)>>>let strHandler = (Identity $ \str -> str) :: Identity (String -> String)>>>catchesUnion (intHandler, strHandler) u :: Identity StringIdentity "3"
Given a Union like , the type of
Union Identity '[Int, String]catchesUnion becomes the following:
catchesUnion:: (Identity(Int->String),Identity(String->String)) ->UnionIdentity'[Int,String] ->IdentityString
Checkout catchesOpenUnion for more examples.
Union optics
_This :: Prism (Union f (a ': as)) (Union f (b ': as)) (f a) (f b) Source #
Lens-compatible Prism for This.
Examples
Use _This to construct a Union:
>>>review _This (Just "hello") :: Union Maybe '[String]Just "hello"
Use _This to try to destruct a Union into a f a:
>>>let u = This (Identity "hello") :: Union Identity '[String, Int]>>>preview _This u :: Maybe (Identity String)Just (Identity "hello")
Use _This to try to destruct a Union into a f a (unsuccessfully):
>>>let v = That (This (Identity 3.3)) :: Union Identity '[String, Double, Int]>>>preview _This v :: Maybe (Identity String)Nothing
_That :: Prism (Union f (a ': as)) (Union f (a ': bs)) (Union f as) (Union f bs) Source #
Lens-compatible Prism for That.
Examples
Use _That to construct a Union:
>>>let u = This (Just "hello") :: Union Maybe '[String]>>>review _That u :: Union Maybe '[Double, String]Just "hello"
Use _That to try to peel off a That from a Union:
>>>let v = That (This (Identity "hello")) :: Union Identity '[Int, String]>>>preview _That v :: Maybe (Union Identity '[String])Just (Identity "hello")
Use _That to try to peel off a That from a Union (unsuccessfully):
>>>let w = This (Identity 3.5) :: Union Identity '[Double, String]>>>preview _That w :: Maybe (Union Identity '[String])Nothing
Typeclasses used with Union
A mere approximation of the natural numbers. And their image as lifted by
-XDataKinds corresponds to the actual natural numbers.
type family RIndex (r :: k) (rs :: [k]) :: Nat where ... Source #
A partial relation that gives the index of a value in a list.
Examples
Find the first item:
>>>import Data.Type.Equality ((:~:)(Refl))>>>Refl :: RIndex String '[String, Int] :~: 'ZRefl
Find the third item:
>>>Refl :: RIndex Char '[String, Int, Char] :~: 'S ('S 'Z)Refl
class i ~ RIndex a as => UElem a as i where Source #
provides a way to potentially get an UElem a as if a out of a
(Union f asunionMatch). It also provides a way to create a
from an Union f asf a (unionLift).
This is safe because of the RIndex contraint. This RIndex constraint
tells us that there actually is an a in as at index i.
As an end-user, you should never need to implement an additional instance of this typeclass.
Minimal complete definition
Methods
unionPrism :: Prism' (Union f as) (f a) Source #
This is implemented as .prism' unionLift unionMatch
unionLift :: f a -> Union f as Source #
This is implemented as .review unionPrism
unionMatch :: Union f as -> Maybe (f a) Source #
This is implemented as .preview unionPrism
type IsMember a as = UElem a as (RIndex a as) Source #
This is a helpful Constraint synonym to assert that a is a member of
as.
OpenProduct (used by OpenUnion)
This Product type is used to easily create a case-analysis for
Unions. You can see it being used in catchesOpenUnion and
catchesEnvelope. The ToProduct type class makes it easy to convert a
tuple to a Product. This makes it so the end user only has to worry
about working with tuples, and can mostly ignore this Product type.
type OpenProduct = Product Identity Source #
data Product f as where Source #
An extensible product type. This is similar to
Union, except a product type
instead of a sum type.
class ToOpenProduct tuple as | as -> tuple Source #
ToOpenProduct gives us a way to convert a tuple to an OpenProduct.
See tupleToOpenProduct.
Minimal complete definition
Instances
| ToOpenProduct a ((:) * a ([] *)) Source # | Convert a single value into an |
| ToOpenProduct (a, b) ((:) * a ((:) * b ([] *))) Source # | Convert a tuple into an |
| ToOpenProduct (a, b, c) ((:) * a ((:) * b ((:) * c ([] *)))) Source # | Convert a 3-tuple into an |
| ToOpenProduct (a, b, c, d) ((:) * a ((:) * b ((:) * c ((:) * d ([] *))))) Source # | Convert a 4-tuple into an |
tupleToOpenProduct :: ToOpenProduct t as => t -> OpenProduct as Source #
Turn a tuple into an OpenProduct.
Examples
Turn a triple into an OpenProduct:
>>>tupleToOpenProduct (1, 2.0, "hello") :: OpenProduct '[Int, Double, String]Cons (Identity 1) (Cons (Identity 2.0) (Cons (Identity "hello") Nil))
Turn a single value into an OpenProduct:
>>>tupleToOpenProduct 'c' :: OpenProduct '[Char]Cons (Identity 'c') Nil
class ToProduct tuple f as | f as -> tuple Source #
This type class provides a way to turn a tuple into a Product.
Minimal complete definition
Instances
| ToProduct u (f a) f ((:) u a ([] u)) Source # | Convert a single value into a |
| ToProduct u (f a, f b) f ((:) u a ((:) u b ([] u))) Source # | Convert a tuple into a |
| ToProduct u (f a, f b, f c) f ((:) u a ((:) u b ((:) u c ([] u)))) Source # | Convert a 3-tuple into a |
| ToProduct u (f a, f b, f c, f d) f ((:) u a ((:) u b ((:) u c ((:) u d ([] u))))) Source # | Convert a 4-tuple into a |
tupleToProduct :: ToProduct t f as => t -> Product f as Source #
Turn a tuple into a Product.
>>>tupleToProduct (Identity 1, Identity 2.0) :: Product Identity '[Int, Double]Cons (Identity 1) (Cons (Identity 2.0) Nil)