| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Servant.Server
Contents
Description
- serve :: HasServer api '[] => Proxy api -> Server api -> Application
 - serveWithContext :: HasServer api context => Proxy api -> Context context -> Server api -> Application
 - toApplication :: RoutingApplication -> Application
 - class HasServer api context where
 - type Server api = ServerT api Handler
 - type Handler = ExceptT ServantErr IO
 - layout :: HasServer api '[] => Proxy api -> Text
 - layoutWithContext :: HasServer api context => Proxy api -> Context context -> Text
 - enter :: Enter typ arg ret => arg -> typ -> ret
 - newtype m :~> n :: (* -> *) -> (* -> *) -> * = Nat {
- unNat :: forall a. m a -> n a
 
 - liftNat :: (MonadTrans t, Monad m) => (:~>) m (t m)
 - runReaderTNat :: r -> (:~>) (ReaderT * r m) m
 - evalStateTLNat :: Monad m => s -> (:~>) (StateT s m) m
 - evalStateTSNat :: Monad m => s -> (:~>) (StateT s m) m
 - logWriterTLNat :: MonadIO m => (w -> IO ()) -> (:~>) (WriterT w m) m
 - logWriterTSNat :: MonadIO m => (w -> IO ()) -> (:~>) (WriterT w m) m
 - hoistNat :: (MFunctor t, Monad m) => (:~>) m n -> (:~>) (t m) (t n)
 - embedNat :: (MMonad t, Monad n) => (:~>) m (t n) -> (:~>) (t m) (t n)
 - squashNat :: (Monad m, MMonad t) => (:~>) (t (t m)) (t m)
 - generalizeNat :: Applicative m => (:~>) Identity m
 - tweakResponse :: (RouteResult Response -> RouteResult Response) -> Router env -> Router env
 - data Context contextTypes where
- EmptyContext :: Context '[]
 - (:.) :: x -> Context xs -> Context (x ': xs)
 
 - class HasContextEntry context val where
 - data NamedContext name subContext = NamedContext (Context subContext)
 - descendIntoNamedContext :: forall context name subContext. HasContextEntry context (NamedContext name subContext) => Proxy (name :: Symbol) -> Context context -> Context subContext
 - newtype BasicAuthCheck usr = BasicAuthCheck {
- unBasicAuthCheck :: BasicAuthData -> IO (BasicAuthResult usr)
 
 - data BasicAuthResult usr
- = Unauthorized
 - | BadPassword
 - | NoSuchUser
 - | Authorized usr
 
 - data ServantErr = ServantErr {
- errHTTPCode :: Int
 - errReasonPhrase :: String
 - errBody :: ByteString
 - errHeaders :: [Header]
 
 - 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
 - type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived
 
Run a wai application from an API
serve :: HasServer api '[] => Proxy api -> Server api -> 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
serveWithContext :: HasServer api context => Proxy api -> Context context -> Server api -> Application Source #
Construct a wai Application from an API
Handlers for all standard combinators
class HasServer api context where Source #
Minimal complete definition
Instances
| HasServer * Raw context 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 context, HasServer * b context) => HasServer * ((:<|>) a b) context 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 = ...  | 
| (HasContextEntry context (NamedContext name subContext), HasServer * subApi subContext) => HasServer * (WithNamedContext name subContext subApi) context Source # | |
| (KnownSymbol realm, HasServer k1 api context, HasContextEntry context (BasicAuthCheck usr)) => HasServer * ((:>) * k1 (BasicAuth realm usr) api) context Source # | Basic Authentication  | 
| HasServer k1 api context => HasServer * ((:>) * k1 HttpVersion api) context Source # | |
| HasServer k1 api context => HasServer * ((:>) * k1 Vault api) context Source # | |
| HasServer k1 api context => HasServer * ((:>) * k1 IsSecure api) context Source # | |
| HasServer k1 api context => HasServer * ((:>) * k1 RemoteHost api) context Source # | |
| (AllCTUnrender list a, HasServer k1 api context) => HasServer * ((:>) * k1 (ReqBody * list a) api) context 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 -> Handler Book postBook book = ...insert into your db...  | 
| (KnownSymbol sym, HasServer k1 api context) => HasServer * ((:>) * k1 (QueryFlag sym) api) context Source # | If you use  Example: type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book] server :: Server MyApi server = getBooks where getBooks :: Bool -> Handler [Book] getBooks onlyPublished = ...return all books, or only the ones that are already published, depending on the argument...  | 
| (KnownSymbol sym, FromHttpApiData a, HasServer k1 api context) => HasServer * ((:>) * k1 (QueryParams * sym a) api) context 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] -> Handler [Book] getBooksBy authors = ...return all books by these authors...  | 
| (KnownSymbol sym, FromHttpApiData a, HasServer k1 api context) => HasServer * ((:>) * k1 (QueryParam * sym a) api) context 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 -> Handler [Book] getBooksBy Nothing = ...return all books... getBooksBy (Just author) = ...return books by the given author...  | 
| (KnownSymbol sym, FromHttpApiData a, HasServer k1 api context) => HasServer * ((:>) * k1 (Header sym a) api) context Source # | If you use  All it asks is for a  Example: newtype Referer = Referer Text deriving (Eq, Show, FromHttpApiData) -- GET /view-my-referer type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get '[JSON] Referer server :: Server MyApi server = viewReferer where viewReferer :: Referer -> Handler referer viewReferer referer = return referer  | 
| (KnownSymbol capture, FromHttpApiData a, HasServer k1 sublayout context) => HasServer * ((:>) * k1 (CaptureAll * capture a) sublayout) context Source # | If you use  You can control how they'll be converted from  Example: type MyApi = "src" :> CaptureAll "segments" Text :> Get '[JSON] SourceFile server :: Server MyApi server = getSourceFile where getSourceFile :: [Text] -> Handler Book getSourceFile pathSegments = ...  | 
| (KnownSymbol capture, FromHttpApiData a, HasServer k1 api context) => HasServer * ((:>) * k1 (Capture * capture a) api) context 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 -> Handler Book getBook isbn = ...  | 
| (KnownSymbol path, HasServer k1 api context) => HasServer * ((:>) Symbol k1 path api) context 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 Source # | |
| (AllCTRender ctypes a, ReflectMethod k1 method, KnownNat status) => HasServer * (Verb k1 * method status ctypes a) context Source # | |
Debugging the server layout
layout :: HasServer api '[] => Proxy api -> Text Source #
The function layout produces a textual description of the internal router layout for debugging purposes. Note that the router layout is determined just by the API, not by the handlers.
Example:
For the following API
type API = "a" :> "d" :> Get '[JSON] NoContent :<|> "b" :> Capture "x" Int :> Get '[JSON] Bool :<|> "c" :> Put '[JSON] Bool :<|> "a" :> "e" :> Get '[JSON] Int :<|> "b" :> Capture "x" Int :> Put '[JSON] Bool :<|> Raw
we get the following output:
/ ├─ a/ │ ├─ d/ │ │ └─• │ └─ e/ │ └─• ├─ b/ │ └─ <capture>/ │ ├─• │ ┆ │ └─• ├─ c/ │ └─• ┆ └─ <raw>
Explanation of symbols:
├- Normal lines reflect static branching via a table.
 a/- Nodes reflect static path components.
 ─•- Leaves reflect endpoints.
 <capture>/- This is a delayed capture of a path component.
 <raw>- This is a part of the API we do not know anything about.
 ┆- Dashed lines suggest a dynamic choice between the part above and below. If there is a success for fatal failure in the first part, that one takes precedence. If both parts fail, the "better" error code will be returned.
 
Enter
Sometimes our cherished ExceptT 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
newtype m :~> n :: (* -> *) -> (* -> *) -> * #
A natural transformation from m to n. Used to enter particular datatypes.
Nat utilities
runReaderTNat :: r -> (:~>) (ReaderT * r m) m #
evalStateTLNat :: Monad m => s -> (:~>) (StateT s m) m #
evalStateTSNat :: Monad m => s -> (:~>) (StateT s m) m #
logWriterTLNat :: MonadIO m => (w -> IO ()) -> (:~>) (WriterT w m) m #
Like logWriterTSNat, but for strict WriterT.
logWriterTSNat :: MonadIO m => (w -> IO ()) -> (:~>) (WriterT w m) m #
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
generalizeNat :: Applicative m => (:~>) Identity m #
Like mmorph's generalize.
tweakResponse :: (RouteResult Response -> RouteResult Response) -> Router env -> Router env Source #
Apply a transformation to the response of a Router.
Context
data Context contextTypes where Source #
Contexts are used to pass values to combinators. (They are not meant to be used to pass parameters to your handlers, i.e. they should not replace any custom ReaderT-monad-stack that you're using with Enter.) If you don't use combinators that require any context entries, you can just use serve as always.
If you are using combinators that require a non-empty Context you have to use serveWithContext and pass it a Context that contains all the values your combinators need. A Context is essentially a heterogenous list and accessing the elements is being done by type (see getContextEntry). The parameter of the type Context is a type-level list reflecting the types of the contained context entries. To create a Context with entries, use the operator (::.)
>>>:type True :. () :. EmptyContextTrue :. () :. EmptyContext :: Context '[Bool, ()]
Constructors
| EmptyContext :: Context '[] | |
| (:.) :: x -> Context xs -> Context (x ': xs) infixr 5 | 
class HasContextEntry context val where Source #
This class is used to access context entries in Contexts. getContextEntry returns the first value where the type matches:
>>>getContextEntry (True :. False :. EmptyContext) :: BoolTrue
If the Context does not contain an entry of the requested type, you'll get an error:
>>>getContextEntry (True :. False :. EmptyContext) :: String... ...No instance for (HasContextEntry '[] [Char]) ...
Minimal complete definition
Methods
getContextEntry :: Context context -> val Source #
Instances
| HasContextEntry ((:) * val xs) val Source # | |
| HasContextEntry xs val => HasContextEntry ((:) * notIt xs) val Source # | |
NamedContext
data NamedContext name subContext Source #
Normally context entries are accessed by their types. In case you need to have multiple values of the same type in your Context and need to access them, we provide NamedContext. You can think of it as sub-namespaces for Contexts.
Constructors
| NamedContext (Context subContext) | 
descendIntoNamedContext :: forall context name subContext. HasContextEntry context (NamedContext name subContext) => Proxy (name :: Symbol) -> Context context -> Context subContext Source #
descendIntoNamedContext allows you to access NamedContexts. Usually you won't have to use it yourself but instead use a combinator like WithNamedContext.
This is how descendIntoNamedContext works:
>>>:set -XFlexibleContexts>>>let subContext = True :. EmptyContext>>>:type subContextsubContext :: Context '[Bool]>>>let parentContext = False :. (NamedContext subContext :: NamedContext "subContext" '[Bool]) :. EmptyContext>>>:type parentContextparentContext :: Context '[Bool, NamedContext "subContext" '[Bool]]>>>descendIntoNamedContext (Proxy :: Proxy "subContext") parentContext :: Context '[Bool]True :. EmptyContext
Basic Authentication
newtype BasicAuthCheck usr Source #
Datatype wrapping a function used to check authentication.
Constructors
| BasicAuthCheck | |
Fields 
  | |
Instances
| Functor BasicAuthCheck Source # | |
| Generic (BasicAuthCheck usr) Source # | |
| type Rep (BasicAuthCheck usr) Source # | |
data BasicAuthResult usr Source #
servant-server's current implementation of basic authentication is not immune to certian kinds of timing attacks. Decoding payloads does not take a fixed amount of time.
The result of authentication/authorization
Constructors
| Unauthorized | |
| BadPassword | |
| NoSuchUser | |
| Authorized usr | 
Instances
| Functor BasicAuthResult Source # | |
| Eq usr => Eq (BasicAuthResult usr) Source # | |
| Read usr => Read (BasicAuthResult usr) Source # | |
| Show usr => Show (BasicAuthResult usr) Source # | |
| Generic (BasicAuthResult usr) Source # | |
| type Rep (BasicAuthResult usr) Source # | |
General Authentication
Default error type
data ServantErr Source #
Constructors
| ServantErr | |
Fields 
  | |
Instances
3XX
err300 :: ServantErr Source #
err300 Multiple Choices
Example:
failingHandler :: Handler () failingHandler = throwError $ err300 { errBody = "I can't choose." }err301 :: ServantErr Source #
err302 :: ServantErr Source #
err303 :: ServantErr Source #
err304 :: ServantErr Source #
err305 :: ServantErr Source #
err307 :: ServantErr Source #
4XX
err400 :: ServantErr Source #
err400 Bad Request
Example:
failingHandler :: Handler () failingHandler = throwError $ err400 { errBody = "Your request makes no sense to me." }err401 :: ServantErr Source #
err401 Unauthorized
Example:
failingHandler :: Handler () failingHandler = throwError $ err401 { errBody = "Your credentials are invalid." }err402 :: ServantErr Source #
err402 Payment Required
Example:
failingHandler :: Handler () failingHandler = throwError $ err402 { errBody = "You have 0 credits. Please give me $$$." }err403 :: ServantErr Source #
err403 Forbidden
Example:
failingHandler :: Handler () failingHandler = throwError $ err403 { errBody = "Please login first." }err404 :: ServantErr Source #
err404 Not Found
Example:
failingHandler :: Handler () failingHandler = throwError $ err404 { errBody = "(╯°□°)╯︵ ┻━┻)." }err405 :: ServantErr Source #
err405 Method Not Allowed
Example:
failingHandler :: Handler () failingHandler = throwError $ err405 { errBody = "Your account privileges does not allow for this. Please pay $$$." }err406 :: ServantErr Source #
err407 :: ServantErr Source #
err407 Proxy Authentication Required
Example:
failingHandler :: Handler () failingHandler = throwError err407
err409 :: ServantErr Source #
err409 Conflict
Example:
failingHandler :: Handler () failingHandler = throwError $ err409 { errBody = "Transaction conflicts with 59879cb56c7c159231eeacdd503d755f7e835f74" }err410 :: ServantErr Source #
err410 Gone
Example:
failingHandler :: Handler () failingHandler = throwError $ err410 { errBody = "I know it was here at some point, but.. I blame bad luck." }err411 :: ServantErr Source #
err412 :: ServantErr Source #
err412 Precondition Failed
Example:
failingHandler :: Handler () failingHandler = throwError $ err412 { errBody = "Precondition fail: x < 42 && y > 57" }err413 :: ServantErr Source #
err413 Request Entity Too Large
Example:
failingHandler :: Handler () failingHandler = throwError $ err413 { errBody = "Request exceeded 64k." }err414 :: ServantErr Source #
err414 Request-URI Too Large
Example:
failingHandler :: Handler () failingHandler = throwError $ err414 { errBody = "Maximum length is 64." }err415 :: ServantErr Source #
err415 Unsupported Media Type
Example:
failingHandler :: Handler () failingHandler = throwError $ err415 { errBody = "Supported media types: gif, png" }err416 :: ServantErr Source #
err416 Request range not satisfiable
Example:
failingHandler :: Handler () failingHandler = throwError $ err416 { errBody = "Valid range is [0, 424242]." }err417 :: ServantErr Source #
err417 Expectation Failed
Example:
failingHandler :: Handler () failingHandler = throwError $ err417 { errBody = "I found a quux in the request. This isn't going to work." }5XX
err500 :: ServantErr Source #
err500 Internal Server Error
Example:
failingHandler :: Handler () failingHandler = throwError $ err500 { errBody = "Exception in module A.B.C:55. Have a great day!" }err501 :: ServantErr Source #
err501 Not Implemented
Example:
failingHandler :: Handler () failingHandler = throwError $ err501 { errBody = "/v1/foo is not supported with quux in the request." }err502 :: ServantErr Source #
err502 Bad Gateway
Example:
failingHandler :: Handler () failingHandler = throwError $ err502 { errBody = "Tried gateway foo, bar, and baz. None responded." }err503 :: ServantErr Source #
err503 Service Unavailable
Example:
failingHandler :: Handler () failingHandler = throwError $ err503 { errBody = "We're rewriting in PHP." }err504 :: ServantErr Source #
err504 Gateway Time-out
Example:
failingHandler :: Handler () failingHandler = throwError $ err504 { errBody = "Backend foobar did not respond in 5 seconds." }err505 :: ServantErr Source #
err505 HTTP Version not supported
Example usage:
failingHandler :: Handler () failingHandler = throwError $ err505 { errBody = "I support HTTP/4.0 only." }Re-exports
type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived #
The WAI application.
Note that, since WAI 3.0, this type is structured in continuation passing style to allow for proper safe resource handling. This was handled in the past via other means (e.g., ResourceT). As a demonstration:
app :: Application app req respond = bracket_ (putStrLn "Allocating scarce resource") (putStrLn "Cleaning up") (respond $ responseLBS status200 [] "Hello World")