Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- 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 Link
Documentation
data AsServerT (m :: * -> *) Source #
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 #
Instances
GProduct (K1 i c :: * -> *) Source # | |
Defined in Servant.Generic type GToServant (K1 i c) :: * Source # gtoServant :: K1 i c p -> GToServant (K1 i c) Source # gfromServant :: GToServant (K1 i c) -> K1 i c p Source # | |
(GProduct l, GProduct r) => GProduct (l :*: r) Source # | |
Defined in Servant.Generic type GToServant (l :*: r) :: * Source # gtoServant :: (l :*: r) p -> GToServant (l :*: r) Source # gfromServant :: GToServant (l :*: r) -> (l :*: r) p Source # | |
GProduct f => GProduct (M1 i c f) Source # | |
Defined in Servant.Generic type GToServant (M1 i c f) :: * Source # gtoServant :: M1 i c f p -> GToServant (M1 i c f) Source # gfromServant :: GToServant (M1 i c f) -> M1 i c f p Source # |
Representable types of kind *
.
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic
instance must satisfy the following laws:
from
.to
≡id
to
.from
≡id
Convert from the datatype to its representation
Convert from the representation to the datatype