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

Safe HaskellNone
LanguageHaskell2010

Servant.Foreign.Internal

Description

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

Synopsis

Documentation

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 #

Show f => Show (Arg f) Source # 

Methods

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

show :: Arg f -> String #

showList :: [Arg f] -> ShowS #

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

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

data SegmentType f Source #

Constructors

Static PathSegment

a static path segment. like "/foo"

Cap (Arg f)

a capture. like "/:userid"

Instances

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

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 #

Show f => Show (Segment f) Source # 

Methods

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

show :: Segment f -> String #

showList :: [Segment f] -> ShowS #

_Segment :: forall f f. Iso (Segment f) (Segment f) (SegmentType f) (SegmentType f) Source #

type Path f = [Segment f] Source #

data ArgType Source #

Constructors

Normal 
Flag 
List 

data QueryArg f Source #

Constructors

QueryArg 

Instances

Eq f => Eq (QueryArg f) Source # 

Methods

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

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

Show f => Show (QueryArg f) Source # 

Methods

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

show :: QueryArg f -> String #

showList :: [QueryArg f] -> ShowS #

queryArgName :: forall f f. Lens (QueryArg f) (QueryArg f) (Arg f) (Arg f) 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 #

Show f => Show (HeaderArg 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 #

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 #

Show f => Show (Url f) Source # 

Methods

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

show :: Url f -> String #

showList :: [Url f] -> ShowS #

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

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

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 #

Show f => Show (Req f) Source # 

Methods

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

show :: Req f -> String #

showList :: [Req f] -> ShowS #

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

reqReturnType :: forall f. Lens' (Req f) (Maybe 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 #

defReq :: Req ftype Source #

class NotFound Source #

To be used exclusively as a "negative" return type/constraint by Elem type family.

type family Elem (a :: *) (ls :: [*]) :: Constraint where ... Source #

Equations

Elem a '[] = NotFound 
Elem a (a ': list) = () 
Elem a (b ': list) = Elem a list 

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 NoContent ftype -> Proxy * ftype -> Proxy NoTypes a -> ftype Source #

data NoTypes Source #

Instances

HasForeignType k * NoTypes NoContent ftype Source # 

Methods

typeFor :: Proxy NoContent ftype -> Proxy * ftype -> Proxy NoTypes a -> ftype 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 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 (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 ((:>) * * 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 ((:>) * * 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 k1 lang ftype a, HasForeign k1 lang ftype api) => HasForeign k1 lang ftype ((:>) * * (ReqBody k list a) api) Source # 

Associated Types

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

Methods

foreignFor :: Proxy lang ftype -> Proxy * ((* :> *) (ReqBody k list a) api) -> Proxy * api -> Req ((* :> *) (ReqBody k list a) api) -> Foreign ((* :> *) (ReqBody k 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 k1 lang ftype a, HasForeign k1 lang ftype api) => HasForeign k1 lang ftype ((:>) * * (QueryParam k sym a) api) Source # 

Associated Types

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

Methods

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

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

Associated Types

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

Methods

foreignFor :: Proxy lang ftype -> Proxy * ((* :> *) (Header sym a) api) -> Proxy * api -> Req ((* :> *) (Header sym a) api) -> Foreign ((* :> *) (Header 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 k1 lang ftype t, HasForeign k1 lang ftype api) => HasForeign k1 lang ftype ((:>) * * (Capture k sym t) api) Source # 

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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.