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

Servant.Util.Combinators.Filtering

Description

Allows complex filtering on specified fields.

Synopsis

General

data FilterKind a Source #

We support two kinds of filters.

Constructors

AutoFilter a

Automatic filter where different operations are supported (eq, in, cmp). When applied to backend, only filtered value should be supplied.

ManualFilter a

User-provided value is passed to backend implementation as-is, and filtering on this value should be written manually.

Instances

Instances details
FilterBackend backend => BackendApplySomeFilter (backend :: k) ('[] :: [TyNamedFilter]) Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Backend

Methods

backendApplySomeFilter' :: FilteringSpecApp backend '[] -> SomeFilter '[] -> Maybe (MatchPredicate backend)

(Typeable fk, Typeable a, FilterBackend backend, KnownSymbol name, BackendApplyTypeFilter backend fk a, BackendApplySomeFilter backend params) => BackendApplySomeFilter (backend :: k) ('TyNamedParam name (fk a) ': params) Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Backend

Methods

backendApplySomeFilter' :: FilteringSpecApp backend ('TyNamedParam name (fk a) ': params) -> SomeFilter ('TyNamedParam name (fk a) ': params) -> Maybe (MatchPredicate backend)

AreFilteringParams ('[] :: [TyNamedFilter]) Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Server

BuildSomeFilter ('[] :: [TyNamedFilter]) Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Logging

(FromHttpApiData ty, Buildable ty, Typeable ty, KnownSymbol name, AreFilteringParams params) => AreFilteringParams ('TyNamedParam name ('ManualFilter ty) ': params) Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Server

(FromHttpApiData ty, Typeable ty, AreAutoFilters (SupportedFilters ty), KnownSymbol name, AreFilteringParams params) => AreFilteringParams ('TyNamedParam name ('AutoFilter ty) ': params) Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Server

Methods

parseFilteringParam :: Text -> Text -> Maybe (Either Text $ SomeFilter ('TyNamedParam name ('AutoFilter ty) ': params))

(KnownSymbol name, Typeable a, Buildable a, BuildSomeFilter params) => BuildSomeFilter ('TyNamedParam name ('ManualFilter a) ': params) Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Logging

(KnownSymbol name, Typeable a, Buildable a, BuildSomeFilter params) => BuildSomeFilter ('TyNamedParam name ('AutoFilter a) ': params) Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Logging

data FilteringParams (params :: [TyNamedFilter]) Source #

Servant API combinator which enables filtering on given fields.

If type T appears with a name name in params argument, then query parameters of name[op]=value format will be accepted, where op is a filtering operation (e.g. equal, not equal, greater) and value is an item of type T we filter against. Multiple filters will form a conjunction.

List of allowed filtering operations depends on type T and is specified by SupportedFilters type family.

Operation argument is optional, when not specified "equality" filter is applied.

Endpoint implementation will receive FilteringSpec value which contains information about all filters passed by user. You can later put it to an appropriate function to apply filtering.

Instances

Instances details
(HasClient m subApi, SomeFilterToReq params) => HasClient m (FilteringParams params :> subApi) Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Client

Associated Types

type Client m (FilteringParams params :> subApi) #

Methods

clientWithRoute :: Proxy m -> Proxy (FilteringParams params :> subApi) -> Request -> Client m (FilteringParams params :> subApi) #

hoistClientMonad :: Proxy m -> Proxy (FilteringParams params :> subApi) -> (forall x. mon x -> mon' x) -> Client mon (FilteringParams params :> subApi) -> Client mon' (FilteringParams params :> subApi) #

(HasLoggingServer config lcontext subApi ctx, AreFilteringParams params, ReifyParamsNames params, BuildSomeFilter params) => HasLoggingServer (config :: Type) lcontext (FilteringParams params :> subApi :: Type) ctx Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Logging

Methods

routeWithLog :: Proxy (LoggingApiRec config lcontext (FilteringParams params :> subApi)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (FilteringParams params :> subApi))) -> Router env Source #

(HasSwagger api, ReifyParamsNames params, FilterParamsHaveSwagger params) => HasSwagger (FilteringParams params :> api :: Type) Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Swagger

Methods

toSwagger :: Proxy (FilteringParams params :> api) -> Swagger #

(HasServer subApi ctx, AreFilteringParams params) => HasServer (FilteringParams params :> subApi :: Type) ctx Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Server

Associated Types

type ServerT (FilteringParams params :> subApi) m #

Methods

route :: Proxy (FilteringParams params :> subApi) -> Context ctx -> Delayed env (Server (FilteringParams params :> subApi)) -> Router env #

hoistServerWithContext :: Proxy (FilteringParams params :> subApi) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (FilteringParams params :> subApi) m -> ServerT (FilteringParams params :> subApi) n #

type Client m (FilteringParams params :> subApi) Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Client

type Client m (FilteringParams params :> subApi) = FilteringSpec params -> Client m subApi
type ServerT (FilteringParams params :> subApi :: Type) m Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Server

type ServerT (FilteringParams params :> subApi :: Type) m = FilteringSpec params -> ServerT subApi m

type family SupportedFilters ty :: [Type -> Type] Source #

For a type of field, get a list of supported filtering operations on this field.

Instances

Instances details
type SupportedFilters Bool Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Char Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Double Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Float Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Int Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Int8 Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Int16 Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Int32 Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Int64 Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Integer Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Natural Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Word Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Word8 Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Word16 Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Word32 Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Word64 Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters () Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters () = '[] :: [Type -> Type]
type SupportedFilters ByteString Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Text Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters UTCTime Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters LocalTime Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

type SupportedFilters Day Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Support

newtype FilteringSpec (params :: [TyNamedFilter]) Source #

This is what you get in endpoint implementation, it contains all filters supplied by a user. Invariant: each filter correspond to some type mentioned in params.

Constructors

FilteringSpec [SomeFilter params] 

Instances

Instances details
IsList (FilteringSpec params) Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Base

Associated Types

type Item (FilteringSpec params) #

Methods

fromList :: [Item (FilteringSpec params)] -> FilteringSpec params #

fromListN :: Int -> [Item (FilteringSpec params)] -> FilteringSpec params #

toList :: FilteringSpec params -> [Item (FilteringSpec params)] #

Default (FilteringSpec params) Source #

By default noFilters is used.

Instance details

Defined in Servant.Util.Combinators.Filtering.Construction

Methods

def :: FilteringSpec params #

type Item (FilteringSpec params) Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Base

type Item (FilteringSpec params) = Item [SomeFilter params]

Shortcuts

type family FilteringParamTypesOf a :: [TyNamedFilter] Source #

For a given return type of an endpoint get corresponding filtering params. This mapping is sensible, since we usually allow to filter only on fields appearing in endpoint's response.

Instances

Instances details
type FilteringParamTypesOf NoContent Source # 
Instance details

Defined in Servant.Util.Combinators.Filtering.Base

type FilteringParamsOf a = FilteringParams (FilteringParamTypesOf a) Source #

This you will most probably want to specify in API.

type FilteringSpecOf a = FilteringSpec (FilteringParamTypesOf a) Source #

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

Filter types

newtype LikePattern Source #

Simple regexp pattern, . and * signed will be considered. Escaping is performed via prefixing with backslash.

Constructors

LikePatternUnsafe 

Fields

Manual construction