servant-js-0.9.4.2: 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
Bitraversable (:<|>) 
Instance details

Defined in Servant.API.Alternative

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (a :<|> b) -> f (c :<|> d) #

Bifoldable (:<|>) 
Instance details

Defined in Servant.API.Alternative

Methods

bifold :: Monoid m => (m :<|> m) -> m #

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

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

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

Bifunctor (:<|>) 
Instance details

Defined in Servant.API.Alternative

Methods

bimap :: (a -> b) -> (c -> d) -> (a :<|> c) -> b :<|> d #

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

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

Biapplicative (:<|>) 
Instance details

Defined in Servant.API.Alternative

Methods

bipure :: a -> b -> a :<|> b #

(<<*>>) :: ((a -> b) :<|> (c -> d)) -> (a :<|> c) -> b :<|> d #

biliftA2 :: (a -> b -> c) -> (d -> e -> f) -> (a :<|> d) -> (b :<|> e) -> c :<|> f #

(*>>) :: (a :<|> b) -> (c :<|> d) -> c :<|> d #

(<<*) :: (a :<|> b) -> (c :<|> d) -> a :<|> b #

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

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (a :<|> b) :: Type #

Methods

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

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

Defined in Servant.Foreign.Internal

Methods

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

Functor ((:<|>) a) 
Instance details

Defined in Servant.API.Alternative

Methods

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

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

Foldable ((:<|>) a) 
Instance details

Defined in Servant.API.Alternative

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Traversable ((:<|>) a) 
Instance details

Defined in Servant.API.Alternative

Methods

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

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

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

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

