Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module lets you implement Server
s for defined APIs. You'll
most likely just need serve
.
- serveSnap :: forall layout m. (HasServer layout '[] m, MonadSnap m) => Proxy layout -> Server layout '[] m -> m ()
- serveSnapWithContext :: forall layout context m. (HasServer layout context m, MonadSnap m) => Proxy layout -> Context context -> Server layout context m -> m ()
- class HasServer api context (m :: * -> *) where
- type Server api context m = ServerT api context m
- module Servant.Server.Internal.BasicAuth
- module Servant.Server.Internal.Context
- data ServantErr = ServantErr {
- errHTTPCode :: Int
- errReasonPhrase :: String
- errBody :: ByteString
- errHeaders :: [Header]
- throwError :: MonadSnap m => ServantErr -> m a
- err300 :: ServantErr
- err301 :: ServantErr
- err302 :: ServantErr
- err303 :: ServantErr
- err304 :: ServantErr
- err305 :: ServantErr
- err307 :: ServantErr
- err400 :: ServantErr
- err401 :: ServantErr
- err402 :: ServantErr
- err403 :: ServantErr
- err404 :: ServantErr
- err405 :: ServantErr
- err406 :: ServantErr
- err407 :: ServantErr
- err409 :: ServantErr
- err410 :: ServantErr
- err411 :: ServantErr
- err412 :: ServantErr
- err413 :: ServantErr
- err414 :: ServantErr
- err415 :: ServantErr
- err416 :: ServantErr
- err417 :: ServantErr
- err500 :: ServantErr
- err501 :: ServantErr
- err502 :: ServantErr
- err503 :: ServantErr
- err504 :: ServantErr
- err505 :: ServantErr
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 #
route :: MonadSnap m => Proxy api -> Context context -> Delayed m env (Server api context m) -> Router m env Source #
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" |
(HasServer * a ctx m, HasServer * b ctx m) => HasServer * ((:<|>) a b) ctx m Source # | A server for 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 = ... |
(HasServer k1 api context m, KnownSymbol realm, HasContextEntry context (BasicAuthCheck m usr)) => HasServer * ((:>) * k1 (BasicAuth realm usr) api) context m Source # | |
HasServer k1 api context m => HasServer * ((:>) * k1 RemoteHost api) context m Source # | |
HasServer k1 api context m => HasServer * ((:>) * k1 IsSecure api) context m Source # | |
HasServer k1 api context m => HasServer * ((:>) * k1 HttpVersion api) context m Source # | |
(AllCTUnrender list a, HasServer k1 sublayout context m) => HasServer * ((:>) * k1 (ReqBody * list a) sublayout) context m Source # | If you use All it asks is for a 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 k1 sublayout context m) => HasServer * ((:>) * k1 (QueryFlag sym) sublayout) context m Source # | If you use 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, FromHttpApiData a, HasServer k1 sublayout context m) => HasServer * ((:>) * k1 (QueryParams * sym a) sublayout) context m Source # | If you use This lets servant worry about looking up 0 or more values in the query string
associated to You can control how the individual values are converted from 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, FromHttpApiData a, HasServer k1 sublayout context m) => HasServer * ((:>) * k1 (QueryParam * sym a) sublayout) context m Source # | If you use 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 You can control how it'll be converted from 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, FromHttpApiData a, HasServer k1 sublayout context m) => HasServer * ((:>) * k1 (Header sym a) sublayout) context m Source # | If you use All it asks is for a 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 |
(FromHttpApiData a, HasServer k1 sublayout context m) => HasServer * ((:>) * k1 (CaptureAll * capture a) sublayout) context m Source # | |
(FromHttpApiData a, HasServer k1 sublayout context m) => HasServer * ((:>) * k1 (Capture * capture a) sublayout) context m Source # | If you use You can control how it'll be converted from 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 k1 sublayout context m) => HasServer * ((:>) Symbol k1 path sublayout) context m Source # | Make sure the incoming request starts with |
(AllCTRender ctypes a, ReflectMethod k1 method, KnownNat status, GetHeaders (Headers h a)) => HasServer * (Verb k1 * method status ctypes (Headers h a)) context m Source # | |
(AllCTRender ctypes a, ReflectMethod k1 method, KnownNat status) => HasServer * (Verb k1 * method status ctypes a) context m Source # | |
Reexports
Basic functions and datatypes
Default error type
data ServantErr Source #
ServantErr | |
|
throwError :: MonadSnap m => ServantErr -> m a Source #
Terminate request handling with a ServantErr
via finishWith
3XX
err300 :: ServantErr Source #
err301 :: ServantErr Source #
err302 :: ServantErr Source #
err303 :: ServantErr Source #
err304 :: ServantErr Source #
err305 :: ServantErr Source #
err307 :: ServantErr Source #
4XX
err400 :: ServantErr Source #
err401 :: ServantErr Source #
err402 :: ServantErr Source #
err403 :: ServantErr Source #
err404 :: ServantErr Source #
err405 :: ServantErr Source #
err406 :: ServantErr Source #
err407 :: ServantErr Source #
err409 :: ServantErr Source #
err410 :: ServantErr Source #
err411 :: ServantErr Source #
err412 :: ServantErr Source #
err413 :: ServantErr Source #
err414 :: ServantErr Source #
err415 :: ServantErr Source #
err416 :: ServantErr Source #
err417 :: ServantErr Source #
5XX
err500 :: ServantErr Source #
err501 :: ServantErr Source #
err502 :: ServantErr Source #
err503 :: ServantErr Source #
err504 :: ServantErr Source #
err505 :: ServantErr Source #