servant-py-0.1.1.0: Automatically derive python functions to query servant webservices.

Safe HaskellNone
LanguageHaskell2010

Servant.PY

Contents

Synopsis

Generating python code from an API type

python :: HasForeign NoTypes NoContent api => Proxy api -> Foreign NoContent api Source #

Generate the data necessary to generate Python code for all the endpoints of an API, as :<|>-separated values of type PyRequest.

pythonTyped :: HasForeign Python Text api => Proxy api -> Foreign Text api Source #

Generate the data necessary to generate Python code for all the endpoints of an API, but try to get as much type-information into Python docstrings, in order to aid discoverability of client functions.

writePythonForAPI Source #

Arguments

:: (HasForeign NoTypes NoContent api, GenerateList NoContent (Foreign NoContent api)) 
=> Proxy api

proxy for your API type

-> PythonGenerator

python code generator to use (requests is the only one for now)

-> FilePath

path to the file you want to write the resulting javascript code into

-> IO () 

Directly generate all the Python functions for your API from a Proxy for your API type using the given generator and write the resulting code to a file at the given path.

pyForAPI Source #

Arguments

:: (HasForeign NoTypes NoContent api, GenerateList NoContent (Foreign NoContent api)) 
=> Proxy api

proxy for your API type

-> PythonGenerator

python code generator to use (requests is the only one for now)

-> Text

a text that you can embed in your pages or write to a file

Directly generate all the Python functions for your API from a Proxy for your API type. You can then write it to a file or integrate it in a page, for example.

pyTypedForAPI Source #

Arguments

:: (HasForeign Python Text api, GenerateList Text (Foreign Text api)) 
=> Proxy api

proxy for your API type

-> PythonGenerator

python code generator to use (requests is the only one for now)

-> Text

a text that you can embed in your pages or write to a file

Directly generate all the Python functions for your API from a Proxy for your API type. You can then write it to a file or integrate it in a page, for example.

writeTypedPythonForAPI Source #

Arguments

:: (HasForeign Python Text api, GenerateList Text (Foreign Text api)) 
=> Proxy api

proxy for your API type

-> PythonGenerator

python code generator to use (requests is the only one for now)

-> FilePath

path to the file you want to write the resulting javascript code into

-> IO () 

Options common to all generators

data CommonGeneratorOptions Source #

This structure is used by specific implementations to let you customize the output

Constructors

CommonGeneratorOptions 

Fields

defCommonGeneratorOptions :: CommonGeneratorOptions Source #

Default options.

> defCommonGeneratorOptions = CommonGeneratorOptions
>   { functionNameBuilder = snakeCase
>   , requestBody = "body"
>   , urlPrefix = ""
>   , indentation = "    "  -- 4 spaces
>   , returnMode = DangerMode
>   }

requests :: PythonGenerator Source #

Generate python functions that use the requests library. Uses defCommonGeneratorOptions for the generator options.

Function renamers

concatCase :: FunctionName -> Text #

Function name builder that simply concat each part together

snakeCase :: FunctionName -> Text #

Function name builder using the snake_case convention. each part is separated by a single underscore character.

camelCase :: FunctionName -> Text #

Function name builder using the CamelCase convention. each part begins with an upper case character.

Misc.

listFromAPI :: (HasForeign lang ftype api, GenerateList ftype (Foreign ftype api)) => Proxy lang -> Proxy ftype -> Proxy api -> [Req ftype] #

Generate the necessary data for codegen as a list, each Req describing one endpoint from your API type.

data NoTypes #

Instances
HasForeignType NoTypes NoContent (ftype :: k) 
Instance details

Defined in Servant.Foreign.Internal

Methods

typeFor :: Proxy NoTypes -> Proxy NoContent -> Proxy ftype -> NoContent #

class GenerateList ftype reqs where #

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] #

Instances
GenerateList ftype EmptyForeignAPI 
Instance details

Defined in Servant.Foreign.Internal

Methods

generateList :: EmptyForeignAPI -> [Req ftype] #

GenerateList ftype (Req ftype) 
Instance details

Defined in Servant.Foreign.Internal

Methods

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

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

Defined in Servant.Foreign.Internal

Methods

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

newtype FunctionName #

Constructors

FunctionName 

Fields

Instances
Eq FunctionName 
Instance details

Defined in Servant.Foreign.Internal

Data FunctionName 
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 :: (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 
Instance details

Defined in Servant.Foreign.Internal

Semigroup FunctionName 
Instance details

Defined in Servant.Foreign.Internal

Monoid FunctionName 
Instance details

Defined in Servant.Foreign.Internal