(HasLink a, HasLink b) => HasLink (a :<|> b :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (a :<|> b) a :: Type #

Methods

toLink :: (Link -> a0) -> Proxy (a :<|> b) -> Link -> MkLink (a :<|> b) a0 #

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

Defined in Servant.API.Alternative

Methods

minBound :: a :<|> b #

maxBound :: a :<|> b #

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

Defined in Servant.API.Alternative

Methods

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

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

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

Defined in Servant.API.Alternative

Methods

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

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

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

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

Defined in Servant.API.Alternative

Methods

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

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

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

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

Defined in Servant.API.Alternative

Methods

mempty :: a :<|> b #

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

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

type Foreign ftype (a :<|> b) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (a :<|> b) = Foreign ftype a :<|> Foreign ftype b
type MkLink (a :<|> b :: Type) r 
Instance details

Defined in Servant.Links

type MkLink (a :<|> b :: Type) r = MkLink a r :<|> MkLink b r

data (path :: k) :> a :: forall k. k -> Type -> Type 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 lang ftype [a], HasForeign lang ftype api) => HasForeign (lang :: k) ftype (QueryParams sym a :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (QueryParams sym a :> api) :: Type #

Methods

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

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

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (QueryFlag sym :> api) :: Type #

Methods

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

(Elem JSON list, HasForeignType lang ftype a, HasForeign lang ftype api) => HasForeign (lang :: k) ftype (ReqBody' mods list a :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (ReqBody' mods list a :> api) :: Type #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (ReqBody' mods list a :> api) -> Req ftype -> Foreign ftype (ReqBody' mods list a :> api) #

HasForeign lang ftype api => HasForeign (lang :: k) ftype (StreamBody' mods framing ctype a :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (StreamBody' mods framing ctype a :> api) :: Type #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (StreamBody' mods framing ctype a :> api) -> Req ftype -> Foreign ftype (StreamBody' mods framing ctype a :> api) #

(KnownSymbol path, HasForeign lang ftype api) => HasForeign (lang :: k) ftype (path :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (path :> api) :: Type #

Methods

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

HasForeign lang ftype api => HasForeign (lang :: k) ftype (RemoteHost :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (RemoteHost :> api) :: Type #

Methods

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

HasForeign lang ftype api => HasForeign (lang :: k) ftype (IsSecure :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (IsSecure :> api) :: Type #

Methods

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

HasForeign lang ftype api => HasForeign (lang :: k) ftype (Vault :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Vault :> api) :: Type #

Methods

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

(KnownSymbol sym, HasForeignType lang ftype t, HasForeign lang ftype api) => HasForeign (lang :: k) ftype (Capture' mods sym t :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Capture' mods sym t :> api) :: Type #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (Capture' mods sym t :> api) -> Req ftype -> Foreign ftype (Capture' mods sym t :> api) #

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

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (CaptureAll sym t :> sublayout) :: Type #

Methods

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

(KnownSymbol sym, HasForeignType lang ftype (RequiredArgument mods a), HasForeign lang ftype api) => HasForeign (lang :: k) ftype (Header' mods sym a :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Header' mods sym a :> api) :: Type #

Methods

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

(KnownSymbol sym, HasForeignType lang ftype (RequiredArgument mods a), HasForeign lang ftype api) => HasForeign (lang :: k) ftype (QueryParam' mods sym a :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (QueryParam' mods sym a :> api) :: Type #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (QueryParam' mods sym a :> api) -> Req ftype -> Foreign ftype (QueryParam' mods sym a :> api) #

HasForeign lang ftype api => HasForeign (lang :: k) ftype (HttpVersion :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (HttpVersion :> api) :: Type #

Methods

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

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

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Summary desc :> api) :: Type #

Methods

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

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

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Description desc :> api) :: Type #

Methods

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

HasLink sub => HasLink (HttpVersion :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (HttpVersion :> sub) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (HttpVersion :> sub) -> Link -> MkLink (HttpVersion :> sub) a #

HasLink sub => HasLink (StreamBody' mods framing ct a :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (StreamBody' mods framing ct a :> sub) a :: Type #

Methods

toLink :: (Link -> a0) -> Proxy (StreamBody' mods framing ct a :> sub) -> Link -> MkLink (StreamBody' mods framing ct a :> sub) a0 #

HasLink sub => HasLink (ReqBody' mods ct a :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (ReqBody' mods ct a :> sub) a :: Type #

Methods

toLink :: (Link -> a0) -> Proxy (ReqBody' mods ct a :> sub) -> Link -> MkLink (ReqBody' mods ct a :> sub) a0 #

HasLink sub => HasLink (RemoteHost :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (RemoteHost :> sub) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (RemoteHost :> sub) -> Link -> MkLink (RemoteHost :> sub) a #

(KnownSymbol sym, ToHttpApiData v, HasLink sub, SBoolI (FoldRequired mods)) => HasLink (QueryParam' mods sym v :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (QueryParam' mods sym v :> sub) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (QueryParam' mods sym v :> sub) -> Link -> MkLink (QueryParam' mods sym v :> sub) a #

(KnownSymbol sym, ToHttpApiData v, HasLink sub) => HasLink (QueryParams sym v :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (QueryParams sym v :> sub) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (QueryParams sym v :> sub) -> Link -> MkLink (QueryParams sym v :> sub) a #

(KnownSymbol sym, HasLink sub) => HasLink (QueryFlag sym :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (QueryFlag sym :> sub) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (QueryFlag sym :> sub) -> Link -> MkLink (QueryFlag sym :> sub) a #

HasLink sub => HasLink (Header' mods sym a :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (Header' mods sym a :> sub) a :: Type #

Methods

toLink :: (Link -> a0) -> Proxy (Header' mods sym a :> sub) -> Link -> MkLink (Header' mods sym a :> sub) a0 #

HasLink sub => HasLink (IsSecure :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (IsSecure :> sub) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (IsSecure :> sub) -> Link -> MkLink (IsSecure :> sub) a #

HasLink sub => HasLink (AuthProtect tag :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (AuthProtect tag :> sub) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (AuthProtect tag :> sub) -> Link -> MkLink (AuthProtect tag :> sub) a #

HasLink sub => HasLink (Summary s :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (Summary s :> sub) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (Summary s :> sub) -> Link -> MkLink (Summary s :> sub) a #

HasLink sub => HasLink (Description s :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (Description s :> sub) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (Description s :> sub) -> Link -> MkLink (Description s :> sub) a #

(ToHttpApiData v, HasLink sub) => HasLink (Capture' mods sym v :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (Capture' mods sym v :> sub) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (Capture' mods sym v :> sub) -> Link -> MkLink (Capture' mods sym v :> sub) a #

(ToHttpApiData v, HasLink sub) => HasLink (CaptureAll sym v :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (CaptureAll sym v :> sub) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (CaptureAll sym v :> sub) -> Link -> MkLink (CaptureAll sym v :> sub) a #

HasLink sub => HasLink (BasicAuth realm a :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (BasicAuth realm a :> sub) a :: Type #

Methods

toLink :: (Link -> a0) -> Proxy (BasicAuth realm a :> sub) -> Link -> MkLink (BasicAuth realm a :> sub) a0 #

HasLink sub => HasLink (Vault :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (Vault :> sub) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (Vault :> sub) -> Link -> MkLink (Vault :> sub) a #

(KnownSymbol sym, HasLink sub) => HasLink (sym :> sub :: Type) 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (sym :> sub) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (sym :> sub) -> Link -> MkLink (sym :> sub) a #

type Foreign ftype (Description desc :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (Description desc :> api) = Foreign ftype api
type Foreign ftype (Summary desc :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (Summary desc :> api) = Foreign ftype api
type Foreign ftype (HttpVersion :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (HttpVersion :> api) = Foreign ftype api
type Foreign ftype (Vault :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (Vault :> api) = Foreign ftype api
type Foreign ftype (IsSecure :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (IsSecure :> api) = Foreign ftype api
type Foreign ftype (RemoteHost :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (RemoteHost :> api) = Foreign ftype api
type Foreign ftype (path :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (path :> api) = Foreign ftype api
type Foreign ftype (StreamBody' mods framing ctype a :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (StreamBody' mods framing ctype a :> api) = Foreign ftype api
type Foreign ftype (ReqBody' mods list a :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (ReqBody' mods list a :> api) = Foreign ftype api
type Foreign ftype (QueryFlag sym :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (QueryFlag sym :> api) = Foreign ftype api
type Foreign ftype (QueryParams sym a :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (QueryParams sym a :> api) = Foreign ftype api
type Foreign ftype (QueryParam' mods sym a :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (QueryParam' mods sym a :> api) = Foreign ftype api
type Foreign ftype (Header' mods sym a :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (Header' mods sym a :> api) = Foreign ftype api
type Foreign ftype (CaptureAll sym t :> sublayout) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (CaptureAll sym t :> sublayout) = Foreign ftype sublayout
type Foreign ftype (Capture' mods sym t :> api) 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype (Capture' mods sym t :> api) = Foreign ftype api
type MkLink (HttpVersion :> sub :: Type) a 
Instance details

Defined in Servant.Links

type MkLink (HttpVersion :> sub :: Type) a = MkLink sub a
type MkLink (StreamBody' mods framing ct a :> sub :: Type) r 
Instance details

Defined in Servant.Links

type MkLink (StreamBody' mods framing ct a :> sub :: Type) r = MkLink sub r
type MkLink (ReqBody' mods ct a :> sub :: Type) r 
Instance details

Defined in Servant.Links

type MkLink (ReqBody' mods ct a :> sub :: Type) r = MkLink sub r
type MkLink (RemoteHost :> sub :: Type) a 
Instance details

Defined in Servant.Links

type MkLink (RemoteHost :> sub :: Type) a = MkLink sub a
type MkLink (QueryParam' mods sym v :> sub :: Type) a 
Instance details

Defined in Servant.Links

type MkLink (QueryParam' mods sym v :> sub :: Type) a = If (FoldRequired mods) v (Maybe v) -> MkLink sub a
type MkLink (QueryParams sym v :> sub :: Type) a 
Instance details

Defined in Servant.Links

type MkLink (QueryParams sym v :> sub :: Type) a = [v] -> MkLink sub a
type MkLink (QueryFlag sym :> sub :: Type) a 
Instance details

Defined in Servant.Links

type MkLink (QueryFlag sym :> sub :: Type) a = Bool -> MkLink sub a
type MkLink (Header' mods sym a :> sub :: Type) r 
Instance details

Defined in Servant.Links

type MkLink (Header' mods sym a :> sub :: Type) r = MkLink sub r
type MkLink (IsSecure :> sub :: Type) a 
Instance details

Defined in Servant.Links

type MkLink (IsSecure :> sub :: Type) a = MkLink sub a
type MkLink (AuthProtect tag :> sub :: Type) a 
Instance details

Defined in Servant.Links

type MkLink (AuthProtect tag :> sub :: Type) a = MkLink sub a
type MkLink (Summary s :> sub :: Type) a 
Instance details

Defined in Servant.Links

type MkLink (Summary s :> sub :: Type) a = MkLink sub a
type MkLink (Description s :> sub :: Type) a 
Instance details

Defined in Servant.Links

type MkLink (Description s :> sub :: Type) a = MkLink sub a
type MkLink (Capture' mods sym v :> sub :: Type) a 
Instance details

Defined in Servant.Links

type MkLink (Capture' mods sym v :> sub :: Type) a = v -> MkLink sub a
type MkLink (CaptureAll sym v :> sub :: Type) a 
Instance details

Defined in Servant.Links

type MkLink (CaptureAll sym v :> sub :: Type) a = [v] -> MkLink sub a
type MkLink (BasicAuth realm a :> sub :: Type) r 
Instance details

Defined in Servant.Links

type MkLink (BasicAuth realm a :> sub :: Type) r = MkLink sub r
type MkLink (Vault :> sub :: Type) a 
Instance details

Defined in Servant.Links

type MkLink (Vault :> sub :: Type) a = MkLink sub a
type MkLink (sym :> sub :: Type) a 
Instance details

Defined in Servant.Links

type MkLink (sym :> sub :: Type) a = MkLink sub a

defReq :: Req ftype #

class HasForeign (lang :: k) ftype api where #

Associated Types

type Foreign ftype api :: Type #

Methods

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

Instances
HasForeign (lang :: k) ftype Raw 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype Raw :: Type #

Methods

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

HasForeign (lang :: k) ftype EmptyAPI 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype EmptyAPI :: Type #

Methods

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

(HasForeignType lang ftype NoContent, ReflectMethod method) => HasForeign (lang :: k) ftype (NoContentVerb method) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (NoContentVerb method) :: Type #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (NoContentVerb method) -> Req ftype -> Foreign ftype (NoContentVerb method) #

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

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (a :<|> b) :: Type #

Methods

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

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

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (WithNamedContext name context api) :: Type #

Methods

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

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

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (QueryParams sym a :> api) :: Type #

Methods

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

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

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (QueryFlag sym :> api) :: Type #

Methods

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

(Elem JSON list, HasForeignType lang ftype a, HasForeign lang ftype api) => HasForeign (lang :: k) ftype (ReqBody' mods list a :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (ReqBody' mods list a :> api) :: Type #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (ReqBody' mods list a :> api) -> Req ftype -> Foreign ftype (ReqBody' mods list a :> api) #

HasForeign lang ftype api => HasForeign (lang :: k) ftype (StreamBody' mods framing ctype a :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (StreamBody' mods framing ctype a :> api) :: Type #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (StreamBody' mods framing ctype a :> api) -> Req ftype -> Foreign ftype (StreamBody' mods framing ctype a :> api) #

(KnownSymbol path, HasForeign lang ftype api) => HasForeign (lang :: k) ftype (path :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (path :> api) :: Type #

Methods

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

HasForeign lang ftype api => HasForeign (lang :: k) ftype (RemoteHost :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (RemoteHost :> api) :: Type #

Methods

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

HasForeign lang ftype api => HasForeign (lang :: k) ftype (IsSecure :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (IsSecure :> api) :: Type #

Methods

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

HasForeign lang ftype api => HasForeign (lang :: k) ftype (Vault :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Vault :> api) :: Type #

Methods

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

(KnownSymbol sym, HasForeignType lang ftype t, HasForeign lang ftype api) => HasForeign (lang :: k) ftype (Capture' mods sym t :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Capture' mods sym t :> api) :: Type #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (Capture' mods sym t :> api) -> Req ftype -> Foreign ftype (Capture' mods sym t :> api) #

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

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (CaptureAll sym t :> sublayout) :: Type #

Methods

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

(KnownSymbol sym, HasForeignType lang ftype (RequiredArgument mods a), HasForeign lang ftype api) => HasForeign (lang :: k) ftype (Header' mods sym a :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Header' mods sym a :> api) :: Type #

Methods

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

(KnownSymbol sym, HasForeignType lang ftype (RequiredArgument mods a), HasForeign lang ftype api) => HasForeign (lang :: k) ftype (QueryParam' mods sym a :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (QueryParam' mods sym a :> api) :: Type #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (QueryParam' mods sym a :> api) -> Req ftype -> Foreign ftype (QueryParam' mods sym a :> api) #

HasForeign lang ftype api => HasForeign (lang :: k) ftype (HttpVersion :> api) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (HttpVersion :> api) :: Type #

Methods

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

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

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Summary desc :> api) :: Type #

Methods

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

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

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Description desc :> api) :: Type #

Methods

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

(Elem JSON list, HasForeignType lang ftype a, ReflectMethod method) => HasForeign (lang :: k) ftype (Verb method status list a) 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Verb method status list a) :: Type #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (Verb method status list a) -> Req ftype -> Foreign ftype (Verb method status list a) #

(ct ~ JSON, HasForeignType lang ftype a, ReflectMethod method) => HasForeign (lang :: k) ftype (Stream method status framing ct a)

TODO: doesn't taking framing into account.

Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype (Stream method status framing ct a) :: Type #

Methods

foreignFor :: Proxy lang -> Proxy ftype -> Proxy (Stream method status framing ct a) -> Req ftype -> Foreign ftype (Stream method status framing ct a) #

class HasForeignType (lang :: k) ftype (a :: k1) 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

Methods

typeFor :: Proxy lang -> Proxy ftype -> Proxy a -> ftype #

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

data NoTypes #

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

Defined in Servant.Foreign.Internal

Methods

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

data ArgType #

Constructors

Normal 
Flag 
List 
Instances
Eq ArgType 
Instance details

Defined in Servant.Foreign.Internal

Methods

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

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

Data ArgType 
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) -> 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 
Instance details

Defined in Servant.Foreign.Internal

data HeaderArg f #

Constructors

HeaderArg 

Fields

ReplaceHeaderArg 
Instances
Eq f => Eq (HeaderArg f) 
Instance details

Defined in Servant.Foreign.Internal

Methods

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

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

Data f => Data (HeaderArg f) 
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) -> 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) 
Instance details

Defined in Servant.Foreign.Internal

data QueryArg f #

Constructors

QueryArg 
Instances
Eq f => Eq (QueryArg f) 
Instance details

Defined in Servant.Foreign.Internal

Methods

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

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

Data f => Data (QueryArg f) 
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) -> 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) 
Instance details

Defined in Servant.Foreign.Internal

Methods

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

show :: QueryArg f -> String #

showList :: [QueryArg f] -> ShowS #

data Req f #

Instances
GenerateList ftype (Req ftype) 
Instance details

Defined in Servant.Foreign.Internal

Methods

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

Eq f => Eq (Req f) 
Instance details

Defined in Servant.Foreign.Internal

Methods

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

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

Data f => Data (Req f) 
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) -> 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) 
Instance details

Defined in Servant.Foreign.Internal

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) 
Instance details

Defined in Servant.Foreign.Internal

Methods

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

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

Data f => Data (Segment f) 
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) -> 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) 
Instance details

Defined in Servant.Foreign.Internal

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) 
Instance details

Defined in Servant.Foreign.Internal

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

Defined in Servant.Foreign.Internal

data Url f #

Constructors

Url 

Fields

Instances
Eq f => Eq (Url f) 
Instance details

Defined in Servant.Foreign.Internal

Methods

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

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

Data f => Data (Url f) 
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) -> 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) 
Instance details

Defined in Servant.Foreign.Internal

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) 
Instance details

Defined in Servant.Foreign.Internal

Methods

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

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

Data f => Data (Arg f) 
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) -> 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) 
Instance details

Defined in Servant.Foreign.Internal

Methods

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

show :: Arg f -> String #

showList :: [Arg f] -> ShowS #

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

newtype PathSegment #

Constructors

PathSegment 

Fields

Instances
Eq PathSegment 
Instance details

Defined in Servant.Foreign.Internal

Data PathSegment 
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) -> 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 
Instance details

Defined in Servant.Foreign.Internal

IsString PathSegment 
Instance details

Defined in Servant.Foreign.Internal

Semigroup PathSegment 
Instance details

Defined in Servant.Foreign.Internal

Monoid PathSegment 
Instance details

Defined in Servant.Foreign.Internal

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.

type ReqBody = ReqBody' (Required ': (Strict ': ([] :: [Type]))) #

Extract the request body as a value of type a.

Example:

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

data JSON #

Instances
Accept JSON
application/json
Instance details

Defined in Servant.API.ContentTypes

ToJSON a => MimeRender JSON a

encode

Instance details

Defined in Servant.API.ContentTypes

Methods

mimeRender :: Proxy JSON -> a -> ByteString #

FromJSON a => MimeUnrender JSON a

eitherDecode

Instance details

Defined in Servant.API.ContentTypes

data FormUrlEncoded #

Instances
Accept FormUrlEncoded
application/x-www-form-urlencoded
Instance details

Defined in Servant.API.ContentTypes

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 ("", ""))

Instance details

Defined in Servant.API.ContentTypes

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 ("", ""))

Instance details

Defined in Servant.API.ContentTypes

type Post = Verb POST 200 #

POST with 200 status code.

type Get = Verb 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 functions from Servant.Server.StaticFiles to serve static files stored in a particular directory on your filesystem

Instances
HasForeign (lang :: k) ftype Raw 
Instance details

Defined in Servant.Foreign.Internal

Associated Types

type Foreign ftype Raw :: Type #

Methods

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

HasLink Raw 
Instance details

Defined in Servant.Links

Associated Types

type MkLink Raw a :: Type #

Methods

toLink :: (Link -> a) -> Proxy Raw -> Link -> MkLink Raw a #

type Foreign ftype Raw 
Instance details

Defined in Servant.Foreign.Internal

type Foreign ftype Raw = Method -> Req ftype
type MkLink Raw a 
Instance details

Defined in Servant.Links

type MkLink Raw a = a

type Header = (Header' (Optional ': (Strict ': ([] :: [Type]))) :: Symbol -> k -> Type) #

Extract the given header's value as a value of type a. I.e. header sent by client, parsed by server.

Example:

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