servant-js-0.6.1: Automatically derive javascript functions to query servant webservices.

LicenseBSD3
MaintainerAlp Mestanogullari <alpmestan@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Servant.JS

Contents

Description

Generating Javascript code to query your APIs using vanilla Javascript, Angular.js or JQuery.

Using this package is very simple. Say you have this API type around:

type API = "users" :> Get '[JSON] [Users]
      :<|> "messages" :> Get '[JSON] [Message]

All you need to do to generate the Javascript code is to write a Proxy for this API type:

api :: Proxy API
api = Proxy

And pick one of the generators:

  • vanillaJS and vanillaJSWith generate functions that use XMLHttpRequest to query your endpoints. The former just calls the latter with default code-generation options.
  • jquery and jqueryWith follow the same pattern except that they generate functions that use jQuery's AJAX functions.
  • angular and angularWith do the same but use Angular.js's $http service. In addition, we provide angularService and angularServiceWith which produce functions under an Angular service that your controlers can depend on to query the API.

Let's keep it simple and produce vanilla Javascript code with the default options.

jsCode :: Text
jsCode = jsForAPI api vanillaJS

That's it! If you want to write that code to a file:

writeJSCode :: IO ()
writeJSCode = writeJSForAPI api vanillaJS "./my_api.js"

If you want to customize the rendering options, take a look at CommonGeneratorOptions which are generic options common to all the generators. the xxxWith variants all take CommonGeneratorOptions whereas the xxx versions use defCommonGeneratorOptions. Once you have some custom

myOptions :: 'CommonGeneratorOptions'

All you need to do to use it is to use vanillaJSWith and pass it myOptions.

jsCodeWithMyOptions :: Text
jsCodeWithMyOptions = jsForAPI api (vanillaJSWith myOptions)

Follow the same pattern for any other generator.

Note: The Angular generators take an additional type of options, namely AngularOptions, to let you tweak aspects of the code generation that are specific to Angular.js.

Synopsis

Generating javascript code from an API type

jsForAPI Source

Arguments

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

proxy for your API type

-> JavaScriptGenerator

js code generator to use (angular, vanilla js, jquery, others)

-> Text

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

Directly generate all the javascript 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.

writeJSForAPI Source

Arguments

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

proxy for your API type

-> JavaScriptGenerator

js code generator to use (angular, vanilla js, jquery, others)

-> FilePath

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

-> IO () 

Directly generate all the javascript 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.

Options common to all generators

data CommonGeneratorOptions Source

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

Constructors

CommonGeneratorOptions 

Fields

functionNameBuilder :: FunctionName -> Text

function generating function names

requestBody :: Text

name used when a user want to send the request body (to let you redefine it)

successCallback :: Text

name of the callback parameter when the request was successful

errorCallback :: Text

name of the callback parameter when the request reported an error

moduleName :: Text

namespace on which we define the foreign function (empty mean local var)

urlPrefix :: Text

a prefix we should add to the Url in the codegen

defCommonGeneratorOptions :: CommonGeneratorOptions Source

Default options.

> defCommonGeneratorOptions = CommonGeneratorOptions
>   { functionNameBuilder = camelCase
>   , requestBody = "body"
>   , successCallback = "onSuccess"
>   , errorCallback = "onError"
>   , moduleName = ""
>   , urlPrefix = ""
>   }

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.

Vanilla Javascript code generation

vanillaJS :: JavaScriptGenerator Source

Generate vanilla javascript functions to make AJAX requests to your API, using XMLHttpRequest. Uses defCommonGeneratorOptions for the CommonGeneratorOptions.

vanillaJSWith :: CommonGeneratorOptions -> JavaScriptGenerator Source

Generate vanilla javascript functions to make AJAX requests to your API, using XMLHttpRequest. Lets you specify your own options.

JQuery code generation

jquery :: JavaScriptGenerator Source

Generate javascript functions that use the jQuery library to make the AJAX calls. Uses defCommonGeneratorOptions for the generator options.

jqueryWith :: CommonGeneratorOptions -> JavaScriptGenerator Source

Generate javascript functions that use the jQuery library to make the AJAX calls. Lets you specify your own CommonGeneratorOptions.

Angular.js code generation

angular :: AngularOptions -> JavaScriptGenerator Source

Generate regular javacript functions that use the $http service, using default values for CommonGeneratorOptions.

angularWith :: AngularOptions -> CommonGeneratorOptions -> JavaScriptGenerator Source

Generate regular javascript functions that use the $http service.

angularService :: AngularOptions -> JavaScriptGenerator Source

Instead of simply generating top level functions, generates a service instance on which your controllers can depend to access your API. This variant uses default AngularOptions.

angularServiceWith :: AngularOptions -> CommonGeneratorOptions -> JavaScriptGenerator Source

Instead of simply generating top level functions, generates a service instance on which your controllers can depend to access your API

data AngularOptions Source

Options specific to the angular code generator

Constructors

AngularOptions 

Fields

serviceName :: Text

When generating code with wrapInService, name of the service to generate

prologue :: Text -> Text -> Text

beginning of the service definition

epilogue :: Text

end of the service definition

defAngularOptions :: AngularOptions Source

Default options for the Angular codegen. Used by wrapInService.

Axios code generation

axios :: AxiosOptions -> JavaScriptGenerator Source

Generate regular javacript functions that use the axios library, using default values for CommonGeneratorOptions.

axiosWith :: AxiosOptions -> CommonGeneratorOptions -> JavaScriptGenerator Source

Generate regular javascript functions that use the axios library.

data AxiosOptions Source

Axios configuration type Let you customize the generation using Axios capabilities

Constructors

AxiosOptions 

Fields

withCredentials :: !Bool

indicates whether or not cross-site Access-Control requests should be made using credentials

xsrfCookieName :: !(Maybe Text)

the name of the cookie to use as a value for xsrf token

xsrfHeaderName :: !(Maybe Text)

the name of the header to use as a value for xsrf token

defAxiosOptions :: AxiosOptions Source

Default instance of the AxiosOptions Defines the settings as they are in the Axios documentation by default

Misc.

listFromAPI :: (HasForeign k lang ftype api, GenerateList ftype (Foreign ftype api)) => Proxy k 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.

javascript :: HasForeign NoTypes () layout => Proxy layout -> Foreign () layout Source

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

data NoTypes :: *

Instances

HasForeignType * k NoTypes () ftype 

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 (Req ftype) 
(GenerateList ftype start, GenerateList ftype rest) => GenerateList ftype ((:<|>) start rest)