Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data EmptyServer = EmptyServer
- type Server api context m = ServerT api context m
- class HasServer api context (m :: * -> *) where
- captured :: FromHttpApiData a => proxy (Capture' mods 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
- streamRouter :: (MimeRender ctype a, FramingRender framing ctype, ToStreamGenerator b a, MonadSnap m) => (c -> ([(HeaderName, ByteString)], b)) -> Method -> Status -> Proxy framing -> Proxy ctype -> Delayed m env (m c) -> Router m env
- emptyServer :: ServerT EmptyAPI context m
- ct_wildcard :: ByteString
- module Servant.Server.Internal.PathInfo
- module Servant.Server.Internal.Router
- module Servant.Server.Internal.RoutingApplication
- module Servant.Server.Internal.ServantErr
Documentation
data EmptyServer Source #
Singleton type representing a server that serves an empty API.
Instances
Bounded EmptyServer Source # | |
Defined in Servant.Server.Internal minBound :: EmptyServer # maxBound :: EmptyServer # | |
Enum EmptyServer Source # | |
Defined in Servant.Server.Internal succ :: EmptyServer -> EmptyServer # pred :: EmptyServer -> EmptyServer # toEnum :: Int -> EmptyServer # fromEnum :: EmptyServer -> Int # enumFrom :: EmptyServer -> [EmptyServer] # enumFromThen :: EmptyServer -> EmptyServer -> [EmptyServer] # enumFromTo :: EmptyServer -> EmptyServer -> [EmptyServer] # enumFromThenTo :: EmptyServer -> EmptyServer -> EmptyServer -> [EmptyServer] # | |
Eq EmptyServer Source # | |
Defined in Servant.Server.Internal (==) :: EmptyServer -> EmptyServer -> Bool # (/=) :: EmptyServer -> EmptyServer -> Bool # | |
Show EmptyServer Source # | |
Defined in Servant.Server.Internal showsPrec :: Int -> EmptyServer -> ShowS # show :: EmptyServer -> String # showList :: [EmptyServer] -> ShowS # |
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 # |
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 #
streamRouter :: (MimeRender ctype a, FramingRender framing ctype, ToStreamGenerator b a, MonadSnap m) => (c -> ([(HeaderName, ByteString)], b)) -> Method -> Status -> Proxy framing -> Proxy ctype -> Delayed m env (m c) -> Router m env Source #