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

Safe HaskellNone
LanguageHaskell2010

Servant.JS.Internal

Synopsis

Documentation

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 = ""
>   }

type AjaxReq = Req () Source

toValidFunctionName :: Text -> Text Source

Attempts to reduce the function name provided to that allowed by Foreign.

https://mathiasbynens.be/notes/javascript-identifiers Couldn't work out how to handle zero-width characters.

@TODO: specify better default function name, or throw error?

data a :<|> b :: * -> * -> * infixr 8

Union of two APIs, first takes precedence in case of overlap.

Example:

>>> :{
type MyApi = "books" :> Get '[JSON] [Book] -- GET /books
       :<|> "books" :> ReqBody '[JSON] Book :> Post '[JSON] () -- POST /books
:}

Constructors

a :<|> b infixr 8 

Instances

(HasForeign k lang ftype a, HasForeign k lang ftype b) => HasForeign k lang ftype ((:<|>) a b) 
(GenerateList ftype start, GenerateList ftype rest) => GenerateList ftype ((:<|>) start rest) 
Functor ((:<|>) a) 
Foldable ((:<|>) a) 
Traversable ((:<|>) a) 
(Bounded a, Bounded b) => Bounded ((:<|>) a b) 
(Eq a, Eq b) => Eq ((:<|>) a b) 
(Show a, Show b) => Show ((:<|>) a b) 
(Monoid a, Monoid b) => Monoid ((:<|>) a b) 
type Foreign ftype ((:<|>) a b) = (:<|>) (Foreign ftype a) (Foreign ftype b) 

data path :> a :: k -> k1 -> * infixr 9

The contained API (second argument) can be found under ("/" ++ path) (path being the first argument).

Example:

>>> -- GET /hello/world
>>> -- returning a JSON encoded World value
>>> type MyApi = "hello" :> "world" :> Get '[JSON] World

Instances

(KnownSymbol sym, HasForeignType k k1 lang ftype t, HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * * (Capture k1 sym t) sublayout) 
(KnownSymbol sym, HasForeignType k * lang ftype a, HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * * (Header sym a) sublayout) 
(KnownSymbol sym, HasForeignType k k1 lang ftype a, HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * * (QueryParam k1 sym a) sublayout) 
(KnownSymbol sym, HasForeignType k * lang ftype [a], HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * * (QueryParams * sym a) sublayout) 
(KnownSymbol sym, HasForeignType k * lang ftype Bool, HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * * (QueryFlag sym) sublayout) 
(Elem JSON list, HasForeignType k k1 lang ftype a, HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * * (ReqBody k1 list a) sublayout) 
(KnownSymbol path, HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) Symbol * path sublayout) 
HasForeign k lang ftype sublayout => HasForeign k lang ftype ((:>) * * RemoteHost sublayout) 
HasForeign k lang ftype sublayout => HasForeign k lang ftype ((:>) * * IsSecure sublayout) 
HasForeign k lang ftype sublayout => HasForeign k lang ftype ((:>) * * Vault sublayout) 
HasForeign k lang ftype sublayout => HasForeign k lang ftype ((:>) * * HttpVersion sublayout) 
type Foreign ftype ((:>) * * HttpVersion sublayout) = Foreign ftype sublayout 
type Foreign ftype ((:>) * * Vault sublayout) = Foreign ftype sublayout 
type Foreign ftype ((:>) * * IsSecure sublayout) = Foreign ftype sublayout 
type Foreign ftype ((:>) * * RemoteHost sublayout) = Foreign ftype sublayout 
type Foreign ftype ((:>) Symbol * path sublayout) = Foreign ftype sublayout 
type Foreign ftype ((:>) * * (ReqBody k list a) sublayout) = Foreign ftype sublayout 
type Foreign ftype ((:>) * * (QueryFlag sym) sublayout) = Foreign ftype sublayout 
type Foreign ftype ((:>) * * (QueryParams * sym a) sublayout) = Foreign ftype sublayout 
type Foreign ftype ((:>) * * (QueryParam k sym a) sublayout) = Foreign ftype sublayout 
type Foreign ftype ((:>) * * (Header sym a) sublayout) = Foreign ftype sublayout 
type Foreign ftype ((:>) * * (Capture k sym a) sublayout) = Foreign ftype sublayout 

defReq :: Req ftype

reqHeaders :: Functor f => ([HeaderArg f0] -> f [HeaderArg f0]) -> Req f0 -> f (Req f0)

class HasForeign lang ftype layout where

Associated Types

type Foreign ftype layout :: *

Methods

foreignFor :: Proxy k lang -> Proxy * ftype -> Proxy * layout -> Req ftype -> Foreign ftype layout

Instances

