Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides combinators to represent named arguments to endpoints. Note that only link generation instances are provided here: you will most likely want one or both of Servant.Client.NamedArgs and Servant.Server.NamedArgs
Synopsis
- data NamedCapture' (mods :: [*]) (sym :: Symbol) (a :: *)
- type NamedCapture = NamedCapture' '[]
- data NamedCaptureAll (sym :: Symbol) (a :: *)
- data NamedParam (mods :: [*]) (sym :: Symbol) (a :: *)
- type RequiredNamedParam = NamedParam '[Required, Strict]
- type OptionalNamedParam = NamedParam '[Optional, Strict]
- data NamedParams (sym :: Symbol) (a :: *)
- data NamedFlag (sym :: Symbol)
- data NamedHeader' (mods :: [*]) (sym :: Symbol) (a :: *)
- type NamedHeader = NamedHeader' '[Optional, Strict]
- type RequiredNamedArgument mods name a = If (FoldRequired mods) (name :! a) (name :? a)
- type RequestNamedArgument mods name a = If (FoldRequired mods) (name :! If (FoldLenient mods) (Either Text a) a) (name :? If (FoldLenient mods) (Either Text a) a)
- foldRequiredNamedArgument :: forall mods name a r. (SBoolI (FoldRequired mods), KnownSymbol name) => (a -> r) -> (Maybe a -> r) -> RequiredNamedArgument mods name a -> r
- foldRequiredAdapter :: forall mods name a r. (SBoolI (FoldRequired mods), KnownSymbol name) => (If (FoldRequired mods) a (Maybe a) -> r) -> RequiredNamedArgument mods name a -> r
- unfoldRequestNamedArgument :: forall mods name m a. (Monad m, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)) => m (RequestNamedArgument mods name a) -> (Text -> m (RequestNamedArgument mods name a)) -> Maybe (Either Text a) -> m (RequestNamedArgument mods name a)
- type family Transform (t :: [Transformation]) (api :: k) :: k where ...
- data AsTransformed (t :: [Transformation]) (m :: *)
- data Transformation
Documentation
data NamedCapture' (mods :: [*]) (sym :: Symbol) (a :: *) Source #
Isomorphism of Capture'
Instances
(ToHttpApiData v, HasLink sub, KnownSymbol name) => HasLink (NamedCapture' mods name v :> sub :: *) Source # | Becomes a named required argument |
Defined in Servant.API.NamedArgs type MkLink (NamedCapture' mods name v :> sub) a :: * # toLink :: (Link -> a) -> Proxy (NamedCapture' mods name v :> sub) -> Link -> MkLink (NamedCapture' mods name v :> sub) a # | |
type MkLink (NamedCapture' mods name v :> sub :: *) a Source # | |
Defined in Servant.API.NamedArgs |
type NamedCapture = NamedCapture' '[] Source #
Isomorphism of Capture
data NamedCaptureAll (sym :: Symbol) (a :: *) Source #
Isomorphism of CaptureAll
Instances
(ToHttpApiData v, HasLink sub, KnownSymbol name) => HasLink (NamedCaptureAll name v :> sub :: *) Source # | Becomes a named optional argument, taking a list and defaulting to an empty list |
Defined in Servant.API.NamedArgs type MkLink (NamedCaptureAll name v :> sub) a :: * # toLink :: (Link -> a) -> Proxy (NamedCaptureAll name v :> sub) -> Link -> MkLink (NamedCaptureAll name v :> sub) a # | |
type MkLink (NamedCaptureAll name v :> sub :: *) a Source # | |
Defined in Servant.API.NamedArgs |
data NamedParam (mods :: [*]) (sym :: Symbol) (a :: *) Source #
Isomorphism of QueryParam'
Instances
(KnownSymbol name, HasLink sub, ToHttpApiData v, SBoolI (FoldRequired mods)) => HasLink (NamedParam mods name v :> sub :: *) Source # | Becomes either a required or optional named argument depending on
whether it is set as |
Defined in Servant.API.NamedArgs type MkLink (NamedParam mods name v :> sub) a :: * # toLink :: (Link -> a) -> Proxy (NamedParam mods name v :> sub) -> Link -> MkLink (NamedParam mods name v :> sub) a # | |
type MkLink (NamedParam mods name v :> sub :: *) a Source # | |
Defined in Servant.API.NamedArgs type MkLink (NamedParam mods name v :> sub :: *) a = RequiredNamedArgument mods name v -> MkLink sub a |
type RequiredNamedParam = NamedParam '[Required, Strict] Source #
Shorthand for a required param, isomorphic to
QueryParam'
'[Required
, Strict
] from Servant
type OptionalNamedParam = NamedParam '[Optional, Strict] Source #
Shorthand for an optional param, isomorphic to
QueryParam'
'[Optional
, Strict
] from Servant
data NamedParams (sym :: Symbol) (a :: *) Source #
Isomorphism of QueryParams
Instances
(KnownSymbol name, HasLink sub, ToHttpApiData v) => HasLink (NamedParams name v :> sub :: *) Source # | Becomes a required named argument, taking a list |
Defined in Servant.API.NamedArgs type MkLink (NamedParams name v :> sub) a :: * # toLink :: (Link -> a) -> Proxy (NamedParams name v :> sub) -> Link -> MkLink (NamedParams name v :> sub) a # | |
type MkLink (NamedParams name v :> sub :: *) a Source # | |
Defined in Servant.API.NamedArgs |
data NamedFlag (sym :: Symbol) Source #
Isomorphism of QueryFlag
data NamedHeader' (mods :: [*]) (sym :: Symbol) (a :: *) Source #
Isomorphism of Header'
Instances
HasLink sub => HasLink (NamedHeader' mods name a :> sub :: *) Source # | Has no effect on the resulting link |
Defined in Servant.API.NamedArgs type MkLink (NamedHeader' mods name a :> sub) a :: * # toLink :: (Link -> a0) -> Proxy (NamedHeader' mods name a :> sub) -> Link -> MkLink (NamedHeader' mods name a :> sub) a0 # | |
type MkLink (NamedHeader' mods name a :> sub :: *) r Source # | |
Defined in Servant.API.NamedArgs |
type NamedHeader = NamedHeader' '[Optional, Strict] Source #
Shorthand for a required Header; Isomorphism of Header
type RequiredNamedArgument mods name a = If (FoldRequired mods) (name :! a) (name :? a) Source #
Returns the type name :! a if given a list including Required
and name :? a otherwise
type RequestNamedArgument mods name a = If (FoldRequired mods) (name :! If (FoldLenient mods) (Either Text a) a) (name :? If (FoldLenient mods) (Either Text a) a) Source #
Returns either a `NamedF Identity` or `NamedF Maybe` depending on if
required/optional, wrapping an `Either Text a` or an a
depending on if
lenient/strict
foldRequiredNamedArgument Source #
:: (SBoolI (FoldRequired mods), KnownSymbol name) | |
=> (a -> r) | Function to apply if the mods includes |
-> (Maybe a -> r) | Function to apply if the mods do not include |
-> RequiredNamedArgument mods name a | Argument to either |
-> r |
:: (SBoolI (FoldRequired mods), KnownSymbol name) | |
=> (If (FoldRequired mods) a (Maybe a) -> r) | Version of functions without named arguments |
-> RequiredNamedArgument mods name a | Argument to either |
-> r |
unfoldRequestNamedArgument Source #
:: (Monad m, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods)) | |
=> m (RequestNamedArgument mods name a) | error when argument is required |
-> (Text -> m (RequestNamedArgument mods name a)) | error when argument is strictly parsed |
-> Maybe (Either Text a) | value |
-> m (RequestNamedArgument mods name a) |
Unfold a value into a RequestNamedArgument
.
type family Transform (t :: [Transformation]) (api :: k) :: k where ... Source #
Transform
is used to transform back and forth between APIs
using the Named combinators and APIs not using the Named combinators
by applying the listed transformations to the api
data AsTransformed (t :: [Transformation]) (m :: *) Source #
AsTransformed
can be used to transform back and forth while using
Servant's generic programming (see Servant.API.Generic)
Instances
GenericMode mode => GenericMode (AsTransformed t mode) Source # | |
Defined in Servant.API.NamedArgs type (AsTransformed t mode) :- api :: * # | |
type (AsTransformed t mode) :- api Source # | |
Defined in Servant.API.NamedArgs |
data Transformation Source #
Possible transformations Transform
can apply
NameParams | Replace |
NameMultiParams | Replace |
NameCaptures | Replace |
NameCaptureAlls | Replace |
NameFlags | |
NameHeaders | Replace |
UnnameParams | Replace |
UnnameMultiParams | Replace |
UnnameCaptures | Replace |
UnnameCaptureAlls | Replace |
UnnameFlags | |
UnnameHeaders | Replace |
Instances
Enum Transformation Source # | |
Defined in Servant.API.NamedArgs succ :: Transformation -> Transformation # pred :: Transformation -> Transformation # toEnum :: Int -> Transformation # fromEnum :: Transformation -> Int # enumFrom :: Transformation -> [Transformation] # enumFromThen :: Transformation -> Transformation -> [Transformation] # enumFromTo :: Transformation -> Transformation -> [Transformation] # enumFromThenTo :: Transformation -> Transformation -> Transformation -> [Transformation] # | |
Eq Transformation Source # | |
Defined in Servant.API.NamedArgs (==) :: Transformation -> Transformation -> Bool # (/=) :: Transformation -> Transformation -> Bool # | |
Read Transformation Source # | |
Defined in Servant.API.NamedArgs readsPrec :: Int -> ReadS Transformation # readList :: ReadS [Transformation] # | |
Show Transformation Source # | |
Defined in Servant.API.NamedArgs showsPrec :: Int -> Transformation -> ShowS # show :: Transformation -> String # showList :: [Transformation] -> ShowS # |