servant-server-0.11: A family of combinators for defining webservices APIs and serving them

Safe HaskellNone
LanguageHaskell2010

Servant.Server.Internal

Contents

Synopsis

Documentation

class HasServer api context where Source #

Minimal complete definition

route

Associated Types

type ServerT api (m :: * -> *) :: * Source #

Methods

route :: Proxy api -> Context context -> Delayed env (Server api) -> Router env Source #

Instances

HasServer * EmptyAPI context Source #

The server for an EmptyAPI is emptyAPIServer.

type MyApi = "nothing" :> EmptyApi

server :: Server MyApi
server = emptyAPIServer

Associated Types

type ServerT EmptyAPI (context :: EmptyAPI) (m :: * -> *) :: * Source #

Methods

route :: Proxy EmptyAPI context -> Context context -> Delayed env (Server EmptyAPI context) -> Router env Source #

HasServer * Raw context Source #

Just pass the request to the underlying application and serve its response.

Example:

type MyApi = "images" :> Raw

server :: Server MyApi
server = serveDirectory "/var/www/images"

Associated Types

type ServerT Raw (context :: Raw) (m :: * -> *) :: * Source #

Methods

route :: Proxy Raw context -> Context context -> Delayed env (Server Raw context) -> Router env Source #

(HasServer * a context, HasServer * b context) => HasServer * ((:<|>) a b) context Source #

A server for a :<|> b first tries to match the request against the route represented by a and if it fails tries b. You must provide a request handler for each route.

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

server :: Server MyApi
server = listAllBooks :<|> postBook
  where listAllBooks = ...
        postBook book = ...

Associated Types

type ServerT ((:<|>) a b) (context :: (:<|>) a b) (m :: * -> *) :: * Source #

Methods

route :: Proxy (a :<|> b) context -> Context context -> Delayed env (Server (a :<|> b) context) -> Router env Source #

(HasContextEntry context (NamedContext name subContext), HasServer * subApi subContext) => HasServer * (WithNamedContext name subContext subApi) context Source # 

Associated Types

type ServerT (WithNamedContext name subContext subApi) (context :: WithNamedContext name subContext subApi) (m :: * -> *) :: * Source #

Methods

route :: Proxy (WithNamedContext name subContext subApi) context -> Context context -> Delayed env (Server (WithNamedContext name subContext subApi) context) -> Router env Source #

(KnownSymbol realm, HasServer k api context, HasContextEntry context (BasicAuthCheck usr)) => HasServer * ((:>) k * (BasicAuth realm usr) api) context Source #

Basic Authentication

Associated Types

