Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype FunctionName = FunctionName {
- unFunctionName :: [Text]
- _FunctionName :: Iso' FunctionName [Text]
- newtype PathSegment = PathSegment {}
- _PathSegment :: Iso' PathSegment Text
- data Arg ftype = Arg {
- _argName :: PathSegment
- _argType :: ftype
- argType :: forall ftype ftype. Lens (Arg ftype) (Arg ftype) ftype ftype
- argName :: forall ftype. Lens' (Arg ftype) PathSegment
- argPath :: Getter (Arg ftype) Text
- data SegmentType ftype
- = Static PathSegment
- | Cap (Arg ftype)
- _Cap :: forall ftype ftype. Prism (SegmentType ftype) (SegmentType ftype) (Arg ftype) (Arg ftype)
- _Static :: forall ftype. Prism' (SegmentType ftype) PathSegment
- newtype Segment ftype = Segment {
- unSegment :: SegmentType ftype
- _Segment :: forall ftype ftype. Iso (Segment ftype) (Segment ftype) (SegmentType ftype) (SegmentType ftype)
- isCapture :: Segment ftype -> Bool
- captureArg :: Segment ftype -> Arg ftype
- type Path ftype = [Segment ftype]
- data ArgType
- _List :: Prism' ArgType ()
- _Flag :: Prism' ArgType ()
- _Normal :: Prism' ArgType ()
- data QueryArg ftype = QueryArg {
- _queryArgName :: Arg ftype
- _queryArgType :: ArgType
- queryArgType :: forall ftype. Lens' (QueryArg ftype) ArgType
- queryArgName :: forall ftype ftype. Lens (QueryArg ftype) (QueryArg ftype) (Arg ftype) (Arg ftype)
- data HeaderArg ftype
- = HeaderArg {
- _headerArg :: Arg ftype
- | ReplaceHeaderArg {
- _headerArg :: Arg ftype
- _headerPattern :: Text
- = HeaderArg {
- headerPattern :: forall ftype. Traversal' (HeaderArg ftype) Text
- headerArg :: forall ftype ftype. Lens (HeaderArg ftype) (HeaderArg ftype) (Arg ftype) (Arg ftype)
- _ReplaceHeaderArg :: forall ftype. Prism' (HeaderArg ftype) (Arg ftype, Text)
- _HeaderArg :: forall ftype. Prism' (HeaderArg ftype) (Arg ftype)
- data Url ftype = Url {}
- defUrl :: Url ftype
- queryStr :: forall ftype. Lens' (Url ftype) [QueryArg ftype]
- path :: forall ftype. Lens' (Url ftype) (Path ftype)
- frag :: forall ftype. Lens' (Url ftype) (Maybe ftype)
- data ReqBodyContentType
- data Req ftype = Req {
- _reqUrl :: Url ftype
- _reqMethod :: Method
- _reqHeaders :: [HeaderArg ftype]
- _reqBody :: Maybe ftype
- _reqReturnType :: Maybe ftype
- _reqFuncName :: FunctionName
- _reqBodyContentType :: ReqBodyContentType
- reqUrl :: forall ftype. Lens' (Req ftype) (Url ftype)
- reqReturnType :: forall ftype. Lens' (Req ftype) (Maybe ftype)
- reqMethod :: forall ftype. Lens' (Req ftype) Method
- reqHeaders :: forall ftype. Lens' (Req ftype) [HeaderArg ftype]
- reqFuncName :: forall ftype. Lens' (Req ftype) FunctionName
- reqBodyContentType :: forall ftype. Lens' (Req ftype) ReqBodyContentType
- reqBody :: forall ftype. Lens' (Req ftype) (Maybe ftype)
- defReq :: Req ftype
- class HasForeignType lang ftype a where
- data NoTypes
- class HasForeign lang ftype (api :: *) where
- data EmptyForeignAPI = EmptyForeignAPI
- class GenerateList ftype reqs where
- generateList :: reqs -> [Req ftype]
- listFromAPI :: (HasForeign lang ftype api, GenerateList ftype (Foreign ftype api)) => Proxy lang -> Proxy ftype -> Proxy api -> [Req ftype]
Documentation
newtype FunctionName Source #
Canonical name of the endpoint, can be used to generate a function name.
You can use the functions in Servant.Foreign.Inflections, like camelCase
to transform to ErrorMessage
.
Instances
_FunctionName :: Iso' FunctionName [Text] Source #
newtype PathSegment Source #
See documentation of Arg
Instances
Maps a name to the foreign type that belongs to the annotated value.
Used for header args, query args, and capture args.
Arg | |
|
Instances
Data ftype => Data (Arg ftype) Source # | |
Defined in Servant.Foreign.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Arg ftype -> c (Arg ftype) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Arg ftype) # toConstr :: Arg ftype -> Constr # dataTypeOf :: Arg ftype -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Arg ftype)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Arg ftype)) # gmapT :: (forall b. Data b => b -> b) -> Arg ftype -> Arg ftype # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Arg ftype -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Arg ftype -> r # gmapQ :: (forall d. Data d => d -> u) -> Arg ftype -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Arg ftype -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Arg ftype -> m (Arg ftype) # | |
Show ftype => Show (Arg ftype) Source # | |
Eq ftype => Eq (Arg ftype) Source # | |
data SegmentType ftype Source #
Static PathSegment | Static path segment. "foo/bar/baz" contains the static segments |
Cap (Arg ftype) | A capture. "user/{userid}/name" would capture the arg |
Instances
Data ftype => Data (SegmentType ftype) Source # | |
Defined in Servant.Foreign.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SegmentType ftype -> c (SegmentType ftype) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SegmentType ftype) # toConstr :: SegmentType ftype -> Constr # dataTypeOf :: SegmentType ftype -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SegmentType ftype)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SegmentType ftype)) # gmapT :: (forall b. Data b => b -> b) -> SegmentType ftype -> SegmentType ftype # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SegmentType ftype -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SegmentType ftype -> r # gmapQ :: (forall d. Data d => d -> u) -> SegmentType ftype -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SegmentType ftype -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SegmentType ftype -> m (SegmentType ftype) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentType ftype -> m (SegmentType ftype) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentType ftype -> m (SegmentType ftype) # | |
Show ftype => Show (SegmentType ftype) Source # | |
Defined in Servant.Foreign.Internal showsPrec :: Int -> SegmentType ftype -> ShowS # show :: SegmentType ftype -> String # showList :: [SegmentType ftype] -> ShowS # | |
Eq ftype => Eq (SegmentType ftype) Source # | |
Defined in Servant.Foreign.Internal (==) :: SegmentType ftype -> SegmentType ftype -> Bool # (/=) :: SegmentType ftype -> SegmentType ftype -> Bool # |
_Cap :: forall ftype ftype. Prism (SegmentType ftype) (SegmentType ftype) (Arg ftype) (Arg ftype) Source #
_Static :: forall ftype. Prism' (SegmentType ftype) PathSegment Source #
newtype Segment ftype Source #
A part of the Url’s path.
Segment | |
|
Instances
Data ftype => Data (Segment ftype) Source # | |
Defined in Servant.Foreign.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Segment ftype -> c (Segment ftype) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Segment ftype) # toConstr :: Segment ftype -> Constr # dataTypeOf :: Segment ftype -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Segment ftype)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Segment ftype)) # gmapT :: (forall b. Data b => b -> b) -> Segment ftype -> Segment ftype # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Segment ftype -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Segment ftype -> r # gmapQ :: (forall d. Data d => d -> u) -> Segment ftype -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Segment ftype -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Segment ftype -> m (Segment ftype) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Segment ftype -> m (Segment ftype) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Segment ftype -> m (Segment ftype) # | |
Show ftype => Show (Segment ftype) Source # | |
Eq ftype => Eq (Segment ftype) Source # | |
_Segment :: forall ftype ftype. Iso (Segment ftype) (Segment ftype) (SegmentType ftype) (SegmentType ftype) Source #
captureArg :: Segment ftype -> Arg ftype Source #
Crashing Arg extraction from segment, TODO: remove
Type of a QueryArg
.
Instances
Data ArgType Source # | |
Defined in Servant.Foreign.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArgType -> c ArgType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArgType # toConstr :: ArgType -> Constr # dataTypeOf :: ArgType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ArgType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArgType) # gmapT :: (forall b. Data b => b -> b) -> ArgType -> ArgType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArgType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArgType -> r # gmapQ :: (forall d. Data d => d -> u) -> ArgType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArgType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArgType -> m ArgType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArgType -> m ArgType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArgType -> m ArgType # | |
Show ArgType Source # | |
Eq ArgType Source # | |
Url Query argument.
Urls can contain query arguments, which is a list of key-value pairs. In a typical url, query arguments look like this:
?foo=bar&alist[]=el1&alist[]=el2&aflag
Each pair can be
?foo=bar
: a plain key-val pair, either optional or required (QueryParam
)?aflag
: a flag (no value, implicitly Bool with defaultfalse
if it’s missing) (QueryFlag
)?alist[]=el1&alist[]=el2
: list of values (QueryParams
)
_queryArgType
will be set accordingly.
For the plain key-val pairs (QueryParam
), _queryArgName
’s ftype
will be wrapped in a Maybe
if the argument is optional.
QueryArg | |
|
Instances
Data ftype => Data (QueryArg ftype) Source # | |
Defined in Servant.Foreign.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QueryArg ftype -> c (QueryArg ftype) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (QueryArg ftype) # toConstr :: QueryArg ftype -> Constr # dataTypeOf :: QueryArg ftype -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (QueryArg ftype)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (QueryArg ftype)) # gmapT :: (forall b. Data b => b -> b) -> QueryArg ftype -> QueryArg ftype # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QueryArg ftype -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QueryArg ftype -> r # gmapQ :: (forall d. Data d => d -> u) -> QueryArg ftype -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> QueryArg ftype -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> QueryArg ftype -> m (QueryArg ftype) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QueryArg ftype -> m (QueryArg ftype) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QueryArg ftype -> m (QueryArg ftype) # | |
Show ftype => Show (QueryArg ftype) Source # | |
Eq ftype => Eq (QueryArg ftype) Source # | |
queryArgName :: forall ftype ftype. Lens (QueryArg ftype) (QueryArg ftype) (Arg ftype) (Arg ftype) Source #
HeaderArg | The name of the header and the foreign type of its value. |
| |
ReplaceHeaderArg | Unused, will never be set. TODO: remove |
|
Instances
Data ftype => Data (HeaderArg ftype) Source # | |
Defined in Servant.Foreign.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HeaderArg ftype -> c (HeaderArg ftype) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HeaderArg ftype) # toConstr :: HeaderArg ftype -> Constr # dataTypeOf :: HeaderArg ftype -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HeaderArg ftype)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HeaderArg ftype)) # gmapT :: (forall b. Data b => b -> b) -> HeaderArg ftype -> HeaderArg ftype # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HeaderArg ftype -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HeaderArg ftype -> r # gmapQ :: (forall d. Data d => d -> u) -> HeaderArg ftype -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HeaderArg ftype -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HeaderArg ftype -> m (HeaderArg ftype) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HeaderArg ftype -> m (HeaderArg ftype) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HeaderArg ftype -> m (HeaderArg ftype) # | |
Show ftype => Show (HeaderArg ftype) Source # | |
Eq ftype => Eq (HeaderArg ftype) Source # | |
headerPattern :: forall ftype. Traversal' (HeaderArg ftype) Text Source #
headerArg :: forall ftype ftype. Lens (HeaderArg ftype) (HeaderArg ftype) (Arg ftype) (Arg ftype) Source #
Full endpoint url, with all captures and parameters
Instances
Data ftype => Data (Url ftype) Source # | |
Defined in Servant.Foreign.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Url ftype -> c (Url ftype) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Url ftype) # toConstr :: Url ftype -> Constr # dataTypeOf :: Url ftype -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Url ftype)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Url ftype)) # gmapT :: (forall b. Data b => b -> b) -> Url ftype -> Url ftype # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Url ftype -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Url ftype -> r # gmapQ :: (forall d. Data d => d -> u) -> Url ftype -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Url ftype -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Url ftype -> m (Url ftype) # | |
Show ftype => Show (Url ftype) Source # | |
Eq ftype => Eq (Url ftype) Source # | |
data ReqBodyContentType Source #
See documentation of _reqBodyContentType
Instances
Full description of an endpoint in your API, generated by listFromAPI
. It should give you all the information needed to generate foreign language bindings.
Every field containing ftype
will use the foreign type mapping specified via HasForeignType
(see its docstring on how to set that up).
See https://docs.servant.dev/en/stable/tutorial/ApiType.html for accessible documentation of the possible content of an endpoint.
Req | |
|
Instances
GenerateList ftype (Req ftype) Source # | |
Defined in Servant.Foreign.Internal generateList :: Req ftype -> [Req ftype] Source # | |
Data ftype => Data (Req ftype) Source # | |
Defined in Servant.Foreign.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Req ftype -> c (Req ftype) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Req ftype) # toConstr :: Req ftype -> Constr # dataTypeOf :: Req ftype -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Req ftype)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Req ftype)) # gmapT :: (forall b. Data b => b -> b) -> Req ftype -> Req ftype # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Req ftype -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Req ftype -> r # gmapQ :: (forall d. Data d => d -> u) -> Req ftype -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Req ftype -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Req ftype -> m (Req ftype) # | |
Show ftype => Show (Req ftype) Source # | |
Eq ftype => Eq (Req ftype) Source # | |
reqFuncName :: forall ftype. Lens' (Req ftype) FunctionName Source #
reqBodyContentType :: forall ftype. Lens' (Req ftype) ReqBodyContentType Source #
class HasForeignType lang ftype a where Source #
HasForeignType
maps Haskell types with types in the target
language of your backend. For example, let's say you're
implementing a backend to some language X, and you want
a Text representation of each input/output type mentioned in the API:
-- First you need to create a dummy type to parametrize your -- instances. data LangX -- Otherwise you define instances for the types you need instance HasForeignType LangX Text Int where typeFor _ _ _ = "intX" -- Or for example in case of lists instance HasForeignType LangX Text a => HasForeignType LangX Text [a] where typeFor lang ftype _ = "listX of " <> typeFor lang ftype (Proxy :: Proxy a)
Finally to generate list of information about all the endpoints for an API you create a function of a form:
getEndpoints :: (HasForeign LangX Text api, GenerateList Text (Foreign Text api)) => Proxy api -> [Req Text] getEndpoints api = listFromAPI (Proxy :: Proxy LangX) (Proxy :: Proxy Text) api
-- If language __X__ is dynamically typed then you can use -- a predefined NoTypes parameter with the NoContent output type:
getEndpoints :: (HasForeign NoTypes NoContent api, GenerateList Text (Foreign NoContent api)) => Proxy api -> [Req NoContent] getEndpoints api = listFromAPI (Proxy :: Proxy NoTypes) (Proxy :: Proxy NoContent) api
The language definition without any foreign types. It can be used for dynamic languages which do not do type annotations.
class HasForeign lang ftype (api :: *) where Source #
Implementation of the Servant framework types.
Relevant instances: Everything containing HasForeignType
.
Instances
HasForeign (lang :: k) ftype EmptyAPI Source # | |
HasForeign (lang :: k) ftype Raw Source # | |
HasForeign lang ftype (ToServantApi r) => HasForeign (lang :: k) ftype (NamedRoutes r) Source # | |
Defined in Servant.Foreign.Internal type Foreign ftype (NamedRoutes r) Source # foreignFor :: Proxy lang -> Proxy ftype -> Proxy (NamedRoutes r) -> Req ftype -> Foreign ftype (NamedRoutes r) Source # | |
(HasForeign lang ftype a, HasForeign lang ftype b) => HasForeign (lang :: k) ftype (a :<|> b) Source # | |
(HasForeignType lang ftype NoContent, ReflectMethod method) => HasForeign (lang :: k) ftype (NoContentVerb method) Source # | |
Defined in Servant.Foreign.Internal type Foreign ftype (NoContentVerb method) Source # foreignFor :: Proxy lang -> Proxy ftype -> Proxy (NoContentVerb method) -> Req ftype -> Foreign ftype (NoContentVerb method) Source # | |
(KnownSymbol path, HasForeign lang ftype api) => HasForeign (lang :: k) ftype (path :> api) Source # | |
HasForeign lang ftype api => HasForeign (lang :: k) ftype (HttpVersion :> api) Source # | |
Defined in Servant.Foreign.Internal type Foreign ftype (HttpVersion :> api) Source # foreignFor :: Proxy lang -> Proxy ftype -> Proxy (HttpVersion :> api) -> Req ftype -> Foreign ftype (HttpVersion :> api) Source # | |
(KnownSymbol sym, HasForeignType lang ftype t, HasForeign lang ftype api) => HasForeign (lang :: k) ftype (Capture' mods sym t :> api) Source # | |
(KnownSymbol sym, HasForeignType lang ftype [t], HasForeign lang ftype sublayout) => HasForeign (lang :: k) ftype (CaptureAll sym t :> sublayout) Source # | |
Defined in Servant.Foreign.Internal type Foreign ftype (CaptureAll sym t :> sublayout) Source # foreignFor :: Proxy lang -> Proxy ftype -> Proxy (CaptureAll sym t :> sublayout) -> Req ftype -> Foreign ftype (CaptureAll sym t :> sublayout) Source # | |
HasForeign lang ftype api => HasForeign (lang :: k) ftype (Description desc :> api) Source # | |
Defined in Servant.Foreign.Internal type Foreign ftype (Description desc :> api) Source # foreignFor :: Proxy lang -> Proxy ftype -> Proxy (Description desc :> api) -> Req ftype -> Foreign ftype (Description desc :> api) Source # | |
HasForeign lang ftype api => HasForeign (lang :: k) ftype (Summary desc :> api) Source # | |
(HasForeignType lang ftype (Maybe a), HasForeign lang ftype api) => HasForeign (lang :: k) ftype (Fragment a :> api) Source # | |
(KnownSymbol sym, HasForeignType lang ftype (RequiredArgument mods a), HasForeign lang ftype api) => HasForeign (lang :: k) ftype (Header' mods sym a :> api) Source # | |
HasForeign lang ftype api => HasForeign (lang :: k) ftype (IsSecure :> api) Source # | |
(KnownSymbol sym, HasForeignType lang ftype Bool, HasForeign lang ftype api) => HasForeign (lang :: k) ftype (QueryFlag sym :> api) Source # | |
(KnownSymbol sym, HasForeignType lang ftype (RequiredArgument mods a), HasForeign lang ftype api) => HasForeign (lang :: k) ftype (QueryParam' mods sym a :> api) Source # | |
Defined in Servant.Foreign.Internal type Foreign ftype (QueryParam' mods sym a :> api) Source # foreignFor :: Proxy lang -> Proxy ftype -> Proxy (QueryParam' mods sym a :> api) -> Req ftype -> Foreign ftype (QueryParam' mods sym a :> api) Source # | |
(KnownSymbol sym, HasForeignType lang ftype [a], HasForeign lang ftype api) => HasForeign (lang :: k) ftype (QueryParams sym a :> api) Source # | |
Defined in Servant.Foreign.Internal type Foreign ftype (QueryParams sym a :> api) Source # foreignFor :: Proxy lang -> Proxy ftype -> Proxy (QueryParams sym a :> api) -> Req ftype -> Foreign ftype (QueryParams sym a :> api) Source # | |
HasForeign lang ftype api => HasForeign (lang :: k) ftype (RemoteHost :> api) Source # | |
Defined in Servant.Foreign.Internal type Foreign ftype (RemoteHost :> api) Source # foreignFor :: Proxy lang -> Proxy ftype -> Proxy (RemoteHost :> api) -> Req ftype -> Foreign ftype (RemoteHost :> api) Source # | |
(Elem JSON list, HasForeignType lang ftype a, HasForeign lang ftype api) => HasForeign (lang :: k) ftype (ReqBody' mods list a :> api) Source # | |
HasForeign lang ftype api => HasForeign (lang :: k) ftype (StreamBody' mods framing ctype a :> api) Source # | |
Defined in Servant.Foreign.Internal type Foreign ftype (StreamBody' mods framing ctype a :> api) Source # foreignFor :: Proxy lang -> Proxy ftype -> Proxy (StreamBody' mods framing ctype a :> api) -> Req ftype -> Foreign ftype (StreamBody' mods framing ctype a :> api) Source # | |
HasForeign lang ftype api => HasForeign (lang :: k) ftype (WithResource res :> api) Source # | |
Defined in Servant.Foreign.Internal type Foreign ftype (WithResource res :> api) Source # foreignFor :: Proxy lang -> Proxy ftype -> Proxy (WithResource res :> api) -> Req ftype -> Foreign ftype (WithResource res :> api) Source # | |
HasForeign lang ftype api => HasForeign (lang :: k) ftype (Vault :> api) Source # | |
HasForeign lang ftype api => HasForeign (lang :: k) ftype (WithNamedContext name context api) Source # | |
Defined in Servant.Foreign.Internal type Foreign ftype (WithNamedContext name context api) Source # foreignFor :: Proxy lang -> Proxy ftype -> Proxy (WithNamedContext name context api) -> Req ftype -> Foreign ftype (WithNamedContext name context api) Source # | |
(Elem JSON list, HasForeignType lang ftype a, ReflectMethod method) => HasForeign (lang :: k) ftype (Verb method status list a) Source # | |
(ct ~ JSON, HasForeignType lang ftype a, ReflectMethod method) => HasForeign (lang :: k) ftype (Stream method status framing ct a) Source # | TODO: doesn't taking framing into account. |
data EmptyForeignAPI Source #
Instances
GenerateList ftype EmptyForeignAPI Source # | |
Defined in Servant.Foreign.Internal generateList :: EmptyForeignAPI -> [Req ftype] Source # |
class GenerateList ftype reqs where Source #
Utility class used by listFromAPI
which computes
the data needed to generate a function for each endpoint
and hands it all back in a list.
generateList :: reqs -> [Req ftype] Source #
Instances
GenerateList ftype EmptyForeignAPI Source # | |
Defined in Servant.Foreign.Internal generateList :: EmptyForeignAPI -> [Req ftype] Source # | |
GenerateList ftype (Req ftype) Source # | |
Defined in Servant.Foreign.Internal generateList :: Req ftype -> [Req ftype] Source # | |
(GenerateList ftype start, GenerateList ftype rest) => GenerateList ftype (start :<|> rest) Source # | |
Defined in Servant.Foreign.Internal generateList :: (start :<|> rest) -> [Req ftype] Source # |
listFromAPI :: (HasForeign lang ftype api, GenerateList ftype (Foreign ftype api)) => Proxy lang -> Proxy ftype -> Proxy api -> [Req ftype] Source #
Generate the necessary data for codegen as a list, each Req
describing one endpoint from your API type.