servant-snap-0.8.1: A family of combinators for defining webservices APIs and serving them

Safe HaskellNone
LanguageHaskell2010

Servant.Server.Internal

Contents

Synopsis

Documentation

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

Minimal complete definition

route

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 #

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"

Associated Types

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

Methods

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

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

Associated Types

type ServerT (a :<|> b) (ctx :: a :<|> b) (m :: [*]) (m :: * -> *) :: * Source #

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

type ServerT ((* :> k1) RemoteHost api) (context :: (* :> k1) RemoteHost api) (m :: [*]) (m :: * -> *) :: * Source #

Methods

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

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

Associated Types

type ServerT ((* :> k1) IsSecure api) (context :: (* :> k1) IsSecure api) (m :: [*]) (m :: * -> *) :: * Source #

Methods

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

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

Associated Types

type ServerT ((* :> k1) HttpVersion api) (context :: (* :> k1) HttpVersion api) (m :: [*]) (m :: * -> *) :: * Source #

Methods

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

(AllCTUnrender list a, HasServer k1 sublayout context m) => HasServer * ((:>) * k1 (ReqBody * list a) sublayout) 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. 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...

Associated Types

type ServerT ((* :> k1) (ReqBody * list a) sublayout) (context :: (* :> k1) (ReqBody * list a) sublayout) (m :: [*]) (m :: * -> *) :: * Source #

Methods

route :: MonadSnap m => Proxy ((* :> k1) (ReqBody * list a) sublayout) context -> Context m -> Delayed m env (Server ((* :> k1) (ReqBody * list a) sublayout) context m m) -> Router m env Source #

(KnownSymbol sym, HasServer k1 sublayout context m) => HasServer * ((:>) * k1 (QueryFlag sym) sublayout) 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...

Associated Types

type ServerT ((* :> k1) (QueryFlag sym) sublayout) (context :: (* :> k1) (QueryFlag sym) sublayout) (m :: [*]) (m :: * -> *) :: * Source #

Methods

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

(KnownSymbol sym, FromHttpApiData a, HasServer k1 sublayout context m) => HasServer * ((:>) * k1 (QueryParams * sym a) sublayout) 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 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...

Associated Types

type ServerT ((* :> k1) (QueryParams * sym a) sublayout) (context :: (* :> k1) (QueryParams * sym a) sublayout) (m :: [*]) (m :: * -> *) :: * Source #

Methods

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

(KnownSymbol sym, FromHttpApiData a, HasServer k1 sublayout context m) => HasServer * ((:>) * k1 (QueryParam * sym a) sublayout) 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 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...

Associated Types

type ServerT ((* :> k1) (QueryParam * sym a) sublayout) (context :: (* :> k1) (QueryParam * sym a) sublayout) (m :: [*]) (m :: * -> *) :: * Source #

Methods

route :: MonadSnap m => Proxy ((* :> k1) (QueryParam * sym a) sublayout) context -> Context m -> Delayed m env (Server ((* :> k1) (QueryParam * sym a) sublayout) context m m) -> Router m env Source #

(KnownSymbol sym, FromHttpApiData a, HasServer k1 sublayout context m) => HasServer * ((:>) * k1 (Header sym a) sublayout) 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 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

Associated Types

type ServerT ((* :> k1) (Header sym a) sublayout) (context :: (* :> k1) (Header sym a) sublayout) (m :: [*]) (m :: * -> *) :: * Source #

Methods

route :: MonadSnap m => Proxy ((* :> k1) (Header sym a) sublayout) context -> Context m -> Delayed m env (Server ((* :> k1) (Header sym a) sublayout) context m m) -> Router m env Source #

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

Associated Types

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

Methods

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

(FromHttpApiData a, HasServer k1 sublayout context m) => HasServer * ((:>) * k1 (Capture * capture a) sublayout) 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 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 = ...

Associated Types

type ServerT ((* :> k1) (Capture * capture a) sublayout) (context :: (* :> k1) (Capture * capture a) sublayout) (m :: [*]) (m :: * -> *) :: * Source #

Methods

route :: MonadSnap m => Proxy ((* :> k1) (Capture * capture a) sublayout) context -> Context m -> Delayed m env (Server ((* :> k1) (Capture * capture a) sublayout) context m m) -> Router m env Source #

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

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

Associated Types

type ServerT ((Symbol :> k1) path sublayout) (context :: (Symbol :> k1) path sublayout) (m :: [*]) (m :: * -> *) :: * Source #

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Instances

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

acceptCheck :: (AllMime list, MonadSnap m) => Proxy list -> ByteString -> DelayedM m () Source #

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

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

data BasicAuthResult usr Source #

Instances

Functor BasicAuthResult Source # 

Methods

fmap :: (a -> b) -> BasicAuthResult a -> BasicAuthResult b #

(<$) :: a -> BasicAuthResult b -> BasicAuthResult a #

Eq usr => Eq (BasicAuthResult usr) Source # 
Read usr => Read (BasicAuthResult usr) Source # 
Show usr => Show (BasicAuthResult usr) Source # 
Generic (BasicAuthResult usr) Source # 

Associated Types

type Rep (BasicAuthResult usr) :: * -> * #

Methods

from :: BasicAuthResult usr -> Rep (BasicAuthResult usr) x #

to :: Rep (BasicAuthResult usr) x -> BasicAuthResult usr #

type Rep (BasicAuthResult usr) Source # 
type Rep (BasicAuthResult usr) = D1 * (MetaData "BasicAuthResult" "Servant.Server.Internal" "servant-snap-0.8.1-CfjhSxc4SFC8Vc95tNVfo" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Unauthorized" PrefixI False) (U1 *)) (C1 * (MetaCons "BadPassword" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NoSuchUser" PrefixI False) (U1 *)) (C1 * (MetaCons "Authorized" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * usr)))))