servant-checked-exceptions-0.1.0.1: Checked exceptions for Servant APIs.

Safe HaskellNone
LanguageHaskell2010

Servant.Checked.Exceptions

Contents

Synopsis

Throws API parameter

data Throws e Source #

Throws is used in Servant API definitions and signifies that an API will throw the given error.

Here is an example of how to create an API that potentially returns a String as an error, or an Int on success:

>>> import Servant.API (Get, JSON, (:>))
>>> type API = Throws String :> Get '[JSON] Int

Instances

type Client * ((:>) * * (Throwing es) ((:>) k * (Throws e) api)) # 
type Client * ((:>) * * (Throwing es) ((:>) k * (Throws e) api)) = Client * ((:>) k * (Throwing (Snoc * es e)) api)
type Client * ((:>) k * (Throws e) api) # 
type Client * ((:>) k * (Throws e) api) = Client * ((:>) k * (Throwing ((:) * e ([] *))) api)
type ServerT * ((:>) * * (Throwing es) ((:>) k * (Throws e) api)) m # 
type ServerT * ((:>) * * (Throwing es) ((:>) k * (Throws e) api)) m = ServerT * ((:>) k * (Throwing (Snoc * es e)) api) m
type ServerT * ((:>) k * (Throws e) api) m # 
type ServerT * ((:>) k * (Throws e) api) m = ServerT * ((:>) k * (Throwing ((:) * e ([] *))) api) m

Envelope response wrapper

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 # 

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 # 

Methods

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

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

MonadFix (Envelope es) Source # 

Methods

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

Applicative (Envelope es) Source # 

Methods

pure :: a -> Envelope es a #

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

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

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

Foldable (Envelope es) Source # 

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 # 

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 # 

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 # 

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 # 

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 # 
(Show (OpenUnion es), Show a) => Show (Envelope es a) Source # 

Methods

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

show :: Envelope es a -> String #

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

Generic (Envelope es a) Source # 

Associated Types

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

Methods

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

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

