servant-routes-0.1.0.0: Generate route descriptions from Servant APIs
Copyright(c) Frederick Pringle 2025
LicenseBSD-3-Clause
Maintainerfreddyjepringle@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

Synopsis

Documentation

data Some a Source #

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 Eq, Ord, Semigroup or any other class that would involve comparing or combining this list.

Instances

Instances details
Foldable Some Source # 
Instance details

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 #

sum :: Num a => Some a -> a Source #

product :: Num a => Some a -> a Source #

Traversable Some Source # 
Instance details

Defined in Servant.API.Routes.Internal.Some

Methods

traverse :: Applicative f => (a -> f b) -> Some a -> f (Some b) Source #

sequenceA :: Applicative f => Some (f a) -> f (Some a) Source #

mapM :: Monad m => (a -> m b) -> Some a -> m (Some b) Source #

sequence :: Monad m => Some (m a) -> m (Some a) Source #

Functor Some Source # 
Instance details

Defined in Servant.API.Routes.Internal.Some

Methods

fmap :: (a -> b) -> Some a -> Some b Source #

(<$) :: a -> Some b -> Some a Source #

Show a => Show (Some a) Source # 
Instance details

Defined in Servant.API.Routes.Internal.Some

Methods

showsPrec :: Int -> Some a -> ShowS Source #

show :: Some a -> String Source #

showList :: [Some a] -> ShowS Source #

toList :: Some a -> [a] Source #

Convert a Some to a list. Inverse of fromList.

fromList :: [a] -> Some a Source #

Convert a list of as to a Some. Inverse of toList.

This maintains the invariant that the argument of Many has to be of length > 1.

eqSome :: forall a. Eq a => ([a] -> [a] -> Bool) -> Some a -> Some a -> Bool Source #

Compare 2 Somes for equality, given a way to compare lists in the Many constructor.

Use this to implement Eq instances for newtypes around Some.

appendSome :: forall a. (a -> [a] -> [a]) -> ([a] -> a -> [a]) -> Some a -> Some a -> Some a Source #

Combine 2 Somes, given a way to combine single elements with lists in the One <> Many cases.

Use this to implement Semigroup instances for newtypes around Some.

someToJSONAs :: (a -> Value) -> Text -> Some a -> Value Source #

Represent a Some as a JSON Value.

Use this to implement ToJSON instances for newtypes around Some.

This choice of representation is opinionated, and some may disagree.

Given a function f to convert an a to JSON, and a label:

None -> null
One a -> f a
Many list -> { label: map f list }