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

Safe HaskellNone
LanguageHaskell2010

Servant.Server

Contents

Description

This module lets you implement Servers for defined APIs. You'll most likely just need serve.

Synopsis

Implementing an API

serve :: HasServer layout => Proxy layout -> Server layout -> Application Source #

serve allows you to implement an API and produce a wai Application.

Example:

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

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

myApi :: Proxy MyApi
myApi = Proxy

app :: Application
app = serve myApi server

main :: IO ()
main = Network.Wai.Handler.Warp.run 8080 app

Handlers for all standard combinators

class HasServer layout where Source #

Minimal complete definition

route

Associated Types

type Server layout :: * Source #

Methods

route :: Proxy layout -> Server layout -> RoutingApplication Source #

Instances

HasServer * Delete Source #

If you have a Delete endpoint in your API, the handler for this endpoint is meant to delete a resource.

The code of the handler will, just like for Get, Post and Put, run in EitherT (Int, String) IO (). The Int represents the status code and the String a message to be returned. You can use left to painlessly error out if the conditions for a successful deletion are not met.

Associated Types

type Server Delete (layout :: Delete) :: * Source #

Methods

route :: Proxy Delete layout -> Server Delete layout -> RoutingApplication Source #

HasServer * Raw 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 Server Raw (layout :: Raw) :: * Source #

Methods

route :: Proxy Raw layout -> Server Raw layout -> RoutingApplication Source #

ToJSON result => HasServer * (Get result) Source #

When implementing the handler for a Get endpoint, just like for Delete, Post and Put, the handler code runs in the EitherT (Int, String) IO monad, where the Int represents the status code and the String a message, returned in case of failure. You can quite handily use left to quickly fail if some conditions are not met.

If successfully returning a value, we just require that its type has a ToJSON instance and servant takes care of encoding it for you, yielding status code 200 along the way.

Associated Types

type Server (Get result) (layout :: Get result) :: * Source #

Methods

route :: Proxy (Get result) layout -> Server (Get result) layout -> RoutingApplication Source #

ToJSON a => HasServer * (Post a) Source #

When implementing the handler for a Post endpoint, just like for Delete, Get and Put, the handler code runs in the EitherT (Int, String) IO monad, where the Int represents the status code and the String a message, returned in case of failure. You can quite handily use left to quickly fail if some conditions are not met.

If successfully returning a value, we just require that its type has a ToJSON instance and servant takes care of encoding it for you, yielding status code 201 along the way.

Associated Types

type Server (Post a) (layout :: Post a) :: * Source #

Methods

route :: Proxy (Post a) layout -> Server (Post a) layout -> RoutingApplication Source #

ToJSON a => HasServer * (Put a) Source #

When implementing the handler for a Put endpoint, just like for Delete, Get and Post, the handler code runs in the EitherT (Int, String) IO monad, where the Int represents the status code and the String a message, returned in case of failure. You can quite handily use left to quickly fail if some conditions are not met.

If successfully returning a value, we just require that its type has a ToJSON instance and servant takes care of encoding it for you, yielding status code 200 along the way.

Associated Types

type Server (Put a) (layout :: Put a) :: * Source #

Methods

route :: Proxy (Put a) layout -> Server (Put a) layout -> RoutingApplication Source #

(HasServer * a, HasServer * b) => HasServer * ((:<|>) a b) 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 [Book] -- GET /books
        :<|> "books" :> ReqBody Book :> Post Book -- POST /books

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

Associated Types

type Server ((:<|>) a b) (layout :: (:<|>) a b) :: * Source #

Methods

route :: Proxy (a :<|> b) layout -> Server (a :<|> b) layout -> RoutingApplication Source #

(KnownSymbol capture, FromText a, HasServer * sublayout) => HasServer * ((:>) * (Capture Symbol * capture a) sublayout) 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 FromText for your type.

Example:

type MyApi = "books" :> Capture "isbn" Text :> Get Book

server :: Server MyApi
server = getBook
  where getBook :: Text -> EitherT (Int, String) IO Book
        getBook isbn = ...

Associated Types

type Server ((:>) * (Capture Symbol * capture a) sublayout) (layout :: (:>) * (Capture Symbol * capture a) sublayout) :: * Source #

Methods

route :: Proxy ((* :> Capture Symbol * capture a) sublayout) layout -> Server ((* :> Capture Symbol * capture a) sublayout) layout -> RoutingApplication Source #

(KnownSymbol sym, FromText a, HasServer * sublayout) => HasServer * ((:>) * (Header Symbol * sym a) sublayout) 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 FromText instance.

Example:

newtype Referer = Referer Text
  deriving (Eq, Show, FromText, ToText)

           -- GET /view-my-referer
type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get Referer

server :: Server MyApi
server = viewReferer
  where viewReferer :: Referer -> EitherT (Int, String) IO referer
        viewReferer referer = return referer

Associated Types

type Server ((:>) * (Header Symbol * sym a) sublayout) (layout :: (:>) * (Header Symbol * sym a) sublayout) :: * Source #

Methods

route :: Proxy ((* :> Header Symbol * sym a) sublayout) layout -> Server ((* :> Header Symbol * sym a) sublayout) layout -> RoutingApplication Source #

