servant-foreign-0.11.1: Helpers for generating clients for servant APIs in any programming language

Safe HaskellNone
LanguageHaskell2010

Servant.Foreign

Description

Generalizes all the data needed to make code generation work with arbitrary programming languages.

Synopsis

Documentation

data ArgType Source #

Constructors

Normal 
Flag 
List 

Instances

Eq ArgType Source # 

Methods

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

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

Data ArgType Source # 

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 :: (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 # 

data HeaderArg f Source #

Constructors

HeaderArg 

Fields

ReplaceHeaderArg 

Instances

Eq f => Eq (HeaderArg f) Source # 

Methods

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

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

Data f => Data (HeaderArg f) Source # 

Methods

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

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

toConstr :: HeaderArg f -> Constr #

dataTypeOf :: HeaderArg f -> DataType #

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

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

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

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

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

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

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

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

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

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

Show f => Show (HeaderArg f) Source # 

data QueryArg f Source #

Constructors

QueryArg 

Instances

Eq f => Eq (QueryArg f) Source # 

Methods

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

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

Data f => Data (QueryArg f) Source # 

Methods

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

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

toConstr :: QueryArg f -> Constr #

dataTypeOf :: QueryArg f -> DataType #

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

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

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

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

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

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

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

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

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

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

Show f => Show (QueryArg f) Source # 

Methods

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

show :: QueryArg f -> String #

showList :: [QueryArg f] -> ShowS #

data Req f Source #

Instances

GenerateList ftype (Req ftype) Source # 

Methods

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

Eq f => Eq (Req f) Source # 

Methods

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

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

Data f => Data (Req f) Source # 

Methods

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

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

toConstr :: Req f -> Constr #

dataTypeOf :: Req f -> DataType #

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

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

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

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

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

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

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

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

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

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

Show f => Show (Req f) Source # 

Methods

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

show :: Req f -> String #

showList :: [Req f] -> ShowS #

newtype Segment f Source #

Constructors

Segment 

Fields

Instances

Eq f => Eq (Segment f) Source # 

Methods

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

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

Data f => Data (Segment f) Source # 

Methods

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

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

toConstr :: Segment f -> Constr #

dataTypeOf :: Segment f -> DataType #

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

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

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

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

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

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

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

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

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

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

Show f => Show (Segment f) Source # 

Methods

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

show :: Segment f -> String #

showList :: [Segment f] -> ShowS #

data SegmentType f Source #

Constructors

Static PathSegment

a static path segment. like "/foo"

Cap (Arg f)

a capture. like "/:userid"

Instances

Eq f => Eq (SegmentType f) Source # 
Data f => Data (SegmentType f) Source # 

Methods

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

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

toConstr :: SegmentType f -> Constr #

dataTypeOf :: SegmentType f -> DataType #

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

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

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

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

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

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

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

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

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

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

Show f => Show (SegmentType f) Source # 

data Url f Source #

Constructors

Url 

Fields

Instances

Eq f => Eq (Url f) Source # 

Methods

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

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

Data f => Data (Url f) Source # 

Methods

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

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

toConstr :: Url f -> Constr #

dataTypeOf :: Url f -> DataType #

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

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

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

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

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

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

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

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

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

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

Show f => Show (Url f) Source # 

Methods

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

show :: Url f -> String #

showList :: [Url f] -> ShowS #

type Path f = [Segment f] Source #

data Arg f Source #

Constructors

Arg 

Fields

Instances

Eq f => Eq (Arg f) Source # 

Methods

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

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

Data f => Data (Arg f) Source # 

Methods

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

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

toConstr :: Arg f -> Constr #

dataTypeOf :: Arg f -> DataType #

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

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

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

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

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

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

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

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

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

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

Show f => Show (Arg f) Source # 

Methods

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

show :: Arg f -> String #

showList :: [Arg f] -> ShowS #

newtype FunctionName Source #

Constructors

FunctionName 

Fields

Instances

Eq FunctionName Source # 
Data FunctionName Source # 

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 :: (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 #

Show FunctionName Source # 
Semigroup FunctionName Source # 
Monoid FunctionName Source # 

newtype PathSegment Source #

Constructors

PathSegment 

Fields

Instances

Eq PathSegment Source # 
Data PathSegment Source # 

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 :: (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 #

Show PathSegment Source # 
IsString PathSegment Source # 
Semigroup PathSegment Source # 
Monoid PathSegment Source # 

argName :: forall f. Lens' (Arg f) PathSegment Source #

argType :: forall f f. Lens (Arg f) (Arg f) f f Source #

reqUrl :: forall f. Lens' (Req f) (Url f) Source #

reqMethod :: forall f. Lens' (Req f) Method Source #

reqHeaders :: forall f. Lens' (Req f) [HeaderArg f] Source #

reqBody :: forall f. Lens' (Req f) (Maybe f) Source #

reqReturnType :: forall f. Lens' (Req f) (Maybe f) Source #

path :: forall f. Lens' (Url f) (Path f) Source #

queryStr :: forall f. Lens' (Url f) [QueryArg f] Source #

queryArgName :: forall f f. Lens (QueryArg f) (QueryArg f) (Arg f) (Arg f) Source #

headerArg :: forall f f. Lens (HeaderArg f) (HeaderArg f) (Arg f) (Arg f) Source #

_HeaderArg :: forall f. Prism' (HeaderArg f) (Arg f) Source #

_Cap :: forall f f. Prism (SegmentType f) (SegmentType f) (Arg f) (Arg f) Source #

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

Minimal complete definition

foreignFor

Associated Types

type Foreign ftype api :: * Source #

Methods

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

Instances

HasForeign k lang ftype Raw Source # 

Associated Types

type Foreign Raw api :: * Source #

Methods

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

HasForeign k lang ftype EmptyAPI Source # 

Associated Types

type Foreign EmptyAPI api :: * Source #

Methods

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

(HasForeign k lang ftype a, HasForeign k lang ftype b) => HasForeign k lang ftype ((:<|>) a b) Source # 

Associated Types

type Foreign (a :<|> b) api :: * Source #

Methods

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

HasForeign k lang ftype api => HasForeign k lang ftype ((:>) * (Description desc) api) Source # 

Associated Types

type Foreign ((* :> Description desc) api) api :: * Source #

Methods

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

HasForeign k lang ftype api => HasForeign k lang ftype ((:>) * (Summary desc) api) Source # 

Associated Types

type Foreign ((* :> Summary desc) api) api :: * Source #

Methods

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

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

Associated Types

type Foreign ((* :> HttpVersion) api) api :: * Source #

Methods

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

HasForeign k lang ftype api => HasForeign k lang ftype (WithNamedContext name context api) Source # 

Associated Types

type Foreign (WithNamedContext name context api) api :: * Source #

Methods

foreignFor :: Proxy lang ftype -> Proxy * (WithNamedContext name context api) -> Proxy * api -> Req (WithNamedContext name context api) -> Foreign (WithNamedContext name context api) api Source #

HasForeign k lang ftype api => HasForeign k lang ftype ((:>) * Vault api) Source # 

Associated Types

type Foreign ((* :> Vault) api) api :: * Source #

Methods

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

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

Associated Types

type Foreign ((* :> IsSecure) api) api :: * Source #

Methods

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

HasForeign k lang ftype api => HasForeign k lang ftype ((:>) * RemoteHost api) Source # 

Associated Types

type Foreign ((* :> RemoteHost) api) api :: * Source #

Methods

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

(KnownSymbol path, HasForeign k lang ftype api) => HasForeign k lang ftype ((:>) Symbol path api) Source # 

Associated Types

type Foreign ((Symbol :> path) api) api :: * Source #

Methods

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

(Elem * JSON list, HasForeignType k * lang ftype a, HasForeign k lang ftype api) => HasForeign k lang ftype ((:>) * (ReqBody' mods list a) api) Source # 

Associated Types

type Foreign ((* :> ReqBody' mods list a) api) api :: * Source #

Methods

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

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

Associated Types

type Foreign ((* :> QueryFlag sym) api) api :: * Source #

Methods

foreignFor :: Proxy lang ftype -> Proxy * ((* :> QueryFlag sym) api) -> Proxy * api -> Req ((* :> QueryFlag sym) api) -> Foreign ((* :> QueryFlag sym) api) api Source #

(KnownSymbol sym, HasForeignType k * lang ftype [a], HasForeign k lang ftype api) => HasForeign k lang ftype ((:>) * (QueryParams sym a) api) Source # 

Associated Types

type Foreign ((* :> QueryParams sym a) api) api :: * Source #

Methods

foreignFor :: Proxy lang ftype -> Proxy * ((* :> QueryParams sym a) api) -> Proxy * api -> Req ((* :> QueryParams sym a) api) -> Foreign ((* :> QueryParams sym a) api) api Source #

(KnownSymbol sym, HasForeignType k * lang ftype (RequiredArgument mods a), HasForeign k lang ftype api) => HasForeign k lang ftype ((:>) * (QueryParam' mods sym a) api) Source # 

Associated Types

type Foreign ((* :> QueryParam' mods sym a) api) api :: * Source #

Methods

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

(KnownSymbol sym, HasForeignType k * lang ftype (RequiredArgument mods a), HasForeign k lang ftype api) => HasForeign k lang ftype ((:>) * (Header' * mods sym a) api) Source # 

Associated Types

type Foreign ((* :> Header' * mods sym a) api) api :: * Source #

Methods

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

(KnownSymbol sym, HasForeignType k * lang ftype [t], HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * (CaptureAll sym t) sublayout) Source # 

Associated Types

type Foreign ((* :> CaptureAll sym t) sublayout) api :: * Source #

Methods

foreignFor :: Proxy lang ftype -> Proxy * ((* :> CaptureAll sym t) sublayout) -> Proxy * api -> Req ((* :> CaptureAll sym t) sublayout) -> Foreign ((* :> CaptureAll sym t) sublayout) api Source #

(KnownSymbol sym, HasForeignType k * lang ftype t, HasForeign k lang ftype api) => HasForeign k lang ftype ((:>) * (Capture' mods sym t) api) Source # 

Associated Types

type Foreign ((* :> Capture' mods sym t) api) api :: * Source #

Methods

foreignFor :: Proxy lang ftype -> Proxy * ((* :> Capture' mods sym t) api) -> Proxy * api -> Req ((* :> Capture' mods sym t) api) -> Foreign ((* :> Capture' mods sym t) api) api Source #

(Elem * JSON list, HasForeignType k * lang ftype a, ReflectMethod k1 method) => HasForeign k lang ftype (Verb k1 method status list a) Source # 

Associated Types

type Foreign (Verb k1 method status list a) api :: * Source #

Methods

foreignFor :: Proxy lang ftype -> Proxy * (Verb k1 method status list a) -> Proxy * api -> Req (Verb k1 method status list a) -> Foreign (Verb k1 method status list a) api 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 type _ = "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

Minimal complete definition

typeFor

Methods

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

Instances

HasForeignType * k NoTypes NoContent ftype Source # 

Methods

typeFor :: Proxy NoTypes ftype -> Proxy * ftype -> Proxy NoContent a -> 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.

Minimal complete definition

generateList

Methods

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

Instances

GenerateList ftype EmptyForeignAPI Source # 

Methods

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

GenerateList ftype (Req ftype) Source # 

Methods

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

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

Methods

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

data NoTypes Source #

Instances

HasForeignType * k NoTypes NoContent ftype Source # 

Methods

typeFor :: Proxy NoTypes ftype -> Proxy * ftype -> Proxy NoContent a -> ftype Source #

defReq :: 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.