servant-0.16.2: A family of combinators for defining webservices APIs

Safe HaskellNone
LanguageHaskell2010

Servant.API

Contents

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
HasLink sub => HasLink (BasicAuth realm a :> sub :: Type) Source # 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (BasicAuth realm a :> sub) a :: Type 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 :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy (CaptureAll sym v :> sub) -> Link -> 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 :: Type 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 :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy (Description s :> sub) -> Link -> 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 :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy (Summary s :> sub) -> Link -> 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 :: Type Source #

Methods

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

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

Defined in Servant.Links

Associated Types

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

Methods

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

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

Defined in Servant.Links

Associated Types

type MkLink (IsSecure :> sub) a :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy (IsSecure :> sub) -> Link -> 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 :: Type 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 :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy (QueryFlag sym :> sub) -> Link -> 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 :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy (QueryParams sym v :> sub) -> Link -> 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 :: Type 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 :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy (RemoteHost :> sub) -> Link -> 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 :: Type Source #

Methods

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

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

Defined in Servant.Links

Associated Types

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

Methods

toLink :: (Link -> a) -> Proxy (Vault :> sub) -> Link -> MkLink (Vault :> sub) a 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 :: Type 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 :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy (sym :> sub) -> Link -> MkLink (sym :> sub) a 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
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 (Description s :> sub :: Type) a = MkLink sub a
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 (HttpVersion :> sub :: Type) a Source # 
Instance details

Defined in Servant.Links

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

Defined in Servant.Links

type MkLink (IsSecure :> sub :: Type) a = MkLink sub a
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 (QueryFlag sym :> sub :: Type) a = Bool -> MkLink sub a
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 (RemoteHost :> sub :: Type) a = MkLink sub a
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 (Vault :> sub :: Type) a Source # 
Instance details

Defined in Servant.Links

type MkLink (Vault :> sub :: Type) a = MkLink sub a
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
Bifunctor (:<|>) Source # 
Instance details

Defined in Servant.API.Alternative

Methods

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

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

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

Biapplicative (:<|>) Source # 
Instance details

Defined in Servant.API.Alternative

Methods

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

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

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

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

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

Bifoldable (:<|>) Source # 
Instance details

Defined in Servant.API.Alternative

Methods

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

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

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

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

Bitraversable (:<|>) Source # 
Instance details

Defined in Servant.API.Alternative

Methods

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

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

Defined in Servant.API.Alternative

Methods

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

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

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

Defined in Servant.API.Alternative

Methods

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]

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

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

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

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

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

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

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

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

Defined in Servant.API.Alternative

Methods

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

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

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

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

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

Defined in Servant.Links

Associated Types

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

Methods

toLink :: (Link -> a0) -> Proxy (a :<|> b) -> Link -> MkLink (a :<|> b) a0 Source #

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

Defined in Servant.API.Alternative

Methods

minBound :: a :<|> b

maxBound :: a :<|> b

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

Defined in Servant.API.Alternative

Methods

(==) :: (a :<|> b) -> (a :<|> b) -> Bool

(/=) :: (a :<|> b) -> (a :<|> b) -> Bool

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

Defined in Servant.API.Alternative

Methods

showsPrec :: Int -> (a :<|> b) -> ShowS

show :: (a :<|> b) -> String

showList :: [a :<|> b] -> ShowS

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

Defined in Servant.API.Alternative

Methods

(<>) :: (a :<|> b) -> (a :<|> b) -> a :<|> b

sconcat :: NonEmpty (a :<|> b) -> a :<|> b

stimes :: Integral b0 => b0 -> (a :<|> b) -> a :<|> b

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

Defined in Servant.API.Alternative

Methods

mempty :: a :<|> b

mappend :: (a :<|> b) -> (a :<|> b) -> a :<|> b

mconcat :: [a :<|> b] -> a :<|> b

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

Defined in Servant.Links

type MkLink (a :<|> b :: Type) r = MkLink a r :<|> MkLink b r

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 
Instances
Bounded EmptyAPI Source # 
Instance details

Defined in Servant.API.Empty

Enum EmptyAPI Source # 
Instance details

Defined in Servant.API.Empty

Eq EmptyAPI Source # 
Instance details

Defined in Servant.API.Empty

Methods

(==) :: EmptyAPI -> EmptyAPI -> Bool

(/=) :: EmptyAPI -> EmptyAPI -> Bool

Show EmptyAPI Source # 
Instance details

Defined in Servant.API.Empty

Methods

showsPrec :: Int -> EmptyAPI -> ShowS

show :: EmptyAPI -> String

showList :: [EmptyAPI] -> ShowS

HasLink EmptyAPI Source # 
Instance details

Defined in Servant.Links

Associated Types

type MkLink EmptyAPI a :: Type Source #

Methods

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

type MkLink EmptyAPI a Source # 
Instance details

Defined in Servant.Links

Type-level combinator for an empty API: EmptyAPI

data Strict Source #

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

Methods

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

