servant-js-0.9.3.1: 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

defCommonGeneratorOptions :: CommonGeneratorOptions Source #

Default options.

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

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

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 3 

Instances

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

Associated Types

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

Methods

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

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

Methods

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

Functor ((:<|>) a) 

Methods

fmap :: (a -> b) -> (a :<|> a) -> a :<|> b #

(<$) :: a -> (a :<|> b) -> a :<|> a #

Foldable ((:<|>) a) 

Methods

fold :: Monoid m => (a :<|> m) -> m #

foldMap :: Monoid m => (a -> m) -> (a :<|> a) -> m #

foldr :: (a -> b -> b) -> b -> (a :<|> a) -> b #

foldr' :: (a -> b -> b) -> b -> (a :<|> a) -> b #

foldl :: (b -> a -> b) -> b -> (a :<|> a) -> b #

foldl' :: (b -> a -> b) -> b -> (a :<|> a) -> b #

foldr1 :: (a -> a -> a) -> (a :<|> a) -> a #

foldl1 :: (a -> a -> a) -> (a :<|> a) -> a #

toList :: (a :<|> a) -> [a] #

null :: (a :<|> a) -> Bool #

length :: (a :<|> a) -> Int #

elem :: Eq a => a -> (a :<|> a) -> Bool #

maximum :: Ord a => (a :<|> a) -> a #

minimum :: Ord a => (a :<|> a) -> a #

sum :: Num a => (a :<|> a) -> a #

product :: Num a => (a :<|> a) -> a #

Traversable ((:<|>) a) 

Methods

traverse :: Applicative f => (a -> f b) -> (a :<|> a) -> f (a :<|> b) #

sequenceA :: Applicative f => (a :<|> f a) -> f (a :<|> a) #

mapM :: Monad m => (a -> m b) -> (a :<|> a) -> m (a :<|> b) #

sequence :: Monad m => (a :<|> m a) -> m (a :<|> a) #

(Bounded b, Bounded a) => Bounded ((:<|>) a b) 

Methods

minBound :: a :<|> b #

maxBound :: a :<|> b #

(Eq b, Eq a) => Eq ((:<|>) a b) 

Methods

(==) :: (a :<|> b) -> (a :<|> b) -> Bool #

(/=) :: (a :<|> b) -> (a :<|> b) -> Bool #

(Show b, Show a) => Show ((:<|>) a b) 

Methods

showsPrec :: Int -> (a :<|> b) -> ShowS #

show :: (a :<|> b) -> String #

showList :: [a :<|> b] -> ShowS #

(Semigroup a, Semigroup b) => Semigroup ((:<|>) a b) 

Methods

(<>) :: (a :<|> b) -> (a :<|> b) -> a :<|> b #

sconcat :: NonEmpty (a :<|> b) -> a :<|> b #

stimes :: Integral b => b -> (a :<|> b) -> a :<|> b #

(Monoid a, Monoid b) => Monoid ((:<|>) a b) 

Methods

mempty :: a :<|> b #

mappend :: (a :<|> b) -> (a :<|> b) -> a :<|> b #

mconcat :: [a :<|> b] -> a :<|> b #

type Foreign ftype ((:<|>) a b) 
type Foreign ftype ((:<|>) a b) = (:<|>) (Foreign ftype a) (Foreign ftype b)

data (k :> k1) path a :: forall k k1. k1 -> k -> * infixr 4 #

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 a, HasForeign k1 lang ftype api) => HasForeign k1 lang ftype ((:>) * * (QueryParam k sym a) api) 

Associated Types

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

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 #

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

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 #

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

(KnownSymbol sym, HasForeignType k k1 lang ftype t, HasForeign k1 lang ftype api) => HasForeign k1 lang ftype ((:>) * * (Capture k sym t) api) 

Associated Types

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

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 #

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

type Foreign ftype ((:>) * * (Description desc) api) 
type Foreign ftype ((:>) * * (Description desc) api) = Foreign ftype api
type Foreign ftype ((:>) * * (Summary desc) api) 
type Foreign ftype ((:>) * * (Summary desc) api) = Foreign ftype api
type Foreign ftype ((:>) * * HttpVersion api) 
type Foreign ftype ((:>) * * HttpVersion api) = Foreign ftype api
type Foreign ftype ((:>) * * Vault api) 
type Foreign ftype ((:>) * * Vault api) = Foreign ftype api
type Foreign ftype ((:>) * * IsSecure api) 
type Foreign ftype ((:>) * * IsSecure api) = Foreign ftype api
type Foreign ftype ((:>) * * RemoteHost api) 
type Foreign ftype ((:>) * * RemoteHost api) = Foreign ftype api
type Foreign ftype ((:>) * Symbol path api) 
type Foreign ftype ((:>) * Symbol path api) = Foreign ftype api
type Foreign ftype ((:>) * * (ReqBody k list a) api) 
type Foreign ftype ((:>) * * (ReqBody k list a) api) = Foreign ftype api
type Foreign ftype ((:>) * * (QueryFlag sym) api) 
type Foreign ftype ((:>) * * (QueryFlag sym) api) = Foreign ftype api
type Foreign ftype ((:>) * * (QueryParams * sym a) api) 
type Foreign ftype ((:>) * * (QueryParams * sym a) api) = Foreign ftype api
type Foreign ftype ((:>) * * (QueryParam k sym a) api) 
type Foreign ftype ((:>) * * (QueryParam k sym a) api) = Foreign ftype api
type Foreign ftype ((:>) * * (Header sym a) api) 
type Foreign ftype ((:>) * * (Header sym a) api) = Foreign ftype api
type Foreign ftype ((:>) * * (CaptureAll * sym t) sublayout) 
type Foreign ftype ((:>) * * (CaptureAll * sym t) sublayout) = Foreign ftype sublayout
type Foreign ftype ((:>) * * (Capture k sym t) api) 
type Foreign ftype ((:>) * * (Capture k sym t) api) = Foreign ftype api

