| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Servant.Server
Contents
Description
- serve :: HasServer layout => Proxy layout -> Server layout -> Application
- toApplication :: RoutingApplication -> Application
- class HasServer layout where
- type ServerT layout m :: *
- route :: Proxy layout -> Server layout -> RoutingApplication
- type Server layout = ServerT layout (EitherT 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
- fromExceptT :: ExceptT e m :~> EitherT e 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
- 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 appConstruct a wai Application from an API
Handlers for all standard combinators
class HasServer layout where Source
Methods
route :: Proxy layout -> Server layout -> RoutingApplication Source
Instances
| HasServer * Raw 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, HasServer * b) => HasServer * ((:<|>) a b) 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 = ... |
| (GetHeaders (Headers h v), AllCTRender ctypes v) => HasServer * (Get ctypes (Headers h v)) Source | |
| HasServer * (Get ctypes ()) Source | |
| AllCTRender ctypes a => HasServer * (Get ctypes a) Source | When implementing the handler for a If successfully returning a value, we use the type-level list, combined
with the request's |
| (GetHeaders (Headers h v), AllCTRender ctypes v) => HasServer * (Post ctypes (Headers h v)) Source | |
| HasServer * (Post ctypes ()) Source | |
| AllCTRender ctypes a => HasServer * (Post ctypes a) Source | When implementing the handler for a If successfully returning a value, we use the type-level list, combined
with the request's |
| (GetHeaders (Headers h v), AllCTRender ctypes v) => HasServer * (Delete ctypes (Headers h v)) Source | |
| HasServer * (Delete ctypes ()) Source | |
| AllCTRender ctypes a => HasServer * (Delete ctypes a) Source | If you have a The code of the handler will, just like
for |
| (GetHeaders (Headers h v), AllCTRender ctypes v) => HasServer * (Put ctypes (Headers h v)) Source | |
| HasServer * (Put ctypes ()) Source | |
| AllCTRender ctypes a => HasServer * (Put ctypes a) Source | When implementing the handler for a If successfully returning a value, we use the type-level list, combined
with the request's |
| (GetHeaders (Headers h v), AllCTRender ctypes v) => HasServer * (Patch ctypes (Headers h v)) Source | |
| HasServer * (Patch ctypes ()) Source | |
| AllCTRender ctypes a => HasServer * (Patch ctypes a) Source | When implementing the handler for a If successfully returning a value, we just require that its type has
a |
| (AllCTUnrender list a, HasServer k sublayout) => HasServer * ((:>) * k (ReqBody * list a) sublayout) 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 k sublayout) => HasServer * ((:>) * k (MatrixFlag sym) sublayout) Source | If you use Example: type MyApi = "books" :> MatrixFlag "published" :> Get [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, FromText a, HasServer k sublayout) => HasServer * ((:>) * k (MatrixParams * sym a) sublayout) 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" :> MatrixParams "authors" Text :> Get [Book]
server :: Server MyApi
server = getBooksBy
where getBooksBy :: [Text] -> EitherT ServantErr IO [Book]
getBooksBy authors = ...return all books by these authors... |
| (KnownSymbol sym, FromText a, HasServer k sublayout) => HasServer * ((:>) * k (MatrixParam * sym a) sublayout) 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" :> MatrixParam "author" Text :> Get [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, HasServer k sublayout) => HasServer * ((:>) * k (QueryFlag sym) sublayout) 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, FromText a, HasServer k sublayout) => HasServer * ((:>) * k (QueryParams * sym a) sublayout) 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, FromText a, HasServer k sublayout) => HasServer * ((:>) * k (QueryParam * sym a) sublayout) 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, FromText a, HasServer k sublayout) => HasServer * ((:>) * k (Header sym a) sublayout) 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 |
| (KnownSymbol capture, FromText a, HasServer k sublayout) => HasServer * ((:>) * k (Capture * capture a) sublayout) 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 k sublayout) => HasServer * ((:>) Symbol k path sublayout) Source | Make sure the incoming request starts with |
Enter
Sometimes our cherished EitherT 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
fromExceptT :: ExceptT e m :~> EitherT e m Source
Functions based on mmorph
generalizeNat :: Applicative m => Identity :~> m Source
Like mmorph's generalize.
Default error type
data ServantErr Source
Constructors
| ServantErr | |
Fields
| |
Instances