| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Servant.Server.Internal
Contents
- class HasServer api where
- type Server api m = ServerT api m
- captured :: FromHttpApiData a => proxy (Capture sym a) -> Text -> Maybe a
- allowedMethodHead :: Method -> Request -> Bool
- allowedMethod :: Method -> Request -> Bool
- processMethodRouter :: Maybe (ByteString, ByteString) -> Status -> Method -> Maybe [(HeaderName, ByteString)] -> Request -> RouteResult Response
- methodCheck :: MonadSnap m => Method -> Request -> DelayedM m ()
- acceptCheck :: (AllMime list, MonadSnap m) => Proxy list -> ByteString -> DelayedM m ()
- methodRouter :: (AllCTRender ctypes a, MonadSnap m) => Method -> Proxy ctypes -> Status -> Delayed m env (m a) -> Router m env
- methodRouterHeaders :: (GetHeaders (Headers h v), AllCTRender ctypes v, MonadSnap m) => Method -> Proxy ctypes -> Status -> Delayed m env (m (Headers h v)) -> Router m env
- ct_wildcard :: ByteString
- module Servant.Server.Internal.PathInfo
- module Servant.Server.Internal.Router
- module Servant.Server.Internal.RoutingApplication
- module Servant.Server.Internal.ServantErr
Documentation
class HasServer api where Source #
Minimal complete definition
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 = ... |
| HasServer k api => HasServer * ((:>) k * RemoteHost api) Source # | |
| HasServer k api => HasServer * ((:>) k * IsSecure api) Source # | |
| HasServer k api => HasServer * ((:>) k * HttpVersion api) Source # | |
| (KnownSymbol path, HasServer k sublayout) => HasServer * ((:>) k Symbol path sublayout) Source # | Make sure the incoming request starts with |
| (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 * (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, FromHttpApiData 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, FromHttpApiData 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, FromHttpApiData 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 |
| (FromHttpApiData a, HasServer k sublayout) => HasServer * ((:>) k * (CaptureAll * capture a) sublayout) Source # | |
| (FromHttpApiData 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 = ... |
| (AllCTRender ctypes a, ReflectMethod k1 method, KnownNat status, GetHeaders (Headers h a)) => HasServer * (Verb * k1 method status ctypes (Headers h a)) Source # | |
| (AllCTRender ctypes a, ReflectMethod k1 method, KnownNat status) => HasServer * (Verb * k1 method status ctypes a) Source # | |
Instances
processMethodRouter :: Maybe (ByteString, ByteString) -> Status -> Method -> Maybe [(HeaderName, ByteString)] -> Request -> RouteResult Response 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 #