Safe Haskell | None |
---|---|
Language | Haskell2010 |
- class HasServer api context where
- type Server api = ServerT api Handler
- allowedMethodHead :: Method -> Request -> Bool
- allowedMethod :: Method -> Request -> Bool
- methodCheck :: Method -> Request -> DelayedIO ()
- acceptCheck :: AllMime list => Proxy list -> ByteString -> DelayedIO ()
- methodRouter :: AllCTRender ctypes a => (b -> ([(HeaderName, ByteString)], a)) -> Method -> Proxy ctypes -> Status -> Delayed env (Handler b) -> Router env
- data EmptyServer = EmptyServer
- emptyServer :: ServerT EmptyAPI m
- ct_wildcard :: ByteString
- module Servant.Server.Internal.BasicAuth
- module Servant.Server.Internal.Context
- module Servant.Server.Internal.Handler
- module Servant.Server.Internal.Router
- module Servant.Server.Internal.RoutingApplication
- module Servant.Server.Internal.ServantErr
Documentation
class HasServer api context where Source #
route :: Proxy api -> Context context -> Delayed env (Server api) -> Router env Source #
hoistServerWithContext :: Proxy api -> Proxy context -> (forall x. m x -> n x) -> ServerT api m -> ServerT api n Source #
HasServer * EmptyAPI context Source # | The server for an type MyApi = "nothing" :> EmptyApi server :: Server MyApi server = emptyAPIServer |
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 ctx => HasServer * ((:>) k * (Description desc) api) ctx Source # | Ignore |
HasServer k api ctx => HasServer * ((:>) k * (Summary desc) api) ctx Source # | Ignore |
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 # | |
(KnownSymbol path, HasServer k api context) => HasServer * ((:>) k Symbol path api) context Source # | Make sure the incoming request starts with |
(AllCTUnrender list a, HasServer k api context) => HasServer * ((:>) k * (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 k api context) => HasServer * ((:>) k * (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 k api context) => HasServer * ((:>) k * (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 k api context) => HasServer * ((:>) k * (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 k api context) => HasServer * ((:>) k * (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 k api context) => HasServer * ((:>) k * (CaptureAll * capture a) api) 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 k api context) => HasServer * ((:>) k * (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 = ... |
(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 # | |
Instances
acceptCheck :: AllMime list => Proxy list -> ByteString -> DelayedIO () Source #
methodRouter :: AllCTRender ctypes a => (b -> ([(HeaderName, ByteString)], a)) -> Method -> Proxy ctypes -> Status -> Delayed env (Handler b) -> Router env Source #
data EmptyServer Source #
Singleton type representing a server that serves an empty API.