(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

Methods

buildHeadersTo :: [Header0] -> HList (Header h v ': xs) Source #

data Lenient Source #

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

data Optional Source #

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

Methods

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

(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

Methods

buildHeadersTo :: [Header0] -> HList (Header h v ': xs) Source #

data Required Source #

Required argument. Not wrapped.

Type-level modifiers for QueryParam, ResponseHeader 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 :: Type) Source # 
Instance details

Defined in Servant.Links

Associated Types

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

Methods

toLink :: (Link -> a) -> Proxy (CaptureAll sym v :> sub) -> Link -> 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
(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 :: Type 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
(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

Methods

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

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

Methods

buildHeadersTo :: [Header0] -> HList (Header h v ': xs) Source #

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

data HttpVersion #

Constructors

HttpVersion 

Fields

Instances
Eq HttpVersion 
Instance details

Defined in Network.HTTP.Types.Version

Methods

(==) :: HttpVersion -> HttpVersion -> Bool

(/=) :: HttpVersion -> HttpVersion -> Bool

Ord HttpVersion 
Instance details

Defined in Network.HTTP.Types.Version

Show HttpVersion 
Instance details

Defined in Network.HTTP.Types.Version

Methods

showsPrec :: Int -> HttpVersion -> ShowS

show :: HttpVersion -> String

showList :: [HttpVersion] -> ShowS

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

Defined in Servant.Links

Associated Types

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

Methods

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

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

Defined in Servant.Links

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

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
(KnownSymbol sym, HasLink sub) => HasLink (QueryFlag sym :> sub :: Type) Source # 
Instance details

Defined in Servant.Links

Associated Types

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

Methods

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

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

Defined in Servant.Links

type MkLink (QueryFlag sym :> sub :: Type) a = Bool -> MkLink sub a

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
(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 :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy (QueryParams sym v :> sub) -> Link -> 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
(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 :: Type 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 ReqBody' (mods :: [*]) (contentTypes :: [*]) (a :: *) Source #

Note: ReqBody' is always Required.

Instances
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 :: Type 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
HasLink sub => HasLink (RemoteHost :> sub :: Type) Source # 
Instance details

Defined in Servant.Links

Associated Types

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

Methods

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

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

Defined in Servant.Links

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

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
Eq IsSecure Source # 
Instance details

Defined in Servant.API.IsSecure

Methods

(==) :: IsSecure -> IsSecure -> Bool

(/=) :: IsSecure -> IsSecure -> Bool

Ord IsSecure Source # 
Instance details

Defined in Servant.API.IsSecure

Methods

compare :: IsSecure -> IsSecure -> Ordering

(<) :: IsSecure -> IsSecure -> Bool

(<=) :: IsSecure -> IsSecure -> Bool

(>) :: IsSecure -> IsSecure -> Bool

(>=) :: IsSecure -> IsSecure -> Bool

max :: IsSecure -> IsSecure -> IsSecure

min :: IsSecure -> IsSecure -> IsSecure

Read IsSecure Source # 
Instance details

Defined in Servant.API.IsSecure

Methods

readsPrec :: Int -> ReadS IsSecure

readList :: ReadS [IsSecure]

readPrec :: ReadPrec IsSecure

readListPrec :: ReadPrec [IsSecure]

Show IsSecure Source # 
Instance details

Defined in Servant.API.IsSecure

Methods

showsPrec :: Int -> IsSecure -> ShowS

show :: IsSecure -> String

showList :: [IsSecure] -> ShowS

Generic IsSecure Source # 
Instance details

Defined in Servant.API.IsSecure

Associated Types

type Rep IsSecure :: Type -> Type #

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

Defined in Servant.Links

Associated Types

type MkLink (IsSecure :> sub) a :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy (IsSecure :> sub) -> Link -> 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.16.2-LdsXzzoRF6kCbrAIs0h8D5" 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

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

Is the request made through HTTPS?

type Vault = Vault RealWorld #

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.

Contexts are only relevant for servant-server.

For more information, see the tutorial.

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

Defined in Servant.Links

Associated Types

type MkLink (WithNamedContext name context sub) a :: Type 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 #

Constructors

GET 
POST 
HEAD 
PUT 
DELETE 
TRACE 
CONNECT 
OPTIONS 
PATCH 
Instances
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

Methods

(==) :: StdMethod -> StdMethod -> Bool

(/=) :: StdMethod -> StdMethod -> Bool

Ord StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Methods

compare :: StdMethod -> StdMethod -> Ordering

(<) :: StdMethod -> StdMethod -> Bool

(<=) :: StdMethod -> StdMethod -> Bool

(>) :: StdMethod -> StdMethod -> Bool

(>=) :: StdMethod -> StdMethod -> Bool

max :: StdMethod -> StdMethod -> StdMethod

min :: StdMethod -> StdMethod -> StdMethod

Read StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Methods

readsPrec :: Int -> ReadS StdMethod

readList :: ReadS [StdMethod]

readPrec :: ReadPrec StdMethod

readListPrec :: ReadPrec [StdMethod]

Show StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Methods

showsPrec :: Int -> StdMethod -> ShowS

show :: StdMethod -> String

showList :: [StdMethod] -> ShowS

Ix StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

ReflectMethod CONNECT Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy CONNECT -> Method Source #

ReflectMethod DELETE Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy DELETE -> Method Source #

ReflectMethod GET Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy GET -> Method Source #

ReflectMethod HEAD Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy HEAD -> Method Source #

ReflectMethod OPTIONS Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy OPTIONS -> Method Source #

ReflectMethod PATCH Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy PATCH -> Method Source #

ReflectMethod POST Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy POST -> Method Source #

ReflectMethod PUT Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy PUT -> Method Source #

ReflectMethod TRACE Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy TRACE -> Method Source #

class ReflectMethod a where Source #

Methods

reflectMethod :: Proxy a -> Method Source #

Instances
ReflectMethod CONNECT Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy CONNECT -> Method Source #

ReflectMethod DELETE Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy DELETE -> Method Source #

ReflectMethod GET Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy GET -> Method Source #

ReflectMethod HEAD Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy HEAD -> Method Source #

ReflectMethod OPTIONS Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy OPTIONS -> Method Source #

ReflectMethod PATCH Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy PATCH -> Method Source #

ReflectMethod POST Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy POST -> Method Source #

ReflectMethod PUT Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy PUT -> Method Source #

ReflectMethod TRACE Source # 
Instance details

Defined in Servant.API.Verbs

Methods

reflectMethod :: Proxy TRACE -> Method Source #

type GetPartialContent = Verb GET 206 Source #

GET with 206 status code.

type PostResetContent = Verb POST 205 Source #

POST with 205 status code.

type GetResetContent = Verb GET 205 Source #

GET with 205 status code.

type PutNoContent = Verb PUT 204 Source #

PUT with 204 status code.

type PatchNoContent = Verb PATCH 204 Source #

PATCH with 204 status code.

type DeleteNoContent = Verb DELETE 204 Source #

DELETE with 204 status code.

type PostNoContent = Verb POST 204 Source #

POST with 204 status code.

type GetNoContent = Verb GET 204 Source #

GET with 204 status code.

type PutNonAuthoritative = Verb PUT 203 Source #

PUT with 203 status code.

type PatchNonAuthoritative = Verb PATCH 203 Source #

PATCH with 203 status code.

type DeleteNonAuthoritative = Verb DELETE 203 Source #

DELETE with 203 status code.

type PostNonAuthoritative = Verb POST 203 Source #

POST with 203 status code.

type GetNonAuthoritative = Verb GET 203 Source #

GET with 203 status code.

type PutAccepted = Verb PUT 202 Source #

PUT with 202 status code.

type PatchAccepted = Verb PATCH 202 Source #

PATCH with 202 status code.

type DeleteAccepted = Verb DELETE 202 Source #

DELETE 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 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
HasLink (Verb m s ct a :: Type) Source # 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (Verb m s ct a) a :: Type 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 #

Methods

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

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

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.16.2-LdsXzzoRF6kCbrAIs0h8D5" False) (V1 :: Type -> 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:,".

Instances
FramingUnrender NetstringFraming Source # 
Instance details

Defined in Servant.API.Stream

Methods

framingUnrender :: Monad m => Proxy NetstringFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source #

FramingRender NetstringFraming Source # 
Instance details

Defined in Servant.API.Stream

Methods

framingRender :: Monad m => Proxy NetstringFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source #

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

Instances
FramingUnrender NewlineFraming Source # 
Instance details

Defined in Servant.API.Stream

Methods

framingUnrender :: Monad m => Proxy NewlineFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source #

FramingRender NewlineFraming Source # 
Instance details

Defined in Servant.API.Stream

Methods

framingRender :: Monad m => Proxy NewlineFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source #

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

Methods

framingUnrender :: Monad m => Proxy NoFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source #

FramingRender NoFraming Source # 
Instance details

Defined in Servant.API.Stream

Methods

framingRender :: Monad m => Proxy NoFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source #

class FramingUnrender strategy where Source #

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

Methods

framingUnrender :: Monad m => Proxy strategy -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source #

Instances
FramingUnrender NetstringFraming Source # 
Instance details

Defined in Servant.API.Stream

Methods

framingUnrender :: Monad m => Proxy NetstringFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source #

FramingUnrender NewlineFraming Source # 
Instance details

Defined in Servant.API.Stream

Methods

framingUnrender :: Monad m => Proxy NewlineFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source #

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

Methods

framingUnrender :: Monad m => Proxy NoFraming -> (ByteString -> Either String a) -> SourceT m ByteString -> SourceT m a Source #

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.

Methods

framingRender :: Monad m => Proxy strategy -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source #

Instances
FramingRender NetstringFraming Source # 
Instance details

Defined in Servant.API.Stream

Methods

framingRender :: Monad m => Proxy NetstringFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source #

FramingRender NewlineFraming Source # 
Instance details

Defined in Servant.API.Stream

Methods

framingRender :: Monad m => Proxy NewlineFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source #

FramingRender NoFraming Source # 
Instance details

Defined in Servant.API.Stream

Methods

framingRender :: Monad m => Proxy NoFraming -> (a -> ByteString) -> SourceT m a -> SourceT m ByteString Source #

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.

Methods

fromSourceIO :: SourceIO chunk -> a Source #

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

Defined in Servant.API.Stream

Methods

fromSourceIO :: SourceIO a -> SourceT m a Source #

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.

Methods

toSourceIO :: a -> SourceIO chunk Source #

Instances
ToSourceIO a [a] Source # 
Instance details

Defined in Servant.API.Stream

Methods

toSourceIO :: [a] -> SourceIO a Source #

ToSourceIO a (NonEmpty a) Source # 
Instance details

Defined in Servant.API.Stream

Methods

toSourceIO :: NonEmpty a -> SourceIO a Source #

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

Relax to use auxiliary class, have m

Instance details

Defined in Servant.API.Stream

Methods

toSourceIO :: SourceT m chunk -> SourceIO chunk Source #

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
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 :: Type 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 #

Methods

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

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

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.16.2-LdsXzzoRF6kCbrAIs0h8D5" 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
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 :: Type 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 #

Methods

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

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

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.16.2-LdsXzzoRF6kCbrAIs0h8D5" False) (V1 :: Type -> Type)

Authentication

data BasicAuthData Source #

A simple datatype to hold data required to decorate a request

Constructors

BasicAuthData 

Fields

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
HasLink sub => HasLink (BasicAuth realm a :> sub :: Type) Source # 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (BasicAuth realm a :> sub) a :: Type 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 support is not perfect \
 \but it's still very readable."
:> Get '[JSON] Book
:}
Instances
HasLink sub => HasLink (Description s :> sub :: Type) Source # 
Instance details

Defined in Servant.Links

Associated Types

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

Methods

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

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

Defined in Servant.Links

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

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
HasLink sub => HasLink (Summary s :> sub :: Type) Source # 
Instance details

Defined in Servant.Links

Associated Types

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

Methods

toLink :: (Link -> a) -> Proxy (Summary s :> sub) -> Link -> 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
Eq NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

(==) :: NoContent -> NoContent -> Bool

(/=) :: NoContent -> NoContent -> Bool

Read NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

readsPrec :: Int -> ReadS NoContent

readList :: ReadS [NoContent]

readPrec :: ReadPrec NoContent

readListPrec :: ReadPrec [NoContent]

Show NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

showsPrec :: Int -> NoContent -> ShowS

show :: NoContent -> String

showList :: [NoContent] -> ShowS

Generic NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

Associated Types

type Rep NoContent :: Type -> Type #

NFData NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

rnf :: NoContent -> ()

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 ': ([] :: [Type])) NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

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

type Rep NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

type Rep NoContent = D1 (MetaData "NoContent" "Servant.API.ContentTypes" "servant-0.16.2-LdsXzzoRF6kCbrAIs0h8D5" False) (C1 (MetaCons "NoContent" PrefixI False) (U1 :: Type -> Type))

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
MimeUnrender OctetStream ByteString Source #
Right . toStrict
Instance details

Defined in Servant.API.ContentTypes

Methods

mimeUnrender :: Proxy OctetStream -> ByteString0 -> Either String ByteString Source #

mimeUnrenderWithType :: Proxy OctetStream -> MediaType -> ByteString0 -> Either String ByteString Source #

MimeUnrender OctetStream ByteString Source #
Right . id
Instance details

Defined in Servant.API.ContentTypes

Methods

mimeUnrender :: Proxy OctetStream -> ByteString -> Either String ByteString Source #

mimeUnrenderWithType :: Proxy OctetStream -> MediaType -> ByteString -> Either String ByteString Source #

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

Methods

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

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

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

Defined in Servant.API.ContentTypes

Methods

mimeUnrender :: Proxy PlainText -> ByteString -> Either String String Source #

mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String String Source #

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

Defined in Servant.API.ContentTypes

Methods

mimeUnrender :: Proxy PlainText -> ByteString -> Either String Text Source #

mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String Text Source #

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

Defined in Servant.API.ContentTypes

Methods

mimeUnrender :: Proxy PlainText -> ByteString -> Either String Text Source #

mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String Text Source #

FromJSON a => MimeUnrender JSON a Source #

eitherDecode

Instance details

Defined in Servant.API.ContentTypes

Methods

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

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

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

Methods

mimeRender :: Proxy ctype -> a -> ByteString Source #

Instances
MimeRender OctetStream ByteString Source #

fromStrict

Instance details

Defined in Servant.API.ContentTypes

Methods

mimeRender :: Proxy OctetStream -> ByteString -> ByteString0 Source #

MimeRender OctetStream ByteString Source #
id
Instance details

Defined in Servant.API.ContentTypes

Methods

mimeRender :: Proxy OctetStream -> ByteString -> ByteString Source #

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

Methods

mimeRender :: Proxy FormUrlEncoded -> a -> ByteString Source #

MimeRender PlainText String Source #
BC.pack
Instance details

Defined in Servant.API.ContentTypes

Methods

mimeRender :: Proxy PlainText -> String -> ByteString Source #

MimeRender PlainText Text Source #

encodeUtf8

Instance details

Defined in Servant.API.ContentTypes

Methods

mimeRender :: Proxy PlainText -> Text -> ByteString Source #

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

Defined in Servant.API.ContentTypes

Methods

mimeRender :: Proxy PlainText -> Text -> ByteString Source #

ToJSON a => MimeRender JSON a Source #

encode

Instance details

Defined in Servant.API.ContentTypes

Methods

mimeRender :: Proxy JSON -> a -> ByteString Source #

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

Methods

contentType :: Proxy ctype -> MediaType Source #

contentTypes :: Proxy ctype -> NonEmpty MediaType Source #

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

Defined in Servant.API.ContentTypes

Methods

contentType :: Proxy OctetStream -> MediaType Source #

contentTypes :: Proxy OctetStream -> NonEmpty MediaType Source #

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

Defined in Servant.API.ContentTypes

Methods

contentType :: Proxy FormUrlEncoded -> MediaType Source #

contentTypes :: Proxy FormUrlEncoded -> NonEmpty MediaType Source #

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

Defined in Servant.API.ContentTypes

Methods

contentType :: Proxy PlainText -> MediaType Source #

contentTypes :: Proxy PlainText -> NonEmpty MediaType Source #

Accept JSON Source #
application/json
Instance details

Defined in Servant.API.ContentTypes

Methods

contentType :: Proxy JSON -> MediaType Source #

contentTypes :: Proxy JSON -> NonEmpty MediaType Source #

data OctetStream Source #

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

Defined in Servant.API.ContentTypes

Methods

contentType :: Proxy OctetStream -> MediaType Source #

contentTypes :: Proxy OctetStream -> NonEmpty MediaType Source #

MimeUnrender OctetStream ByteString Source #
Right . toStrict
Instance details

Defined in Servant.API.ContentTypes

Methods

mimeUnrender :: Proxy OctetStream -> ByteString0 -> Either String ByteString Source #

mimeUnrenderWithType :: Proxy OctetStream -> MediaType -> ByteString0 -> Either String ByteString Source #

MimeUnrender OctetStream ByteString Source #
Right . id
Instance details

Defined in Servant.API.ContentTypes

Methods

mimeUnrender :: Proxy OctetStream -> ByteString -> Either String ByteString Source #

mimeUnrenderWithType :: Proxy OctetStream -> MediaType -> ByteString -> Either String ByteString Source #

MimeRender OctetStream ByteString Source #

fromStrict

Instance details

Defined in Servant.API.ContentTypes

Methods

mimeRender :: Proxy OctetStream -> ByteString -> ByteString0 Source #

MimeRender OctetStream ByteString Source #
id
Instance details

Defined in Servant.API.ContentTypes

Methods

mimeRender :: Proxy OctetStream -> ByteString -> ByteString Source #

data FormUrlEncoded Source #

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

Defined in Servant.API.ContentTypes

Methods

contentType :: Proxy FormUrlEncoded -> MediaType Source #

contentTypes :: Proxy FormUrlEncoded -> NonEmpty MediaType Source #

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

Methods

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

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

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

Methods

mimeRender :: Proxy FormUrlEncoded -> a -> ByteString Source #

data PlainText Source #

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

Defined in Servant.API.ContentTypes

Methods

contentType :: Proxy PlainText -> MediaType Source #

contentTypes :: Proxy PlainText -> NonEmpty MediaType Source #

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

Defined in Servant.API.ContentTypes

Methods

mimeUnrender :: Proxy PlainText -> ByteString -> Either String String Source #

mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String String Source #

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

Defined in Servant.API.ContentTypes

Methods

mimeUnrender :: Proxy PlainText -> ByteString -> Either String Text Source #

mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String Text Source #

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

Defined in Servant.API.ContentTypes

Methods

mimeUnrender :: Proxy PlainText -> ByteString -> Either String Text Source #

mimeUnrenderWithType :: Proxy PlainText -> MediaType -> ByteString -> Either String Text Source #

MimeRender PlainText String Source #
BC.pack
Instance details

Defined in Servant.API.ContentTypes

Methods

mimeRender :: Proxy PlainText -> String -> ByteString Source #

MimeRender PlainText Text Source #

encodeUtf8

Instance details

Defined in Servant.API.ContentTypes

Methods

mimeRender :: Proxy PlainText -> Text -> ByteString Source #

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

Defined in Servant.API.ContentTypes

Methods

mimeRender :: Proxy PlainText -> Text -> ByteString Source #

data JSON Source #

Instances
Accept JSON Source #
application/json
Instance details

Defined in Servant.API.ContentTypes

Methods

contentType :: Proxy JSON -> MediaType Source #

contentTypes :: Proxy JSON -> NonEmpty MediaType Source #

FromJSON a => MimeUnrender JSON a Source #

eitherDecode

Instance details

Defined in Servant.API.ContentTypes

Methods

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

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

ToJSON a => MimeRender JSON a Source #

encode

Instance details

Defined in Servant.API.ContentTypes

Methods

mimeRender :: Proxy JSON -> a -> ByteString Source #

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

Response Headers

class HasResponseHeader h a headers Source #

Minimal complete definition

hlistLookupHeader

Instances
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

Methods

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

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

Minimal complete definition

addOptionalHeader

Instances
(KnownSymbol h, ToHttpApiData v, new ~ Headers (Header h v ': ([] :: [Type])) 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 #

Methods

getHeaders :: ls -> [Header] Source #

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

Defined in Servant.API.ResponseHeaders

Methods

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

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

Defined in Servant.API.ResponseHeaders

Methods

getHeaders :: Headers hs a -> [Header] Source #

class BuildHeadersTo hs where Source #

Methods

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 ([] :: [Type]) Source # 
Instance details

Defined in Servant.API.ResponseHeaders

Methods

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

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

Defined in Servant.API.ResponseHeaders

Methods

buildHeadersTo :: [Header0] -> HList (Header h v ': xs) Source #

data HList a where Source #

Constructors

HNil :: HList '[] 
HCons :: ResponseHeader h x -> HList xs -> HList (Header h x ': xs) 
Instances
NFDataHList xs => NFData (HList xs) Source # 
Instance details

Defined in Servant.API.ResponseHeaders

Methods

rnf :: HList xs -> ()

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

Defined in Servant.API.ResponseHeaders

Methods

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

data ResponseHeader (sym :: Symbol) a Source #

Constructors

Header a 
MissingHeader 
UndecodableHeader ByteString 
Instances
Functor (ResponseHeader sym) Source # 
Instance details

Defined in Servant.API.ResponseHeaders

Methods

fmap :: (a -> b) -> ResponseHeader sym a -> ResponseHeader sym b

(<$) :: a -> ResponseHeader sym b -> ResponseHeader sym a

Eq a => Eq (ResponseHeader sym a) Source # 
Instance details

Defined in Servant.API.ResponseHeaders

Methods

(==) :: ResponseHeader sym a -> ResponseHeader sym a -> Bool

(/=) :: ResponseHeader sym a -> ResponseHeader sym a -> Bool

Show a => Show (ResponseHeader sym a) Source # 
Instance details

Defined in Servant.API.ResponseHeaders

Methods

showsPrec :: Int -> ResponseHeader sym a -> ShowS

show :: ResponseHeader sym a -> String

showList :: [ResponseHeader sym a] -> ShowS

NFData a => NFData (ResponseHeader sym a) Source # 
Instance details

Defined in Servant.API.ResponseHeaders

Methods

rnf :: ResponseHeader sym a -> ()

data Headers ls a Source #

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

Constructors

Headers 

Fields

Instances
(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

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

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

Defined in Servant.API.ResponseHeaders

Methods

rnf :: Headers ls a -> ()

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

Defined in Servant.API.ResponseHeaders

Methods

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:

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

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 Applications, this can also be used with serveDirectory to serve static files stored in a particular directory on your filesystem

Instances
HasLink Raw Source # 
Instance details

Defined in Servant.Links

Associated Types

type MkLink Raw a :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy Raw -> Link -> 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 FromHttpApiData a where #

Minimal complete definition

parseUrlPiece | parseQueryParam

Methods

parseUrlPiece :: Text -> Either Text a #

parseHeader :: ByteString -> Either Text a #

parseQueryParam :: Text -> Either Text a #

Instances
FromHttpApiData Bool 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Bool #

parseHeader :: ByteString -> Either Text Bool #

parseQueryParam :: Text -> Either Text Bool #

FromHttpApiData Char 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Char #

parseHeader :: ByteString -> Either Text Char #

parseQueryParam :: Text -> Either Text Char #

FromHttpApiData Double 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Double #

parseHeader :: ByteString -> Either Text Double #

parseQueryParam :: Text -> Either Text Double #

FromHttpApiData Float 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Float #

parseHeader :: ByteString -> Either Text Float #

parseQueryParam :: Text -> Either Text Float #

FromHttpApiData Int 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Int #

parseHeader :: ByteString -> Either Text Int #

parseQueryParam :: Text -> Either Text Int #

FromHttpApiData Int8 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Int8 #

parseHeader :: ByteString -> Either Text Int8 #

parseQueryParam :: Text -> Either Text Int8 #

FromHttpApiData Int16 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Int16 #

parseHeader :: ByteString -> Either Text Int16 #

parseQueryParam :: Text -> Either Text Int16 #

FromHttpApiData Int32 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Int32 #

parseHeader :: ByteString -> Either Text Int32 #

parseQueryParam :: Text -> Either Text Int32 #

FromHttpApiData Int64 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Int64 #

parseHeader :: ByteString -> Either Text Int64 #

parseQueryParam :: Text -> Either Text Int64 #

FromHttpApiData Integer 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Integer #

parseHeader :: ByteString -> Either Text Integer #

parseQueryParam :: Text -> Either Text Integer #

FromHttpApiData Natural 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Natural #

parseHeader :: ByteString -> Either Text Natural #

parseQueryParam :: Text -> Either Text Natural #

FromHttpApiData Ordering 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Ordering #

parseHeader :: ByteString -> Either Text Ordering #

parseQueryParam :: Text -> Either Text Ordering #

FromHttpApiData Word 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Word #

parseHeader :: ByteString -> Either Text Word #

parseQueryParam :: Text -> Either Text Word #

FromHttpApiData Word8 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Word8 #

parseHeader :: ByteString -> Either Text Word8 #

parseQueryParam :: Text -> Either Text Word8 #

FromHttpApiData Word16 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Word16 #

parseHeader :: ByteString -> Either Text Word16 #

parseQueryParam :: Text -> Either Text Word16 #

FromHttpApiData Word32 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Word32 #

parseHeader :: ByteString -> Either Text Word32 #

parseQueryParam :: Text -> Either Text Word32 #

FromHttpApiData Word64 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Word64 #

parseHeader :: ByteString -> Either Text Word64 #

parseQueryParam :: Text -> Either Text Word64 #

FromHttpApiData () 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text () #

parseHeader :: ByteString -> Either Text () #

parseQueryParam :: Text -> Either Text () #

FromHttpApiData String 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text String #

parseHeader :: ByteString -> Either Text String #

parseQueryParam :: Text -> Either Text String #

FromHttpApiData All 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text All #

parseHeader :: ByteString -> Either Text All #

parseQueryParam :: Text -> Either Text All #

FromHttpApiData Any 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Any #

parseHeader :: ByteString -> Either Text Any #

parseQueryParam :: Text -> Either Text Any #

FromHttpApiData Version 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Version #

parseHeader :: ByteString -> Either Text Version #

parseQueryParam :: Text -> Either Text Version #

FromHttpApiData Void 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Void #

parseHeader :: ByteString -> Either Text Void #

parseQueryParam :: Text -> Either Text Void #

FromHttpApiData Text 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text0 -> Either Text0 Text #

parseHeader :: ByteString -> Either Text0 Text #

parseQueryParam :: Text0 -> Either Text0 Text #

FromHttpApiData Text 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Text #

parseHeader :: ByteString -> Either Text Text #

parseQueryParam :: Text -> Either Text Text #

FromHttpApiData Day 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text Day #

parseHeader :: ByteString -> Either Text Day #

parseQueryParam :: Text -> Either Text Day #

FromHttpApiData UTCTime 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text UTCTime #

parseHeader :: ByteString -> Either Text UTCTime #

parseQueryParam :: Text -> Either Text UTCTime #

FromHttpApiData LocalTime 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text LocalTime #

parseHeader :: ByteString -> Either Text LocalTime #

parseQueryParam :: Text -> Either Text LocalTime #

FromHttpApiData TimeOfDay 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text TimeOfDay #

parseHeader :: ByteString -> Either Text TimeOfDay #

parseQueryParam :: Text -> Either Text TimeOfDay #

FromHttpApiData ZonedTime 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text ZonedTime #

parseHeader :: ByteString -> Either Text ZonedTime #

parseQueryParam :: Text -> Either Text ZonedTime #

FromHttpApiData NominalDiffTime 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text NominalDiffTime #

parseHeader :: ByteString -> Either Text NominalDiffTime #

parseQueryParam :: Text -> Either Text NominalDiffTime #

FromHttpApiData DayOfWeek 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text DayOfWeek #

parseHeader :: ByteString -> Either Text DayOfWeek #

parseQueryParam :: Text -> Either Text DayOfWeek #

FromHttpApiData UUID 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text UUID #

parseHeader :: ByteString -> Either Text UUID #

parseQueryParam :: Text -> Either Text UUID #

FromHttpApiData SetCookie 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text SetCookie #

parseHeader :: ByteString -> Either Text SetCookie #

parseQueryParam :: Text -> Either Text SetCookie #

FromHttpApiData a => FromHttpApiData (Maybe a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text (Maybe a) #

parseHeader :: ByteString -> Either Text (Maybe a) #

parseQueryParam :: Text -> Either Text (Maybe a) #

FromHttpApiData a => FromHttpApiData (Dual a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text (Dual a) #

parseHeader :: ByteString -> Either Text (Dual a) #

parseQueryParam :: Text -> Either Text (Dual a) #

FromHttpApiData a => FromHttpApiData (First a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text (First a) #

parseHeader :: ByteString -> Either Text (First a) #

parseQueryParam :: Text -> Either Text (First a) #

FromHttpApiData a => FromHttpApiData (Product a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text (Product a) #

parseHeader :: ByteString -> Either Text (Product a) #

parseQueryParam :: Text -> Either Text (Product a) #

FromHttpApiData a => FromHttpApiData (Sum a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text (Sum a) #

parseHeader :: ByteString -> Either Text (Sum a) #

parseQueryParam :: Text -> Either Text (Sum a) #

FromHttpApiData a => FromHttpApiData (First a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text (First a) #

parseHeader :: ByteString -> Either Text (First a) #

parseQueryParam :: Text -> Either Text (First a) #

FromHttpApiData a => FromHttpApiData (Last a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text (Last a) #

parseHeader :: ByteString -> Either Text (Last a) #

parseQueryParam :: Text -> Either Text (Last a) #

FromHttpApiData a => FromHttpApiData (Max a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text (Max a) #

parseHeader :: ByteString -> Either Text (Max a) #

parseQueryParam :: Text -> Either Text (Max a) #

FromHttpApiData a => FromHttpApiData (Min a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text (Min a) #

parseHeader :: ByteString -> Either Text (Min a) #

parseQueryParam :: Text -> Either Text (Min a) #

FromHttpApiData a => FromHttpApiData (Last a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text (Last a) #

parseHeader :: ByteString -> Either Text (Last a) #

parseQueryParam :: Text -> Either Text (Last a) #

HasResolution a => FromHttpApiData (Fixed a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text (Fixed a) #

parseHeader :: ByteString -> Either Text (Fixed a) #

parseQueryParam :: Text -> Either Text (Fixed a) #

FromHttpApiData a => FromHttpApiData (LenientData a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text (LenientData a) #

parseHeader :: ByteString -> Either Text (LenientData a) #

parseQueryParam :: Text -> Either Text (LenientData a) #

(FromHttpApiData a, FromHttpApiData b) => FromHttpApiData (Either a b) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text (Either a b) #

parseHeader :: ByteString -> Either Text (Either a b) #

parseQueryParam :: Text -> Either Text (Either a b) #

FromHttpApiData a => FromHttpApiData (Tagged b a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

parseUrlPiece :: Text -> Either Text (Tagged b a) #

parseHeader :: ByteString -> Either Text (Tagged b a) #

parseQueryParam :: Text -> Either Text (Tagged b a) #

class ToHttpApiData a where #

Minimal complete definition

toUrlPiece | toQueryParam

Methods

toUrlPiece :: a -> Text #

toEncodedUrlPiece :: a -> Builder #

toHeader :: a -> ByteString #

toQueryParam :: a -> Text #

Instances
ToHttpApiData Bool 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Bool -> Text #

toEncodedUrlPiece :: Bool -> Builder #

toHeader :: Bool -> ByteString #

toQueryParam :: Bool -> Text #

ToHttpApiData Char 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Char -> Text #

toEncodedUrlPiece :: Char -> Builder #

toHeader :: Char -> ByteString #

toQueryParam :: Char -> Text #

ToHttpApiData Double 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Double -> Text #

toEncodedUrlPiece :: Double -> Builder #

toHeader :: Double -> ByteString #

toQueryParam :: Double -> Text #

ToHttpApiData Float 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Float -> Text #

toEncodedUrlPiece :: Float -> Builder #

toHeader :: Float -> ByteString #

toQueryParam :: Float -> Text #

ToHttpApiData Int 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Int -> Text #

toEncodedUrlPiece :: Int -> Builder #

toHeader :: Int -> ByteString #

toQueryParam :: Int -> Text #

ToHttpApiData Int8 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Int8 -> Text #

toEncodedUrlPiece :: Int8 -> Builder #

toHeader :: Int8 -> ByteString #

toQueryParam :: Int8 -> Text #

ToHttpApiData Int16 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Int16 -> Text #

toEncodedUrlPiece :: Int16 -> Builder #

toHeader :: Int16 -> ByteString #

toQueryParam :: Int16 -> Text #

ToHttpApiData Int32 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Int32 -> Text #

toEncodedUrlPiece :: Int32 -> Builder #

toHeader :: Int32 -> ByteString #

toQueryParam :: Int32 -> Text #

ToHttpApiData Int64 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Int64 -> Text #

toEncodedUrlPiece :: Int64 -> Builder #

toHeader :: Int64 -> ByteString #

toQueryParam :: Int64 -> Text #

ToHttpApiData Integer 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Integer -> Text #

toEncodedUrlPiece :: Integer -> Builder #

toHeader :: Integer -> ByteString #

toQueryParam :: Integer -> Text #

ToHttpApiData Natural 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Natural -> Text #

toEncodedUrlPiece :: Natural -> Builder #

toHeader :: Natural -> ByteString #

toQueryParam :: Natural -> Text #

ToHttpApiData Ordering 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Ordering -> Text #

toEncodedUrlPiece :: Ordering -> Builder #

toHeader :: Ordering -> ByteString #

toQueryParam :: Ordering -> Text #

ToHttpApiData Word 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Word -> Text #

toEncodedUrlPiece :: Word -> Builder #

toHeader :: Word -> ByteString #

toQueryParam :: Word -> Text #

ToHttpApiData Word8 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Word8 -> Text #

toEncodedUrlPiece :: Word8 -> Builder #

toHeader :: Word8 -> ByteString #

toQueryParam :: Word8 -> Text #

ToHttpApiData Word16 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Word16 -> Text #

toEncodedUrlPiece :: Word16 -> Builder #

toHeader :: Word16 -> ByteString #

toQueryParam :: Word16 -> Text #

ToHttpApiData Word32 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Word32 -> Text #

toEncodedUrlPiece :: Word32 -> Builder #

toHeader :: Word32 -> ByteString #

toQueryParam :: Word32 -> Text #

ToHttpApiData Word64 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Word64 -> Text #

toEncodedUrlPiece :: Word64 -> Builder #

toHeader :: Word64 -> ByteString #

toQueryParam :: Word64 -> Text #

ToHttpApiData () 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: () -> Text #

toEncodedUrlPiece :: () -> Builder #

toHeader :: () -> ByteString #

toQueryParam :: () -> Text #

ToHttpApiData String 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: String -> Text #

toEncodedUrlPiece :: String -> Builder #

toHeader :: String -> ByteString #

toQueryParam :: String -> Text #

ToHttpApiData All 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: All -> Text #

toEncodedUrlPiece :: All -> Builder #

toHeader :: All -> ByteString #

toQueryParam :: All -> Text #

ToHttpApiData Any 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Any -> Text #

toEncodedUrlPiece :: Any -> Builder #

toHeader :: Any -> ByteString #

toQueryParam :: Any -> Text #

ToHttpApiData Version 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Version -> Text #

toEncodedUrlPiece :: Version -> Builder #

toHeader :: Version -> ByteString #

toQueryParam :: Version -> Text #

ToHttpApiData Void 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Void -> Text #

toEncodedUrlPiece :: Void -> Builder #

toHeader :: Void -> ByteString #

toQueryParam :: Void -> Text #

ToHttpApiData Text 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Text -> Text0 #

toEncodedUrlPiece :: Text -> Builder #

toHeader :: Text -> ByteString #

toQueryParam :: Text -> Text0 #

ToHttpApiData Text 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Text -> Text #

toEncodedUrlPiece :: Text -> Builder #

toHeader :: Text -> ByteString #

toQueryParam :: Text -> Text #

ToHttpApiData Day 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Day -> Text #

toEncodedUrlPiece :: Day -> Builder #

toHeader :: Day -> ByteString #

toQueryParam :: Day -> Text #

ToHttpApiData UTCTime 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: UTCTime -> Text #

toEncodedUrlPiece :: UTCTime -> Builder #

toHeader :: UTCTime -> ByteString #

toQueryParam :: UTCTime -> Text #

ToHttpApiData LocalTime 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: LocalTime -> Text #

toEncodedUrlPiece :: LocalTime -> Builder #

toHeader :: LocalTime -> ByteString #

toQueryParam :: LocalTime -> Text #

ToHttpApiData TimeOfDay 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: TimeOfDay -> Text #

toEncodedUrlPiece :: TimeOfDay -> Builder #

toHeader :: TimeOfDay -> ByteString #

toQueryParam :: TimeOfDay -> Text #

ToHttpApiData ZonedTime 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: ZonedTime -> Text #

toEncodedUrlPiece :: ZonedTime -> Builder #

toHeader :: ZonedTime -> ByteString #

toQueryParam :: ZonedTime -> Text #

ToHttpApiData NominalDiffTime 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: NominalDiffTime -> Text #

toEncodedUrlPiece :: NominalDiffTime -> Builder #

toHeader :: NominalDiffTime -> ByteString #

toQueryParam :: NominalDiffTime -> Text #

ToHttpApiData DayOfWeek 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: DayOfWeek -> Text #

toEncodedUrlPiece :: DayOfWeek -> Builder #

toHeader :: DayOfWeek -> ByteString #

toQueryParam :: DayOfWeek -> Text #

ToHttpApiData UUID 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: UUID -> Text #

toEncodedUrlPiece :: UUID -> Builder #

toHeader :: UUID -> ByteString #

toQueryParam :: UUID -> Text #

ToHttpApiData SetCookie 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: SetCookie -> Text #

toEncodedUrlPiece :: SetCookie -> Builder #

toHeader :: SetCookie -> ByteString #

toQueryParam :: SetCookie -> Text #

ToHttpApiData Link Source # 
Instance details

Defined in Servant.Links

Methods

toUrlPiece :: Link -> Text #

toEncodedUrlPiece :: Link -> Builder #

toHeader :: Link -> ByteString #

toQueryParam :: Link -> Text #

ToHttpApiData a => ToHttpApiData (Maybe a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Maybe a -> Text #

toEncodedUrlPiece :: Maybe a -> Builder #

toHeader :: Maybe a -> ByteString #

toQueryParam :: Maybe a -> Text #

ToHttpApiData a => ToHttpApiData (Dual a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Dual a -> Text #

toEncodedUrlPiece :: Dual a -> Builder #

toHeader :: Dual a -> ByteString #

toQueryParam :: Dual a -> Text #

ToHttpApiData a => ToHttpApiData (First a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: First a -> Text #

toEncodedUrlPiece :: First a -> Builder #

toHeader :: First a -> ByteString #

toQueryParam :: First a -> Text #

ToHttpApiData a => ToHttpApiData (Product a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Product a -> Text #

toEncodedUrlPiece :: Product a -> Builder #

toHeader :: Product a -> ByteString #

toQueryParam :: Product a -> Text #

ToHttpApiData a => ToHttpApiData (Sum a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Sum a -> Text #

toEncodedUrlPiece :: Sum a -> Builder #

toHeader :: Sum a -> ByteString #

toQueryParam :: Sum a -> Text #

ToHttpApiData a => ToHttpApiData (First a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: First a -> Text #

toEncodedUrlPiece :: First a -> Builder #

toHeader :: First a -> ByteString #

toQueryParam :: First a -> Text #

ToHttpApiData a => ToHttpApiData (Last a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Last a -> Text #

toEncodedUrlPiece :: Last a -> Builder #

toHeader :: Last a -> ByteString #

toQueryParam :: Last a -> Text #

ToHttpApiData a => ToHttpApiData (Max a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Max a -> Text #

toEncodedUrlPiece :: Max a -> Builder #

toHeader :: Max a -> ByteString #

toQueryParam :: Max a -> Text #

ToHttpApiData a => ToHttpApiData (Min a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Min a -> Text #

toEncodedUrlPiece :: Min a -> Builder #

toHeader :: Min a -> ByteString #

toQueryParam :: Min a -> Text #

ToHttpApiData a => ToHttpApiData (Last a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Last a -> Text #

toEncodedUrlPiece :: Last a -> Builder #

toHeader :: Last a -> ByteString #

toQueryParam :: Last a -> Text #

HasResolution a => ToHttpApiData (Fixed a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Fixed a -> Text #

toEncodedUrlPiece :: Fixed a -> Builder #

toHeader :: Fixed a -> ByteString #

toQueryParam :: Fixed a -> Text #

(ToHttpApiData a, ToHttpApiData b) => ToHttpApiData (Either a b) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Either a b -> Text #

toEncodedUrlPiece :: Either a b -> Builder #

toHeader :: Either a b -> ByteString #

toQueryParam :: Either a b -> Text #

ToHttpApiData a => ToHttpApiData (Tagged b a) 
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: Tagged b a -> Text #

toEncodedUrlPiece :: Tagged b a -> Builder #

toHeader :: Tagged b a -> ByteString #

toQueryParam :: Tagged b a -> Text #

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 :: Type) Source # 
Instance details

Defined in Servant.Links

Associated Types

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

Methods

toLink :: (Link -> a) -> Proxy (AuthProtect tag :> sub) -> Link -> 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

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

Equations

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

data URI #

Constructors

URI 

Fields

Instances
Eq URI 
Instance details

Defined in Network.URI

Methods

(==) :: URI -> URI -> Bool

(/=) :: URI -> URI -> Bool

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

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

toConstr :: URI -> Constr

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

Defined in Network.URI

Methods

compare :: URI -> URI -> Ordering

(<) :: URI -> URI -> Bool

(<=) :: URI -> URI -> Bool

(>) :: URI -> URI -> Bool

(>=) :: URI -> URI -> Bool

max :: URI -> URI -> URI

min :: URI -> URI -> URI

Show URI 
Instance details

Defined in Network.URI

Methods

showsPrec :: Int -> URI -> ShowS

show :: URI -> String

showList :: [URI] -> ShowS

Generic URI 
Instance details

Defined in Network.URI

Associated Types

type Rep URI :: Type -> Type #

Methods

from :: URI -> Rep URI x

to :: Rep URI x -> URI

Lift URI 
Instance details

Defined in Network.URI

Methods

lift :: URI -> Q Exp

NFData URI 
Instance details

Defined in Network.URI

Methods

rnf :: URI -> ()

type Rep URI 
Instance details

Defined in Network.URI

type Rep URI = D1 (MetaData "URI" "Network.URI" "network-uri-2.6.2.0-LHnNi9N4lmbFWCwIyvTSKY" 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)))))

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 

data Link Source #

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.

safeLink Source #

Arguments

:: (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 ... #

Equations

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

data SBool (b :: Bool) where Source #

Constructors

STrue :: forall (b :: Bool). SBool True 
SFalse :: forall (b :: Bool). SBool False 
Instances
Eq (SBool b)

Since: singleton-bool-0.1.5

Instance details

Defined in Data.Singletons.Bool

Methods

(==) :: SBool b -> SBool b -> Bool

(/=) :: SBool b -> SBool b -> Bool

Ord (SBool b)

Since: singleton-bool-0.1.5

Instance details

Defined in Data.Singletons.Bool

Methods

compare :: SBool b -> SBool b -> Ordering

(<) :: SBool b -> SBool b -> Bool

(<=) :: SBool b -> SBool b -> Bool

(>) :: SBool b -> SBool b -> Bool

(>=) :: SBool b -> SBool b -> Bool

max :: SBool b -> SBool b -> SBool b

min :: SBool b -> SBool b -> SBool b

Show (SBool b)

Since: singleton-bool-0.1.5

Instance details

Defined in Data.Singletons.Bool

Methods

showsPrec :: Int -> SBool b -> ShowS

show :: SBool b -> String

showList :: [SBool b] -> ShowS

class SBoolI (b :: Bool) where Source #

Methods

sbool :: SBool b Source #

Instances
SBoolI False 
Instance details

Defined in Data.Singletons.Bool

Methods

sbool :: SBool False Source #

SBoolI True 
Instance details

Defined in Data.Singletons.Bool

Methods

sbool :: SBool True Source #