servant-server-0.4.4.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

Run a wai application from 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 '[JSON] [Book] -- GET /books
        :<|> "books" :> ReqBody Book :> Post '[JSON] 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

Construct a wai Application from an API

Handlers for all standard combinators

class HasServer layout where Source

Associated Types

type ServerT layout m :: * Source

Methods

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

Instances

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"
(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 '[JSON] [Book] -- GET /books
        :<|> "books" :> ReqBody Book :> Post '[JSON] Book -- POST /books

server :: Server MyApi
server = listAllBooks :<|> postBook
  where listAllBooks = ...
        postBook book = ...
(GetHeaders (Headers h v), AllCTRender ctypes v) => HasServer * (Get ctypes (Headers h v)) Source 
HasServer * (Get ctypes ()) Source 
AllCTRender ctypes a => HasServer * (Get ctypes a) Source

When implementing the handler for a Get endpoint, just like for Delete, Post and Put, the handler code runs in the EitherT ServantErr 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 use the type-level list, combined with the request's Accept header, to encode the value for you (returning a status code of 200). If there was no Accept header or it was */*, we return encode using the first Content-Type type on the list.

(GetHeaders (Headers h v), AllCTRender ctypes v) => HasServer * (Post ctypes (Headers h v)) Source 
HasServer * (Post ctypes ()) Source 
AllCTRender ctypes a => HasServer * (Post ctypes a) Source

When implementing the handler for a Post endpoint, just like for Delete, Get and Put, the handler code runs in the EitherT ServantErr 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 use the type-level list, combined with the request's Accept header, to encode the value for you (returning a status code of 201). If there was no Accept header or it was */*, we return encode using the first Content-Type type on the list.

(GetHeaders (Headers h v), AllCTRender ctypes v) => HasServer * (Delete ctypes (Headers h v)) Source 
HasServer * (Delete ctypes ()) Source 
AllCTRender ctypes a => HasServer * (Delete ctypes a) 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 ServantErr 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.

(GetHeaders (Headers h v), AllCTRender ctypes v) => HasServer * (Put ctypes (Headers h v)) Source 
HasServer * (Put ctypes ()) Source 
AllCTRender ctypes a => HasServer * (Put ctypes a) Source

When implementing the handler for a Put endpoint, just like for Delete, Get and Post, the handler code runs in the EitherT ServantErr 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 use the type-level list, combined with the request's Accept header, to encode the value for you (returning a status code of 200). If there was no Accept header or it was */*, we return encode using the first Content-Type type on the list.

(GetHeaders (Headers h v), AllCTRender ctypes v) => HasServer * (Patch ctypes (Headers h v)) Source 
HasServer * (Patch ctypes ()) Source 
AllCTRender ctypes a => HasServer * (Patch ctypes a) Source

When implementing the handler for a Patch endpoint, just like for Delete, Get and Put, the handler code runs in the EitherT ServantErr 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.

(AllCTUnrender list a, HasServer k sublayout) => HasServer * ((:>) * k (ReqBody * list 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. 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. 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 -> EitherT ServantErr IO Book
        postBook book = ...insert into your db...
(KnownSymbol sym, HasServer k sublayout) => HasServer * ((:>) * k (MatrixFlag 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 ServantErr IO [Book]
        getBooks onlyPublished = ...return all books, or only the ones that are already published, depending on the argument...
(KnownSymbol sym, FromText a, HasServer k sublayout) => HasServer * ((:>) * k (MatrixParams * 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 ServantErr IO [Book]
        getBooksBy authors = ...return all books by these authors...
(KnownSymbol sym, FromText a, HasServer k sublayout) => HasServer * ((:>) * k (MatrixParam * 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 ServantErr IO [Book]
        getBooksBy Nothing       = ...return all books...
        getBooksBy (Just author) = ...return books by the given author...
(KnownSymbol sym, HasServer k sublayout) => HasServer * ((:>) * k (QueryFlag 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 '[JSON] [Book]

server :: Server MyApi
server = getBooks
  where getBooks :: Bool -> EitherT ServantErr IO [Book]
        getBooks onlyPublished = ...return all books, or only the ones that are already published, depending on the argument...
(KnownSymbol sym, FromText a, HasServer k sublayout) => HasServer * ((:>) * k (QueryParams * 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 '[JSON] [Book]

server :: Server MyApi
server = getBooksBy
  where getBooksBy :: [Text] -> EitherT ServantErr IO [Book]
        getBooksBy authors = ...return all books by these authors...
(KnownSymbol sym, FromText a, HasServer k sublayout) => HasServer * ((:>) * k (QueryParam * 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 '[JSON] [Book]

server :: Server MyApi
server = getBooksBy
  where getBooksBy :: Maybe Text -> EitherT ServantErr IO [Book]
        getBooksBy Nothing       = ...return all books...
        getBooksBy (Just author) = ...return books by the given author...
(KnownSymbol sym, FromText a, HasServer k sublayout) => HasServer * ((:>) * k (Header 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 '[JSON] Referer

server :: Server MyApi
server = viewReferer
  where viewReferer :: Referer -> EitherT ServantErr IO referer
        viewReferer referer = return referer
(KnownSymbol capture, FromText a, HasServer k sublayout) => HasServer * ((:>) * k (Capture * 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 '[JSON] Book

server :: Server MyApi
server = getBook
  where getBook :: Text -> EitherT ServantErr IO Book
        getBook isbn = ...
(KnownSymbol path, HasServer k sublayout) => HasServer * ((:>) Symbol k path sublayout) Source

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

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

Enter

Sometimes our cherished EitherT monad isn't quite the type you'd like for your handlers. Maybe you want to thread some configuration in a Reader monad. Or have your types ensure that your handlers don't do any IO. Enter enter.

With enter, you can provide a function, wrapped in the `(:~>)` / Nat newtype, to convert any number of endpoints from one type constructor to another. For example

>>> import Control.Monad.Reader
>>> import qualified Control.Category as C
>>> type ReaderAPI = "ep1" :> Get '[JSON] Int :<|> "ep2" :> Get '[JSON] String
>>> let readerServer = return 1797 :<|> ask :: ServerT ReaderAPI (Reader String)
>>> let mainServer = enter (generalizeNat C.. (runReaderTNat "hi")) readerServer :: Server ReaderAPI

Basic functions and datatypes

enter :: Enter typ arg ret => arg -> typ -> ret Source

newtype m :~> n Source

A natural transformation from m to n. Used to enter particular datatypes.

Constructors

Nat 

Fields

unNat :: forall a. m a -> n a
 

Instances

Enter (m a) ((:~>) m n) (n a) Source 
Category (* -> *) (:~>) Source 

Nat utilities

liftNat :: (MonadTrans t, Monad m) => m :~> t m Source

Like lift.

evalStateTLNat :: Monad m => s -> StateT s m :~> m Source

evalStateTSNat :: Monad m => s -> StateT s m :~> m Source

logWriterTLNat :: MonadIO m => (w -> IO ()) -> WriterT w m :~> m Source

Like logWriterTSNat, but for strict WriterT.

logWriterTSNat :: MonadIO m => (w -> IO ()) -> WriterT w m :~> m Source

Log the contents of WriterT with the function provided as the first argument, and return the value of the WriterT computation

Functions based on mmorph

hoistNat :: (MFunctor t, Monad m) => (m :~> n) -> t m :~> t n Source

Like mmorph's hoist.

embedNat :: (MMonad t, Monad n) => (m :~> t n) -> t m :~> t n Source

Like mmorph's embed.

squashNat :: (Monad m, MMonad t) => t (t m) :~> t m Source

Like mmorph's squash.

Default error type

3XX

4XX

5XX