Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data (path :: k) :> (a :: *)
- data a :<|> b = a :<|> b
- data EmptyAPI = EmptyAPI
- data Strict
- data Lenient
- data Optional
- data Required
- data CaptureAll (sym :: Symbol) (a :: *)
- data Capture' (mods :: [*]) (sym :: Symbol) (a :: *)
- type Capture = Capture' '[]
- data Header' (mods :: [*]) (sym :: Symbol) a
- type Header = Header' '[Optional, Strict]
- data HttpVersion = HttpVersion {}
- data QueryFlag (sym :: Symbol)
- data QueryParams (sym :: Symbol) (a :: *)
- data QueryParam' (mods :: [*]) (sym :: Symbol) (a :: *)
- type QueryParam = QueryParam' '[Optional, Strict]
- data ReqBody' (mods :: [*]) (contentTypes :: [*]) (a :: *)
- type ReqBody = ReqBody' '[Required, Strict]
- data RemoteHost
- data IsSecure
- type Vault = Vault RealWorld
- data WithNamedContext (name :: Symbol) (subContext :: [*]) subApi
- data StdMethod
- class ReflectMethod a where
- type GetPartialContent = Verb GET 206
- type PostResetContent = Verb POST 205
- type GetResetContent = Verb GET 205
- type PutNoContent = Verb PUT 204
- type PatchNoContent = Verb PATCH 204
- type DeleteNoContent = Verb DELETE 204
- type PostNoContent = Verb POST 204
- type GetNoContent = Verb GET 204
- type PutNonAuthoritative = Verb PUT 203
- type PatchNonAuthoritative = Verb PATCH 203
- type DeleteNonAuthoritative = Verb DELETE 203
- type PostNonAuthoritative = Verb POST 203
- type GetNonAuthoritative = Verb GET 203
- type PutAccepted = Verb PUT 202
- type PatchAccepted = Verb PATCH 202
- type DeleteAccepted = Verb DELETE 202
- type PostAccepted = Verb POST 202
- type GetAccepted = Verb GET 202
- type PostCreated = Verb POST 201
- type Patch = Verb PATCH 200
- type Delete = Verb DELETE 200
- type Put = Verb PUT 200
- type Post = Verb POST 200
- type Get = Verb GET 200
- data Verb (method :: k1) (statusCode :: Nat) (contentTypes :: [*]) (a :: *)
- data NetstringFraming
- data NewlineFraming
- data NoFraming
- class FramingUnrender strategy a where
- data ByteStringParser a = ByteStringParser {
- parseIncremental :: ByteString -> Maybe (a, ByteString)
- parseEOF :: ByteString -> (a, ByteString)
- data BoundaryStrategy
- class FramingRender strategy a where
- class BuildFromStream a b where
- newtype ResultStream a = ResultStream (forall b. (IO (Maybe (Either String a)) -> IO b) -> IO b)
- class ToStreamGenerator a b | a -> b where
- newtype StreamGenerator a = StreamGenerator {
- getStreamGenerator :: (a -> IO ()) -> (a -> IO ()) -> IO ()
- type StreamPost = Stream POST 200
- type StreamGet = Stream GET 200
- data Stream (method :: k1) (status :: Nat) (framing :: *) (contentType :: *) (a :: *)
- data BasicAuthData = BasicAuthData {}
- data BasicAuth (realm :: Symbol) (userData :: *)
- data Description (sym :: Symbol)
- data Summary (sym :: Symbol)
- data NoContent = NoContent
- class Accept ctype => MimeUnrender ctype a where
- class Accept ctype => MimeRender ctype a where
- class Accept ctype where
- data OctetStream
- data FormUrlEncoded
- data PlainText
- data JSON
- class AddHeader h v orig new | h v orig -> new, new -> h, new -> v, new -> orig
- class GetHeaders ls where
- class BuildHeadersTo hs where
- data HList a where
- data ResponseHeader (sym :: Symbol) a
- data Headers ls a = Headers {
- getResponse :: a
- getHeadersHList :: HList ls
- addHeader :: AddHeader h v orig new => v -> orig -> new
- noHeader :: AddHeader h v orig new => orig -> new
- data Raw
- class ToHttpApiData a where
- class FromHttpApiData a where
- data AuthProtect (tag :: k)
- data URI = URI {}
- type family IsElem endpoint api :: Constraint where ...
- type family IsElem' a s :: Constraint
- class HasLink endpoint where
- data Link
- safeLink :: forall endpoint api. (IsElem endpoint api, HasLink endpoint) => Proxy api -> Proxy endpoint -> MkLink endpoint Link
- type family If (cond :: Bool) (tru :: k) (fls :: k) :: k where ...
- data SBool (b :: Bool) where
- class SBoolI (b :: Bool) where
Combinators
data (path :: k) :> (a :: *) infixr 4 Source #
The contained API (second argument) can be found under ("/" ++ path)
(path being the first argument).
Example:
>>>
-- GET /hello/world
>>>
-- returning a JSON encoded World value
>>>
type MyApi = "hello" :> "world" :> Get '[JSON] World
Instances
Type-level combinator for expressing subrouting: :>
data a :<|> b infixr 3 Source #
Union of two APIs, first takes precedence in case of overlap.
Example:
>>>
:{
type MyApi = "books" :> Get '[JSON] [Book] -- GET /books :<|> "books" :> ReqBody '[JSON] Book :> Post '[JSON] () -- POST /books :}
a :<|> b infixr 3 |
Instances
Functor ((:<|>) a) Source # | |
Foldable ((:<|>) a) Source # | |
Defined in Servant.API.Alternative fold :: Monoid m => (a :<|> m) -> m # foldMap :: Monoid m => (a0 -> m) -> (a :<|> a0) -> m # foldr :: (a0 -> b -> b) -> b -> (a :<|> a0) -> b # foldr' :: (a0 -> b -> b) -> b -> (a :<|> a0) -> b # foldl :: (b -> a0 -> b) -> b -> (a :<|> a0) -> b # foldl' :: (b -> a0 -> b) -> b -> (a :<|> a0) -> b # foldr1 :: (a0 -> a0 -> a0) -> (a :<|> a0) -> a0 # foldl1 :: (a0 -> a0 -> a0) -> (a :<|> a0) -> a0 # toList :: (a :<|> a0) -> [a0] # length :: (a :<|> a0) -> Int # elem :: Eq a0 => a0 -> (a :<|> a0) -> Bool # maximum :: Ord a0 => (a :<|> a0) -> a0 # minimum :: Ord a0 => (a :<|> a0) -> a0 # | |
Traversable ((:<|>) a) Source # | |
(HasLink a, HasLink b) => HasLink (a :<|> b :: *) Source # | |
(Bounded a, Bounded b) => Bounded (a :<|> b) Source # | |
(Eq a, Eq b) => Eq (a :<|> b) Source # | |
(Show a, Show b) => Show (a :<|> b) Source # | |
(Semigroup a, Semigroup b) => Semigroup (a :<|> b) Source # | |
(Monoid a, Monoid b) => Monoid (a :<|> b) Source # | |
(Enter typ1 m1 n1 ret1, Enter typ2 m2 n2 ret2, m1 ~ m2, n1 ~ n2, Entered m1 n1 (typ1 :<|> typ2) ~ (ret1 :<|> ret2), Entered n1 m1 (ret1 :<|> ret2) ~ (typ1 :<|> typ2)) => Enter (typ1 :<|> typ2) m1 n1 (ret1 :<|> ret2) Source # | |
type MkLink (a :<|> b :: *) r Source # | |
Type-level combinator for alternative endpoints: :<|>
An empty API: one which serves nothing. Morally speaking, this should be
the unit of :<|>
. Implementors of interpretations of API types should
treat EmptyAPI
as close to the unit as possible.
Instances
Bounded EmptyAPI Source # | |
Enum EmptyAPI Source # | |
Eq EmptyAPI Source # | |
Show EmptyAPI Source # | |
HasLink EmptyAPI Source # | |
type MkLink EmptyAPI a Source # | |
Defined in Servant.Links |
Type-level combinator for an empty API: EmptyAPI
Strictly parsed argument. Not wrapped.
Instances
(KnownSymbol h, ToHttpApiData v) => AddHeader h v (Headers (fst ': rest) a) (Headers (Header h v ': (fst ': rest)) a) Source # | |
Defined in Servant.API.ResponseHeaders addOptionalHeader :: ResponseHeader h v -> Headers (fst ': rest) a -> Headers (Header h v ': (fst ': rest)) a | |
(FromHttpApiData v, BuildHeadersTo xs, KnownSymbol h) => BuildHeadersTo (Header h v ': xs) Source # | |
Defined in Servant.API.ResponseHeaders |
Optional argument. Wrapped in Maybe
.
Instances
(KnownSymbol h, ToHttpApiData v) => AddHeader h v (Headers (fst ': rest) a) (Headers (Header h v ': (fst ': rest)) a) Source # | |
Defined in Servant.API.ResponseHeaders addOptionalHeader :: ResponseHeader h v -> Headers (fst ': rest) a -> Headers (Header h v ': (fst ': rest)) a | |
(FromHttpApiData v, BuildHeadersTo xs, KnownSymbol h) => BuildHeadersTo (Header h v ': xs) Source # | |
Defined in Servant.API.ResponseHeaders |
Type-level modifiers for QueryParam
, Header
and ReqBody
.
Accessing information from the request
data CaptureAll (sym :: Symbol) (a :: *) Source #
Capture all remaining values from the request path under a certain type
a
.
Example:
>>>
-- GET /src/*
>>>
type MyAPI = "src" :> CaptureAll "segments" Text :> Get '[JSON] SourceFile
Instances
(ToHttpApiData v, HasLink sub) => HasLink (CaptureAll sym v :> sub :: *) Source # | |
Defined in Servant.Links | |
type MkLink (CaptureAll sym v :> sub :: *) a Source # | |
Defined in Servant.Links |
data Capture' (mods :: [*]) (sym :: Symbol) (a :: *) Source #
Capture
which can be modified. For example with Description
.
type Capture = Capture' '[] Source #
Capture a value from the request path under a certain type a
.
Example:
>>>
-- GET /books/:isbn
>>>
type MyApi = "books" :> Capture "isbn" Text :> Get '[JSON] Book
Capturing parts of the url path as parsed values:
and Capture
CaptureAll
data Header' (mods :: [*]) (sym :: Symbol) a Source #
Instances
(KnownSymbol h, ToHttpApiData v) => AddHeader h v (Headers (fst ': rest) a) (Headers (Header h v ': (fst ': rest)) a) Source # | |
Defined in Servant.API.ResponseHeaders addOptionalHeader :: ResponseHeader h v -> Headers (fst ': rest) a -> Headers (Header h v ': (fst ': rest)) a | |
HasLink sub => HasLink (Header' mods sym a :> sub :: *) Source # | |
(FromHttpApiData v, BuildHeadersTo xs, KnownSymbol h) => BuildHeadersTo (Header h v ': xs) Source # | |
Defined in Servant.API.ResponseHeaders | |
type MkLink (Header' mods sym a :> sub :: *) r Source # | |
type Header = Header' '[Optional, Strict] Source #
Extract the given header's value as a value of type a
.
I.e. header sent by client, parsed by server.
Example:
>>>
newtype Referer = Referer Text deriving (Eq, Show)
>>>
>>>
-- GET /view-my-referer
>>>
type MyApi = "view-my-referer" :> Header "from" Referer :> Get '[JSON] Referer
Retrieving specific headers from the request
data HttpVersion #
HTTP Version.
Note that the Show instance is intended merely for debugging.
Instances
Eq HttpVersion | |
Defined in Network.HTTP.Types.Version (==) :: HttpVersion -> HttpVersion -> Bool # (/=) :: HttpVersion -> HttpVersion -> Bool # | |
Ord HttpVersion | |
Defined in Network.HTTP.Types.Version compare :: HttpVersion -> HttpVersion -> Ordering # (<) :: HttpVersion -> HttpVersion -> Bool # (<=) :: HttpVersion -> HttpVersion -> Bool # (>) :: HttpVersion -> HttpVersion -> Bool # (>=) :: HttpVersion -> HttpVersion -> Bool # max :: HttpVersion -> HttpVersion -> HttpVersion # min :: HttpVersion -> HttpVersion -> HttpVersion # | |
Show HttpVersion | |
Defined in Network.HTTP.Types.Version showsPrec :: Int -> HttpVersion -> ShowS # show :: HttpVersion -> String # showList :: [HttpVersion] -> ShowS # | |
HasLink sub => HasLink (HttpVersion :> sub :: *) Source # | |
Defined in Servant.Links | |
type MkLink (HttpVersion :> sub :: *) a Source # | |
Defined in Servant.Links |
Retrieving the HTTP version of the request
data QueryFlag (sym :: Symbol) Source #
Lookup a potentially value-less query string parameter
with boolean semantics. If the param sym
is there without any value,
or if it's there with value "true" or "1", it's interpreted as True
.
Otherwise, it's interpreted as False
.
Example:
>>>
-- /books?published
>>>
type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book]
data QueryParams (sym :: Symbol) (a :: *) Source #
Lookup the values associated to the sym
query string parameter
and try to extract it as a value of type [a]
. This is typically
meant to support query string parameters of the form
param[]=val1¶m[]=val2
and so on. Note that servant doesn't actually
require the []
s and will fetch the values just fine with
param=val1¶m=val2
, too.
Example:
>>>
-- /books?authors[]=<author1>&authors[]=<author2>&...
>>>
type MyApi = "books" :> QueryParams "authors" Text :> Get '[JSON] [Book]
Instances
(KnownSymbol sym, ToHttpApiData v, HasLink sub) => HasLink (QueryParams sym v :> sub :: *) Source # | |
Defined in Servant.Links | |
type MkLink (QueryParams sym v :> sub :: *) a Source # | |
Defined in Servant.Links |
data QueryParam' (mods :: [*]) (sym :: Symbol) (a :: *) Source #
QueryParam
which can be Required
, Lenient
, or modified otherwise.
Instances
(KnownSymbol sym, ToHttpApiData v, HasLink sub, SBoolI (FoldRequired mods)) => HasLink (QueryParam' mods sym v :> sub :: *) Source # | |
Defined in Servant.Links | |
type MkLink (QueryParam' mods sym v :> sub :: *) a Source # | |
Defined in Servant.Links type MkLink (QueryParam' mods sym v :> sub :: *) a = If (FoldRequired mods) v (Maybe v) -> MkLink sub a |
type QueryParam = QueryParam' '[Optional, Strict] Source #
Lookup the value associated to the sym
query string parameter
and try to extract it as a value of type a
.
Example:
>>>
-- /books?author=<author name>
>>>
type MyApi = "books" :> QueryParam "author" Text :> Get '[JSON] [Book]
Retrieving parameters from the query string of the URI
: QueryParam
data ReqBody' (mods :: [*]) (contentTypes :: [*]) (a :: *) Source #
type ReqBody = ReqBody' '[Required, Strict] Source #
Extract the request body as a value of type a
.
Example:
>>>
-- POST /books
>>>
type MyApi = "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book
Accessing the request body as a JSON-encoded type: ReqBody
data RemoteHost Source #
Provides access to the host or IP address from which the HTTP request was sent.
Instances
HasLink sub => HasLink (RemoteHost :> sub :: *) Source # | |
Defined in Servant.Links | |
type MkLink (RemoteHost :> sub :: *) a Source # | |
Defined in Servant.Links |
Retrieving the IP of the client
Was this request made over an SSL connection?
Note that this value will not tell you if the client originally
made this request over SSL, but rather whether the current
connection is SSL. The distinction lies with reverse proxies.
In many cases, the client will connect to a load balancer over SSL,
but connect to the WAI handler without SSL. In such a case,
the handlers would get NotSecure
, but from a user perspective,
there is a secure connection.
Secure | the connection to the server is secure (HTTPS) |
NotSecure | the connection to the server is not secure (HTTP) |
Is the request made through HTTPS?
type Vault = Vault RealWorld #
A persistent store for values of arbitrary types.
This variant is the simplest and creates keys in the IO
monad.
See the module Data.Vault.ST if you want to use it with the ST
monad instead.
Access the location for arbitrary data to be shared by applications and middleware
data WithNamedContext (name :: Symbol) (subContext :: [*]) subApi Source #
WithNamedContext
names a specific tagged context to use for the
combinators in the API. (See also in servant-server
,
Servant.Server.Context
.) For example:
type UseNamedContextAPI = WithNamedContext "myContext" '[String] ( ReqBody '[JSON] Int :> Get '[JSON] Int)
Both the ReqBody
and Get
combinators will use the WithNamedContext
with
type tag "myContext" as their context.
Context
s are only relevant for servant-server
.
For more information, see the tutorial.
Instances
HasLink sub => HasLink (WithNamedContext name context sub :: *) Source # | |
Defined in Servant.Links type MkLink (WithNamedContext name context sub) a :: * Source # toLink :: (Link -> a) -> Proxy (WithNamedContext name context sub) -> Link -> MkLink (WithNamedContext name context sub) a Source # | |
type MkLink (WithNamedContext name context sub :: *) a Source # | |
Defined in Servant.Links |
Access context entries in combinators in servant-server
Actual endpoints, distinguished by HTTP method
HTTP standard method (as defined by RFC 2616, and PATCH which is defined by RFC 5789).
Instances
class ReflectMethod a where Source #
reflectMethod :: Proxy a -> Method Source #
Instances
ReflectMethod PATCH Source # | |
Defined in Servant.API.Verbs | |
ReflectMethod OPTIONS Source # | |
Defined in Servant.API.Verbs | |
ReflectMethod CONNECT Source # | |
Defined in Servant.API.Verbs | |
ReflectMethod TRACE Source # | |
Defined in Servant.API.Verbs | |
ReflectMethod DELETE Source # | |
Defined in Servant.API.Verbs | |
ReflectMethod PUT Source # | |
Defined in Servant.API.Verbs | |
ReflectMethod HEAD Source # | |
Defined in Servant.API.Verbs | |
ReflectMethod POST Source # | |
Defined in Servant.API.Verbs | |
ReflectMethod GET Source # | |
Defined in Servant.API.Verbs |
data Verb (method :: k1) (statusCode :: Nat) (contentTypes :: [*]) (a :: *) Source #
Verb
is a general type for representing HTTP verbs (a.k.a. methods). For
convenience, type synonyms for each verb with a 200 response code are
provided, but you are free to define your own:
>>>
type Post204 contentTypes a = Verb 'POST 204 contentTypes a
Streaming endpoints, distinguished by HTTP method
data NetstringFraming Source #
The netstring framing strategy as defined by djb: http://cr.yp.to/proto/netstrings.txt
Instances
FramingUnrender NetstringFraming (a :: k) Source # | |
Defined in Servant.API.Stream | |
FramingRender NetstringFraming (a :: k) Source # | |
Defined in Servant.API.Stream header :: Proxy NetstringFraming -> Proxy a -> ByteString Source # boundary :: Proxy NetstringFraming -> Proxy a -> BoundaryStrategy Source # trailer :: Proxy NetstringFraming -> Proxy a -> ByteString Source # |
data NewlineFraming Source #
A simple framing strategy that has no header or termination, and inserts a newline character between each frame. This assumes that it is used with a Content-Type that encodes without newlines (e.g. JSON).
Instances
FramingUnrender NewlineFraming (a :: k) Source # | |
Defined in Servant.API.Stream unrenderFrames :: Proxy NewlineFraming -> Proxy a -> ByteStringParser (ByteStringParser (Either String ByteString)) Source # | |
FramingRender NewlineFraming (a :: k) Source # | |
Defined in Servant.API.Stream header :: Proxy NewlineFraming -> Proxy a -> ByteString Source # boundary :: Proxy NewlineFraming -> Proxy a -> BoundaryStrategy Source # trailer :: Proxy NewlineFraming -> Proxy a -> ByteString Source # |
A framing strategy that does not do any framing at all, it just passes the input data This will be used most of the time with binary data, such as files
Instances
FramingUnrender NoFraming (a :: k) Source # | |
Defined in Servant.API.Stream unrenderFrames :: Proxy NoFraming -> Proxy a -> ByteStringParser (ByteStringParser (Either String ByteString)) Source # | |
FramingRender NoFraming (a :: k) Source # | |
class FramingUnrender strategy a where Source #
The FramingUnrender class provides the logic for parsing a framing strategy. The outer ByteStringParser
strips the header from a stream of bytes, and yields a parser that can handle the remainder, stepwise. Each frame may be a ByteString, or a String indicating the error state for that frame. Such states are per-frame, so that protocols that can resume after errors are able to do so. Eventually this returns an empty ByteString to indicate termination.
unrenderFrames :: Proxy strategy -> Proxy a -> ByteStringParser (ByteStringParser (Either String ByteString)) Source #
Instances
FramingUnrender NoFraming (a :: k) Source # | |
Defined in Servant.API.Stream unrenderFrames :: Proxy NoFraming -> Proxy a -> ByteStringParser (ByteStringParser (Either String ByteString)) Source # | |
FramingUnrender NewlineFraming (a :: k) Source # | |
Defined in Servant.API.Stream unrenderFrames :: Proxy NewlineFraming -> Proxy a -> ByteStringParser (ByteStringParser (Either String ByteString)) Source # | |
FramingUnrender NetstringFraming (a :: k) Source # | |
Defined in Servant.API.Stream |
data ByteStringParser a Source #
A type of parser that can never fail, and has different parsing strategies (incremental, or EOF) depending if more input can be sent. The incremental parser should return Nothing
if it would like to be sent a longer ByteString. If it returns a value, it also returns the remainder following that value.
ByteStringParser | |
|
data BoundaryStrategy Source #
The bracketing strategy generates things to precede and follow the content, as with netstrings. The intersperse strategy inserts seperators between things, as with newline framing. Finally, the general strategy performs an arbitrary rewrite on the content, to allow escaping rules and such.
class FramingRender strategy a where Source #
The FramingRender class provides the logic for emitting a framing strategy. The strategy emits a header, followed by boundary-delimited data, and finally a termination character. For many strategies, some of these will just be empty bytestrings.
header :: Proxy strategy -> Proxy a -> ByteString Source #
boundary :: Proxy strategy -> Proxy a -> BoundaryStrategy Source #
Instances
FramingRender NoFraming (a :: k) Source # | |
FramingRender NewlineFraming (a :: k) Source # | |
Defined in Servant.API.Stream header :: Proxy NewlineFraming -> Proxy a -> ByteString Source # boundary :: Proxy NewlineFraming -> Proxy a -> BoundaryStrategy Source # trailer :: Proxy NewlineFraming -> Proxy a -> ByteString Source # | |
FramingRender NetstringFraming (a :: k) Source # | |
Defined in Servant.API.Stream header :: Proxy NetstringFraming -> Proxy a -> ByteString Source # boundary :: Proxy NetstringFraming -> Proxy a -> BoundaryStrategy Source # trailer :: Proxy NetstringFraming -> Proxy a -> ByteString Source # |
class BuildFromStream a b where Source #
BuildFromStream is intended to be implemented for types such as Conduit, Pipe, etc. By implementing this class, all such streaming abstractions can be used directly on the client side for talking to streaming endpoints.
buildFromStream :: ResultStream a -> b Source #
Instances
BuildFromStream a (ResultStream a) Source # | |
Defined in Servant.API.Stream buildFromStream :: ResultStream a -> ResultStream a Source # |
newtype ResultStream a Source #
Clients reading from streaming endpoints can be implemented as producing a ResultStream
that captures the setup, takedown, and incremental logic for a read, being an IO continuation that takes a producer of Just either values or errors that terminates with a Nothing.
Instances
BuildFromStream a (ResultStream a) Source # | |
Defined in Servant.API.Stream buildFromStream :: ResultStream a -> ResultStream a Source # |
class ToStreamGenerator a b | a -> b where Source #
ToStreamGenerator is intended to be implemented for types such as Conduit, Pipe, etc. By implementing this class, all such streaming abstractions can be used directly as endpoints.
toStreamGenerator :: a -> StreamGenerator b Source #
Instances
ToStreamGenerator (StreamGenerator a) a Source # | |
Defined in Servant.API.Stream toStreamGenerator :: StreamGenerator a -> StreamGenerator a Source # |
newtype StreamGenerator a Source #
Stream endpoints may be implemented as producing a StreamGenerator
-- a function that itself takes two emit functions -- the first to be used on the first value the stream emits, and the second to be used on all subsequent values (to allow interspersed framing strategies such as comma separation).
StreamGenerator | |
|
Instances
ToStreamGenerator (StreamGenerator a) a Source # | |
Defined in Servant.API.Stream toStreamGenerator :: StreamGenerator a -> StreamGenerator a Source # |
type StreamPost = Stream POST 200 Source #
data Stream (method :: k1) (status :: Nat) (framing :: *) (contentType :: *) (a :: *) Source #
A Stream endpoint for a given method emits a stream of encoded values at a given Content-Type, delimited by a framing strategy. Stream endpoints always return response code 200 on success. Type synonyms are provided for standard methods.
Authentication
data BasicAuthData Source #
A simple datatype to hold data required to decorate a request
data BasicAuth (realm :: Symbol) (userData :: *) Source #
Combinator for Basic Access Authentication.
- IMPORTANT*: Only use Basic Auth over HTTPS! Credentials are not hashed or encrypted. Note also that because the same credentials are sent on every request, Basic Auth is not as secure as some alternatives. Further, the implementation in servant-server does not protect against some types of timing attacks.
In Basic Auth, username and password are base64-encoded and transmitted via
the Authorization
header. Handshakes are not required, making it
relatively efficient.
Endpoints description
data Description (sym :: Symbol) Source #
Add more verbose description for (part of) API.
Example:
>>>
:{
type MyApi = Description "This comment is visible in multiple Servant interpretations \ \and can be really long if necessary. \ \Haskell multiline support is not perfect \ \but it's still very readable." :> Get '[JSON] Book :}
Instances
HasLink sub => HasLink (Description s :> sub :: *) Source # | |
Defined in Servant.Links | |
type MkLink (Description s :> sub :: *) a Source # | |
Defined in Servant.Links |
data Summary (sym :: Symbol) Source #
Add a short summary for (part of) API.
Example:
>>>
type MyApi = Summary "Get book by ISBN." :> "books" :> Capture "isbn" Text :> Get '[JSON] Book
Content Types
A type for responses without content-body.
Instances
Eq NoContent Source # | |
Read NoContent Source # | |
Show NoContent Source # | |
Generic NoContent Source # | |
AllMime (ctyp ': (ctyp' ': ctyps)) => AllMimeRender (ctyp ': (ctyp' ': ctyps)) NoContent Source # | |
Defined in Servant.API.ContentTypes allMimeRender :: Proxy (ctyp ': (ctyp' ': ctyps)) -> NoContent -> [(MediaType, ByteString)] Source # | |
Accept ctyp => AllMimeRender (ctyp ': ([] :: [*])) NoContent Source # | |
Defined in Servant.API.ContentTypes allMimeRender :: Proxy (ctyp ': []) -> NoContent -> [(MediaType, ByteString)] Source # | |
type Rep NoContent Source # | |
class Accept ctype => MimeUnrender ctype a where Source #
Instantiate this class to register a way of deserializing a type based
on the request's Content-Type
header.
>>>
import Network.HTTP.Media hiding (Accept)
>>>
import qualified Data.ByteString.Lazy.Char8 as BSC
>>>
data MyContentType = MyContentType String
>>>
:{
instance Accept MyContentType where contentType _ = "example" // "prs.me.mine" /: ("charset", "utf-8") :}
>>>
:{
instance Read a => MimeUnrender MyContentType a where mimeUnrender _ bs = case BSC.take 12 bs of "MyContentType" -> return . read . BSC.unpack $ BSC.drop 12 bs _ -> Left "didn't start with the magic incantation" :}
>>>
type MyAPI = "path" :> ReqBody '[MyContentType] Int :> Get '[JSON] Int
mimeUnrender :: Proxy ctype -> ByteString -> Either String a Source #
mimeUnrenderWithType :: Proxy ctype -> MediaType -> ByteString -> Either String a Source #
Instances
class Accept ctype => MimeRender ctype a where Source #
Instantiate this class to register a way of serializing a type based
on the Accept
header.
Example:
data MyContentType instance Accept MyContentType where contentType _ = "example" // "prs.me.mine" /: ("charset", "utf-8") instance Show a => MimeRender MyContentType a where mimeRender _ val = pack ("This is MINE! " ++ show val) type MyAPI = "path" :> Get '[MyContentType] Int
mimeRender :: Proxy ctype -> a -> ByteString Source #
Instances
class Accept ctype where Source #
Instances of Accept
represent mimetypes. They are used for matching
against the Accept
HTTP header of the request, and for setting the
Content-Type
header of the response
Example:
>>>
import Network.HTTP.Media ((//), (/:))
>>>
data HTML
>>>
:{
instance Accept HTML where contentType _ = "text" // "html" /: ("charset", "utf-8") :}
contentType :: Proxy ctype -> MediaType Source #
Instances
Accept OctetStream Source # | application/octet-stream |
Defined in Servant.API.ContentTypes | |
Accept FormUrlEncoded Source # | application/x-www-form-urlencoded |
Defined in Servant.API.ContentTypes | |
Accept PlainText Source # | text/plain;charset=utf-8 |
Defined in Servant.API.ContentTypes | |
Accept JSON Source # | application/json |
Defined in Servant.API.ContentTypes |
data OctetStream Source #
Instances
Accept OctetStream Source # | application/octet-stream |
Defined in Servant.API.ContentTypes | |
MimeUnrender OctetStream ByteString Source # | Right . toStrict |
Defined in Servant.API.ContentTypes | |
MimeUnrender OctetStream ByteString Source # | Right . id |
Defined in Servant.API.ContentTypes mimeUnrender :: Proxy OctetStream -> ByteString -> Either String ByteString Source # mimeUnrenderWithType :: Proxy OctetStream -> MediaType -> ByteString -> Either String ByteString Source # | |
MimeRender OctetStream ByteString Source # | |
Defined in Servant.API.ContentTypes mimeRender :: Proxy OctetStream -> ByteString -> ByteString0 Source # | |
MimeRender OctetStream ByteString Source # | id |
Defined in Servant.API.ContentTypes mimeRender :: Proxy OctetStream -> ByteString -> ByteString Source # |
data FormUrlEncoded Source #
Instances
Accept FormUrlEncoded Source # | application/x-www-form-urlencoded |
Defined in Servant.API.ContentTypes | |
FromForm a => MimeUnrender FormUrlEncoded a Source # |
|
Defined in Servant.API.ContentTypes mimeUnrender :: Proxy FormUrlEncoded -> ByteString -> Either String a Source # mimeUnrenderWithType :: Proxy FormUrlEncoded -> MediaType -> ByteString -> Either String a Source # | |
ToForm a => MimeRender FormUrlEncoded a Source # |
|
Defined in Servant.API.ContentTypes mimeRender :: Proxy FormUrlEncoded -> a -> ByteString Source # |
Instances
Instances
Accept JSON Source # | application/json |
Defined in Servant.API.ContentTypes | |
FromJSON a => MimeUnrender JSON a Source # |
|
Defined in Servant.API.ContentTypes mimeUnrender :: Proxy JSON -> ByteString -> Either String a Source # mimeUnrenderWithType :: Proxy JSON -> MediaType -> ByteString -> Either String a Source # | |
ToJSON a => MimeRender JSON a Source # | |
Defined in Servant.API.ContentTypes mimeRender :: Proxy JSON -> a -> ByteString Source # |
Serializing and deserializing types based on Accept
and
Content-Type
headers.
Response Headers
class AddHeader h v orig new | h v orig -> new, new -> h, new -> v, new -> orig Source #
addOptionalHeader
Instances
(KnownSymbol h, ToHttpApiData v, new ~ Headers (Header h v ': ([] :: [*])) a) => AddHeader h v a new Source # | |
Defined in Servant.API.ResponseHeaders addOptionalHeader :: ResponseHeader h v -> a -> new | |
(KnownSymbol h, ToHttpApiData v) => AddHeader h v (Headers (fst ': rest) a) (Headers (Header h v ': (fst ': rest)) a) Source # | |
Defined in Servant.API.ResponseHeaders addOptionalHeader :: ResponseHeader h v -> Headers (fst ': rest) a -> Headers (Header h v ': (fst ': rest)) a |
class GetHeaders ls where Source #
getHeaders :: ls -> [Header] Source #
Instances
GetHeadersFromHList hs => GetHeaders (HList hs) Source # | |
Defined in Servant.API.ResponseHeaders getHeaders :: HList hs -> [Header] Source # | |
GetHeaders' hs => GetHeaders (Headers hs a) Source # | |
Defined in Servant.API.ResponseHeaders getHeaders :: Headers hs a -> [Header] Source # |
class BuildHeadersTo hs where Source #
buildHeadersTo :: [Header] -> HList hs Source #
Note: if there are multiple occurences of a header in the argument, the values are interspersed with commas before deserialization (see RFC2616 Sec 4.2)
Instances
BuildHeadersTo ([] :: [*]) Source # | |
Defined in Servant.API.ResponseHeaders buildHeadersTo :: [Header] -> HList [] Source # | |
(FromHttpApiData v, BuildHeadersTo xs, KnownSymbol h) => BuildHeadersTo (Header h v ': xs) Source # | |
Defined in Servant.API.ResponseHeaders |
Instances
GetHeadersFromHList hs => GetHeaders (HList hs) Source # | |
Defined in Servant.API.ResponseHeaders getHeaders :: HList hs -> [Header] Source # |
data ResponseHeader (sym :: Symbol) a Source #
Instances
Functor (ResponseHeader sym) Source # | |
Defined in Servant.API.ResponseHeaders fmap :: (a -> b) -> ResponseHeader sym a -> ResponseHeader sym b # (<$) :: a -> ResponseHeader sym b -> ResponseHeader sym a # | |
Eq a => Eq (ResponseHeader sym a) Source # | |
Defined in Servant.API.ResponseHeaders (==) :: ResponseHeader sym a -> ResponseHeader sym a -> Bool # (/=) :: ResponseHeader sym a -> ResponseHeader sym a -> Bool # | |
Show a => Show (ResponseHeader sym a) Source # | |
Defined in Servant.API.ResponseHeaders showsPrec :: Int -> ResponseHeader sym a -> ShowS # show :: ResponseHeader sym a -> String # showList :: [ResponseHeader sym a] -> ShowS # |
Response Header objects. You should never need to construct one directly.
Instead, use addOptionalHeader
.
Headers | |
|
Instances
(KnownSymbol h, ToHttpApiData v) => AddHeader h v (Headers (fst ': rest) a) (Headers (Header h v ': (fst ': rest)) a) Source # | |
Defined in Servant.API.ResponseHeaders addOptionalHeader :: ResponseHeader h v -> Headers (fst ': rest) a -> Headers (Header h v ': (fst ': rest)) a | |
Functor (Headers ls) Source # | |
GetHeaders' hs => GetHeaders (Headers hs a) Source # | |
Defined in Servant.API.ResponseHeaders getHeaders :: Headers hs a -> [Header] Source # |
addHeader :: AddHeader h v orig new => v -> orig -> new Source #
addHeader
adds a header to a response. Note that it changes the type of
the value in the following ways:
- A simple value is wrapped in "Headers '[hdr]":
>>>
let example1 = addHeader 5 "hi" :: Headers '[Header "someheader" Int] String;
>>>
getHeaders example1
[("someheader","5")]
- A value that already has a header has its new header *prepended* to the existing list:
>>>
let example1 = addHeader 5 "hi" :: Headers '[Header "someheader" Int] String;
>>>
let example2 = addHeader True example1 :: Headers '[Header "1st" Bool, Header "someheader" Int] String
>>>
getHeaders example2
[("1st","true"),("someheader","5")]
Note that while in your handlers type annotations are not required, since the type can be inferred from the API type, in other cases you may find yourself needing to add annotations.
noHeader :: AddHeader h v orig new => orig -> new Source #
Deliberately do not add a header to a value.
>>>
let example1 = noHeader "hi" :: Headers '[Header "someheader" Int] String
>>>
getHeaders example1
[]
Untyped endpoints
Endpoint for plugging in your own Wai Application
s.
The given Application
will get the request as received by the server, potentially with
a modified (stripped) pathInfo
if the Application
is being routed with :>
.
In addition to just letting you plug in your existing WAI Application
s,
this can also be used with serveDirectory to serve
static files stored in a particular directory on your filesystem
Plugging in a wai Application
, serving directories
FromHttpApiData and ToHttpApiData
class ToHttpApiData a where #
Convert value to HTTP API data.
WARNING: Do not derive this using DeriveAnyClass
as the generated
instance will loop indefinitely.
toUrlPiece :: a -> Text #
Convert to URL path piece.
toEncodedUrlPiece :: a -> Builder #
Convert to a URL path piece, making sure to encode any special chars.
The default definition uses encodePathSegmentsRelative
,
but this may be overriden with a more efficient version.
toHeader :: a -> ByteString #
Convert to HTTP header value.
toQueryParam :: a -> Text #
Convert to query param value.
Instances
class FromHttpApiData a where #
Parse value from HTTP API data.
WARNING: Do not derive this using DeriveAnyClass
as the generated
instance will loop indefinitely.
parseUrlPiece :: Text -> Either Text a #
Parse URL path piece.
parseHeader :: ByteString -> Either Text a #
Parse HTTP header value.
parseQueryParam :: Text -> Either Text a #
Parse query param value.
Instances
Classes and instances for types that can be converted to and from HTTP API data.
Experimental modules
data AuthProtect (tag :: k) Source #
A generalized Authentication combinator. Use this if you have a non-standard authentication technique.
NOTE: THIS API IS EXPERIMENTAL AND SUBJECT TO CHANGE.
Instances
HasLink sub => HasLink (AuthProtect tag :> sub :: *) Source # | |
Defined in Servant.Links | |
type MkLink (AuthProtect tag :> sub :: *) a Source # | |
Defined in Servant.Links |
General Authentication
Links
Represents a general universal resource identifier using its component parts.
For example, for the URI
foo://anonymous@www.haskell.org:42/ghc?query#frag
the components are:
Instances
Eq URI | |
Data URI | |
Defined in Network.URI gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> URI -> c URI # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c URI # dataTypeOf :: URI -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c URI) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c URI) # gmapT :: (forall b. Data b => b -> b) -> URI -> URI # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> URI -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> URI -> r # gmapQ :: (forall d. Data d => d -> u) -> URI -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> URI -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> URI -> m URI # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> URI -> m URI # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> URI -> m URI # | |
Ord URI | |
Show URI | |
Generic URI | |
NFData URI | |
Defined in Network.URI | |
type Rep URI | |
Defined in Network.URI type Rep URI = D1 (MetaData "URI" "Network.URI" "network-uri-2.6.1.0-AstEwZoXrlUJQq4VkxaVo9" False) (C1 (MetaCons "URI" PrefixI True) ((S1 (MetaSel (Just "uriScheme") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "uriAuthority") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe URIAuth))) :*: (S1 (MetaSel (Just "uriPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "uriQuery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "uriFragment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) |
type family IsElem endpoint api :: Constraint where ... Source #
Closed type family, check if endpoint
is within api
.
Uses
if it exhausts all other options.IsElem'
>>>
ok (Proxy :: Proxy (IsElem ("hello" :> Get '[JSON] Int) SampleAPI))
OK
>>>
ok (Proxy :: Proxy (IsElem ("bye" :> Get '[JSON] Int) SampleAPI))
... ... Could not deduce... ...
An endpoint is considered within an api even if it is missing combinators that don't affect the URL:
>>>
ok (Proxy :: Proxy (IsElem (Get '[JSON] Int) (Header "h" Bool :> Get '[JSON] Int)))
OK
>>>
ok (Proxy :: Proxy (IsElem (Get '[JSON] Int) (ReqBody '[JSON] Bool :> Get '[JSON] Int)))
OK
- N.B.:*
IsElem a b
can be seen as capturing the notion of whether the URL represented bya
would match the URL represented byb
, *not* whether a request represented bya
matches the endpoints servingb
(for the latter, useIsIn
).
IsElem e (sa :<|> sb) = Or (IsElem e sa) (IsElem e sb) | |
IsElem (e :> sa) (e :> sb) = IsElem sa sb | |
IsElem sa (Header sym x :> sb) = IsElem sa sb | |
IsElem sa (ReqBody y x :> sb) = IsElem sa sb | |
IsElem (CaptureAll z y :> sa) (CaptureAll x y :> sb) = IsElem sa sb | |
IsElem (Capture z y :> sa) (Capture x y :> sb) = IsElem sa sb | |
IsElem sa (QueryParam x y :> sb) = IsElem sa sb | |
IsElem sa (QueryParams x y :> sb) = IsElem sa sb | |
IsElem sa (QueryFlag x :> sb) = IsElem sa sb | |
IsElem (Verb m s ct typ) (Verb m s ct' typ) = IsSubList ct ct' | |
IsElem e e = () | |
IsElem e a = IsElem' e a |
type family IsElem' a s :: Constraint Source #
You may use this type family to tell the type checker that your custom
type may be skipped as part of a link. This is useful for things like
that are optional in a URI and do not affect them if they are
omitted.QueryParam
>>>
data CustomThing
>>>
type instance IsElem' e (CustomThing :> s) = IsElem e s
Note that
is called, which will mutually recurse back to IsElem
if it exhausts all other options again.IsElem'
Once you have written a HasLink
instance for CustomThing
you are ready to go.
class HasLink endpoint where Source #
Construct a toLink for an endpoint.
Instances
A safe link datatype.
The only way of constructing a Link
is using safeLink
, which means any
Link
is guaranteed to be part of the mentioned API.
Instances
Show Link Source # | |
ToHttpApiData Link Source # | |
Defined in Servant.Links toUrlPiece :: Link -> Text # toEncodedUrlPiece :: Link -> Builder # toHeader :: Link -> ByteString # toQueryParam :: Link -> Text # |
:: (IsElem endpoint api, HasLink endpoint) | |
=> Proxy api | The whole API that this endpoint is a part of |
-> Proxy endpoint | The API endpoint you would like to point to |
-> MkLink endpoint Link |
Create a valid (by construction) relative URI with query params.
This function will only typecheck if endpoint
is part of the API api
Type-safe internal URIs