servant-foreign-0.16.1: Helpers for generating clients for servant APIs in any programming language
Safe HaskellNone
LanguageHaskell2010

Servant.Foreign.Internal

Synopsis

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

Constructors

FunctionName 

Fields

Instances

Instances details
Data FunctionName Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunctionName -> c FunctionName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunctionName #

toConstr :: FunctionName -> Constr #

dataTypeOf :: FunctionName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunctionName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunctionName) #

gmapT :: (forall b. Data b => b -> b) -> FunctionName -> FunctionName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunctionName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunctionName -> r #

gmapQ :: (forall d. Data d => d -> u) -> FunctionName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FunctionName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunctionName -> m FunctionName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionName -> m FunctionName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionName -> m FunctionName #

Monoid FunctionName Source # 
Instance details

Defined in Servant.Foreign.Internal

Semigroup FunctionName Source # 
Instance details

Defined in Servant.Foreign.Internal

Show FunctionName Source # 
Instance details

Defined in Servant.Foreign.Internal

Eq FunctionName Source # 
Instance details

Defined in Servant.Foreign.Internal

newtype PathSegment Source #

See documentation of Arg

Constructors

PathSegment 

Fields

Instances

Instances details
Data PathSegment Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PathSegment -> c PathSegment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PathSegment #

toConstr :: PathSegment -> Constr #

dataTypeOf :: PathSegment -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PathSegment) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PathSegment) #

gmapT :: (forall b. Data b => b -> b) -> PathSegment -> PathSegment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PathSegment -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PathSegment -> r #

gmapQ :: (forall d. Data d => d -> u) -> PathSegment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PathSegment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PathSegment -> m PathSegment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PathSegment -> m PathSegment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PathSegment -> m PathSegment #

IsString PathSegment Source # 
Instance details

Defined in Servant.Foreign.Internal

Monoid PathSegment Source # 
Instance details

Defined in Servant.Foreign.Internal

Semigroup PathSegment Source # 
Instance details

Defined in Servant.Foreign.Internal

Show PathSegment Source # 
Instance details

Defined in Servant.Foreign.Internal

Eq PathSegment Source # 
Instance details

Defined in Servant.Foreign.Internal

data Arg ftype Source #

Maps a name to the foreign type that belongs to the annotated value.

Used for header args, query args, and capture args.

Constructors

Arg 

Fields

  • _argName :: PathSegment

    The name to be captured.

    Only for capture args it really denotes a path segment.

  • _argType :: ftype

    Foreign type the associated value will have

Instances