type ServerT ((:>) k * (BasicAuth realm usr) api) (context :: (:>) k * (BasicAuth realm usr) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((k :> *) (BasicAuth realm usr) api) context -> Context context -> Delayed env (Server ((k :> *) (BasicAuth realm usr) api) context) -> Router env Source #

HasServer k api context => HasServer * ((:>) k * HttpVersion api) context Source # 

Associated Types

type ServerT ((:>) k * HttpVersion api) (context :: (:>) k * HttpVersion api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((k :> *) HttpVersion api) context -> Context context -> Delayed env (Server ((k :> *) HttpVersion api) context) -> Router env Source #

HasServer k api context => HasServer * ((:>) k * Vault api) context Source # 

Associated Types

type ServerT ((:>) k * Vault api) (context :: (:>) k * Vault api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((k :> *) Vault api) context -> Context context -> Delayed env (Server ((k :> *) Vault api) context) -> Router env Source #

HasServer k api context => HasServer * ((:>) k * IsSecure api) context Source # 

Associated Types

type ServerT ((:>) k * IsSecure api) (context :: (:>) k * IsSecure api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((k :> *) IsSecure api) context -> Context context -> Delayed env (Server ((k :> *) IsSecure api) context) -> Router env Source #

HasServer k api context => HasServer * ((:>) k * RemoteHost api) context Source # 

Associated Types

type ServerT ((:>) k * RemoteHost api) (context :: (:>) k * RemoteHost api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((k :> *) RemoteHost api) context -> Context context -> Delayed env (Server ((k :> *) RemoteHost api) context) -> Router env Source #

(KnownSymbol path, HasServer k api context) => HasServer * ((:>) k Symbol path api) context Source #

Make sure the incoming request starts with "/path", strip it and pass the rest of the request path to api.

Associated Types

type ServerT ((:>) k Symbol path api) (context :: (:>) k Symbol path api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((k :> Symbol) path api) context -> Context context -> Delayed env (Server ((k :> Symbol) path api) context) -> Router env Source #

(AllCTUnrender list a, HasServer k api context) => HasServer * ((:>) k * (ReqBody * list a) api) context Source #

If you use ReqBody in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of the type specified by ReqBody. The Content-Type header is inspected, and the list provided is used to attempt deserialization. If the request does not have a Content-Type header, it is treated as application/octet-stream (as specified in RFC7231. This lets servant worry about extracting it from the request and turning it into a value of the type you specify.

All it asks is for a FromJSON instance.

Example:

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

server :: Server MyApi
server = postBook
  where postBook :: Book -> Handler Book
        postBook book = ...insert into your db...

Associated Types

type ServerT ((:>) k * (ReqBody * list a) api) (context :: (:>) k * (ReqBody * list a) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((k :> *) (ReqBody * list a) api) context -> Context context -> Delayed env (Server ((k :> *) (ReqBody * list a) api) context) -> Router env Source #

(KnownSymbol sym, HasServer k api context) => HasServer * ((:>) k * (QueryFlag sym) api) context Source #

If you use QueryFlag "published" in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of type Bool.

Example:

type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book]

server :: Server MyApi
server = getBooks
  where getBooks :: Bool -> Handler [Book]
        getBooks onlyPublished = ...return all books, or only the ones that are already published, depending on the argument...

Associated Types

type ServerT ((:>) k * (QueryFlag sym) api) (context :: (:>) k * (QueryFlag sym) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((k :> *) (QueryFlag sym) api) context -> Context context -> Delayed env (Server ((k :> *) (QueryFlag sym) api) context) -> Router env Source #

(KnownSymbol sym, FromHttpApiData a, HasServer k api context) => HasServer * ((:>) k * (QueryParams * sym a) api) context Source #

If you use QueryParams "authors" Text in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of type [Text].

This lets servant worry about looking up 0 or more values in the query string associated to authors and turning each of them into a value of the type you specify.

You can control how the individual values are converted from Text to your type by simply providing an instance of FromHttpApiData for your type.

Example:

type MyApi = "books" :> QueryParams "authors" Text :> Get '[JSON] [Book]

server :: Server MyApi
server = getBooksBy
  where getBooksBy :: [Text] -> Handler [Book]
        getBooksBy authors = ...return all books by these authors...

Associated Types

type ServerT ((:>) k * (QueryParams * sym a) api) (context :: (:>) k * (QueryParams * sym a) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((k :> *) (QueryParams * sym a) api) context -> Context context -> Delayed env (Server ((k :> *) (QueryParams * sym a) api) context) -> Router env Source #

(KnownSymbol sym, FromHttpApiData a, HasServer k api context) => HasServer * ((:>) k * (QueryParam * sym a) api) context Source #

If you use QueryParam "author" Text in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of type Maybe Text.

This lets servant worry about looking it up in the query string and turning it into a value of the type you specify, enclosed in Maybe, because it may not be there and servant would then hand you Nothing.

You can control how it'll be converted from Text to your type by simply providing an instance of FromHttpApiData for your type.

Example:

type MyApi = "books" :> QueryParam "author" Text :> Get '[JSON] [Book]

server :: Server MyApi
server = getBooksBy
  where getBooksBy :: Maybe Text -> Handler [Book]
        getBooksBy Nothing       = ...return all books...
        getBooksBy (Just author) = ...return books by the given author...

Associated Types

type ServerT ((:>) k * (QueryParam * sym a) api) (context :: (:>) k * (QueryParam * sym a) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((k :> *) (QueryParam * sym a) api) context -> Context context -> Delayed env (Server ((k :> *) (QueryParam * sym a) api) context) -> Router env Source #

(KnownSymbol sym, FromHttpApiData a, HasServer k api context) => HasServer * ((:>) k * (Header sym a) api) context Source #

If you use Header in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of the type specified by Header. This lets servant worry about extracting it from the request and turning it into a value of the type you specify.

All it asks is for a FromHttpApiData instance.

Example:

newtype Referer = Referer Text
  deriving (Eq, Show, FromHttpApiData)

           -- GET /view-my-referer
type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get '[JSON] Referer

server :: Server MyApi
server = viewReferer
  where viewReferer :: Referer -> Handler referer
        viewReferer referer = return referer

Associated Types

type ServerT ((:>) k * (Header sym a) api) (context :: (:>) k * (Header sym a) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((k :> *) (Header sym a) api) context -> Context context -> Delayed env (Server ((k :> *) (Header sym a) api) context) -> Router env Source #

(KnownSymbol capture, FromHttpApiData a, HasServer k sublayout context) => HasServer * ((:>) k * (CaptureAll * capture a) sublayout) context Source #

If you use CaptureAll in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of a list of the type specified by the CaptureAll. This lets servant worry about getting values from the URL and turning them into values of the type you specify.

You can control how they'll be converted from Text to your type by simply providing an instance of FromHttpApiData for your type.

Example:

type MyApi = "src" :> CaptureAll "segments" Text :> Get '[JSON] SourceFile

server :: Server MyApi
server = getSourceFile
  where getSourceFile :: [Text] -> Handler Book
        getSourceFile pathSegments = ...

Associated Types

type ServerT ((:>) k * (CaptureAll * capture a) sublayout) (context :: (:>) k * (CaptureAll * capture a) sublayout) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((k :> *) (CaptureAll * capture a) sublayout) context -> Context context -> Delayed env (Server ((k :> *) (CaptureAll * capture a) sublayout) context) -> Router env Source #

(KnownSymbol capture, FromHttpApiData a, HasServer k api context) => HasServer * ((:>) k * (Capture * capture a) api) context Source #

If you use Capture in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of the type specified by the Capture. This lets servant worry about getting it from the URL and turning it into a value of the type you specify.

You can control how it'll be converted from Text to your type by simply providing an instance of FromHttpApiData for your type.

Example:

type MyApi = "books" :> Capture "isbn" Text :> Get '[JSON] Book

server :: Server MyApi
server = getBook
  where getBook :: Text -> Handler Book
        getBook isbn = ...

Associated Types

type ServerT ((:>) k * (Capture * capture a) api) (context :: (:>) k * (Capture * capture a) api) (m :: * -> *) :: * Source #

Methods

route :: Proxy ((k :> *) (Capture * capture a) api) context -> Context context -> Delayed env (Server ((k :> *) (Capture * capture a) api) context) -> Router env Source #

(AllCTRender ctypes a, ReflectMethod k1 method, KnownNat status, GetHeaders (Headers h a)) => HasServer * (Verb * k1 method status ctypes (Headers h a)) context Source # 

Associated Types

type ServerT (Verb * k1 method status ctypes (Headers h a)) (context :: Verb * k1 method status ctypes (Headers h a)) (m :: * -> *) :: * Source #

Methods

route :: Proxy (Verb * k1 method status ctypes (Headers h a)) context -> Context context -> Delayed env (Server (Verb * k1 method status ctypes (Headers h a)) context) -> Router env Source #

(AllCTRender ctypes a, ReflectMethod k1 method, KnownNat status) => HasServer * (Verb * k1 method status ctypes a) context Source # 

Associated Types

type ServerT (Verb * k1 method status ctypes a) (context :: Verb * k1 method status ctypes a) (m :: * -> *) :: * Source #

Methods

route :: Proxy (Verb * k1 method status ctypes a) context -> Context context -> Delayed env (Server (Verb * k1 method status ctypes a) context) -> Router env Source #

type Server api = ServerT api Handler Source #

Instances

methodRouter :: AllCTRender ctypes a => Method -> Proxy ctypes -> Status -> Delayed env (Handler a) -> Router env Source #

methodRouterHeaders :: (GetHeaders (Headers h v), AllCTRender ctypes v) => Method -> Proxy ctypes -> Status -> Delayed env (Handler (Headers h v)) -> Router env Source #

helpers

General Authentication

contexts