servant-util-0.1.0.2: Servant servers utilities.
Safe HaskellNone
LanguageHaskell2010

Servant.Util.Combinators.Sorting

Description

Provides combinator for lexicographical sorting.

Synopsis

General

data SortingParams (provided :: [TyNamedParam *]) (base :: [TyNamedParam (SortingOrderType *)]) Source #

Servant API combinator which allows to accept sorting parameters as a query parameter.

Example: with the following combinator

SortingParams ["time" ?: Timestamp, "name" ?: Text] '[]

the endpoint can parse "sortBy=-time,+name" or "sortBy=desc(time),asc(name)" formats, which would mean sorting by mentioned fields lexicographically. All sorting subparameters are optional, as well as entire "sortBy" parameter.

The second type-level list stands for the base sorting order, it will be applied in the end disregard the user's input. It is highly recommended to specify the base sorting that unambigously orders the result(for example - by the primary key of the database), otherwise pagination may behave unexpectedly for the client when it specifies no sorting.

If you want the base sorting order to be overridable by the user, you can put the respective fields in both lists. For example, this combinator:

SortingParams
  '["time" ?: Timestamp]
   ["id" ?: '(Id, 'Descendant), "time" ?: '(Timestamp, 'Ascendant)]

will sort results lexicographically by (Down id, time), but if the client specifies sorting by time, you will get sorting by (time, Down id) as the trailing "time" will not affect anything.

It is preferred to put a base sorting at least by ID, this way results will be more deterministic.

Your handler will be provided with SortingSpec argument which can later be passed in an appropriate function to perform sorting.

Instances

Instances details
HasClient m subApi => HasClient m (SortingParams provided base :> subApi) Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Client

Associated Types

type Client m (SortingParams provided base :> subApi) #

Methods

clientWithRoute :: Proxy m -> Proxy (SortingParams provided base :> subApi) -> Request -> Client m (SortingParams provided base :> subApi) #

