Copyright | (c) Frederick Pringle 2025 |
---|---|
License | BSD-3-Clause |
Maintainer | freddyjepringle@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Servant.API.Routes.Internal.Some
Description
Internal module, subject to change.
For both requests and responses, we want to represent three situations, depending on the number of X present: 0, 1, or many.
For example, if multiple ReqBody'
s are chained together with :>
, the resulting
type's HasServer
instance would try to parse the request body as all of the relevant types. In this
case the _routeRequestBody
field needs to be able to contain several
TypeRep
s as a conjunction (AND).
On the other hand, the UVerb
combinator lets us represent an endpoint that may return one of
several types: hence the _routeResponse
field needs to be able to contain
several possible responses as a disjunction (OR).
The Some
type lets us represent both of these situations.
However we need to abstract over the type contained in Some
, since we need to represent different
data in those 2 different situations, because of the way that Servant represents them:
- for requests, different
ReqBody
s andHeader
s are independent. Therefore inRoute
, for requests we have
and_routeRequestHeaders
::HeaderRep
._routeRequestBody
~Some
TypeRep
- for responses, multiple response options are represented using
UVerb
, which bundles response types and headers together. Therefore for responses we have just one field,
._routeResponse
~Some
(TypeRep
, [HeaderRep
])
Documentation
Simple ADT which codifies whether a list contains 0, 1, or many elements.
Constructors
None | |
One a | |
Many [a] | Invariant: list needs to have length > 1 Whether or not order is important is left up to the user. Therefore we define no instances of
|
Instances
Foldable Some Source # | |
Defined in Servant.API.Routes.Internal.Some Methods fold :: Monoid m => Some m -> m Source # foldMap :: Monoid m => (a -> m) -> Some a -> m Source # foldMap' :: Monoid m => (a -> m) -> Some a -> m Source # foldr :: (a -> b -> b) -> b -> Some a -> b Source # foldr' :: (a -> b -> b) -> b -> Some a -> b Source # foldl :: (b -> a -> b) -> b -> Some a -> b Source # foldl' :: (b -> a -> b) -> b -> Some a -> b Source # foldr1 :: (a -> a -> a) -> Some a -> a Source # foldl1 :: (a -> a -> a) -> Some a -> a Source # toList :: Some a -> [a] Source # null :: Some a -> Bool Source # length :: Some a -> Int Source # elem :: Eq a => a -> Some a -> Bool Source # maximum :: Ord a => Some a -> a Source # minimum :: Ord a => Some a -> a Source # | |
Traversable Some Source # | |
Defined in Servant.API.Routes.Internal.Some | |
Functor Some Source # | |
Show a => Show (Some a) Source # | |
appendSome :: forall a. (a -> [a] -> [a]) -> ([a] -> a -> [a]) -> Some a -> Some a -> Some a Source #