Instances details
Data ftype => Data (Arg ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Methods

showsPrec :: Int -> Arg ftype -> ShowS #

show :: Arg ftype -> String #

showList :: [Arg ftype] -> ShowS #

Eq ftype => Eq (Arg ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

(==) :: Arg ftype -> Arg ftype -> Bool #

(/=) :: Arg ftype -> Arg ftype -> Bool #

argName :: forall ftype f. Functor f => (PathSegment -> f PathSegment) -> Arg ftype -> f (Arg ftype) Source #

argType :: forall ftype1 ftype2 f. Functor f => (ftype1 -> f ftype2) -> Arg ftype1 -> f (Arg ftype2) Source #

argPath :: forall ftype f. (Contravariant f, Functor f) => (Text -> f Text) -> Arg ftype -> f (Arg ftype) Source #

data SegmentType ftype Source #

Constructors

Static PathSegment

Static path segment.

"foo/bar/baz"

contains the static segments "foo", "bar" and "baz".

Cap (Arg ftype)

A capture.

"user/{userid}/name"

would capture the arg userid with type ftype.

Instances

Instances details
Data ftype => Data (SegmentType ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Methods

showsPrec :: Int -> SegmentType ftype -> ShowS #

show :: SegmentType ftype -> String #

showList :: [SegmentType ftype] -> ShowS #

Eq ftype => Eq (SegmentType ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

(==) :: SegmentType ftype -> SegmentType ftype -> Bool #

(/=) :: SegmentType ftype -> SegmentType ftype -> Bool #

_Static :: forall ftype p f. (Choice p, Applicative f) => p PathSegment (f PathSegment) -> p (SegmentType ftype) (f (SegmentType ftype)) Source #

_Cap :: forall ftype1 ftype2 p f. (Choice p, Applicative f) => p (Arg ftype1) (f (Arg ftype2)) -> p (SegmentType ftype1) (f (SegmentType ftype2)) Source #

newtype Segment ftype Source #

A part of the Url’s path.

Constructors

Segment 

Fields

Instances

Instances details
Data ftype => Data (Segment ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Methods

showsPrec :: Int -> Segment ftype -> ShowS #

show :: Segment ftype -> String #

showList :: [Segment ftype] -> ShowS #

Eq ftype => Eq (Segment ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

(==) :: Segment ftype -> Segment ftype -> Bool #

(/=) :: Segment ftype -> Segment ftype -> Bool #

_Segment :: forall ftype1 ftype2 p f. (Profunctor p, Functor f) => p (SegmentType ftype1) (f (SegmentType ftype2)) -> p (Segment ftype1) (f (Segment ftype2)) Source #

isCapture :: Segment ftype -> Bool Source #

Whether a segment is a Cap.

captureArg :: Segment ftype -> Arg ftype Source #

Crashing Arg extraction from segment, TODO: remove

type Path ftype = [Segment ftype] Source #

data ArgType Source #

Type of a QueryArg.

Constructors

Normal 
Flag 
List 

Instances

Instances details
Data ArgType Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Eq ArgType Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

(==) :: ArgType -> ArgType -> Bool #

(/=) :: ArgType -> ArgType -> Bool #

data QueryArg ftype 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 default false 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.

Constructors

QueryArg 

Fields

  • _queryArgName :: Arg ftype

    Name and foreign type of the argument. Will be wrapped in Maybe if the query is optional and in a `[]` if the query is a list

  • _queryArgType :: ArgType

    one of normal/plain, list or flag

Instances

Instances details
Data ftype => Data (QueryArg ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Methods

showsPrec :: Int -> QueryArg ftype -> ShowS #

show :: QueryArg ftype -> String #

showList :: [QueryArg ftype] -> ShowS #

Eq ftype => Eq (QueryArg ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

(==) :: QueryArg ftype -> QueryArg ftype -> Bool #

(/=) :: QueryArg ftype -> QueryArg ftype -> Bool #

queryArgName :: forall ftype1 ftype2 f. Functor f => (Arg ftype1 -> f (Arg ftype2)) -> QueryArg ftype1 -> f (QueryArg ftype2) Source #

queryArgType :: forall ftype f. Functor f => (ArgType -> f ArgType) -> QueryArg ftype -> f (QueryArg ftype) Source #

data HeaderArg ftype Source #

Constructors

HeaderArg

The name of the header and the foreign type of its value.

Fields

ReplaceHeaderArg

Unused, will never be set.

TODO: remove

Fields

Instances

Instances details
Data ftype => Data (HeaderArg ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Methods

showsPrec :: Int -> HeaderArg ftype -> ShowS #

show :: HeaderArg ftype -> String #

showList :: [HeaderArg ftype] -> ShowS #

Eq ftype => Eq (HeaderArg ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

(==) :: HeaderArg ftype -> HeaderArg ftype -> Bool #

(/=) :: HeaderArg ftype -> HeaderArg ftype -> Bool #

headerArg :: forall ftype1 ftype2 f. Functor f => (Arg ftype1 -> f (Arg ftype2)) -> HeaderArg ftype1 -> f (HeaderArg ftype2) Source #

headerPattern :: forall ftype f. Applicative f => (Text -> f Text) -> HeaderArg ftype -> f (HeaderArg ftype) Source #

_HeaderArg :: forall ftype p f. (Choice p, Applicative f) => p (Arg ftype) (f (Arg ftype)) -> p (HeaderArg ftype) (f (HeaderArg ftype)) Source #

_ReplaceHeaderArg :: forall ftype p f. (Choice p, Applicative f) => p (Arg ftype, Text) (f (Arg ftype, Text)) -> p (HeaderArg ftype) (f (HeaderArg ftype)) Source #

data Url ftype Source #

Full endpoint url, with all captures and parameters

Constructors

Url 

Fields

  • _path :: Path ftype

    Url path, list of either static segments or captures

    "foo/{id}/bar"
  • _queryStr :: [QueryArg ftype]

    List of query args

    "?foo=bar&a=b"
  • _frag :: Maybe ftype

    Url fragment.

    Not sent to the HTTP server, so only useful for frontend matters (e.g. inter-page linking).

    #fragmentText

Instances

Instances details
Data ftype => Data (Url ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Methods

showsPrec :: Int -> Url ftype -> ShowS #

show :: Url ftype -> String #

showList :: [Url ftype] -> ShowS #

Eq ftype => Eq (Url ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

(==) :: Url ftype -> Url ftype -> Bool #

(/=) :: Url ftype -> Url ftype -> Bool #

defUrl :: Url ftype Source #

frag :: forall ftype f. Functor f => (Maybe ftype -> f (Maybe ftype)) -> Url ftype -> f (Url ftype) Source #

path :: forall ftype f. Functor f => (Path ftype -> f (Path ftype)) -> Url ftype -> f (Url ftype) Source #

queryStr :: forall ftype f. Functor f => ([QueryArg ftype] -> f [QueryArg ftype]) -> Url ftype -> f (Url ftype) Source #

data ReqBodyContentType Source #

See documentation of _reqBodyContentType

Instances

Instances details
Data ReqBodyContentType Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReqBodyContentType -> c ReqBodyContentType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReqBodyContentType #

toConstr :: ReqBodyContentType -> Constr #

dataTypeOf :: ReqBodyContentType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ReqBodyContentType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReqBodyContentType) #

gmapT :: (forall b. Data b => b -> b) -> ReqBodyContentType -> ReqBodyContentType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReqBodyContentType -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReqBodyContentType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReqBodyContentType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReqBodyContentType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReqBodyContentType -> m ReqBodyContentType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReqBodyContentType -> m ReqBodyContentType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReqBodyContentType -> m ReqBodyContentType #

Read ReqBodyContentType Source # 
Instance details

Defined in Servant.Foreign.Internal

Show ReqBodyContentType Source # 
Instance details

Defined in Servant.Foreign.Internal

Eq ReqBodyContentType Source # 
Instance details

Defined in Servant.Foreign.Internal

data Req ftype Source #

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.

Constructors

Req 

Fields

  • _reqUrl :: Url ftype

    Full list of URL segments, including captures

  • _reqMethod :: Method

    "GET"/"POST"/"PUT"/…

  • _reqHeaders :: [HeaderArg ftype]

    Headers required by this endpoint, with their type

  • _reqBody :: Maybe ftype

    Foreign type of the expected request body (ReqBody), if any

  • _reqReturnType :: Maybe ftype

    The foreign type of the response, if any

  • _reqFuncName :: FunctionName

    The URL segments rendered in a way that they can be easily concatenated into a canonical function name

  • _reqBodyContentType :: ReqBodyContentType

    The content type the request body is transferred as.

    This is a severe limitation of servant-foreign currently, as we only allow the content type to be JSON no user-defined content types. (ReqBodyMultipart is not actually implemented.)

    Thus, any routes looking like this will work:

    "foo" :> Get '[JSON] Foo

    while routes like

    "foo" :> Get '[MyFancyContentType] Foo

    will fail with an error like

    • JSON expected in list '[MyFancyContentType]

Instances

Instances details
GenerateList ftype (Req ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

generateList :: Req ftype -> [Req ftype] Source #

Data ftype => Data (Req ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Methods

showsPrec :: Int -> Req ftype -> ShowS #

show :: Req ftype -> String #

showList :: [Req ftype] -> ShowS #

Eq ftype => Eq (Req ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

(==) :: Req ftype -> Req ftype -> Bool #

(/=) :: Req ftype -> Req ftype -> Bool #

reqBody :: forall ftype f. Functor f => (Maybe ftype -> f (Maybe ftype)) -> Req ftype -> f (Req ftype) Source #

reqBodyContentType :: forall ftype f. Functor f => (ReqBodyContentType -> f ReqBodyContentType) -> Req ftype -> f (Req ftype) Source #

reqFuncName :: forall ftype f. Functor f => (FunctionName -> f FunctionName) -> Req ftype -> f (Req ftype) Source #

reqHeaders :: forall ftype f. Functor f => ([HeaderArg ftype] -> f [HeaderArg ftype]) -> Req ftype -> f (Req ftype) Source #

reqMethod :: forall ftype f. Functor f => (Method -> f Method) -> Req ftype -> f (Req ftype) Source #

reqReturnType :: forall ftype f. Functor f => (Maybe ftype -> f (Maybe ftype)) -> Req ftype -> f (Req ftype) Source #

reqUrl :: forall ftype f. Functor f => (Url ftype -> f (Url ftype)) -> Req ftype -> f (Req ftype) Source #

defReq :: Req ftype Source #

class HasForeignType (lang :: k) ftype (a :: k1) 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

Methods

typeFor :: Proxy lang -> Proxy ftype -> Proxy a -> ftype Source #

Instances

Instances details
HasForeignType NoTypes NoContent (a :: k) Source #

Use if the foreign language does not have any types.

Instance details

Defined in Servant.Foreign.Internal

data NoTypes Source #

The language definition without any foreign types. It can be used for dynamic languages which do not do type annotations.

Instances

Instances details
HasForeignType NoTypes NoContent (a :: k) Source #

Use if the foreign language does not have any types.

Instance details

Defined in Servant.Foreign.Internal

class HasForeign (lang :: k) ftype api where Source #

Implementation of the Servant framework types.

Relevant instances: Everything containing HasForeignType.

Associated Types

type Foreign ftype api Source #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy api -> Req ftype -> Foreign ftype api Source #

Instances

Instances details
HasForeign (lang :: k) ftype EmptyAPI Source # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype EmptyAPI 
Instance details

Defined in Servant.Foreign.Internal

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy EmptyAPI -> Req ftype -> Foreign ftype EmptyAPI Source #

HasForeign (lang :: k) ftype Raw Source # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype Raw 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype Raw = Method -> Req ftype

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy Raw -> Req ftype -> Foreign ftype Raw Source #

HasForeign lang ftype (ToServantApi r) => HasForeign (lang :: k) ftype (NamedRoutes r) Source # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (NamedRoutes r) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (NamedRoutes r) = Foreign ftype (ToServantApi r)

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (a :<|> b) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (a :<|> b) = Foreign ftype a :<|> Foreign ftype b

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (a :<|> b) -> Req ftype -> Foreign ftype (a :<|> b) Source #

(HasForeignType lang ftype NoContent, ReflectMethod method) => HasForeign (lang :: k) ftype (NoContentVerb method) Source # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (NoContentVerb method) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (NoContentVerb method) = Req ftype

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (path :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (path :> api) = Foreign ftype api

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (path :> api) -> Req ftype -> Foreign ftype (path :> api) Source #

HasForeign lang ftype api => HasForeign (lang :: k) ftype (HttpVersion :> api) Source # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (HttpVersion :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (HttpVersion :> api) = Foreign ftype api

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Capture' mods sym t :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (Capture' mods sym t :> api) = Foreign ftype api

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (Capture' mods sym t :> api) -> Req ftype -> Foreign 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 # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (CaptureAll sym t :> sublayout) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (CaptureAll sym t :> sublayout) = Foreign ftype sublayout

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Description desc :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (Description desc :> api) = Foreign ftype api

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Summary desc :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (Summary desc :> api) = Foreign ftype api

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (Summary desc :> api) -> Req ftype -> Foreign ftype (Summary desc :> api) Source #

(HasForeignType lang ftype (Maybe a), HasForeign lang ftype api) => HasForeign (lang :: k) ftype (Fragment a :> api) Source # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Fragment a :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (Fragment a :> api) = Foreign ftype api

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (Fragment a :> api) -> Req ftype -> Foreign 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 # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Header' mods sym a :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (Header' mods sym a :> api) = Foreign ftype api

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (Header' mods sym a :> api) -> Req ftype -> Foreign ftype (Header' mods sym a :> api) Source #

HasForeign lang ftype api => HasForeign (lang :: k) ftype (IsSecure :> api) Source # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (IsSecure :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (IsSecure :> api) = Foreign ftype api

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (IsSecure :> api) -> Req ftype -> Foreign ftype (IsSecure :> api) Source #

(KnownSymbol sym, HasForeignType lang ftype Bool, HasForeign lang ftype api) => HasForeign (lang :: k) ftype (QueryFlag sym :> api) Source # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (QueryFlag sym :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (QueryFlag sym :> api) = Foreign ftype api

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (QueryFlag sym :> api) -> Req ftype -> Foreign 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 # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (QueryParam' mods sym a :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (QueryParam' mods sym a :> api) = Foreign ftype api

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (QueryParams sym a :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (QueryParams sym a :> api) = Foreign ftype api

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (RemoteHost :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (RemoteHost :> api) = Foreign ftype api

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (ReqBody' mods list a :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (ReqBody' mods list a :> api) = Foreign ftype api

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (ReqBody' mods list a :> api) -> Req ftype -> Foreign ftype (ReqBody' mods list a :> api) Source #

HasForeign lang ftype api => HasForeign (lang :: k) ftype (StreamBody' mods framing ctype a :> api) Source # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (StreamBody' mods framing ctype a :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (StreamBody' mods framing ctype a :> api) = Foreign ftype api

Methods

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 (Vault :> api) Source # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Vault :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (Vault :> api) = Foreign ftype api

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (Vault :> api) -> Req ftype -> Foreign ftype (Vault :> api) Source #

HasForeign lang ftype api => HasForeign (lang :: k1) ftype (WithResource res :> api) Source # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (WithResource res :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (WithResource res :> api) = Foreign ftype api

Methods

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 (WithNamedContext name context api) Source # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (WithNamedContext name context api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (WithNamedContext name context api) = Foreign ftype api

Methods

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 # 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Verb method status list a) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (Verb method status list a) = Req ftype

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (Verb method status list a) -> Req ftype -> Foreign 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.

Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Stream method status framing ct a) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (Stream method status framing ct a) = Req ftype

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (Stream method status framing ct a) -> Req ftype -> Foreign ftype (Stream method status framing ct a) Source #

data EmptyForeignAPI Source #

Constructors

EmptyForeignAPI 

Instances

Instances details
GenerateList ftype EmptyForeignAPI Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

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.

Methods

generateList :: reqs -> [Req ftype] Source #

Instances

Instances details
GenerateList ftype EmptyForeignAPI Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

generateList :: EmptyForeignAPI -> [Req ftype] Source #

GenerateList ftype (Req ftype) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

generateList :: Req ftype -> [Req ftype] Source #

(GenerateList ftype start, GenerateList ftype rest) => GenerateList ftype (start :<|> rest) Source # 
Instance details

Defined in Servant.Foreign.Internal

Methods

generateList :: (start :<|> rest) -> [Req ftype] Source #

listFromAPI :: forall {k} (lang :: k) ftype api. (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.