Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module lets you implement Server
s for defined APIs. You'll
most likely just need serve
.
Synopsis
- serveSnap :: forall layout m. (HasServer layout '[] m, MonadSnap m) => Proxy layout -> Server layout '[] m -> m ()
- serveSnapWithContext :: forall layout context m. (HasServer layout context m, MonadSnap m) => Proxy layout -> Context context -> Server layout context m -> m ()
- class HasServer api context (m :: * -> *) where
- type Server api context m = ServerT api context m
- module Servant.Server.Internal.BasicAuth
- module Servant.Server.Internal.Context
- data ServantErr = ServantErr {
- errHTTPCode :: Int
- errReasonPhrase :: String
- errBody :: ByteString
- errHeaders :: [Header]
- throwError :: MonadSnap m => ServantErr -> m a
- 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 snap handler from an API
serveSnap :: forall layout m. (HasServer layout '[] m, MonadSnap m) => Proxy layout -> Server layout '[] m -> m () Source #
serveSnapWithContext :: forall layout context m. (HasServer layout context m, MonadSnap m) => Proxy layout -> Context context -> Server layout context m -> m () Source #
Handlers for all standard combinators
class HasServer api context (m :: * -> *) where Source #
route :: MonadSnap m => Proxy api -> Context context -> Delayed m env (Server api context m) -> Router m env Source #
hoistServerWithContext :: proxy api -> proxy' context -> (forall x. m x -> n x) -> ServerT api context m -> ServerT api context n Source #
Instances
HasServer Raw context m 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" |
Defined in Servant.Server.Internal | |
HasServer EmptyAPI context m Source # | The server for an type MyApi = "nothing" :> EmptyApi server :: Server MyApi server = emptyAPIServer |
Defined in Servant.Server.Internal | |
(HasServer a ctx m, HasServer b ctx m) => HasServer (a :<|> b :: Type) ctx m 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 = ... |
Defined in Servant.Server.Internal | |
(AllCTUnrender list a, HasServer api context m, SBoolI (FoldLenient mods), MonadSnap m) => HasServer (ReqBody' mods list a :> api :: Type) context m 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... |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (ReqBody' mods list a :> api) -> Context context -> Delayed m env (Server (ReqBody' mods list a :> api) context m) -> Router m env Source # hoistServerWithContext :: proxy (ReqBody' mods list a :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (ReqBody' mods list a :> api) context m -> ServerT (ReqBody' mods list a :> api) context n Source # | |
HasServer api context m => HasServer (RemoteHost :> api :: Type) context m Source # | |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (RemoteHost :> api) -> Context context -> Delayed m env (Server (RemoteHost :> api) context m) -> Router m env Source # hoistServerWithContext :: proxy (RemoteHost :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (RemoteHost :> api) context m -> ServerT (RemoteHost :> api) context n Source # | |
(KnownSymbol sym, FromHttpApiData a, HasServer api context m, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)) => HasServer (QueryParam' mods sym a :> api :: Type) context m 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... |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (QueryParam' mods sym a :> api) -> Context context -> Delayed m env (Server (QueryParam' mods sym a :> api) context m) -> Router m env Source # hoistServerWithContext :: proxy (QueryParam' mods sym a :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (QueryParam' mods sym a :> api) context m -> ServerT (QueryParam' mods sym a :> api) context n Source # | |
(KnownSymbol sym, FromHttpApiData a, HasServer api context m) => HasServer (QueryParams sym a :> api :: Type) context m 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... |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (QueryParams sym a :> api) -> Context context -> Delayed m env (Server (QueryParams sym a :> api) context m) -> Router m env Source # hoistServerWithContext :: proxy (QueryParams sym a :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (QueryParams sym a :> api) context m -> ServerT (QueryParams sym a :> api) context n Source # | |
(KnownSymbol sym, HasServer api context m) => HasServer (QueryFlag sym :> api :: Type) context m 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... |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (QueryFlag sym :> api) -> Context context -> Delayed m env (Server (QueryFlag sym :> api) context m) -> Router m env Source # hoistServerWithContext :: proxy (QueryFlag sym :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (QueryFlag sym :> api) context m -> ServerT (QueryFlag sym :> api) context n Source # | |
(KnownSymbol sym, FromHttpApiData a, HasServer api context m, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)) => HasServer (Header' mods sym a :> api :: Type) context m 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 |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (Header' mods sym a :> api) -> Context context -> Delayed m env (Server (Header' mods sym a :> api) context m) -> Router m env Source # hoistServerWithContext :: proxy (Header' mods sym a :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (Header' mods sym a :> api) context m -> ServerT (Header' mods sym a :> api) context n Source # | |
HasServer api context m => HasServer (IsSecure :> api :: Type) context m Source # | |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (IsSecure :> api) -> Context context -> Delayed m env (Server (IsSecure :> api) context m) -> Router m env Source # hoistServerWithContext :: proxy (IsSecure :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (IsSecure :> api) context m -> ServerT (IsSecure :> api) context n Source # | |
HasServer api ctx m => HasServer (Summary desc :> api :: Type) ctx m Source # | Ignore |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (Summary desc :> api) -> Context ctx -> Delayed m env (Server (Summary desc :> api) ctx m) -> Router m env Source # hoistServerWithContext :: proxy (Summary desc :> api) -> proxy' ctx -> (forall x. m x -> n x) -> ServerT (Summary desc :> api) ctx m -> ServerT (Summary desc :> api) ctx n Source # | |
HasServer api ctx m => HasServer (Description desc :> api :: Type) ctx m Source # | Ignore |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (Description desc :> api) -> Context ctx -> Delayed m env (Server (Description desc :> api) ctx m) -> Router m env Source # hoistServerWithContext :: proxy (Description desc :> api) -> proxy' ctx -> (forall x. m x -> n x) -> ServerT (Description desc :> api) ctx m -> ServerT (Description desc :> api) ctx n Source # | |
(FromHttpApiData a, HasServer api context m) => HasServer (Capture' mods capture a :> api :: Type) context m 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 = ... |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (Capture' mods capture a :> api) -> Context context -> Delayed m env (Server (Capture' mods capture a :> api) context m) -> Router m env Source # hoistServerWithContext :: proxy (Capture' mods capture a :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (Capture' mods capture a :> api) context m -> ServerT (Capture' mods capture a :> api) context n Source # | |
(FromHttpApiData a, HasServer api context m) => HasServer (CaptureAll capture a :> api :: Type) context m Source # | |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (CaptureAll capture a :> api) -> Context context -> Delayed m env (Server (CaptureAll capture a :> api) context m) -> Router m env Source # hoistServerWithContext :: proxy (CaptureAll capture a :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (CaptureAll capture a :> api) context m -> ServerT (CaptureAll capture a :> api) context n Source # | |
(KnownSymbol realm, HasServer api context m, HasContextEntry context (BasicAuthCheck m usr)) => HasServer (BasicAuth realm usr :> api :: Type) context m Source # | Basic Authentication |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (BasicAuth realm usr :> api) -> Context context -> Delayed m env (Server (BasicAuth realm usr :> api) context m) -> Router m env Source # hoistServerWithContext :: proxy (BasicAuth realm usr :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (BasicAuth realm usr :> api) context m -> ServerT (BasicAuth realm usr :> api) context n Source # | |
HasServer api context m => HasServer (HttpVersion :> api :: Type) context m Source # | |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (HttpVersion :> api) -> Context context -> Delayed m env (Server (HttpVersion :> api) context m) -> Router m env Source # hoistServerWithContext :: proxy (HttpVersion :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (HttpVersion :> api) context m -> ServerT (HttpVersion :> api) context n Source # | |
(KnownSymbol path, HasServer api context m) => HasServer (path :> api :: Type) context m Source # | Make sure the incoming request starts with |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (path :> api) -> Context context -> Delayed m env (Server (path :> api) context m) -> Router m env Source # hoistServerWithContext :: proxy (path :> api) -> proxy' context -> (forall x. m x -> n x) -> ServerT (path :> api) context m -> ServerT (path :> api) context n Source # | |
(AllCTRender ctypes a, ReflectMethod method, KnownNat status, GetHeaders (Headers h a)) => HasServer (Verb method status ctypes (Headers h a) :: Type) context m Source # | |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (Verb method status ctypes (Headers h a)) -> Context context -> Delayed m env (Server (Verb method status ctypes (Headers h a)) context m) -> Router m env Source # hoistServerWithContext :: proxy (Verb method status ctypes (Headers h a)) -> proxy' context -> (forall x. m x -> n x) -> ServerT (Verb method status ctypes (Headers h a)) context m -> ServerT (Verb method status ctypes (Headers h a)) context n Source # | |
(AllCTRender ctypes a, ReflectMethod method, KnownNat status) => HasServer (Verb method status ctypes a :: Type) context m Source # | |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (Verb method status ctypes a) -> Context context -> Delayed m env (Server (Verb method status ctypes a) context m) -> Router m env Source # hoistServerWithContext :: proxy (Verb method status ctypes a) -> proxy' context -> (forall x. m x -> n x) -> ServerT (Verb method status ctypes a) context m -> ServerT (Verb method status ctypes a) context n Source # | |
(MimeRender ctype a, ReflectMethod method, KnownNat status, FramingRender framing ctype, ToStreamGenerator b a, GetHeaders (Headers h b)) => HasServer (Stream method status framing ctype (Headers h b) :: Type) context m Source # | |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (Stream method status framing ctype (Headers h b)) -> Context context -> Delayed m env (Server (Stream method status framing ctype (Headers h b)) context m) -> Router m env Source # hoistServerWithContext :: proxy (Stream method status framing ctype (Headers h b)) -> proxy' context -> (forall x. m x -> n x) -> ServerT (Stream method status framing ctype (Headers h b)) context m -> ServerT (Stream method status framing ctype (Headers h b)) context n Source # | |
(MimeRender ctype a, ReflectMethod method, KnownNat status, FramingRender framing ctype, ToStreamGenerator b a) => HasServer (Stream method status framing ctype b :: Type) context m Source # | |
Defined in Servant.Server.Internal route :: MonadSnap m => Proxy (Stream method status framing ctype b) -> Context context -> Delayed m env (Server (Stream method status framing ctype b) context m) -> Router m env Source # hoistServerWithContext :: proxy (Stream method status framing ctype b) -> proxy' context -> (forall x. m x -> n x) -> ServerT (Stream method status framing ctype b) context m -> ServerT (Stream method status framing ctype b) context n Source # |
Reexports
Basic functions and datatypes
Default error type
data ServantErr Source #
ServantErr | |
|
Instances
Eq ServantErr Source # | |
Defined in Servant.Server.Internal.ServantErr (==) :: ServantErr -> ServantErr -> Bool # (/=) :: ServantErr -> ServantErr -> Bool # | |
Read ServantErr Source # | |
Defined in Servant.Server.Internal.ServantErr readsPrec :: Int -> ReadS ServantErr # readList :: ReadS [ServantErr] # readPrec :: ReadPrec ServantErr # readListPrec :: ReadPrec [ServantErr] # | |
Show ServantErr Source # | |
Defined in Servant.Server.Internal.ServantErr showsPrec :: Int -> ServantErr -> ShowS # show :: ServantErr -> String # showList :: [ServantErr] -> ShowS # |
throwError :: MonadSnap m => ServantErr -> m a Source #
Terminate request handling with a ServantErr
via finishWith
3XX
err300 :: ServantErr Source #
err301 :: ServantErr Source #
err302 :: ServantErr Source #
err303 :: ServantErr Source #
err304 :: ServantErr Source #
err305 :: ServantErr Source #
err307 :: ServantErr Source #
4XX
err400 :: ServantErr Source #
err401 :: ServantErr Source #
err402 :: ServantErr Source #
err403 :: ServantErr Source #
err404 :: ServantErr Source #
err405 :: ServantErr Source #
err406 :: ServantErr Source #
err407 :: ServantErr Source #
err409 :: ServantErr Source #
err410 :: ServantErr Source #
err411 :: ServantErr Source #
err412 :: ServantErr Source #
err413 :: ServantErr Source #
err414 :: ServantErr Source #
err415 :: ServantErr Source #
err416 :: ServantErr Source #
err417 :: ServantErr Source #
5XX
err500 :: ServantErr Source #
err501 :: ServantErr Source #
err502 :: ServantErr Source #
err503 :: ServantErr Source #
err504 :: ServantErr Source #
err505 :: ServantErr Source #