hoistClientMonad :: Proxy m -> Proxy (SortingParams provided base :> subApi) -> (forall x. mon x -> mon' x) -> Client mon (SortingParams provided base :> subApi) -> Client mon' (SortingParams provided base :> subApi) #

(HasLoggingServer config subApi ctx, HasContextEntry (ctx .++ DefaultErrorFormatters) ErrorFormatters, ReifySortingItems base, ReifyParamsNames provided) => HasLoggingServer (config :: Type) (SortingParams provided base :> subApi :: Type) ctx Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Logging

Methods

routeWithLog :: Proxy (LoggingApiRec config (SortingParams provided base :> subApi)) -> Context ctx -> Delayed env (Server (LoggingApiRec config (SortingParams provided base :> subApi))) -> Router env Source #

(HasSwagger api, ReifySortingItems base, ReifyParamsNames provided) => HasSwagger (SortingParams provided base :> api :: Type) Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Swagger

Methods

toSwagger :: Proxy (SortingParams provided base :> api) -> Swagger #

(HasServer subApi ctx, HasContextEntry (ctx .++ DefaultErrorFormatters) ErrorFormatters, ReifySortingItems base, ReifyParamsNames provided) => HasServer (SortingParams provided base :> subApi :: Type) ctx Source #

Consumes "sortBy" query parameter and fetches sorting parameters contained in it.

Instance details

Defined in Servant.Util.Combinators.Sorting.Server

Associated Types

type ServerT (SortingParams provided base :> subApi) m #

Methods

route :: Proxy (SortingParams provided base :> subApi) -> Context ctx -> Delayed env (Server (SortingParams provided base :> subApi)) -> Router env #

hoistServerWithContext :: Proxy (SortingParams provided base :> subApi) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (SortingParams provided base :> subApi) m -> ServerT (SortingParams provided base :> subApi) n #

type Client m (SortingParams provided base :> subApi) Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Client

type Client m (SortingParams provided base :> subApi) = SortingSpec provided base -> Client m subApi
type ServerT (SortingParams provided base :> subApi :: Type) m Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Server

type ServerT (SortingParams provided base :> subApi :: Type) m = SortingSpec provided base -> ServerT subApi m

data SortingSpec (provided :: [TyNamedParam *]) (base :: [TyNamedParam (SortingOrderType *)]) Source #

What is passed to an endpoint, contains all sorting parameters provided by a user.

Instances

Instances details
ReifySortingItems base => IsList (SortingSpec provided base) Source #

Instance for SortingSpec construction.

Instance details

Defined in Servant.Util.Combinators.Sorting.Construction

Associated Types

type Item (SortingSpec provided base) #

Methods

fromList :: [Item (SortingSpec provided base)] -> SortingSpec provided base #

fromListN :: Int -> [Item (SortingSpec provided base)] -> SortingSpec provided base #

toList :: SortingSpec provided base -> [Item (SortingSpec provided base)] #

Show (SortingSpec provided base) Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Base

Methods

showsPrec :: Int -> SortingSpec provided base -> ShowS #

show :: SortingSpec provided base -> String #

showList :: [SortingSpec provided base] -> ShowS #

(ReifySortingItems base, ReifyParamsNames provided) => Arbitrary (SortingSpec provided base) Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Arbitrary

Methods

arbitrary :: Gen (SortingSpec provided base) #

shrink :: SortingSpec provided base -> [SortingSpec provided base] #

ReifySortingItems base => Default (SortingSpec provided base) Source #

By default noSorting is used.

Instance details

Defined in Servant.Util.Combinators.Sorting.Construction

Methods

def :: SortingSpec provided base #

type Item (SortingSpec provided base) Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Construction

type Item (SortingSpec provided base) = SortingRequestItem provided

data SortingOrderType k Source #

Order of sorting for type-level.

Its constructors accept the type of thing we order by, e.g. Asc Id.

Constructors

Desc k 
Asc k 

Instances

Instances details
ReifySortingItems ('[] :: [TyNamedParam (SortingOrderType Type)]) Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Base

(ReifySortingOrder order, KnownSymbol name, ReifySortingItems items) => ReifySortingItems ('TyNamedParam name (order field) ': items) Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Base

Shortcuts

type family SortingParamProvidedOf a :: [TyNamedParam *] Source #

For a given return type of an endpoint get corresponding sorting params that can be specified by user. This mapping is sensible, since we usually allow to sort only on fields appearing in endpoint's response.

Instances

Instances details
type SortingParamProvidedOf NoContent Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Base

type family SortingParamBaseOf a :: [TyNamedParam (SortingOrderType *)] Source #

For a given return type of an endpoint get corresponding base sorting params.

Instances

Instances details
type SortingParamBaseOf NoContent Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Base

type SortingParamsOf a = SortingParams (SortingParamProvidedOf a) (SortingParamBaseOf a) Source #

This you will most probably want to specify in API.

type SortingSpecOf a = SortingSpec (SortingParamProvidedOf a) (SortingParamBaseOf a) Source #

This you will most probably want to specify in an endpoint implementation.

Manual construction

data SortingRequestItem (provided :: [TyNamedParam *]) Source #

Helper for defining custom SortingSpecs, contains SortingItem corresponding to one of parameter in provided list.

Instances

Instances details
Show (SortingRequestItem provided) Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Construction

Methods

showsPrec :: Int -> SortingRequestItem provided -> ShowS #

show :: SortingRequestItem provided -> String #

showList :: [SortingRequestItem provided] -> ShowS #

asc :: forall name provided. (KnownSymbol name, KnownTypeName provided name provided) => NameLabel name -> SortingRequestItem provided Source #

Ascendant sorting on a field with given name.

desc :: forall name provided. (KnownSymbol name, KnownTypeName provided name provided) => NameLabel name -> SortingRequestItem provided Source #

Ascendant sorting on a field with given name.

mkSortingSpec :: ReifySortingItems base => [SortingRequestItem provided] -> SortingSpec provided base Source #

Make a sorting specification. Specified list should contain sorting on distinct fields; we do not enforce this at type-level for convenience.

Example:

-- 

sortingSpec :: SortingSpec ["id" ?: Int, "desc" ?: Text]
sortingSpec = mkSortingSpec [asc #id]

noSorting :: ReifySortingItems base => SortingSpec provided base Source #

Do not specify ordering.

class ReifySortingItems (items :: [TyNamedParam (SortingOrderType *)]) Source #

Requires given type-level items to be valid specification of sorting.

Minimal complete definition

reifySortingItems

Instances

Instances details
ReifySortingItems ('[] :: [TyNamedParam (SortingOrderType Type)]) Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Base

(ReifySortingOrder order, KnownSymbol name, ReifySortingItems items) => ReifySortingItems ('TyNamedParam name (order field) ': items) Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Base

Re-exports

type (?:) = 'TyNamedParam Source #

Convenient type alias for TyNamedParam.