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

Safe HaskellNone
LanguageHaskell2010

Servant.Server.Internal

Contents

Synopsis

Documentation

class HasServer layout context where Source

Associated Types

type ServerT layout m :: * Source

Methods

route :: Proxy layout -> Context context -> Delayed (Server layout) -> Router Source

Instances

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"
(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 = ...
(HasContextEntry context (NamedContext name subContext), HasServer * subApi subContext) => HasServer * (WithNamedContext name subContext subApi) context Source 
(KnownSymbol realm, HasServer k api context, HasContextEntry context (BasicAuthCheck usr)) => HasServer * ((:>) * k (BasicAuth realm usr) api) context Source

Basic Authentication

HasServer k api context => HasServer * ((:>) * k HttpVersion api) context Source 
HasServer k api context => HasServer * ((:>) * k Vault api) context Source 
HasServer k api context => HasServer * ((:>) * k IsSecure api) context Source 
HasServer k api context => HasServer * ((:>) * k RemoteHost api) context Source 
(AllCTUnrender list a, HasServer k sublayout context) => HasServer * ((:>) * k (ReqBody * list a) sublayout) 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 -> ExceptT ServantErr IO Book
        postBook book = ...insert into your db...
(KnownSymbol sym, HasServer k sublayout context) => HasServer * ((:>) * k (QueryFlag sym) sublayout) 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 -> ExceptT ServantErr IO [Book]
        getBooks onlyPublished = ...return all books, or only the ones that are already published, depending on the argument...
(KnownSymbol sym, FromHttpApiData a, HasServer k sublayout context) => HasServer * ((:>) * k (QueryParams * sym a) sublayout) 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] -> ExceptT ServantErr IO [Book]
        getBooksBy authors = ...return all books by these authors...
(KnownSymbol sym, FromHttpApiData a, HasServer k sublayout context) => HasServer * ((:>) * k (QueryParam * sym a) sublayout) 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 -> ExceptT ServantErr IO [Book]
        getBooksBy Nothing       = ...return all books...
        getBooksBy (Just author) = ...return books by the given author...
(KnownSymbol sym, FromHttpApiData a, HasServer k sublayout context) => HasServer * ((:>) * k (Header sym a) sublayout) 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, ToText)

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

server :: Server MyApi
server = viewReferer
  where viewReferer :: Referer -> ExceptT ServantErr IO referer
        viewReferer referer = return referer
(KnownSymbol capture, FromHttpApiData a, HasServer k sublayout context) => HasServer * ((:>) * k (Capture * capture a) sublayout) 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 -> ExceptT ServantErr IO Book
        getBook isbn = ...
(KnownSymbol path, HasServer k sublayout context) => HasServer * ((:>) Symbol k path sublayout) context Source

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

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

type Server layout = ServerT layout (ExceptT ServantErr IO) Source

Instances

captured :: FromHttpApiData a => proxy (Capture sym a) -> Text -> Maybe a Source

helpers

General Authentication

contexts