HasForeign k lang ftype Raw 
(HasForeign k lang ftype a, HasForeign k lang ftype b) => HasForeign k lang ftype ((:<|>) a b) 
HasForeign k lang ftype sublayout => HasForeign k lang ftype (WithNamedContext name context sublayout) 
(KnownSymbol sym, HasForeignType k k1 lang ftype t, HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * * (Capture k1 sym t) sublayout) 
(KnownSymbol sym, HasForeignType k * lang ftype a, HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * * (Header sym a) sublayout) 
(KnownSymbol sym, HasForeignType k k1 lang ftype a, HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * * (QueryParam k1 sym a) sublayout) 
(KnownSymbol sym, HasForeignType k * lang ftype [a], HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * * (QueryParams * sym a) sublayout) 
(KnownSymbol sym, HasForeignType k * lang ftype Bool, HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * * (QueryFlag sym) sublayout) 
(Elem JSON list, HasForeignType k k1 lang ftype a, HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * * (ReqBody k1 list a) sublayout) 
(KnownSymbol path, HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) Symbol * path sublayout) 
HasForeign k lang ftype sublayout => HasForeign k lang ftype ((:>) * * RemoteHost sublayout) 
HasForeign k lang ftype sublayout => HasForeign k lang ftype ((:>) * * IsSecure sublayout) 
HasForeign k lang ftype sublayout => HasForeign k lang ftype ((:>) * * Vault sublayout) 
HasForeign k lang ftype sublayout => HasForeign k lang ftype ((:>) * * HttpVersion sublayout) 
(Elem JSON list, HasForeignType k k2 lang ftype a, ReflectMethod k1 method) => HasForeign k lang ftype (Verb k1 k2 method status list a) 

class HasForeignType lang ftype a where

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 () output type:
getEndpoints :: (HasForeign NoTypes () api, GenerateList Text (Foreign () api))
             => Proxy api -> [Req ()]
getEndpoints api = listFromAPI (Proxy :: Proxy NoTypes) (Proxy :: Proxy ()) api

Methods

typeFor :: Proxy k lang -> Proxy * ftype -> Proxy k1 a -> ftype

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) 

data NoTypes :: *

Instances

HasForeignType * k NoTypes () ftype 

data ArgType :: *

Constructors

Normal 
Flag 
List 

Instances

data HeaderArg f :: * -> *

Constructors

HeaderArg 

Fields

_headerArg :: Arg f
 
ReplaceHeaderArg 

Instances

Eq f => Eq (HeaderArg f) 
Show f => Show (HeaderArg f) 

data QueryArg f :: * -> *

Constructors

QueryArg 

Instances

Eq f => Eq (QueryArg f) 
Show f => Show (QueryArg f) 

data Req f :: * -> *

Instances

GenerateList ftype (Req ftype) 
Eq f => Eq (Req f) 
Show f => Show (Req f) 

newtype Segment f :: * -> *

Constructors

Segment 

Fields

unSegment :: SegmentType f
 

Instances

Eq f => Eq (Segment f) 
Show f => Show (Segment f) 

data SegmentType f :: * -> *

Constructors

Static PathSegment

a static path segment. like "/foo"

Cap (Arg f)

a capture. like "/:userid"

Instances

Eq f => Eq (SegmentType f) 
Show f => Show (SegmentType f) 

data Url f :: * -> *

Constructors

Url 

Fields

_path :: Path f
 
_queryStr :: [QueryArg f]
 

Instances

Eq f => Eq (Url f) 
Show f => Show (Url f) 

type Path f = [Segment f]

data Arg f :: * -> *

Constructors

Arg 

Fields

_argName :: PathSegment
 
_argType :: f
 

Instances

Eq f => Eq (Arg f) 
Show f => Show (Arg f) 

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.

data ReqBody contentTypes a :: [*] -> k -> *

Extract the request body as a value of type a.

Example:

>>> -- POST /books
>>> type MyApi = "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book

Instances

(Elem JSON list, HasForeignType k k1 lang ftype a, HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * * (ReqBody k1 list a) sublayout) 
type Foreign ftype ((:>) * * (ReqBody k list a) sublayout) = Foreign ftype sublayout 

data JSON :: *

Instances

Accept * JSON
application/json
ToJSON a => MimeRender * JSON a

encode

FromJSON a => MimeUnrender * JSON a

eitherDecode

data FormUrlEncoded :: *

Instances

Accept * FormUrlEncoded
application/x-www-form-urlencoded
ToFormUrlEncoded a => MimeRender * FormUrlEncoded a

encodeFormUrlEncoded . toFormUrlEncoded Note that the mimeUnrender p (mimeRender p x) == Right x law only holds if every element of x is non-null (i.e., not ("", ""))

FromFormUrlEncoded a => MimeUnrender * FormUrlEncoded a

decodeFormUrlEncoded >=> fromFormUrlEncoded Note that the mimeUnrender p (mimeRender p x) == Right x law only holds if every element of x is non-null (i.e., not ("", ""))

type Post = Verb StdMethod k POST 200

POST with 200 status code.

type Get = Verb StdMethod k GET 200

GET with 200 status code.

data Raw :: *

Endpoint for plugging in your own Wai Applications.

The given Application will get the request as received by the server, potentially with a modified (stripped) pathInfo if the Application is being routed with :>.

In addition to just letting you plug in your existing WAI Applications, this can also be used with serveDirectory to serve static files stored in a particular directory on your filesystem

Instances

HasForeign k lang ftype Raw 
type Foreign ftype Raw = Method -> Req ftype 

data Header sym a :: Symbol -> * -> *

Extract the given header's value as a value of type a.

Example:

>>> newtype Referer = Referer Text deriving (Eq, Show)
>>> 
>>> -- GET /view-my-referer
>>> type MyApi = "view-my-referer" :> Header "from" Referer :> Get '[JSON] Referer

Instances

(KnownSymbol sym, HasForeignType k * lang ftype a, HasForeign k lang ftype sublayout) => HasForeign k lang ftype ((:>) * * (Header sym a) sublayout) 
Functor (Header sym) 
Eq a => Eq (Header sym a) 
Show a => Show (Header sym a) 
type Foreign ftype ((:>) * * (Header sym a) sublayout) = Foreign ftype sublayout