servant-snap-0.9.0: 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 snap handler from an API

serveSnap :: forall layout m. (HasServer layout '[] m, MonadSnap m) => Proxy layout -> Server layout '[] m -> m () Source #

serveSnapWithContext :: forall layout context m. (HasServer layout context m, MonadSnap m) => Proxy layout -> Context context -> Server layout context m -> m () Source #

Handlers for all standard combinators

class HasServer api context (m :: * -> *) where Source #

Associated Types

type ServerT api context m :: * Source #

Methods

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

hoistServerWithContext :: proxy api -> proxy' context -> (forall x. m x -> n x) -> ServerT api context m -> ServerT api context n Source #

Instances
HasServer Raw context m 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"
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT Raw context m :: Type Source #

Methods

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

hoistServerWithContext :: proxy Raw -> proxy' context -> (forall x. m x -> n x) -> ServerT Raw context m -> ServerT Raw context n Source #

HasServer EmptyAPI context m Source #

The server for an EmptyAPI is emptyAPIServer.

type MyApi = "nothing" :> EmptyApi

server :: Server MyApi
server = emptyAPIServer
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT EmptyAPI context m :: Type Source #

Methods

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

hoistServerWithContext :: proxy EmptyAPI -> proxy' context -> (forall x. m x -> n x) -> ServerT EmptyAPI context m -> ServerT EmptyAPI context n Source #

(HasServer a ctx m, HasServer b ctx m) => HasServer (a :<|> b :: Type) ctx m 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 = ...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (a :<|> b) ctx m :: Type Source #

Methods

route :: MonadSnap m => Proxy (a :<|> b) -> Context ctx -> Delayed m env (Server (a :<|> b) ctx m) -> Router m env Source #

hoistServerWithContext :: proxy (a :<|> b) -> proxy' ctx -> (forall x. m x -> n x) -> ServerT (a :<|> b) ctx m -> ServerT (a :<|> b) ctx n Source #

(AllCTUnrender list a, HasServer api context m, SBoolI (FoldLenient mods), MonadSnap m) => HasServer (ReqBody' mods list a :> api :: Type) context m 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 -> EitherT ServantErr IO Book
        postBook book = ...insert into your db...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (ReqBody' mods list a :> api) context m :: Type Source #

Methods

route :: MonadSnap m => Proxy (ReqBody' mods list a :> api) -> Context context -> Delayed m env (Server (ReqBody' mods list a :> api) context m) -> Router m env Source #

hoistServerWithContext :: proxy (ReqBody' mods list a :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (ReqBody' mods list a :> api) context m -> ServerT (ReqBody' mods list a :> api) context n Source #

HasServer api context m => HasServer (RemoteHost :> api :: Type) context m Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (RemoteHost :> api) context m :: Type Source #

Methods

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

hoistServerWithContext :: proxy (RemoteHost :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (RemoteHost :> api) context m -> ServerT (RemoteHost :> api) context n Source #

(KnownSymbol sym, FromHttpApiData a, HasServer api context m, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)) => HasServer (QueryParam' mods sym a :> api :: Type) context m 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 -> EitherT ServantErr IO [Book]
        getBooksBy Nothing       = ...return all books...
        getBooksBy (Just author) = ...return books by the given author...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (QueryParam' mods sym a :> api) context m :: Type Source #

Methods

route :: MonadSnap m => Proxy (QueryParam' mods sym a :> api) -> Context context -> Delayed m env (Server (QueryParam' mods sym a :> api) context m) -> Router m env Source #

hoistServerWithContext :: proxy (QueryParam' mods sym a :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (QueryParam' mods sym a :> api) context m -> ServerT (QueryParam' mods sym a :> api) context n Source #

(KnownSymbol sym, FromHttpApiData a, HasServer api context m) => HasServer (QueryParams sym a :> api :: Type) context m 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] -> EitherT ServantErr IO [Book]
        getBooksBy authors = ...return all books by these authors...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (QueryParams sym a :> api) context m :: Type Source #

Methods

route :: MonadSnap m => Proxy (QueryParams sym a :> api) -> Context context -> Delayed m env (Server (QueryParams sym a :> api) context m) -> Router m env Source #

hoistServerWithContext :: proxy (QueryParams sym a :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (QueryParams sym a :> api) context m -> ServerT (QueryParams sym a :> api) context n Source #

(KnownSymbol sym, HasServer api context m) => HasServer (QueryFlag sym :> api :: Type) context m 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...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (QueryFlag sym :> api) context m :: Type Source #

Methods

route :: MonadSnap m => Proxy (QueryFlag sym :> api) -> Context context -> Delayed m env (Server (QueryFlag sym :> api) context m) -> Router m env Source #

hoistServerWithContext :: proxy (QueryFlag sym :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (QueryFlag sym :> api) context m -> ServerT (QueryFlag sym :> api) context n Source #

(KnownSymbol sym, FromHttpApiData a, HasServer api context m, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)) => HasServer (Header' mods sym a :> api :: Type) context m 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, 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
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Header' mods sym a :> api) context m :: Type Source #

Methods

route :: MonadSnap m => Proxy (Header' mods sym a :> api) -> Context context -> Delayed m env (Server (Header' mods sym a :> api) context m) -> Router m env Source #

hoistServerWithContext :: proxy (Header' mods sym a :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (Header' mods sym a :> api) context m -> ServerT (Header' mods sym a :> api) context n Source #

HasServer api context m => HasServer (IsSecure :> api :: Type) context m Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (IsSecure :> api) context m :: Type Source #

Methods

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

hoistServerWithContext :: proxy (IsSecure :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (IsSecure :> api) context m -> ServerT (IsSecure :> api) context n Source #

HasServer api ctx m => HasServer (Summary desc :> api :: Type) ctx m Source #

Ignore Summary in server handlers.

Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Summary desc :> api) ctx m :: Type Source #

Methods

route :: MonadSnap m => Proxy (Summary desc :> api) -> Context ctx -> Delayed m env (Server (Summary desc :> api) ctx m) -> Router m env Source #

hoistServerWithContext :: proxy (Summary desc :> api) -> proxy' ctx -> (forall x. m x -> n x) -> ServerT (Summary desc :> api) ctx m -> ServerT (Summary desc :> api) ctx n Source #

HasServer api ctx m => HasServer (Description desc :> api :: Type) ctx m Source #

Ignore Description in server handlers.

Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Description desc :> api) ctx m :: Type Source #

Methods

route :: MonadSnap m => Proxy (Description desc :> api) -> Context ctx -> Delayed m env (Server (Description desc :> api) ctx m) -> Router m env Source #

hoistServerWithContext :: proxy (Description desc :> api) -> proxy' ctx -> (forall x. m x -> n x) -> ServerT (Description desc :> api) ctx m -> ServerT (Description desc :> api) ctx n Source #

(FromHttpApiData a, HasServer api context m) => HasServer (Capture' mods capture a :> api :: Type) context m 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 -> EitherT ServantErr IO Book
        getBook isbn = ...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Capture' mods capture a :> api) context m :: Type Source #

Methods

route :: MonadSnap m => Proxy (Capture' mods capture a :> api) -> Context context -> Delayed m env (Server (Capture' mods capture a :> api) context m) -> Router m env Source #

hoistServerWithContext :: proxy (Capture' mods capture a :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (Capture' mods capture a :> api) context m -> ServerT (Capture' mods capture a :> api) context n Source #

(FromHttpApiData a, HasServer api context m) => HasServer (CaptureAll capture a :> api :: Type) context m Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (CaptureAll capture a :> api) context m :: Type Source #

Methods

route :: MonadSnap m => Proxy (CaptureAll capture a :> api) -> Context context -> Delayed m env (Server (CaptureAll capture a :> api) context m) -> Router m env Source #

hoistServerWithContext :: proxy (CaptureAll capture a :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (CaptureAll capture a :> api) context m -> ServerT (CaptureAll capture a :> api) context n Source #

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

Basic Authentication

Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (BasicAuth realm usr :> api) context m :: Type Source #

Methods

route :: MonadSnap m => Proxy (BasicAuth realm usr :> api) -> Context context -> Delayed m env (Server (BasicAuth realm usr :> api) context m) -> Router m env Source #

hoistServerWithContext :: proxy (BasicAuth realm usr :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (BasicAuth realm usr :> api) context m -> ServerT (BasicAuth realm usr :> api) context n Source #

HasServer api context m => HasServer (HttpVersion :> api :: Type) context m Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (HttpVersion :> api) context m :: Type Source #

Methods

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

hoistServerWithContext :: proxy (HttpVersion :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (HttpVersion :> api) context m -> ServerT (HttpVersion :> api) context n Source #

(KnownSymbol path, HasServer api context m) => HasServer (path :> api :: Type) context m Source #

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

Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (path :> api) context m :: Type Source #

Methods

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

hoistServerWithContext :: proxy (path :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (path :> api) context m -> ServerT (path :> api) context n Source #

(AllCTRender ctypes a, ReflectMethod method, KnownNat status, GetHeaders (Headers h a)) => HasServer (Verb method status ctypes (Headers h a) :: Type) context m Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Verb method status ctypes (Headers h a)) context m :: Type Source #

Methods

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

hoistServerWithContext :: proxy (Verb method status ctypes (Headers h a)) -> proxy' context -> (forall x. m x -> n x) -> ServerT (Verb method status ctypes (Headers h a)) context m -> ServerT (Verb method status ctypes (Headers h a)) context n Source #

(AllCTRender ctypes a, ReflectMethod method, KnownNat status) => HasServer (Verb method status ctypes a :: Type) context m Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Verb method status ctypes a) context m :: Type Source #

Methods

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

hoistServerWithContext :: proxy (Verb method status ctypes a) -> proxy' context -> (forall x. m x -> n x) -> ServerT (Verb method status ctypes a) context m -> ServerT (Verb method status ctypes a) context n Source #

(MimeRender ctype chunk, ReflectMethod method, MimeRender ctype a, KnownNat status, MonadSnap m, FramingRender framing, ToSourceIO chunk a, GetHeaders (Headers h a)) => HasServer (Stream method status framing ctype (Headers h a) :: Type) context m Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Stream method status framing ctype (Headers h a)) context m :: Type Source #

Methods

route :: MonadSnap m => Proxy (Stream method status framing ctype (Headers h a)) -> Context context -> Delayed m env (Server (Stream method status framing ctype (Headers h a)) context m) -> Router m env Source #

hoistServerWithContext :: proxy (Stream method status framing ctype (Headers h a)) -> proxy' context -> (forall x. m x -> n x) -> ServerT (Stream method status framing ctype (Headers h a)) context m -> ServerT (Stream method status framing ctype (Headers h a)) context n Source #

(MimeRender ctype chunk, ReflectMethod method, KnownNat status, FramingRender framing, MonadSnap m, ToSourceIO chunk a) => HasServer (Stream method status framing ctype a :: Type) context m Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Stream method status framing ctype a) context m :: Type Source #

Methods

route :: MonadSnap m => Proxy (Stream method status framing ctype a) -> Context context -> Delayed m env (Server (Stream method status framing ctype a) context m) -> Router m env Source #

hoistServerWithContext :: proxy (Stream method status framing ctype a) -> proxy' context -> (forall x. m x -> n x) -> ServerT (Stream method status framing ctype a) context m -> ServerT (Stream method status framing ctype a) context n Source #

type Server api context m = ServerT api context m Source #

Reexports

Basic functions and datatypes

Default error type

throwError :: MonadSnap m => ServantErr -> m a Source #

Terminate request handling with a ServantErr via finishWith

3XX

4XX

5XX