Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type family mode :- api
- data AsServerT m
- type AsServer = AsServerT Handler
- data AsApi
- data AsLink
- type ToServant a = GToServant (Rep a)
- toServant :: GenericProduct a => a -> ToServant a
- fromServant :: GenericProduct a => ToServant a -> a
- type GenericProduct a = (Generic a, GProduct (Rep a))
- class GProduct f where
- type GToServant f
- class Generic a where
- fieldLink :: forall routes endpoint. (IsElem endpoint (ToServant (routes AsApi)), HasLink endpoint) => (routes AsApi -> endpoint) -> MkLink endpoint
Documentation
A type that specifies that an API record contains a server implementation.
A type that specifies that an API record contains an API definition. Only useful at type-level.
A type that specifies that an API record contains a set of links.
(Useful since servant 0.12)
type ToServant a = GToServant (Rep a) Source #
Turns a generic product type into a linear tree of :<|>
combinators.
For example, given
data Foo route = Foo { foo :: route :- Get '[PlainText] Text , bar :: route :- Get '[PlainText] Text }
ToServant (Foo AsApi) ~ Get '[PlainText] Text :<|> Get '[PlainText] Text
fromServant :: GenericProduct a => ToServant a -> a Source #
Inverse of toServant
.
This can be used to turn generated
values such as client functions into records.
You may need to provide a type signature for the output type (your record type).
Internals
class GProduct f where Source #
A class of generic product types.
type GToServant f Source #
gtoServant :: f p -> GToServant f Source #
gfromServant :: GToServant f -> f p Source #
Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.
Convert from the datatype to its representation
Convert from the representation to the datatype
Generic Bool | |
Generic Ordering | |
Generic () | |
Generic Version | |
Generic Fixity | |
Generic Associativity | |
Generic SourceUnpackedness | |
Generic SourceStrictness | |
Generic DecidedStrictness | |
Generic IsSecure | |
Generic [a] | |
Generic (Maybe a) | |
Generic (V1 p) | |
Generic (U1 p) | |
Generic (Par1 p) | |
Generic (Identity a) | |
Generic (Complex a) | |
Generic (Handler a) | |
Generic (Either a b) | |
Generic (Rec1 f p) | |
Generic (URec Char p) | |
Generic (URec Double p) | |
Generic (URec Float p) | |
Generic (URec Int p) | |
Generic (URec Word p) | |
Generic (URec (Ptr ()) p) | |
Generic (a, b) | |
Generic (Proxy k t) | |
Generic (K1 i c p) | |
Generic ((:+:) f g p) | |
Generic ((:*:) f g p) | |
Generic ((:.:) f g p) | |
Generic (a, b, c) | |
Generic (Tagged k s b) | |
Generic (M1 i c f p) | |
Generic (a, b, c, d) | |
Generic (a, b, c, d, e) | |
Generic (a, b, c, d, e, f) | |
Generic (Verb k k1 method statusCode contentTypes a) | |
Generic (a, b, c, d, e, f, g) | |