Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data QueryFlag (sym :: Symbol)
- type QueryParam = QueryParam' '[Optional, Strict]
- data QueryParam' (mods :: [*]) (sym :: Symbol) (a :: *)
- data QueryParams (sym :: Symbol) (a :: *)
Documentation
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]
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]
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 # | |
Defined in Servant.Links | |
type MkLink (QueryParam' mods sym v :> sub :: Type) a Source # | |
Defined in Servant.Links type MkLink (QueryParam' mods sym v :> sub :: Type) a = If (FoldRequired mods) v (Maybe v) -> 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¶m[]=val2
and so on. Note that servant doesn't actually
require the []
s and will fetch the values just fine with
param=val1¶m=val2
, too.
Example:
>>>
-- /books?authors[]=<author1>&authors[]=<author2>&...
>>>
type MyApi = "books" :> QueryParams "authors" Text :> Get '[JSON] [Book]
Instances
(KnownSymbol sym, ToHttpApiData v, HasLink sub) => HasLink (QueryParams sym v :> sub :: Type) Source # | |
Defined in Servant.Links | |
type MkLink (QueryParams sym v :> sub :: Type) a Source # | |
Defined in Servant.Links |