hlrdb-core-0.1.3.0: High-level Redis Database Core API

Safe HaskellNone
LanguageHaskell2010

HLRDB.Primitives.Aggregate

Description

Combinators that can be used for aggregating independent queries. See my article about aggregating mget queries for more information.

Synopsis

Documentation

newtype T x y a b Source #

Abstract representation for aggregation.

Constructors

T (Traversal a b x y) 
Instances
Profunctor (T x y) Source # 
Instance details

Defined in HLRDB.Primitives.Aggregate

Methods

dimap :: (a -> b) -> (c -> d) -> T x y b c -> T x y a d #

lmap :: (a -> b) -> T x y b c -> T x y a c #

rmap :: (b -> c) -> T x y a b -> T x y a c #

(#.) :: Coercible c b => q b c -> T x y a b -> T x y a c #

(.#) :: Coercible b a => T x y b c -> q a b -> T x y a c #

Choice (T x y) Source # 
Instance details

Defined in HLRDB.Primitives.Aggregate

Methods

left' :: T x y a b -> T x y (Either a c) (Either b c) #

right' :: T x y a b -> T x y (Either c a) (Either c b) #

Traversing (T x y) Source # 
Instance details

Defined in HLRDB.Primitives.Aggregate

Methods

traverse' :: Traversable f => T x y a b -> T x y (f a) (f b) #

wander :: (forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t) -> T x y a b -> T x y s t #

Strong (T x y) Source # 
Instance details

Defined in HLRDB.Primitives.Aggregate

Methods

first' :: T x y a b -> T x y (a, c) (b, c) #

second' :: T x y a b -> T x y (c, a) (c, b) #

Functor (T x y a) Source # 
Instance details

Defined in HLRDB.Primitives.Aggregate

Methods

fmap :: (a0 -> b) -> T x y a a0 -> T x y a b #

(<$) :: a0 -> T x y a b -> T x y a a0 #

Applicative (T x y a) Source # 
Instance details

Defined in HLRDB.Primitives.Aggregate

Methods

pure :: a0 -> T x y a a0 #

(<*>) :: T x y a (a0 -> b) -> T x y a a0 -> T x y a b #

liftA2 :: (a0 -> b -> c) -> T x y a a0 -> T x y a b -> T x y a c #

(*>) :: T x y a a0 -> T x y a b -> T x y a b #

(<*) :: T x y a a0 -> T x y a b -> T x y a a0 #

type (⟿) a b = T ByteString (Maybe ByteString) a b Source #

A query using input of type a and yielding an output of type b

type (~~>) a b = T ByteString (Maybe ByteString) a b Source #

An ASCII version of ⟿

type Query a b = a b Source #

Non-infix alias of ⟿

aggregatePair :: (Traversing p, Functor (p (a, a')), Applicative (p (a, a'))) => p a b -> p a' b' -> p (a, a') (b, b') Source #

We can merge any two arbitrary mget queries.

remember :: T x y a b -> T x y a (a, b) Source #

And we can remember the lookup

runT :: Functor f => ([x] -> f [y]) -> T x y a b -> a -> f b Source #

Reify aggregation into a target functor.

Aggregate, atomic multi-set query (as in setting multiple things in a single query)

data MSET Source #

Aggregated mset query

Instances
Semigroup MSET Source # 
Instance details

Defined in HLRDB.Internal

Methods

(<>) :: MSET -> MSET -> MSET #

sconcat :: NonEmpty MSET -> MSET #

stimes :: Integral b => b -> MSET -> MSET #

Monoid MSET Source # 
Instance details

Defined in HLRDB.Internal

Methods

mempty :: MSET #

mappend :: MSET -> MSET -> MSET #

mconcat :: [MSET] -> MSET #