(KnownSymbol sym, FromText a, HasServer * sublayout) => HasServer * ((:>) * (QueryParam Symbol * sym a) sublayout) 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 FromText for your type.

Example:

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

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

Associated Types

type Server ((:>) * (QueryParam Symbol * sym a) sublayout) (layout :: (:>) * (QueryParam Symbol * sym a) sublayout) :: * Source #

Methods

route :: Proxy ((* :> QueryParam Symbol * sym a) sublayout) layout -> Server ((* :> QueryParam Symbol * sym a) sublayout) layout -> RoutingApplication Source #

(KnownSymbol sym, FromText a, HasServer * sublayout) => HasServer * ((:>) * (QueryParams Symbol * sym a) sublayout) 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 FromText for your type.

Example:

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

server :: Server MyApi
server = getBooksBy
  where getBooksBy :: [Text] -> EitherT (Int, String) IO [Book]
        getBooksBy authors = ...return all books by these authors...

Associated Types

type Server ((:>) * (QueryParams Symbol * sym a) sublayout) (layout :: (:>) * (QueryParams Symbol * sym a) sublayout) :: * Source #

Methods

route :: Proxy ((* :> QueryParams Symbol * sym a) sublayout) layout -> Server ((* :> QueryParams Symbol * sym a) sublayout) layout -> RoutingApplication Source #

(KnownSymbol sym, HasServer * sublayout) => HasServer * ((:>) * (QueryFlag Symbol sym) sublayout) 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 [Book]

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

Associated Types

type Server ((:>) * (QueryFlag Symbol sym) sublayout) (layout :: (:>) * (QueryFlag Symbol sym) sublayout) :: * Source #

Methods

route :: Proxy ((* :> QueryFlag Symbol sym) sublayout) layout -> Server ((* :> QueryFlag Symbol sym) sublayout) layout -> RoutingApplication Source #

(FromJSON a, HasServer * sublayout) => HasServer * ((:>) * (ReqBody * a) sublayout) 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. 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 Book :> Post Book

server :: Server MyApi
server = postBook
  where postBook :: Book -> EitherT (Int, String) IO Book
        postBook book = ...insert into your db...

Associated Types

type Server ((:>) * (ReqBody * a) sublayout) (layout :: (:>) * (ReqBody * a) sublayout) :: * Source #

Methods

route :: Proxy ((* :> ReqBody * a) sublayout) layout -> Server ((* :> ReqBody * a) sublayout) layout -> RoutingApplication Source #

(KnownSymbol sym, FromText a, HasServer * sublayout) => HasServer * ((:>) * (MatrixParam Symbol * sym a) sublayout) Source #

If you use MatrixParam "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 FromText for your type.

Example:

type MyApi = "books" :> MatrixParam "author" Text :> Get [Book]

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

Associated Types

type Server ((:>) * (MatrixParam Symbol * sym a) sublayout) (layout :: (:>) * (MatrixParam Symbol * sym a) sublayout) :: * Source #

Methods

route :: Proxy ((* :> MatrixParam Symbol * sym a) sublayout) layout -> Server ((* :> MatrixParam Symbol * sym a) sublayout) layout -> RoutingApplication Source #

(KnownSymbol sym, FromText a, HasServer * sublayout) => HasServer * ((:>) * (MatrixParams Symbol * sym a) sublayout) Source #

If you use MatrixParams "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 FromText for your type.

Example:

type MyApi = "books" :> MatrixParams "authors" Text :> Get [Book]

server :: Server MyApi
server = getBooksBy
  where getBooksBy :: [Text] -> EitherT (Int, String) IO [Book]
        getBooksBy authors = ...return all books by these authors...

Associated Types

type Server ((:>) * (MatrixParams Symbol * sym a) sublayout) (layout :: (:>) * (MatrixParams Symbol * sym a) sublayout) :: * Source #

Methods

route :: Proxy ((* :> MatrixParams Symbol * sym a) sublayout) layout -> Server ((* :> MatrixParams Symbol * sym a) sublayout) layout -> RoutingApplication Source #

(KnownSymbol sym, HasServer * sublayout) => HasServer * ((:>) * (MatrixFlag Symbol sym) sublayout) Source #

If you use MatrixFlag "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" :> MatrixFlag "published" :> Get [Book]

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

Associated Types

type Server ((:>) * (MatrixFlag Symbol sym) sublayout) (layout :: (:>) * (MatrixFlag Symbol sym) sublayout) :: * Source #

Methods

route :: Proxy ((* :> MatrixFlag Symbol sym) sublayout) layout -> Server ((* :> MatrixFlag Symbol sym) sublayout) layout -> RoutingApplication Source #

(KnownSymbol path, HasServer * sublayout) => HasServer * ((:>) Symbol path sublayout) Source #

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

Associated Types

type Server ((:>) Symbol path sublayout) (layout :: (:>) Symbol path sublayout) :: * Source #

Methods

route :: Proxy ((Symbol :> path) sublayout) layout -> Server ((Symbol :> path) sublayout) layout -> RoutingApplication Source #