| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Servant.Server
Contents
Description
- serve :: HasServer layout `[]` => Proxy layout -> Server layout -> Application
- serveWithContext :: HasServer layout context => Proxy layout -> Context context -> Server layout -> Application
- toApplication :: RoutingApplication -> Application
- class HasServer layout context where
- type Server layout = ServerT layout (ExceptT ServantErr IO)
- 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 -> Router
- data Context contextTypes where
- EmptyContext :: Context `[]`
- (:.) :: x -> Context xs -> Context (x : xs)
- class HasContextEntry context val where
- getContextEntry :: Context context -> val
- 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
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 appserveWithContext :: HasServer layout context => Proxy layout -> Context context -> Server layout -> Application Source
Construct a wai Application from an API
Handlers for all standard combinators
class HasServer layout context where Source
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 k api context, HasContextEntry context (BasicAuthCheck usr)) => HasServer * ((:>) * k (BasicAuth realm usr) api) context Source | Basic Authentication |
| HasServer k api context => HasServer * ((:>) * k HttpVersion api) context Source | |
| HasServer k api context => HasServer * ((:>) * k Vault api) context Source | |
| HasServer k api context => HasServer * ((:>) * k IsSecure api) context Source | |
| HasServer k api context => HasServer * ((:>) * k RemoteHost api) context Source | |
| (AllCTUnrender list a, HasServer k sublayout context) => HasServer * ((:>) * k (ReqBody * list a) sublayout) 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 -> ExceptT ServantErr IO Book
postBook book = ...insert into your db... |
| (KnownSymbol sym, HasServer k sublayout context) => HasServer * ((:>) * k (QueryFlag sym) sublayout) context Source | If you use Example: type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book]
server :: Server MyApi
server = getBooks
where getBooks :: Bool -> ExceptT 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 k sublayout context) => HasServer * ((:>) * k (QueryParams * sym a) sublayout) 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] -> ExceptT ServantErr IO [Book]
getBooksBy authors = ...return all books by these authors... |
| (KnownSymbol sym, FromHttpApiData a, HasServer k sublayout context) => HasServer * ((:>) * k (QueryParam * sym a) sublayout) 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 -> ExceptT ServantErr IO [Book]
getBooksBy Nothing = ...return all books...
getBooksBy (Just author) = ...return books by the given author... |
| (KnownSymbol sym, FromHttpApiData a, HasServer k sublayout context) => HasServer * ((:>) * k (Header sym a) sublayout) context Source | If you use All it asks is for a Example: newtype Referer = Referer Text
deriving (Eq, Show, FromHttpApiData, ToText)
-- GET /view-my-referer
type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get '[JSON] Referer
server :: Server MyApi
server = viewReferer
where viewReferer :: Referer -> ExceptT ServantErr IO referer
viewReferer referer = return referer |
| (KnownSymbol capture, FromHttpApiData a, HasServer k sublayout context) => HasServer * ((:>) * k (Capture * capture a) sublayout) 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 -> ExceptT ServantErr IO Book
getBook isbn = ... |
| (KnownSymbol path, HasServer k sublayout context) => HasServer * ((:>) Symbol k path sublayout) context Source | Make sure the incoming request starts with |
| (AllCTRender ctypes a, ReflectMethod k method, KnownNat status, GetHeaders (Headers h a)) => HasServer * (Verb k * method status ctypes (Headers h a)) context Source | |
| (AllCTRender ctypes a, ReflectMethod k method, KnownNat status) => HasServer * (Verb k * method status ctypes a) context Source |
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
A natural transformation from m to n. Used to enter particular
datatypes.
Nat utilities
runReaderTNat :: r -> ReaderT r m :~> m Source
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
generalizeNat :: Applicative m => Identity :~> m Source
Like mmorph's generalize.
tweakResponse :: (RouteResult Response -> RouteResult Response) -> Router -> Router 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]) ...
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
| |