Safe Haskell | None |
---|---|
Language | Haskell2010 |
Traits and middleware to handle request query parameters.
The queryParam
middleware can extract a query parameter value trait
and invoke another handler. An error handler is invoked if the parameter
is missing or the parsing fails.
The optionalQueryParam
middleware is similar but will not invoke
the error handling in case the prameter is missing. Instead, the
trait value will be set to Nothing
in that case.
The lenientQueryParam
middleware requires the parameter to be
present. But the trait attribute will be set to Left
msg
if an
error occurs while parsing it to a Haskell value. Here msg
will
indicate the error in parsing.
Finally, we have optionalLenientQueryParam
which combines the
behaviors of optionalQueryParam
and lenientQueryParam
. In this
case, the parameter extraction never fails. Missing parameters and
parse errors are indicated in the trait attribute passed to next
handler.
Synopsis
- data QueryParam (e :: Existence) (p :: ParseStyle) (name :: Symbol) (val :: Type) = QueryParam
- type RequiredQueryParam = QueryParam Required Strict
- type OptionalQueryParam = QueryParam Optional Strict
- data ParamNotFound = ParamNotFound
- newtype ParamParseError = ParamParseError Text
- queryParam :: forall name val h req. (Get h (QueryParam Required Strict name val) Request, ArrowChoice h) => h (Linked req Request, Either ParamNotFound ParamParseError) Response -> Middleware h req (QueryParam Required Strict name val ': req)
- optionalQueryParam :: forall name val h req. (Get h (QueryParam Optional Strict name val) Request, ArrowChoice h) => h (Linked req Request, ParamParseError) Response -> Middleware h req (QueryParam Optional Strict name val ': req)
- lenientQueryParam :: forall name val h req. (Get h (QueryParam Required Lenient name val) Request, ArrowChoice h) => h (Linked req Request, ParamNotFound) Response -> Middleware h req (QueryParam Required Lenient name val ': req)
- optionalLenientQueryParam :: forall name val h req. (Get h (QueryParam Optional Lenient name val) Request, ArrowChoice h) => Middleware h req (QueryParam Optional Lenient name val ': req)
Traits
data QueryParam (e :: Existence) (p :: ParseStyle) (name :: Symbol) (val :: Type) Source #
Capture a query parameter with a specified name
and convert it to
a value of type val
. The type parameter e
denotes whether the
query parameter is required to be present. The parse style parameter
p
determines whether the conversion is applied strictly or
leniently.
Instances
type RequiredQueryParam = QueryParam Required Strict Source #
QueryParam
that is required and parsed strictly
type OptionalQueryParam = QueryParam Optional Strict Source #
QueryParam
that is optional and parsed strictly
data ParamNotFound Source #
Indicates a missing query parameter
Instances
Eq ParamNotFound Source # | |
Defined in WebGear.Core.Trait.QueryParam (==) :: ParamNotFound -> ParamNotFound -> Bool # (/=) :: ParamNotFound -> ParamNotFound -> Bool # | |
Read ParamNotFound Source # | |
Defined in WebGear.Core.Trait.QueryParam readsPrec :: Int -> ReadS ParamNotFound # readList :: ReadS [ParamNotFound] # | |
Show ParamNotFound Source # | |
Defined in WebGear.Core.Trait.QueryParam showsPrec :: Int -> ParamNotFound -> ShowS # show :: ParamNotFound -> String # showList :: [ParamNotFound] -> ShowS # |
newtype ParamParseError Source #
Error in converting a query parameter
Instances
Eq ParamParseError Source # | |
Defined in WebGear.Core.Trait.QueryParam (==) :: ParamParseError -> ParamParseError -> Bool # (/=) :: ParamParseError -> ParamParseError -> Bool # | |
Read ParamParseError Source # | |
Defined in WebGear.Core.Trait.QueryParam | |
Show ParamParseError Source # | |
Defined in WebGear.Core.Trait.QueryParam showsPrec :: Int -> ParamParseError -> ShowS # show :: ParamParseError -> String # showList :: [ParamParseError] -> ShowS # |
Middlewares
queryParam :: forall name val h req. (Get h (QueryParam Required Strict name val) Request, ArrowChoice h) => h (Linked req Request, Either ParamNotFound ParamParseError) Response -> Middleware h req (QueryParam Required Strict name val ': req) Source #
Extract a query parameter and convert it to a value of type
val
.
The associated trait attribute has type val
.
Example usage:
queryParam @"limit" @Integer errorHandler okHandler
optionalQueryParam :: forall name val h req. (Get h (QueryParam Optional Strict name val) Request, ArrowChoice h) => h (Linked req Request, ParamParseError) Response -> Middleware h req (QueryParam Optional Strict name val ': req) Source #
Extract an optional query parameter and convert it to a value of
type val
.
The associated trait attribute has type Maybe val
; a Nothing
value indicates that the parameter is missing from the request.
Example usage:
optionalQueryParam @"limit" @Integer errorHandler okHandler
lenientQueryParam :: forall name val h req. (Get h (QueryParam Required Lenient name val) Request, ArrowChoice h) => h (Linked req Request, ParamNotFound) Response -> Middleware h req (QueryParam Required Lenient name val ': req) Source #
Extract a query parameter and convert it to a value of type val
.
The associated trait attribute has type Either Text val
. The
parsing is done leniently and any errors are reported in the trait
attribute.
Example usage:
lenientQueryParam @"limit" @Integer errorHandler okHandler
optionalLenientQueryParam :: forall name val h req. (Get h (QueryParam Optional Lenient name val) Request, ArrowChoice h) => Middleware h req (QueryParam Optional Lenient name val ': req) Source #
Extract a query parameter and convert it to a value of type val
.
Example usage:
optionalLenientQueryParam @"Content-Length" @Integer handler
The associated trait attribute has type Maybe (Either Text
val)
. The parsing is done leniently. Any parsing errors and
missing query parameters are reported in the trait attribute.