Semigroup (Envelope es a) Source # 

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}
(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.

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

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

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.

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.

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.

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

When working with an Envelope with a large number of possible error types, it can be easier to use catchesEnvelope than envelope.

Envelope optics

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

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

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.

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

Most users will not use _ErrEnvelope, but instead _ErrEnvelopeErr.

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

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

Most users will use _ErrEnvelopeErr instead of _ErrEnvelope.

Envelope and 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.

OpenUnion (used in ErrEnvelope)

type OpenUnion = Union Identity Source #

We can use Union Identity as a standard open sum type.

OpenUnion Helpers

openUnion :: (OpenUnion as -> c) -> (a -> c) -> OpenUnion (a ': as) -> c Source #

Case analysis for OpenUnion.

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.

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 #

Just like unionLift but for OpenUnion.

Creating an OpenUnion:

>>> let string = "hello" :: String
>>> openUnionLift string :: OpenUnion '[Double, String, Int]
Identity "hello"

openUnionMatch :: forall a as. IsMember a as => OpenUnion as -> Maybe a Source #

Just like unionMatch but for OpenUnion.

Successful matching:

>>> let string = "hello" :: String
>>> let o = openUnionLift string :: OpenUnion '[Double, String, Int]
>>> openUnionMatch o :: Maybe String
Just "hello"

Failure matching:

>>> let double = 3.3 :: Double
>>> let p = openUnionLift double :: OpenUnion '[Double, String]
>>> openUnionMatch p :: Maybe String
Nothing

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.

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 OpenUnion '[Int, String], the type of 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"

When working with large OpenUnions, it can be easier to use catchesOpenUnion than openUnion.

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 :: *.

Constructors

This :: !(f a) -> Union f (a ': as) 
That :: !(Union f as) -> Union f (a ': as) 

Instances

(Eq (f a1), Eq (Union a f as)) => Eq (Union a f ((:) a a1 as)) Source # 

Methods

(==) :: Union a f ((a ': a1) as) -> Union a f ((a ': a1) as) -> Bool #

(/=) :: Union a f ((a ': a1) as) -> Union a f ((a ': a1) as) -> Bool #

Eq (Union u f ([] u)) Source # 

Methods

(==) :: Union u f [u] -> Union u f [u] -> Bool #

(/=) :: Union u f [u] -> Union u f [u] -> Bool #

(Ord (f a1), Ord (Union a f as)) => Ord (Union a f ((:) a a1 as)) Source # 

Methods

compare :: Union a f ((a ': a1) as) -> Union a f ((a ': a1) as) -> Ordering #

(<) :: Union a f ((a ': a1) as) -> Union a f ((a ': a1) as) -> Bool #

(<=) :: Union a f ((a ': a1) as) -> Union a f ((a ': a1) as) -> Bool #

(>) :: Union a f ((a ': a1) as) -> Union a f ((a ': a1) as) -> Bool #

(>=) :: Union a f ((a ': a1) as) -> Union a f ((a ': a1) as) -> Bool #

max :: Union a f ((a ': a1) as) -> Union a f ((a ': a1) as) -> Union a f ((a ': a1) as) #

min :: Union a f ((a ': a1) as) -> Union a f ((a ': a1) as) -> Union a f ((a ': a1) as) #

Ord (Union u f ([] u)) Source # 

Methods

compare :: Union u f [u] -> Union u f [u] -> Ordering #

(<) :: Union u f [u] -> Union u f [u] -> Bool #

(<=) :: Union u f [u] -> Union u f [u] -> Bool #

(>) :: Union u f [u] -> Union u f [u] -> Bool #

(>=) :: Union u f [u] -> Union u f [u] -> Bool #

max :: Union u f [u] -> Union u f [u] -> Union u f [u] #

min :: Union u f [u] -> Union u f [u] -> Union u f [u] #

(Read (f a1), Read (Union a f as)) => Read (Union a f ((:) a a1 as)) Source #

This is only a valid instance when the Read instances for the types don't overlap.

For instance, imagine we are working with a Union of a String and a Double. 3.5 can only be read as a Double, not as a String. Oppositely, "hello" can only be read as a String, not as a Double.

>>> let o = readMaybe "Identity 3.5" :: Maybe (Union Identity '[Double, String])
>>> o
Just (Identity 3.5)
>>> o >>= openUnionMatch :: Maybe Double
Just 3.5
>>> o >>= openUnionMatch :: Maybe String
Nothing
>>> let p = readMaybe "Identity \"hello\"" :: Maybe (Union Identity '[Double, String])
>>> p
Just (Identity "hello")
>>> p >>= openUnionMatch :: Maybe Double
Nothing
>>> p >>= openUnionMatch :: Maybe String
Just "hello"

However, imagine are we working with a Union of a String and Text. "hello" can be read as both a String and Text. However, in the following example, it can only be read as a String:

>>> let q = readMaybe "Identity \"hello\"" :: Maybe (Union Identity '[String, Text])
>>> q
Just (Identity "hello")
>>> q >>= openUnionMatch :: Maybe String
Just "hello"
>>> q >>= openUnionMatch :: Maybe Text
Nothing

If the order of the types is flipped around, we are are able to read "hello" as a Text but not as a String.

>>> let r = readMaybe "Identity \"hello\"" :: Maybe (Union Identity '[Text, String])
>>> r
Just (Identity "hello")
>>> r >>= openUnionMatch :: Maybe String
Nothing
>>> r >>= openUnionMatch :: Maybe Text
Just "hello"

Methods

readsPrec :: Int -> ReadS (Union a f ((a ': a1) as)) #

readList :: ReadS [Union a f ((a ': a1) as)] #

readPrec :: ReadPrec (Union a f ((a ': a1) as)) #

readListPrec :: ReadPrec [Union a f ((a ': a1) as)] #

Read (Union u f ([] u)) Source #

This will always fail, since Union f '[] is effectively Void.

Methods

readsPrec :: Int -> ReadS (Union u f [u]) #

readList :: ReadS [Union u f [u]] #

readPrec :: ReadPrec (Union u f [u]) #

readListPrec :: ReadPrec [Union u f [u]] #

(Show (f a1), Show (Union a f as)) => Show (Union a f ((:) a a1 as)) Source # 

Methods

showsPrec :: Int -> Union a f ((a ': a1) as) -> ShowS #

show :: Union a f ((a ': a1) as) -> String #

showList :: [Union a f ((a ': a1) as)] -> ShowS #

Show (Union u f ([] u)) Source # 

Methods

showsPrec :: Int -> Union u f [u] -> ShowS #

show :: Union u f [u] -> String #

showList :: [Union u f [u]] -> ShowS #

(ToJSON (f a1), ToJSON (Union a f as)) => ToJSON (Union a f ((:) a a1 as)) Source # 

Methods

toJSON :: Union a f ((a ': a1) as) -> Value #

toEncoding :: Union a f ((a ': a1) as) -> Encoding #

toJSONList :: [Union a f ((a ': a1) as)] -> Value #

toEncodingList :: [Union a f ((a ': a1) as)] -> Encoding #

ToJSON (Union u f ([] u)) Source # 

Methods

toJSON :: Union u f [u] -> Value #

toEncoding :: Union u f [u] -> Encoding #

toJSONList :: [Union u f [u]] -> Value #

toEncodingList :: [Union u f [u]] -> Encoding #

(FromJSON (f a1), FromJSON (Union a f as)) => FromJSON (Union a f ((:) a a1 as)) Source #

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

This is similar to the Read instance.

Methods

parseJSON :: Value -> Parser (Union a f ((a ': a1) as)) #

parseJSONList :: Value -> Parser [Union a f ((a ': a1) as)] #

FromJSON (Union u f ([] u)) Source #

This will always fail, since Union f '[] is effectively Void.

Methods

parseJSON :: Value -> Parser (Union u f [u]) #

parseJSONList :: Value -> Parser [Union u f [u]] #

(NFData (f a1), NFData (Union a f as)) => NFData (Union a f ((:) a a1 as)) Source # 

Methods

rnf :: Union a f ((a ': a1) as) -> () #

NFData (Union u f ([] u)) Source # 

Methods

rnf :: Union u f [u] -> () #

Union helpers

union :: (Union f as -> c) -> (f a -> c) -> Union f (a ': as) -> c Source #

Case analysis for Union.

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.

umap :: (forall a. f a -> g a) -> Union f as -> Union g as Source #

Map over the interpretation f in the Union.

Here is an example of changing a Union Identity '[String, Int] to Union Maybe '[String, Int]:

>>> let u = This (Identity "hello") :: Union Identity '[String, Int]
>>> umap (Just . runIdentity) u :: Union Maybe '[String, Int]
Just "hello"

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.

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 String
Identity "3"

Given a Union like Union Identity '[Int, String], the type of catchesUnion becomes the following:

  catchesUnion
    :: (Identity (Int -> String), Identity (String -> String))
    -> Union Identity '[Int, String]
    -> Identity String

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.

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.

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

data Nat Source #

A mere approximation of the natural numbers. And their image as lifted by -XDataKinds corresponds to the actual natural numbers.

Constructors

Z 
S !Nat 

type family RIndex (r :: k) (rs :: [k]) :: Nat where ... Source #

A partial relation that gives the index of a value in a list.

Find the first item:

>>> import Data.Type.Equality ((:~:)(Refl))
>>> Refl :: RIndex String '[String, Int] :~: 'Z
Refl

Find the third item:

>>> Refl :: RIndex Char '[String, Int, Char] :~: 'S ('S 'Z)
Refl

Equations

RIndex r (r ': rs) = Z 
RIndex r (s ': rs) = S (RIndex r rs) 

class i ~ RIndex a as => UElem a as i where Source #

UElem a as i provides a way to potentially get an f a out of a Union f as (unionMatch). It also provides a way to create a Union f as from an f 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

unionPrism | unionLift, unionMatch

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.

Instances

UElem a a1 ((:) a a1 as) Z Source # 

Methods

unionPrism :: (Choice p, Applicative f) => p (f ((a ': a1) as)) (f (f ((a ': a1) as))) -> p (Union a1 f Z) (f (Union a1 f Z)) Source #

unionLift :: f ((a ': a1) as) -> Union a1 f Z Source #

unionMatch :: Union a1 f Z -> Maybe (f ((a ': a1) as)) Source #

((~) Nat (RIndex a a1 ((:) a b as)) (S i), UElem a a1 as i) => UElem a a1 ((:) a b as) (S i) Source # 

Methods

unionPrism :: (Choice p, Applicative f) => p (f ((a ': b) as)) (f (f ((a ': b) as))) -> p (Union a1 f (S i)) (f (Union a1 f (S i))) Source #

unionLift :: f ((a ': b) as) -> Union a1 f (S i) Source #

unionMatch :: Union a1 f (S i) -> Maybe (f ((a ': b) as)) Source #

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 #

Product Identity is used as a standard open product type.

data Product f as where Source #

An extensible product type. This is similar to Union, except a product type instead of a sum type.

Constructors

Nil :: Product f '[] 
Cons :: !(f a) -> Product f as -> Product f (a ': as) 

Instances

(Show (f a1), Show (Product a f as)) => Show (Product a f ((:) a a1 as)) Source #

Show Cons values.

Methods

showsPrec :: Int -> Product a f ((a ': a1) as) -> ShowS #

show :: Product a f ((a ': a1) as) -> String #

showList :: [Product a f ((a ': a1) as)] -> ShowS #

Show (Product u f ([] u)) Source #

Show Nil values.

Methods

showsPrec :: Int -> Product u f [u] -> ShowS #

show :: Product u f [u] -> String #

showList :: [Product u f [u]] -> ShowS #

class ToOpenProduct tuple as | as -> tuple Source #

ToOpenProduct gives us a way to convert a tuple to an OpenProduct. See tupleToOpenProduct.

Minimal complete definition

toOpenProduct

Instances

ToOpenProduct a ((:) * a ([] *)) Source #

Convert a single value into an OpenProduct.

Methods

toOpenProduct :: a -> OpenProduct ((* ': a) [*]) Source #

ToOpenProduct (a, b) ((:) * a ((:) * b ([] *))) Source #

Convert a tuple into an OpenProduct.

Methods

toOpenProduct :: (a, b) -> OpenProduct ((* ': a) ((* ': b) [*])) Source #

ToOpenProduct (a, b, c) ((:) * a ((:) * b ((:) * c ([] *)))) Source #

Convert a 3-tuple into an OpenProduct.

Methods

toOpenProduct :: (a, b, c) -> OpenProduct ((* ': a) ((* ': b) ((* ': c) [*]))) Source #

ToOpenProduct (a, b, c, d) ((:) * a ((:) * b ((:) * c ((:) * d ([] *))))) Source #

Convert a 4-tuple into an OpenProduct.

Methods

toOpenProduct :: (a, b, c, d) -> OpenProduct ((* ': a) ((* ': b) ((* ': c) ((* ': d) [*])))) Source #

tupleToOpenProduct :: ToOpenProduct t as => t -> OpenProduct as Source #

Turn a tuple into an OpenProduct.

For example, 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

toProduct

Instances

ToProduct u (f a) f ((:) u a ([] u)) Source #

Convert a single value into a Product.

Methods

toProduct :: f -> Product (f a) ((u ': a) [u]) as Source #

ToProduct u (f a, f b) f ((:) u a ((:) u b ([] u))) Source #

Convert a tuple into a Product.

Methods

toProduct :: f -> Product (f a, f b) ((u ': a) ((u ': b) [u])) as Source #

ToProduct u (f a, f b, f c) f ((:) u a ((:) u b ((:) u c ([] u)))) Source #

Convert a 3-tuple into a Product.

Methods

toProduct :: f -> Product (f a, f b, f c) ((u ': a) ((u ': b) ((u ': c) [u]))) as Source #

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

Methods

toProduct :: f -> Product (f a, f b, f c, f d) ((u ': a) ((u ': b) ((u ': c) ((u ': d) [u])))) as Source #

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)

type family ReturnX x as where ... Source #

Change a list of types into a list of functions that take the given type and return x.

>>> Refl :: ReturnX Double '[String, Int] :~: '[String -> Double, Int -> Double]
Refl

Don't do anything with an empty list:

>>> Refl :: ReturnX Double '[] :~: '[]
Refl

Equations

ReturnX x (a ': as) = (a -> x) ': ReturnX x as 
ReturnX x '[] = '[]