| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Servant.API.UVerb.Union
Description
Type-level code for implementing and using UVerb.  Heavily inspired by
 world-peace.
Synopsis
- type IsMember (a :: u) (as :: [u]) = (Unique as, CheckElemIsMember a as, UElem a as)
- type family Unique xs :: Constraint where ...
- type Union = NS I
- inject :: UElem x xs => f x -> NS f xs
- eject :: UElem x xs => NS f xs -> Maybe (f x)
- foldMapUnion :: forall (c :: * -> Constraint) (a :: *) (as :: [*]). All c as => Proxy c -> (forall x. c x => x -> a) -> Union as -> a
- matchUnion :: forall (a :: *) (as :: [*]). IsMember a as => Union as -> Maybe a
Documentation
type family Unique xs :: Constraint where ... Source #
foldMapUnion :: forall (c :: * -> Constraint) (a :: *) (as :: [*]). All c as => Proxy c -> (forall x. c x => x -> a) -> Union as -> a Source #
Convenience function to apply a function to an unknown union element using a type class. All elements of the union must have instances in the type class, and the function is applied unconditionally.
See also: matchUnion.
matchUnion :: forall (a :: *) (as :: [*]). IsMember a as => Union as -> Maybe a Source #
Convenience function to extract a union element using cast, ie. return the value if the
 selected type happens to be the actual type of the union in this value, or Nothing
 otherwise.
See also: foldMapUnion.