defReq :: Req ftype #

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

class HasForeign k lang ftype api where #

Minimal complete definition

foreignFor

Associated Types

type Foreign ftype api :: * #

Methods

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

Instances

HasForeign k lang ftype Raw 

Associated Types

type Foreign Raw api :: * #

Methods

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

HasForeign k lang ftype EmptyAPI 

Associated Types

type Foreign EmptyAPI api :: * #

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

(KnownSymbol sym, HasForeignType k k1 lang ftype a, HasForeign k1 lang ftype api) => HasForeign k1 lang ftype ((:>) * * (QueryParam k sym a) api) 

Associated Types

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

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 #

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

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 #

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

(KnownSymbol sym, HasForeignType k k1 lang ftype t, HasForeign k1 lang ftype api) => HasForeign k1 lang ftype ((:>) * * (Capture k sym t) api) 

Associated Types

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

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 #

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

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 #

class HasForeignType k k1 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 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 k1 lang -> Proxy * ftype -> Proxy k a -> ftype #

Instances

HasForeignType k * NoTypes NoContent ftype 

Methods

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

Minimal complete definition

generateList

Methods

generateList :: reqs -> [Req ftype] #

Instances

GenerateList ftype EmptyForeignAPI 

Methods

generateList :: EmptyForeignAPI -> [Req ftype] #

GenerateList ftype (Req ftype) 

Methods

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

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

Methods

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

data NoTypes :: * #

Instances

HasForeignType k * NoTypes NoContent ftype 

Methods

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

data ArgType :: * #

Constructors

Normal 
Flag 
List 

Instances

Eq ArgType 

Methods

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

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

Data ArgType 

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 

data HeaderArg f :: * -> * #

Constructors

HeaderArg 

Fields

ReplaceHeaderArg 

Instances

Eq f => Eq (HeaderArg f) 

Methods

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

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

Data f => Data (HeaderArg f) 

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) 

data QueryArg f :: * -> * #

Constructors

QueryArg 

Instances

Eq f => Eq (QueryArg f) 

Methods

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

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

Data f => Data (QueryArg f) 

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) 

Methods

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

show :: QueryArg f -> String #

showList :: [QueryArg f] -> ShowS #

data Req f :: * -> * #

Instances

GenerateList ftype (Req ftype) 

Methods

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

Eq f => Eq (Req f) 

Methods

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

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

Data f => Data (Req f) 

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) 

Methods

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

show :: Req f -> String #

showList :: [Req f] -> ShowS #

newtype Segment f :: * -> * #

Constructors

Segment 

Fields

Instances

Eq f => Eq (Segment f) 

Methods

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

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

Data f => Data (Segment f) 

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) 

Methods

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

show :: Segment f -> String #

showList :: [Segment f] -> ShowS #

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) 
Data f => Data (SegmentType f) 

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) 

data Url f :: * -> * #

Constructors

Url 

Fields

Instances

Eq f => Eq (Url f) 

Methods

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

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

Data f => Data (Url f) 

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) 

Methods

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

show :: Url f -> String #

showList :: [Url f] -> ShowS #

type Path f = [Segment f] #

data Arg f :: * -> * #

Constructors

Arg 

Fields

Instances

Eq f => Eq (Arg f) 

Methods

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

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

Data f => Data (Arg f) 

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) 

Methods

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

show :: Arg f -> String #

showList :: [Arg f] -> ShowS #

newtype FunctionName :: * #

Constructors

FunctionName 

Fields

Instances

Eq FunctionName 
Data FunctionName 

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 
Monoid FunctionName 

newtype PathSegment :: * #

Constructors

PathSegment 

Fields

Instances

Eq PathSegment 
Data PathSegment 

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 
IsString PathSegment 
Monoid PathSegment 

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 k contentTypes a :: forall k. [*] -> 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 k1 lang ftype api) => HasForeign k1 lang ftype ((:>) * * (ReqBody k list a) api) 

Associated Types

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

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 #

type Foreign ftype ((:>) * * (ReqBody k list a) api) 
type Foreign ftype ((:>) * * (ReqBody k list a) api) = Foreign ftype api

data JSON :: * #

data FormUrlEncoded :: * #

Instances

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

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

FromForm a => MimeUnrender * FormUrlEncoded a

urlDecodeAsForm 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 k = Verb k StdMethod POST 200 #

POST with 200 status code.

type Get k = Verb k StdMethod 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 

Associated Types

type Foreign Raw api :: * #

Methods

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

type Foreign 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 api) => HasForeign k lang ftype ((:>) * * (Header sym a) api) 

Associated Types

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

Methods

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

Functor (Header sym) 

Methods

fmap :: (a -> b) -> Header sym a -> Header sym b #

(<$) :: a -> Header sym b -> Header sym a #

Eq a => Eq (Header sym a) 

Methods

(==) :: Header sym a -> Header sym a -> Bool #

(/=) :: Header sym a -> Header sym a -> Bool #

Show a => Show (Header sym a) 

Methods

showsPrec :: Int -> Header sym a -> ShowS #

show :: Header sym a -> String #

showList :: [Header sym a] -> ShowS #

type Foreign ftype ((:>) * * (Header sym a) api) 
type Foreign ftype ((:>) * * (Header sym a) api) = Foreign ftype api