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

Servant.Util.Combinators.Sorting.Backend

Description

Applying sorting specifications.

Synopsis

Documentation

class SortingBackend backend where Source #

Implementation of filtering backend.

Associated Types

type SortedValue backend a :: * Source #

The part of object which we are filtering on, provided by server backend implementor.

type SortedValueConstraint backend a :: Constraint Source #

What we require from sorted values in order to be sortable.

type SortedValueConstraint backend a = ()

type BackendOrdering backend :: * Source #

A resulting ordering.

Methods

backendFieldSort :: SortedValueConstraint backend a => SortedValue backend a -> SortingApp backend ('TyNamedParam name a) Source #

Implement SortingApp as sorting on the given field.

fieldSort :: forall name a backend. (SortingBackend backend, SortedValueConstraint backend a) => SortedValue backend a -> SortingApp backend ('TyNamedParam name a) Source #

newtype SortingApp backend param Source #

A function defining a way to apply the given SortingItem (which is sorting order on a single parameter).

Constructors

SortingApp (SortingItemTagged param -> BackendOrdering backend) 

type SortingSpecApp backend (allParams :: [TyNamedParam *]) = HList (SortingApp backend) allParams Source #

List of SortingApp functions. Describes how to apply SortingSpec params (each of possible SortingItem) to an SQL query.

Instance of this type can be created using fieldSort function. For example:

sortingSpecApp :: SortingSpecApp ["course" ?: Course, "desc" ?: Text]
sortingSpecApp =
    fieldSort "course" courseField .*.
    fieldSort "desc" descField .*.
    HNil

Annotating fieldSort call with parameter name is not mandatory but recommended to prevent possible mistakes in fieldSorts ordering.

class ApplyToSortItem backend params where Source #

Lookup for appropriate SortingApp in SortingSpecApp and apply it to SortingItem.

Methods

applyToSortItem :: SortingSpecApp backend params -> SortingItem -> Maybe (BackendOrdering backend) Source #

Apply spec app to the given SortingItem We return Maybe here (instead of forcing presence at type-level) for convenience.

Instances

Instances details
ApplyToSortItem backend ('[] :: [TyNamedParam Type]) Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Backend

(KnownSymbol name, ApplyToSortItem backend params) => ApplyToSortItem backend ('TyNamedParam name p ': params) Source # 
Instance details

Defined in Servant.Util.Combinators.Sorting.Backend

Methods

applyToSortItem :: SortingSpecApp backend ('TyNamedParam name p ': params) -> SortingItem -> Maybe (BackendOrdering backend) Source #

backendApplySorting :: forall provided base allParams backend. (allParams ~ AllSortingParams provided base, ApplyToSortItem backend allParams) => SortingSpec provided base -> SortingSpecApp backend allParams -> [BackendOrdering backend] Source #

Apply a given SortingSpecApp to a SortingSpec producing a pack of ordering values which define lexicographical sorting order.