servant-0.19.1: A family of combinators for defining webservices APIs
Safe Haskell None
Language Haskell2010

Servant.API

Synopsis

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

Instances details
( TypeError ( PartialApplication ( HasLink :: k -> Constraint ) arr) :: Constraint ) => HasLink (arr :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink (arr :> sub) a Source #

Methods

toLink :: ( Link -> a) -> Proxy (arr :> sub) -> Link -> MkLink (arr :> sub) a Source #

HasLink sub => HasLink ( HttpVersion :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( HttpVersion :> sub) a Source #

HasLink sub => HasLink ( Vault :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( Vault :> sub) a Source #

HasLink sub => HasLink ( BasicAuth realm a :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( BasicAuth realm a :> sub) a Source #

Methods

toLink :: ( Link -> a0) -> Proxy ( BasicAuth realm a :> sub) -> Link -> MkLink ( BasicAuth realm a :> sub) a0 Source #

( ToHttpApiData v, HasLink sub) => HasLink ( CaptureAll sym v :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( CaptureAll sym v :> sub) a Source #

( ToHttpApiData v, HasLink sub) => HasLink ( Capture' mods sym v :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( Capture' mods sym v :> sub) a Source #

Methods

toLink :: ( Link -> a) -> Proxy ( Capture' mods sym v :> sub) -> Link -> MkLink ( Capture' mods sym v :> sub) a Source #

HasLink sub => HasLink ( Description s :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( Description s :> sub) a Source #

HasLink sub => HasLink ( Summary s :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( Summary s :> sub) a Source #

HasLink sub => HasLink ( AuthProtect tag :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( AuthProtect tag :> sub) a Source #

( HasLink sub, ToHttpApiData v) => HasLink ( Fragment v :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( Fragment v :> sub) a Source #

HasLink sub => HasLink ( IsSecure :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( IsSecure :> sub) a Source #

HasLink sub => HasLink ( Header' mods sym a :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( Header' mods sym a :> sub) a Source #

Methods

toLink :: ( Link -> a0) -> Proxy ( Header' mods sym a :> sub) -> Link -> MkLink ( Header' mods sym a :> sub) a0 Source #

( KnownSymbol sym, HasLink sub) => HasLink ( QueryFlag sym :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( QueryFlag sym :> sub) a Source #

( KnownSymbol sym, ToHttpApiData v, HasLink sub) => HasLink ( QueryParams sym v :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( QueryParams sym v :> sub) a Source #

( KnownSymbol sym, ToHttpApiData v, HasLink sub, SBoolI ( FoldRequired mods)) => HasLink ( QueryParam' mods sym v :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( QueryParam' mods sym v :> sub) a Source #

Methods

toLink :: ( Link -> a) -> Proxy ( QueryParam' mods sym v :> sub) -> Link -> MkLink ( QueryParam' mods sym v :> sub) a Source #

HasLink sub => HasLink ( RemoteHost :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( RemoteHost :> sub) a Source #

HasLink sub => HasLink ( ReqBody' mods ct a :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( ReqBody' mods ct a :> sub) a Source #

Methods

toLink :: ( Link -> a0) -> Proxy ( ReqBody' mods ct a :> sub) -> Link -> MkLink ( ReqBody' mods ct a :> sub) a0 Source #

HasLink sub => HasLink ( StreamBody' mods framing ct a :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( StreamBody' mods framing ct a :> sub) a Source #

Methods

toLink :: ( Link -> a0) -> Proxy ( StreamBody' mods framing ct a :> sub) -> Link -> MkLink ( StreamBody' mods framing ct a :> sub) a0 Source #

( KnownSymbol sym, HasLink sub) => HasLink (sym :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink (sym :> sub) a Source #

Methods

toLink :: ( Link -> a) -> Proxy (sym :> sub) -> Link -> MkLink (sym :> sub) a Source #

( TypeError ( NoInstanceForSub ( HasLink :: k2 -> Constraint ) ty) :: Constraint ) => HasLink (ty :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink (ty :> sub) a Source #

Methods

toLink :: ( Link -> a) -> Proxy (ty :> sub) -> Link -> MkLink (ty :> sub) a Source #

type MkLink (arr :> sub :: Type ) _1 Source #
Instance details

Defined in Servant.Links

type MkLink ( HttpVersion :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( Vault :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( Vault :> sub :: Type ) a = MkLink sub a
type MkLink ( BasicAuth realm a :> sub :: Type ) r Source #
Instance details

Defined in Servant.Links

type MkLink ( BasicAuth realm a :> sub :: Type ) r = MkLink sub r
type MkLink ( CaptureAll sym v :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( CaptureAll sym v :> sub :: Type ) a = [v] -> MkLink sub a
type MkLink ( Capture' mods sym v :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( Capture' mods sym v :> sub :: Type ) a = v -> MkLink sub a
type MkLink ( Description s :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( Summary s :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( Summary s :> sub :: Type ) a = MkLink sub a
type MkLink ( AuthProtect tag :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( AuthProtect tag :> sub :: Type ) a = MkLink sub a
type MkLink ( Fragment v :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( Fragment v :> sub :: Type ) a = v -> MkLink sub a
type MkLink ( IsSecure :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( Header' mods sym a :> sub :: Type ) r Source #
Instance details

Defined in Servant.Links

type MkLink ( Header' mods sym a :> sub :: Type ) r = MkLink sub r
type MkLink ( QueryFlag sym :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( QueryParams sym v :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( QueryParams sym v :> sub :: Type ) a = [v] -> MkLink sub a
type MkLink ( QueryParam' mods sym v :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( QueryParam' mods sym v :> sub :: Type ) a = If ( FoldRequired mods) v ( Maybe v) -> MkLink sub a
type MkLink ( RemoteHost :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( ReqBody' mods ct a :> sub :: Type ) r Source #
Instance details

Defined in Servant.Links

type MkLink ( ReqBody' mods ct a :> sub :: Type ) r = MkLink sub r
type MkLink ( StreamBody' mods framing ct a :> sub :: Type ) r Source #
Instance details

Defined in Servant.Links

type MkLink ( StreamBody' mods framing ct a :> sub :: Type ) r = MkLink sub r
type MkLink (sym :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink (sym :> sub :: Type ) a = MkLink sub a

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
:}

Constructors

a :<|> b infixr 3

Instances

Instances details
Bifunctor (:<|>) Source #
Instance details

Defined in Servant.API.Alternative

Methods

bimap :: (a -> b) -> (c -> d) -> (a :<|> c) -> b :<|> d Source #

first :: (a -> b) -> (a :<|> c) -> b :<|> c Source #

second :: (b -> c) -> (a :<|> b) -> a :<|> c Source #

Bitraversable (:<|>) Source #
Instance details

Defined in Servant.API.Alternative

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (a :<|> b) -> f (c :<|> d) Source #

Bifoldable (:<|>) Source #
Instance details

Defined in Servant.API.Alternative

Methods

bifold :: Monoid m => (m :<|> m) -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> (a :<|> b) -> m Source #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> (a :<|> b) -> c Source #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> (a :<|> b) -> c Source #

Biapplicative (:<|>) Source #
Instance details

Defined in Servant.API.Alternative

Methods

bipure :: a -> b -> a :<|> b Source #

(<<*>>) :: ((a -> b) :<|> (c -> d)) -> (a :<|> c) -> b :<|> d Source #

biliftA2 :: (a -> b -> c) -> (d -> e -> f) -> (a :<|> d) -> (b :<|> e) -> c :<|> f Source #

(*>>) :: (a :<|> b) -> (c :<|> d) -> c :<|> d Source #

(<<*) :: (a :<|> b) -> (c :<|> d) -> a :<|> b Source #

Functor ( (:<|>) a) Source #
Instance details

Defined in Servant.API.Alternative

Methods

fmap :: (a0 -> b) -> (a :<|> a0) -> a :<|> b Source #

(<$) :: a0 -> (a :<|> b) -> a :<|> a0 Source #

Foldable ( (:<|>) a) Source #
Instance details

Defined in Servant.API.Alternative

Methods

fold :: Monoid m => (a :<|> m) -> m Source #

foldMap :: Monoid m => (a0 -> m) -> (a :<|> a0) -> m Source #

foldMap' :: Monoid m => (a0 -> m) -> (a :<|> a0) -> m Source #

foldr :: (a0 -> b -> b) -> b -> (a :<|> a0) -> b Source #

foldr' :: (a0 -> b -> b) -> b -> (a :<|> a0) -> b Source #

foldl :: (b -> a0 -> b) -> b -> (a :<|> a0) -> b Source #

foldl' :: (b -> a0 -> b) -> b -> (a :<|> a0) -> b Source #

foldr1 :: (a0 -> a0 -> a0) -> (a :<|> a0) -> a0 Source #

foldl1 :: (a0 -> a0 -> a0) -> (a :<|> a0) -> a0 Source #

toList :: (a :<|> a0) -> [a0] Source #

null :: (a :<|> a0) -> Bool Source #

length :: (a :<|> a0) -> Int Source #

elem :: Eq a0 => a0 -> (a :<|> a0) -> Bool Source #

maximum :: Ord a0 => (a :<|> a0) -> a0 Source #

minimum :: Ord a0 => (a :<|> a0) -> a0 Source #

sum :: Num a0 => (a :<|> a0) -> a0 Source #

product :: Num a0 => (a :<|> a0) -> a0 Source #

Traversable ( (:<|>) a) Source #
Instance details

Defined in Servant.API.Alternative

Methods

traverse :: Applicative f => (a0 -> f b) -> (a :<|> a0) -> f (a :<|> b) Source #

sequenceA :: Applicative f => (a :<|> f a0) -> f (a :<|> a0) Source #

mapM :: Monad m => (a0 -> m b) -> (a :<|> a0) -> m (a :<|> b) Source #

sequence :: Monad m => (a :<|> m a0) -> m (a :<|> a0) Source #

( HasLink a, HasLink b) => HasLink (a :<|> b :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink (a :<|> b) a Source #

( Bounded a, Bounded b) => Bounded (a :<|> b) Source #
Instance details

Defined in Servant.API.Alternative

( Eq a, Eq b) => Eq (a :<|> b) Source #
Instance details

Defined in Servant.API.Alternative

( Show a, Show b) => Show (a :<|> b) Source #
Instance details

Defined in Servant.API.Alternative

( Semigroup a, Semigroup b) => Semigroup (a :<|> b) Source #
Instance details

Defined in Servant.API.Alternative

( Monoid a, Monoid b) => Monoid (a :<|> b) Source #
Instance details

Defined in Servant.API.Alternative

type MkLink (a :<|> b :: Type ) r Source #
Instance details

Defined in Servant.Links

Type-level combinator for alternative endpoints: :<|>

data EmptyAPI Source #

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.

Constructors

EmptyAPI

Type-level combinator for an empty API: EmptyAPI

data Strict Source #

Strictly parsed argument. Not wrapped.

Instances

Instances details
( KnownSymbol h, ToHttpApiData v) => AddHeader h v ( Headers (fst ': rest) a) ( Headers ( Header h v ': (fst ': rest)) a) Source #
Instance details

Defined in Servant.API.ResponseHeaders

Methods

addOptionalHeader :: ResponseHeader h v -> Headers (fst ': rest) a -> Headers ( Header h v ': (fst ': rest)) a

HasResponseHeader h a ( Header h a ': rest) Source #
Instance details

Defined in Servant.API.ResponseHeaders

( KnownSymbol h, GetHeadersFromHList rest, ToHttpApiData v) => GetHeaders' ( Header h v ': rest) Source #
Instance details

Defined in Servant.API.ResponseHeaders

Methods

getHeaders' :: Headers ( Header h v ': rest) a -> [ Header0 ]

( FromHttpApiData v, BuildHeadersTo xs, KnownSymbol h) => BuildHeadersTo ( Header h v ': xs) Source #
Instance details

Defined in Servant.API.ResponseHeaders

data Lenient Source #

Leniently parsed argument, i.e. parsing never fail. Wrapped in Either Text .

data Optional Source #

Optional argument. Wrapped in Maybe .

Instances

Instances details
( KnownSymbol h, ToHttpApiData v) => AddHeader h v ( Headers (fst ': rest) a) ( Headers ( Header h v ': (fst ': rest)) a) Source #
Instance details

Defined in Servant.API.ResponseHeaders

Methods

addOptionalHeader :: ResponseHeader h v -> Headers (fst ': rest) a -> Headers ( Header h v ': (fst ': rest)) a

HasResponseHeader h a ( Header h a ': rest) Source #
Instance details

Defined in Servant.API.ResponseHeaders

( KnownSymbol h, GetHeadersFromHList rest, ToHttpApiData v) => GetHeaders' ( Header h v ': rest) Source #
Instance details

Defined in Servant.API.ResponseHeaders

Methods

getHeaders' :: Headers ( Header h v ': rest) a -> [ Header0 ]

( FromHttpApiData v, BuildHeadersTo xs, KnownSymbol h) => BuildHeadersTo ( Header h v ': xs) Source #
Instance details

Defined in Servant.API.ResponseHeaders

data Required Source #

Required argument. Not wrapped.

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

Instances details
( ToHttpApiData v, HasLink sub) => HasLink ( CaptureAll sym v :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( CaptureAll sym v :> sub) a Source #

type MkLink ( CaptureAll sym v :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( CaptureAll sym v :> sub :: Type ) a = [v] -> MkLink sub a

data Capture' (mods :: [*]) (sym :: Symbol ) (a :: *) Source #

Capture which can be modified. For example with Description .

Instances

Instances details
( ToHttpApiData v, HasLink sub) => HasLink ( Capture' mods sym v :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( Capture' mods sym v :> sub) a Source #

Methods

toLink :: ( Link -> a) -> Proxy ( Capture' mods sym v :> sub) -> Link -> MkLink ( Capture' mods sym v :> sub) a Source #

type MkLink ( Capture' mods sym v :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( Capture' mods sym v :> sub :: Type ) a = v -> MkLink sub a

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: Capture and CaptureAll

data Header' (mods :: [*]) (sym :: Symbol ) (a :: *) Source #

Instances

Instances details
( KnownSymbol h, ToHttpApiData v) => AddHeader h v ( Headers (fst ': rest) a) ( Headers ( Header h v ': (fst ': rest)) a) Source #
Instance details

Defined in Servant.API.ResponseHeaders

Methods

addOptionalHeader :: ResponseHeader h v -> Headers (fst ': rest) a -> Headers ( Header h v ': (fst ': rest)) a

HasResponseHeader h a ( Header h a ': rest) Source #
Instance details

Defined in Servant.API.ResponseHeaders

HasLink sub => HasLink ( Header' mods sym a :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( Header' mods sym a :> sub) a Source #

Methods

toLink :: ( Link -> a0) -> Proxy ( Header' mods sym a :> sub) -> Link -> MkLink ( Header' mods sym a :> sub) a0 Source #

( KnownSymbol h, GetHeadersFromHList rest, ToHttpApiData v) => GetHeaders' ( Header h v ': rest) Source #
Instance details

Defined in Servant.API.ResponseHeaders

Methods

getHeaders' :: Headers ( Header h v ': rest) a -> [ Header0 ]

( FromHttpApiData v, BuildHeadersTo xs, KnownSymbol h) => BuildHeadersTo ( Header h v ': xs) Source #
Instance details

Defined in Servant.API.ResponseHeaders

type MkLink ( Header' mods sym a :> sub :: Type ) r Source #
Instance details

Defined in Servant.Links

type MkLink ( Header' mods sym a :> sub :: Type ) r = MkLink sub r

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

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]

Instances

Instances details
( KnownSymbol sym, HasLink sub) => HasLink ( QueryFlag sym :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( QueryFlag sym :> sub) a Source #

type MkLink ( QueryFlag sym :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

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&param[]=val2 and so on. Note that servant doesn't actually require the [] s and will fetch the values just fine with param=val1&param=val2 , too.

Example:

>>> -- /books?authors[]=<author1>&authors[]=<author2>&...
>>> type MyApi = "books" :> QueryParams "authors" Text :> Get '[JSON] [Book]

Instances

Instances details
( KnownSymbol sym, ToHttpApiData v, HasLink sub) => HasLink ( QueryParams sym v :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( QueryParams sym v :> sub) a Source #

type MkLink ( QueryParams sym v :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( QueryParams sym v :> sub :: Type ) a = [v] -> MkLink sub a

data QueryParam' (mods :: [*]) (sym :: Symbol ) (a :: *) Source #

QueryParam which can be Required , Lenient , or modified otherwise.

Instances

Instances details
( KnownSymbol sym, ToHttpApiData v, HasLink sub, SBoolI ( FoldRequired mods)) => HasLink ( QueryParam' mods sym v :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( QueryParam' mods sym v :> sub) a Source #

Methods

toLink :: ( Link -> a) -> Proxy ( QueryParam' mods sym v :> sub) -> Link -> MkLink ( QueryParam' mods sym v :> sub) a Source #

type MkLink ( QueryParam' mods sym v :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( QueryParam' mods sym v :> sub :: Type ) 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 Fragment (a :: *) Source #

Document the URI fragment in API. Useful in combination with Link .

Example:

>>> -- /post#TRACKING
>>> type MyApi = "post" :> Fragment Text :> Get '[JSON] Tracking

Instances

Instances details
AtLeastOneFragment ( Fragment a) Source #
Instance details

Defined in Servant.API.TypeLevel

( HasLink sub, ToHttpApiData v) => HasLink ( Fragment v :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( Fragment v :> sub) a Source #

type MkLink ( Fragment v :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( Fragment v :> sub :: Type ) a = v -> MkLink sub a

Documenting the fragment of the URI : Fragment

data ReqBody' (mods :: [*]) (contentTypes :: [*]) (a :: *) Source #

Note: ReqBody' is always Required .

Instances

Instances details
HasLink sub => HasLink ( ReqBody' mods ct a :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( ReqBody' mods ct a :> sub) a Source #

Methods

toLink :: ( Link -> a0) -> Proxy ( ReqBody' mods ct a :> sub) -> Link -> MkLink ( ReqBody' mods ct a :> sub) a0 Source #

type MkLink ( ReqBody' mods ct a :> sub :: Type ) r Source #
Instance details

Defined in Servant.Links

type MkLink ( ReqBody' mods ct a :> sub :: Type ) r = MkLink sub r

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

Instances details
HasLink sub => HasLink ( RemoteHost :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( RemoteHost :> sub) a Source #

type MkLink ( RemoteHost :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

Retrieving the IP of the client

data IsSecure Source #

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.

Constructors

Secure

the connection to the server is secure (HTTPS)

NotSecure

the connection to the server is not secure (HTTP)

Instances

Instances details
Eq IsSecure Source #
Instance details

Defined in Servant.API.IsSecure

Ord IsSecure Source #
Instance details

Defined in Servant.API.IsSecure

Read IsSecure Source #
Instance details

Defined in Servant.API.IsSecure

Show IsSecure Source #
Instance details

Defined in Servant.API.IsSecure

Generic IsSecure Source #
Instance details

Defined in Servant.API.IsSecure

HasLink sub => HasLink ( IsSecure :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( IsSecure :> sub) a Source #

type Rep IsSecure Source #
Instance details

Defined in Servant.API.IsSecure

type Rep IsSecure = D1 (' MetaData "IsSecure" "Servant.API.IsSecure" "servant-0.19.1-BZaZ2hTnOxc1hRbbpN6lAP" ' False ) ( C1 (' MetaCons "Secure" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: C1 (' MetaCons "NotSecure" ' PrefixI ' False ) ( U1 :: Type -> Type ))
type MkLink ( IsSecure :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

Is the request made through HTTPS?

type Vault = Vault RealWorld Source #

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

Instances details
HasLink sub => HasLink ( WithNamedContext name context sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( WithNamedContext name context sub) a Source #

Methods

toLink :: ( Link -> a) -> Proxy ( WithNamedContext name context sub) -> Link -> MkLink ( WithNamedContext name context sub) a Source #

type MkLink ( WithNamedContext name context sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( WithNamedContext name context sub :: Type ) a = MkLink sub a

Access context entries in combinators in servant-server

Actual endpoints, distinguished by HTTP method

data StdMethod Source #

HTTP standard method (as defined by RFC 2616, and PATCH which is defined by RFC 5789).

Instances

Instances details
Bounded StdMethod
Instance details

Defined in Network.HTTP.Types.Method

Enum StdMethod
Instance details

Defined in Network.HTTP.Types.Method

Eq StdMethod
Instance details

Defined in Network.HTTP.Types.Method

Ord StdMethod
Instance details

Defined in Network.HTTP.Types.Method

Read StdMethod
Instance details

Defined in Network.HTTP.Types.Method

Show StdMethod
Instance details

Defined in Network.HTTP.Types.Method

Ix StdMethod
Instance details

Defined in Network.HTTP.Types.Method

ReflectMethod ' PATCH Source #
Instance details

Defined in Servant.API.Verbs

ReflectMethod ' OPTIONS Source #
Instance details

Defined in Servant.API.Verbs

ReflectMethod ' CONNECT Source #
Instance details

Defined in Servant.API.Verbs

ReflectMethod ' TRACE Source #
Instance details

Defined in Servant.API.Verbs

ReflectMethod ' DELETE Source #
Instance details

Defined in Servant.API.Verbs

ReflectMethod ' PUT Source #
Instance details

Defined in Servant.API.Verbs

ReflectMethod ' HEAD Source #
Instance details

Defined in Servant.API.Verbs

ReflectMethod ' POST Source #
Instance details

Defined in Servant.API.Verbs

ReflectMethod ' GET Source #
Instance details

Defined in Servant.API.Verbs

type GetResetContent = Verb ' GET 205 Source #

GET with 205 status code.

type PutAccepted = Verb ' PUT 202 Source #

PUT with 202 status code.

type PostAccepted = Verb ' POST 202 Source #

POST with 202 status code.

type GetAccepted = Verb ' GET 202 Source #

GET with 202 status code.

type PutCreated = Verb ' PUT 201 Source #

PUT with 201 status code.

type PostCreated = Verb ' POST 201 Source #

POST with 201 status code.

type Patch = Verb ' PATCH 200 Source #

PATCH with 200 status code.

type Delete = Verb ' DELETE 200 Source #

DELETE with 200 status code.

type Put = Verb ' PUT 200 Source #

PUT with 200 status code.

type Post = Verb ' POST 200 Source #

POST with 200 status code.

type Get = Verb ' GET 200 Source #

GET with 200 status code.

data NoContentVerb (method :: k1) Source #

NoContentVerb is a specific type to represent NoContent responses. It does not require either a list of content types (because there's no content) or a status code (because it should always be 204).

Instances

Instances details
HasLink ( NoContentVerb m :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( NoContentVerb m) a Source #

Generic ( NoContentVerb method) Source #
Instance details

Defined in Servant.API.Verbs

Associated Types

type Rep ( NoContentVerb method) :: Type -> Type Source #

type MkLink ( NoContentVerb m :: Type ) r Source #
Instance details

Defined in Servant.Links

type Rep ( NoContentVerb method) Source #
Instance details

Defined in Servant.API.Verbs

type Rep ( NoContentVerb method) = D1 (' MetaData "NoContentVerb" "Servant.API.Verbs" "servant-0.19.1-BZaZ2hTnOxc1hRbbpN6lAP" ' False ) ( V1 :: Type -> Type )

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

Instances

Instances details
HasLink ( Verb m s ct a :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( Verb m s ct a) a Source #

Methods

toLink :: ( Link -> a0) -> Proxy ( Verb m s ct a) -> Link -> MkLink ( Verb m s ct a) a0 Source #

Generic ( Verb method statusCode contentTypes a) Source #
Instance details

Defined in Servant.API.Verbs

Associated Types

type Rep ( Verb method statusCode contentTypes a) :: Type -> Type Source #

Methods

from :: Verb method statusCode contentTypes a -> Rep ( Verb method statusCode contentTypes a) x Source #

to :: Rep ( Verb method statusCode contentTypes a) x -> Verb method statusCode contentTypes a Source #

AtLeastOneFragment ( Verb m s ct typ) Source #

If fragment appeared in API endpoint twice, compile-time error would be raised.

>>> -- type FailAPI = Fragment Bool :> Fragment Int :> Get '[JSON] NoContent
>>> instance AtLeastOneFragment FailAPI
...
...Only one Fragment allowed per endpoint in api...
...
...In the instance declaration for...
Instance details

Defined in Servant.API.TypeLevel

type MkLink ( Verb m s ct a :: Type ) r Source #
Instance details

Defined in Servant.Links

type MkLink ( Verb m s ct a :: Type ) r = r
type Rep ( Verb method statusCode contentTypes a) Source #
Instance details

Defined in Servant.API.Verbs

type Rep ( Verb method statusCode contentTypes a) = D1 (' MetaData "Verb" "Servant.API.Verbs" "servant-0.19.1-BZaZ2hTnOxc1hRbbpN6lAP" ' False ) ( V1 :: Type -> Type )

type family Unique xs :: Constraint where ... Source #

Equations

Unique xs = If (Nubbed xs == ' True ) (() :: Constraint ) ( TypeError (DuplicateElementError xs))

inject :: UElem x xs => f x -> NS f xs Source #

type IsMember (a :: u) (as :: [u]) = ( Unique as, CheckElemIsMember a as, UElem a as) Source #

data UVerb (method :: StdMethod ) (contentTypes :: [*]) (as :: [*]) Source #

A variant of Verb that can have any of a number of response values and status codes.

FUTUREWORK: it would be nice to make Verb a special case of UVerb , and only write instances for HasServer etc. for the latter, getting them for the former for free. Something like:

type Verb method statusCode contentTypes a = UVerb method contentTypes [WithStatus statusCode a]

Backwards compatibility is tricky, though: this type alias would mean people would have to use respond instead of pure or return , so all old handlers would have to be rewritten.

Instances

Instances details
HasLink ( UVerb m ct a :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( UVerb m ct a) a Source #

Methods

toLink :: ( Link -> a0) -> Proxy ( UVerb m ct a) -> Link -> MkLink ( UVerb m ct a) a0 Source #

AtLeastOneFragment ( UVerb m cts as) Source #
Instance details

Defined in Servant.API.TypeLevel

type MkLink ( UVerb m ct a :: Type ) r Source #
Instance details

Defined in Servant.Links

type MkLink ( UVerb m ct a :: Type ) r = r

newtype WithStatus (k :: Nat ) a Source #

A simple newtype wrapper that pairs a type with its status code. It implements all the content types that Servant ships with by default.

Constructors

WithStatus a

Instances

Instances details
MimeUnrender OctetStream a => MimeUnrender OctetStream ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeUnrender FormUrlEncoded a => MimeUnrender FormUrlEncoded ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeUnrender PlainText a => MimeUnrender PlainText ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeUnrender JSON a => MimeUnrender JSON ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeRender OctetStream a => MimeRender OctetStream ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeRender FormUrlEncoded a => MimeRender FormUrlEncoded ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeRender PlainText a => MimeRender PlainText ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeRender JSON a => MimeRender JSON ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

Eq a => Eq ( WithStatus k a) Source #
Instance details

Defined in Servant.API.UVerb

Show a => Show ( WithStatus k a) Source #
Instance details

Defined in Servant.API.UVerb

KnownStatus n => HasStatus ( WithStatus n a) Source #

an instance of this typeclass assigns a HTTP status code to a return type

Example:

   data NotFoundError = NotFoundError String

   instance HasStatus NotFoundError where
     type StatusOf NotFoundError = 404

You can also use the convience newtype wrapper WithStatus if you want to avoid writing a HasStatus instance manually. It also has the benefit of showing the status code in the type; which might aid in readability.

Instance details

Defined in Servant.API.UVerb

Associated Types

type StatusOf ( WithStatus n a) :: Nat Source #

type StatusOf ( WithStatus n a) Source #
Instance details

Defined in Servant.API.UVerb

type StatusOf ( WithStatus n a) = n

type family Statuses (as :: [*]) :: [ Nat ] Source #

Instances

Instances details
type Statuses ('[] :: [ Type ]) Source #
Instance details

Defined in Servant.API.UVerb

type Statuses ('[] :: [ Type ]) = '[] :: [ Nat ]
type Statuses (a ': as) Source #
Instance details

Defined in Servant.API.UVerb

type Statuses (a ': as) = StatusOf a ': Statuses as

type family Statuses (as :: [*]) :: [ Nat ] Source #

Instances

Instances details
type Statuses ('[] :: [ Type ]) Source #
Instance details

Defined in Servant.API.UVerb

type Statuses ('[] :: [ Type ]) = '[] :: [ Nat ]
type Statuses (a ': as) Source #
Instance details

Defined in Servant.API.UVerb

type Statuses (a ': as) = StatusOf a ': Statuses as

class KnownStatus ( StatusOf a) => HasStatus (a :: *) Source #

Associated Types

type StatusOf (a :: *) :: Nat Source #

Instances

Instances details
HasStatus NoContent Source #

If an API can respond with NoContent we assume that this will happen with the status code 204 No Content. If this needs to be overridden, WithStatus can be used.

Instance details

Defined in Servant.API.UVerb

KnownStatus n => HasStatus ( WithStatus n a) Source #

an instance of this typeclass assigns a HTTP status code to a return type

Example:

   data NotFoundError = NotFoundError String

   instance HasStatus NotFoundError where
     type StatusOf NotFoundError = 404

You can also use the convience newtype wrapper WithStatus if you want to avoid writing a HasStatus instance manually. It also has the benefit of showing the status code in the type; which might aid in readability.

Instance details

Defined in Servant.API.UVerb

Associated Types

type StatusOf ( WithStatus n a) :: Nat Source #

statusOf :: forall a proxy. HasStatus a => proxy a -> Status Source #

Sub-APIs defined as records of routes

data NamedRoutes (api :: * -> *) Source #

Combinator for embedding a record of named routes into a Servant API type.

Instances

Instances details
( HasLink ( ToServantApi routes), forall a. GLink routes a) => HasLink ( NamedRoutes routes :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( NamedRoutes routes) a Source #

type MkLink ( NamedRoutes routes :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( NamedRoutes routes :: Type ) a = routes ( AsLink a)

class GServantProduct f Source #

Minimal complete definition

gtoServant, gfromServant

Instances

Instances details
GServantProduct ( K1 i c :: Type -> Type ) Source #
Instance details

Defined in Servant.API.Generic

Associated Types

type GToServant ( K1 i c)

Methods

gtoServant :: K1 i c p -> GToServant ( K1 i c)

gfromServant :: GToServant ( K1 i c) -> K1 i c p

( GServantProduct l, GServantProduct r) => GServantProduct (l :*: r) Source #
Instance details

Defined in Servant.API.Generic

Associated Types

type GToServant (l :*: r)

Methods

gtoServant :: (l :*: r) p -> GToServant (l :*: r)

gfromServant :: GToServant (l :*: r) -> (l :*: r) p

GServantProduct f => GServantProduct ( M1 i c f) Source #
Instance details

Defined in Servant.API.Generic

Associated Types

type GToServant ( M1 i c f)

Methods

gtoServant :: M1 i c f p -> GToServant ( M1 i c f)

gfromServant :: GToServant ( M1 i c f) -> M1 i c f p

data AsApi Source #

A type that specifies that an API record contains an API definition. Only useful at type-level.

Instances

Instances details
GenericMode AsApi Source #
Instance details

Defined in Servant.API.Generic

Associated Types

type AsApi :- api Source #

type AsApi :- api Source #
Instance details

Defined in Servant.API.Generic

type AsApi :- api = api

type ToServant routes mode = GToServant ( Rep (routes mode)) Source #

Turns a generic product type into a tree of :<|> combinators.

class GenericMode mode Source #

A class with a type family that applies an appropriate type family to the api parameter. For example, AsApi will leave api untouched, while AsServerT m will produce ServerT api m .

Associated Types

type mode :- api :: * infixl 0 Source #

Instances

Instances details
GenericMode AsApi Source #
Instance details

Defined in Servant.API.Generic

Associated Types

type AsApi :- api Source #

GenericMode ( AsLink a) Source #
Instance details

Defined in Servant.Links

Associated Types

type ( AsLink a) :- api Source #

type GenericServant routes mode = ( GenericMode mode, Generic (routes mode), GServantProduct ( Rep (routes mode))) Source #

A constraint alias, for work with mode and routes .

toServant :: GenericServant routes mode => routes mode -> ToServant routes mode Source #

See ToServant , but at value-level.

fromServant :: GenericServant routes mode => ToServant routes mode -> routes mode Source #

Inverse of toServant .

This can be used to turn generated values such as client functions into records.

You may need to provide a type signature for the output type (your record type).

Streaming endpoints, distinguished by HTTP method

data NetstringFraming Source #

The netstring framing strategy as defined by djb: http://cr.yp.to/proto/netstrings.txt

Any string of 8-bit bytes may be encoded as [len]":"[string]"," . Here [string] is the string and [len] is a nonempty sequence of ASCII digits giving the length of [string] in decimal. The ASCII digits are 30 for 0, 31 for 1, and so on up through 39 for 9. Extra zeros at the front of [len] are prohibited: [len] begins with 30 exactly when [string] is empty.

For example, the string "hello world!" is encoded as 32 3a 68 65 6c 6c 6f 20 77 6f 72 6c 64 21 2c , i.e., "12:hello world!," . The empty string is encoded as "0:," .

data NewlineFraming Source #

A simple framing strategy that has no header, and inserts a newline character after each frame. This assumes that it is used with a Content-Type that encodes without newlines (e.g. JSON).

data NoFraming 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

Instances details
FramingUnrender NoFraming Source #

As NoFraming doesn't have frame separators, we take the chunks as given and try to convert them one by one.

That works well when a is a ByteString .

Instance details

Defined in Servant.API.Stream

FramingRender NoFraming Source #
Instance details

Defined in Servant.API.Stream

class FramingUnrender strategy where Source #

The FramingUnrender class provides the logic for parsing a framing strategy.

class FramingRender strategy where Source #

The FramingRender class provides the logic for emitting a framing strategy. The strategy transforms a SourceT m a into SourceT m ByteString , therefore it can prepend, append and intercalate framing structure around chunks.

Note: as the Monad m is generic, this is pure transformation.

class FromSourceIO chunk a | a -> chunk where Source #

FromSourceIO 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.

Instances

Instances details
MonadIO m => FromSourceIO a ( SourceT m a) Source #
Instance details

Defined in Servant.API.Stream

class ToSourceIO chunk a | a -> chunk where Source #

ToSourceIO 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.

Instances

Instances details
ToSourceIO a [a] Source #
Instance details

Defined in Servant.API.Stream

ToSourceIO a ( NonEmpty a) Source #
Instance details

Defined in Servant.API.Stream

SourceToSourceIO m => ToSourceIO chunk ( SourceT m chunk) Source #

Relax to use auxiliary class, have m

Instance details

Defined in Servant.API.Stream

type SourceIO = SourceT IO Source #

Stream endpoints may be implemented as producing a SourceIO chunk .

Clients reading from streaming endpoints can be implemented as consuming a SourceIO chunk .

data StreamBody' (mods :: [*]) (framing :: *) (contentType :: *) (a :: *) Source #

Instances

Instances details
HasLink sub => HasLink ( StreamBody' mods framing ct a :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( StreamBody' mods framing ct a :> sub) a Source #

Methods

toLink :: ( Link -> a0) -> Proxy ( StreamBody' mods framing ct a :> sub) -> Link -> MkLink ( StreamBody' mods framing ct a :> sub) a0 Source #

Generic ( StreamBody' mods framing contentType a) Source #
Instance details

Defined in Servant.API.Stream

Associated Types

type Rep ( StreamBody' mods framing contentType a) :: Type -> Type Source #

Methods

from :: StreamBody' mods framing contentType a -> Rep ( StreamBody' mods framing contentType a) x Source #

to :: Rep ( StreamBody' mods framing contentType a) x -> StreamBody' mods framing contentType a Source #

type MkLink ( StreamBody' mods framing ct a :> sub :: Type ) r Source #
Instance details

Defined in Servant.Links

type MkLink ( StreamBody' mods framing ct a :> sub :: Type ) r = MkLink sub r
type Rep ( StreamBody' mods framing contentType a) Source #
Instance details

Defined in Servant.API.Stream

type Rep ( StreamBody' mods framing contentType a) = D1 (' MetaData "StreamBody'" "Servant.API.Stream" "servant-0.19.1-BZaZ2hTnOxc1hRbbpN6lAP" ' False ) ( V1 :: Type -> Type )

type StreamBody = StreamBody' '[] Source #

A stream request body.

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. Type synonyms are provided for standard methods.

Instances

Instances details
HasLink ( Stream m status fr ct a :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( Stream m status fr ct a) a Source #

Methods

toLink :: ( Link -> a0) -> Proxy ( Stream m status fr ct a) -> Link -> MkLink ( Stream m status fr ct a) a0 Source #

Generic ( Stream method status framing contentType a) Source #
Instance details

Defined in Servant.API.Stream

Associated Types

type Rep ( Stream method status framing contentType a) :: Type -> Type Source #

Methods

from :: Stream method status framing contentType a -> Rep ( Stream method status framing contentType a) x Source #

to :: Rep ( Stream method status framing contentType a) x -> Stream method status framing contentType a Source #

type MkLink ( Stream m status fr ct a :: Type ) r Source #
Instance details

Defined in Servant.Links

type MkLink ( Stream m status fr ct a :: Type ) r = r
type Rep ( Stream method status framing contentType a) Source #
Instance details

Defined in Servant.API.Stream

type Rep ( Stream method status framing contentType a) = D1 (' MetaData "Stream" "Servant.API.Stream" "servant-0.19.1-BZaZ2hTnOxc1hRbbpN6lAP" ' False ) ( V1 :: Type -> Type )

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.

Instances

Instances details
HasLink sub => HasLink ( BasicAuth realm a :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( BasicAuth realm a :> sub) a Source #

Methods

toLink :: ( Link -> a0) -> Proxy ( BasicAuth realm a :> sub) -> Link -> MkLink ( BasicAuth realm a :> sub) a0 Source #

type MkLink ( BasicAuth realm a :> sub :: Type ) r Source #
Instance details

Defined in Servant.Links

type MkLink ( BasicAuth realm a :> sub :: Type ) r = MkLink sub r

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 String support is not perfect \
 \but it's still very readable."
:> Get '[JSON] Book
:}

Instances

Instances details
HasLink sub => HasLink ( Description s :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( Description s :> sub) a Source #

type MkLink ( Description s :> sub :: Type ) a Source #
Instance details

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

Instances

Instances details
HasLink sub => HasLink ( Summary s :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( Summary s :> sub) a Source #

type MkLink ( Summary s :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( Summary s :> sub :: Type ) a = MkLink sub a

Content Types

data NoContent Source #

A type for responses without content-body.

Constructors

NoContent

Instances

Instances details
Eq NoContent Source #
Instance details

Defined in Servant.API.ContentTypes

Read NoContent Source #
Instance details

Defined in Servant.API.ContentTypes

Show NoContent Source #
Instance details

Defined in Servant.API.ContentTypes

Generic NoContent Source #
Instance details

Defined in Servant.API.ContentTypes

NFData NoContent Source #
Instance details

Defined in Servant.API.ContentTypes

HasStatus NoContent Source #

If an API can respond with NoContent we assume that this will happen with the status code 204 No Content. If this needs to be overridden, WithStatus can be used.

Instance details

Defined in Servant.API.UVerb

AllMime (ctyp ': (ctyp' ': ctyps)) => AllMimeRender (ctyp ': (ctyp' ': ctyps)) NoContent Source #
Instance details

Defined in Servant.API.ContentTypes

Methods

allMimeRender :: Proxy (ctyp ': (ctyp' ': ctyps)) -> NoContent -> [( MediaType , ByteString )] Source #

Accept ctyp => AllMimeRender '[ctyp] NoContent Source #
Instance details

Defined in Servant.API.ContentTypes

type Rep NoContent Source #
Instance details

Defined in Servant.API.ContentTypes

type Rep NoContent = D1 (' MetaData "NoContent" "Servant.API.ContentTypes" "servant-0.19.1-BZaZ2hTnOxc1hRbbpN6lAP" ' False ) ( C1 (' MetaCons "NoContent" ' PrefixI ' False ) ( U1 :: Type -> Type ))
type StatusOf NoContent Source #
Instance details

Defined in Servant.API.UVerb

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

Minimal complete definition

mimeUnrender | mimeUnrenderWithType

Methods

mimeUnrender :: Proxy ctype -> ByteString -> Either String a Source #

mimeUnrenderWithType :: Proxy ctype -> MediaType -> ByteString -> Either String a Source #

Variant which is given the actual MediaType provided by the other party.

In the most cases you don't want to branch based on the MediaType . See pr552 for a motivating example.

Instances

Instances details
MimeUnrender OctetStream ByteString Source #
Right . toStrict
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender OctetStream ByteString Source #
Right . id
Instance details

Defined in Servant.API.ContentTypes

FromForm a => MimeUnrender FormUrlEncoded a Source #

urlDecodeAsForm Note that the mimeUnrender p (mimeRender p x) == Right x law only holds if every element of x is non-null (i.e., not ("", "") )

Instance details

Defined in Servant.API.ContentTypes

MimeUnrender PlainText String Source #
Right . BC.unpack
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender PlainText Text Source #
left show . TextS.decodeUtf8' . toStrict
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender PlainText Text Source #
left show . TextL.decodeUtf8'
Instance details

Defined in Servant.API.ContentTypes

FromJSON a => MimeUnrender JSON a Source #

eitherDecode

Instance details

Defined in Servant.API.ContentTypes

MimeUnrender OctetStream a => MimeUnrender OctetStream ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeUnrender FormUrlEncoded a => MimeUnrender FormUrlEncoded ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeUnrender PlainText a => MimeUnrender PlainText ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeUnrender JSON a => MimeUnrender JSON ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

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

Instances

Instances details
MimeRender OctetStream ByteString Source #

fromStrict

Instance details

Defined in Servant.API.ContentTypes

MimeRender OctetStream ByteString Source #
id
Instance details

Defined in Servant.API.ContentTypes

ToForm a => MimeRender FormUrlEncoded a Source #

urlEncodeAsForm Note that the mimeUnrender p (mimeRender p x) == Right x law only holds if every element of x is non-null (i.e., not ("", "") )

Instance details

Defined in Servant.API.ContentTypes

MimeRender PlainText String Source #
BC.pack
Instance details

Defined in Servant.API.ContentTypes

MimeRender PlainText Text Source #
fromStrict . TextS.encodeUtf8
Instance details

Defined in Servant.API.ContentTypes

MimeRender PlainText Text Source #

encodeUtf8

Instance details

Defined in Servant.API.ContentTypes

ToJSON a => MimeRender JSON a Source #

encode

Instance details

Defined in Servant.API.ContentTypes

MimeRender OctetStream a => MimeRender OctetStream ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeRender FormUrlEncoded a => MimeRender FormUrlEncoded ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeRender PlainText a => MimeRender PlainText ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeRender JSON a => MimeRender JSON ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

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")
:}

Minimal complete definition

contentType | contentTypes

data OctetStream Source #

Instances

Instances details
Accept OctetStream Source #
application/octet-stream
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender OctetStream ByteString Source #
Right . toStrict
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender OctetStream ByteString Source #
Right . id
Instance details

Defined in Servant.API.ContentTypes

MimeRender OctetStream ByteString Source #

fromStrict

Instance details

Defined in Servant.API.ContentTypes

MimeRender OctetStream ByteString Source #
id
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender OctetStream a => MimeUnrender OctetStream ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeRender OctetStream a => MimeRender OctetStream ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

data FormUrlEncoded Source #

Instances

Instances details
Accept FormUrlEncoded Source #
application/x-www-form-urlencoded
Instance details

Defined in Servant.API.ContentTypes

FromForm a => MimeUnrender FormUrlEncoded a Source #

urlDecodeAsForm Note that the mimeUnrender p (mimeRender p x) == Right x law only holds if every element of x is non-null (i.e., not ("", "") )

Instance details

Defined in Servant.API.ContentTypes

ToForm a => MimeRender FormUrlEncoded a Source #

urlEncodeAsForm Note that the mimeUnrender p (mimeRender p x) == Right x law only holds if every element of x is non-null (i.e., not ("", "") )

Instance details

Defined in Servant.API.ContentTypes

MimeUnrender FormUrlEncoded a => MimeUnrender FormUrlEncoded ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeRender FormUrlEncoded a => MimeRender FormUrlEncoded ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

data PlainText Source #

Instances

Instances details
Accept PlainText Source #
text/plain;charset=utf-8
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender PlainText String Source #
Right . BC.unpack
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender PlainText Text Source #
left show . TextS.decodeUtf8' . toStrict
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender PlainText Text Source #
left show . TextL.decodeUtf8'
Instance details

Defined in Servant.API.ContentTypes

MimeRender PlainText String Source #
BC.pack
Instance details

Defined in Servant.API.ContentTypes

MimeRender PlainText Text Source #
fromStrict . TextS.encodeUtf8
Instance details

Defined in Servant.API.ContentTypes

MimeRender PlainText Text Source #

encodeUtf8

Instance details

Defined in Servant.API.ContentTypes

MimeUnrender PlainText a => MimeUnrender PlainText ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

MimeRender PlainText a => MimeRender PlainText ( WithStatus _status a) Source #
Instance details

Defined in Servant.API.UVerb

Serializing and deserializing types based on Accept and Content-Type headers.

Response Headers

class HasResponseHeader h a headers Source #

Minimal complete definition

hlistLookupHeader

Instances

Instances details
HasResponseHeader h a rest => HasResponseHeader h a (first ': rest) Source #
Instance details

Defined in Servant.API.ResponseHeaders

Methods

hlistLookupHeader :: HList (first ': rest) -> ResponseHeader h a

HasResponseHeader h a ( Header h a ': rest) Source #
Instance details

Defined in Servant.API.ResponseHeaders

class AddHeader h v orig new | h v orig -> new, new -> h, new -> v, new -> orig Source #

Minimal complete definition

addOptionalHeader

Instances

Instances details
( KnownSymbol h, ToHttpApiData v, new ~ Headers '[ Header h v] a) => AddHeader h v a new Source #
Instance details

Defined in Servant.API.ResponseHeaders

Methods

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 #
Instance details

Defined in Servant.API.ResponseHeaders

Methods

addOptionalHeader :: ResponseHeader h v -> Headers (fst ': rest) a -> Headers ( Header h v ': (fst ': rest)) a

class GetHeaders ls where Source #

Instances

Instances details
GetHeadersFromHList hs => GetHeaders ( HList hs) Source #
Instance details

Defined in Servant.API.ResponseHeaders

GetHeaders' hs => GetHeaders ( Headers hs a) Source #
Instance details

Defined in Servant.API.ResponseHeaders

class BuildHeadersTo hs where Source #

Methods

buildHeadersTo :: [ Header ] -> HList hs Source #

Note: if there are multiple occurrences of a header in the argument, the values are interspersed with commas before deserialization (see RFC2616 Sec 4.2 )

data HList a where Source #

Constructors

HNil :: HList '[]
HCons :: ResponseHeader h x -> HList xs -> HList ( Header h x ': xs)

Instances

Instances details
NFDataHList xs => NFData ( HList xs) Source #
Instance details

Defined in Servant.API.ResponseHeaders

Methods

rnf :: HList xs -> () Source #

GetHeadersFromHList hs => GetHeaders ( HList hs) Source #
Instance details

Defined in Servant.API.ResponseHeaders

data Headers ls a Source #

Response Header objects. You should never need to construct one directly. Instead, use addOptionalHeader .

Constructors

Headers

Fields

Instances

Instances details
( KnownSymbol h, ToHttpApiData v) => AddHeader h v ( Headers (fst ': rest) a) ( Headers ( Header h v ': (fst ': rest)) a) Source #
Instance details

Defined in Servant.API.ResponseHeaders

Methods

addOptionalHeader :: ResponseHeader h v -> Headers (fst ': rest) a -> Headers ( Header h v ': (fst ': rest)) a

Functor ( Headers ls) Source #
Instance details

Defined in Servant.API.ResponseHeaders

Methods

fmap :: (a -> b) -> Headers ls a -> Headers ls b Source #

(<$) :: a -> Headers ls b -> Headers ls a Source #

(NFDataHList ls, NFData a) => NFData ( Headers ls a) Source #
Instance details

Defined in Servant.API.ResponseHeaders

Methods

rnf :: Headers ls a -> () Source #

GetHeaders' hs => GetHeaders ( Headers hs a) Source #
Instance details

Defined in Servant.API.ResponseHeaders

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:

  1. A simple value is wrapped in "Headers '[hdr]":
>>> let example1 = addHeader 5 "hi" :: Headers '[Header "someheader" Int] String;
>>> getHeaders example1
[("someheader","5")]
  1. 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
[]

lookupResponseHeader :: HasResponseHeader h a headers => Headers headers r -> ResponseHeader h a Source #

Look up a specific ResponseHeader, without having to know what position it is in the HList.

>>> let example1 = addHeader 5 "hi" :: Headers '[Header "someheader" Int] String
>>> let example2 = addHeader True example1 :: Headers '[Header "1st" Bool, Header "someheader" Int] String
>>> lookupResponseHeader example2 :: ResponseHeader "someheader" Int
Header 5
>>> lookupResponseHeader example2 :: ResponseHeader "1st" Bool
Header True

Usage of this function relies on an explicit type annotation of the header to be looked up. This can be done with type annotations on the result, or with an explicit type application. In this example, the type of header value is determined by the type-inference, we only specify the name of the header:

>>> :set -XTypeApplications
>>> case lookupResponseHeader @"1st" example2 of { Header b -> b ; _ -> False }
True

Since: 0.15

Untyped endpoints

data Raw Source #

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 functions from Servant.Server.StaticFiles to serve static files stored in a particular directory on your filesystem

Instances

Instances details
HasLink Raw Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink Raw a Source #

type MkLink Raw a Source #
Instance details

Defined in Servant.Links

type MkLink Raw a = a

Plugging in a wai Application , serving directories

FromHttpApiData and ToHttpApiData

class ToHttpApiData a where Source #

Convert value to HTTP API data.

WARNING : Do not derive this using DeriveAnyClass as the generated instance will loop indefinitely.

Minimal complete definition

toUrlPiece | toQueryParam

Methods

toUrlPiece :: a -> Text Source #

Convert to URL path piece.

toEncodedUrlPiece :: a -> Builder Source #

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 Source #

Convert to HTTP header value.

toQueryParam :: a -> Text Source #

Convert to query param value.

Instances

Instances details
ToHttpApiData Bool
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Char
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Double
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Float
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Int
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Int8
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Int16
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Int32
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Int64
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Integer
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Natural
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Ordering
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Word
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Word8
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Word16
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Word32
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Word64
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData ()
>>> toUrlPiece ()
"_"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData String
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Version
>>> toUrlPiece (Version [1, 2, 3] [])
"1.2.3"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData UTCTime
>>> toUrlPiece $ UTCTime (fromGregorian 2015 10 03) 864.5
"2015-10-03T00:14:24.5Z"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Text
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Text
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Void
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData All
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Any
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData SetCookie

Note: this instance works correctly for alphanumeric name and value

>>> let Right c = parseUrlPiece "SESSID=r2t5uvjq435r4q7ib3vtdjq120" :: Either Text SetCookie
>>> toUrlPiece c
"SESSID=r2t5uvjq435r4q7ib3vtdjq120"
>>> toHeader c
"SESSID=r2t5uvjq435r4q7ib3vtdjq120"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData ZonedTime
>>> toUrlPiece $ ZonedTime (LocalTime (fromGregorian 2015 10 03) (TimeOfDay 14 55 51.001)) utc
"2015-10-03T14:55:51.001+0000"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData LocalTime
>>> toUrlPiece $ LocalTime (fromGregorian 2015 10 03) (TimeOfDay 14 55 21.687)
"2015-10-03T14:55:21.687"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData TimeOfDay
>>> toUrlPiece $ TimeOfDay 14 55 23.1
"14:55:23.1"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData NominalDiffTime
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData DayOfWeek
>>> toUrlPiece Monday
"monday"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Day
>>> toUrlPiece (fromGregorian 2015 10 03)
"2015-10-03"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData QuarterOfYear
>>> toUrlPiece Q4
"q4"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Quarter
>>> import Data.Time.Calendar.Quarter.Compat (Quarter (..))
>>> MkQuarter 8040
2010-Q1
>>> toUrlPiece $ MkQuarter 8040
"2010-q1"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Month
>>> import Data.Time.Calendar.Month.Compat (Month (..))
>>> MkMonth 24482
2040-03
>>> toUrlPiece $ MkMonth 24482
"2040-03"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData UUID
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Link Source #
Instance details

Defined in Servant.Links

ToHttpApiData a => ToHttpApiData ( Maybe a)
>>> toUrlPiece (Just "Hello")
"just Hello"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData ( Min a)
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData ( Max a)
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData ( First a)
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData ( Last a)
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData ( Identity a)

Since: http-api-data-0.4.2

Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData ( First a)
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData ( Last a)
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData ( Dual a)
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData ( Sum a)
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData ( Product a)
Instance details

Defined in Web.Internal.HttpApiData

( ToHttpApiData a, ToHttpApiData b) => ToHttpApiData ( Either a b)
>>> toUrlPiece (Left "err" :: Either String Int)
"left err"
>>> toUrlPiece (Right 3 :: Either String Int)
"right 3"
Instance details

Defined in Web.Internal.HttpApiData

HasResolution a => ToHttpApiData ( Fixed a)

Note: this instance is not polykinded

Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData ( Const a b)

Since: http-api-data-0.4.2

Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData ( Tagged b a)

Note: this instance is not polykinded

Instance details

Defined in Web.Internal.HttpApiData

class FromHttpApiData a where Source #

Parse value from HTTP API data.

WARNING : Do not derive this using DeriveAnyClass as the generated instance will loop indefinitely.

Minimal complete definition

parseUrlPiece | parseQueryParam

Instances

Instances details
FromHttpApiData Bool
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Char
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Double
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Float
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Int
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Int8
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Int16
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Int32
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Int64
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Integer
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Natural
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Ordering
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Word
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Word8
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Word16
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Word32
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Word64
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData ()
>>> parseUrlPiece "_" :: Either Text ()
Right ()
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData String
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Version
>>> showVersion <$> parseUrlPiece "1.2.3"
Right "1.2.3"
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData UTCTime
>>> parseUrlPiece "2015-10-03T00:14:24Z" :: Either Text UTCTime
Right 2015-10-03 00:14:24 UTC
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Text
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Text
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Void

Parsing a Void value is always an error, considering Void as a data type with no constructors.

Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData All
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Any
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData SetCookie

Note: this instance works correctly for alphanumeric name and value

>>> parseUrlPiece "SESSID=r2t5uvjq435r4q7ib3vtdjq120" :: Either Text SetCookie
Right (SetCookie {setCookieName = "SESSID", setCookieValue = "r2t5uvjq435r4q7ib3vtdjq120", setCookiePath = Nothing, setCookieExpires = Nothing, setCookieMaxAge = Nothing, setCookieDomain = Nothing, setCookieHttpOnly = False, setCookieSecure = False, setCookieSameSite = Nothing})
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData ZonedTime
>>> parseUrlPiece "2015-10-03T14:55:01+0000" :: Either Text ZonedTime
Right 2015-10-03 14:55:01 +0000
>>> parseQueryParam "2016-12-31T01:00:00Z" :: Either Text ZonedTime
Right 2016-12-31 01:00:00 +0000
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData LocalTime
>>> parseUrlPiece "2015-10-03T14:55:01" :: Either Text LocalTime
Right 2015-10-03 14:55:01
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData TimeOfDay
>>> parseUrlPiece "14:55:01.333" :: Either Text TimeOfDay
Right 14:55:01.333
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData NominalDiffTime
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData DayOfWeek
>>> parseUrlPiece "Monday" :: Either Text DayOfWeek
Right Monday
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Day
>>> toGregorian <$> parseUrlPiece "2016-12-01"
Right (2016,12,1)
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData QuarterOfYear
>>> parseUrlPiece "q2" :: Either Text QuarterOfYear
Right Q2
>>> parseUrlPiece "Q3" :: Either Text QuarterOfYear
Right Q3
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Quarter
>>> parseUrlPiece "2021-q1" :: Either Text Quarter
Right 2021-Q1
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData Month
>>> parseUrlPiece "2021-01" :: Either Text Month
Right 2021-01
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData UUID
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData a => FromHttpApiData ( Maybe a)
>>> parseUrlPiece "Just 123" :: Either Text (Maybe Int)
Right (Just 123)
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData a => FromHttpApiData ( Min a)
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData a => FromHttpApiData ( Max a)
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData a => FromHttpApiData ( First a)
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData a => FromHttpApiData ( Last a)
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData a => FromHttpApiData ( Identity a)

Since: http-api-data-0.4.2

Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData a => FromHttpApiData ( First a)
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData a => FromHttpApiData ( Last a)
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData a => FromHttpApiData ( Dual a)
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData a => FromHttpApiData ( Sum a)
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData a => FromHttpApiData ( Product a)
Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData a => FromHttpApiData ( LenientData a)
Instance details

Defined in Web.Internal.HttpApiData

( FromHttpApiData a, FromHttpApiData b) => FromHttpApiData ( Either a b)
>>> parseUrlPiece "Right 123" :: Either Text (Either String Int)
Right (Right 123)
Instance details

Defined in Web.Internal.HttpApiData

HasResolution a => FromHttpApiData ( Fixed a)

Note: this instance is not polykinded

Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData a => FromHttpApiData ( Const a b)

Since: http-api-data-0.4.2

Instance details

Defined in Web.Internal.HttpApiData

FromHttpApiData a => FromHttpApiData ( Tagged b a)

Note: this instance is not polykinded

Instance details

Defined in Web.Internal.HttpApiData

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

Instances details
HasLink sub => HasLink ( AuthProtect tag :> sub :: Type ) Source #
Instance details

Defined in Servant.Links

Associated Types

type MkLink ( AuthProtect tag :> sub) a Source #

type MkLink ( AuthProtect tag :> sub :: Type ) a Source #
Instance details

Defined in Servant.Links

type MkLink ( AuthProtect tag :> sub :: Type ) a = MkLink sub a

General Authentication

Links

data URI Source #

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:

Constructors

URI

Instances

Instances details
Eq URI
Instance details

Defined in Network.URI

Data URI
Instance details

Defined in Network.URI

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> URI -> c URI Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c URI Source #

toConstr :: URI -> Constr Source #

dataTypeOf :: URI -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c URI ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c URI ) Source #

gmapT :: ( forall b. Data b => b -> b) -> URI -> URI Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> URI -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> URI -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> URI -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> URI -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> URI -> m URI Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> URI -> m URI Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> URI -> m URI Source #

Ord URI
Instance details

Defined in Network.URI

Show URI
Instance details

Defined in Network.URI

Generic URI
Instance details

Defined in Network.URI

Associated Types

type Rep URI :: Type -> Type Source #

NFData URI
Instance details

Defined in Network.URI

Methods

rnf :: URI -> () Source #

Lift URI
Instance details

Defined in Network.URI

type Rep URI
Instance details

Defined in Network.URI

type family IsElem endpoint api :: Constraint where ... Source #

Closed type family, check if endpoint is within api . Uses IsElem' if it exhausts all other options.

>>> ok (Proxy :: Proxy (IsElem ("hello" :> Get '[JSON] Int) SampleAPI))
OK
>>> ok (Proxy :: Proxy (IsElem ("bye" :> Get '[JSON] Int) SampleAPI))
...
... Could not ...
...

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 by a would match the URL represented by b , *not* whether a request represented by a matches the endpoints serving b (for the latter, use IsIn ).

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 QueryParam that are optional in a URI and do not affect them if they are omitted.

>>> data CustomThing
>>> type instance IsElem' e (CustomThing :> s) = IsElem e s

Note that IsElem is called, which will mutually recurse back to IsElem' if it exhausts all other options again.

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.

Associated Types

type MkLink endpoint (a :: *) Source #

Methods

toLink Source #

Arguments

:: ( Link -> a)
-> Proxy endpoint

The API endpoint you would like to point to

-> Link
-> MkLink endpoint a

Instances

safeLink Source #

Arguments

:: forall endpoint api. ( 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

Re-exports

type family If (cond :: Bool ) (tru :: k) (fls :: k) :: k where ... Source #

Type-level If . If True a b ==> a ; If False a b ==> b

Equations

If ' True (tru :: k) (fls :: k) = tru
If ' False (tru :: k) (fls :: k) = fls

class SBoolI (b :: Bool ) where Source #

Instances

Instances details
SBoolI ' False
Instance details

Defined in Data.Singletons.Bool

SBoolI ' True
Instance details

Defined in Data.Singletons.Bool