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

Safe HaskellNone
LanguageHaskell2010

HLRDB.Core

Contents

Description

This package is an abstract API for modeling high-level Redis functionality. It makes no opinion on either serialization or key construction, which means there is a fair amount of work to do to make this library usable. If you do not want to do this work and don't mind these decisions being made for you, you may use the HLRDB library, which gives you a ready-to-go API.

This package depends on the Hedis library for low-level Redis bindings, but it is not recommended to import them together in the same module, as there are many name conflicts, since much of what HLRDB does is simply assign types to commands. Despite this, much of the HLRDB API does differ entirely, with many commands added, removed, merged, or simply rethought from a Haskell perspective.

When using this package, you should always ensure that your Eq instances respect the induced equality via whatever serialization mechanism you've specified, since many commands perform comparisons in Redis directly.

Synopsis

Basic

get :: MonadRedis m => RedisStructure (BASIC w) a b -> a -> m b Source #

Simple get command. Works on RedisBasic a b and RedisIntegral a b.

liftq :: RedisStructure (BASIC w) a b -> a b Source #

Construct a query to be used with mget. You may combine many of these together to create complex queries. Use mget to execute the query back in the Redis monad. Works on RedisBasic a b and RedisIntegral a b.

mget :: MonadRedis m => (a b) -> a -> m b Source #

Reify a (⟿) query into the Redis monad via a single mget command.

set :: MonadRedis m => RedisStructure (BASIC w) a b -> a -> b -> m () Source #

Set a value for a given key. Works on RedisBasic a b and RedisIntegral a b.

set' :: MonadRedis m => RedisBasic a (Maybe b) -> a -> b -> m () Source #

Convenient alias for setting a value for an optional path

liftqs :: RedisStructure (BASIC w) a b -> (a, b) -> MSET Source #

Construct a query to be used with mset. The MSET type is a Monoid, so you may combine many of these together before executing the batch with the mset command.

mset :: MonadRedis m => MSET -> m () Source #

Execute a MSET query.

setex :: MonadRedis m => RedisStructure (BASIC w) a b -> a -> Integer -> b -> m () Source #

Set a value together with a given expiration timeout (in seconds).

incr :: MonadRedis m => RedisIntegral a b -> a -> m b Source #

Increment an Integer in Redis. Empty values are treated as 0.

incrby :: MonadRedis m => RedisIntegral a b -> a -> b -> m b Source #

Increment an Integer in Redis by a specific amount. Empty values are treated as 0.

decr :: MonadRedis m => RedisIntegral a b -> a -> m b Source #

Decrement an Integer in Redis. Empty values are treated as 0.

decrby :: MonadRedis m => RedisIntegral a b -> a -> b -> m b Source #

Decrement an Integer in Redis by a specific amount. Empty values are treated as 0.

List

lrange :: MonadRedis m => RedisList a b -> a -> Integer -> Integer -> m [b] Source #

Retrieve a range of elements. Endpoints are inclusive, just as with Haskell's [ 1 .. 5 ] notation.

lprepend :: (MonadRedis m, Traversable t) => RedisList a b -> a -> t b -> m () Source #

Prepend items to the front of a list

lappend :: (MonadRedis m, Traversable t) => RedisList a b -> a -> t b -> m () Source #

Append items to the end of a list

lpop :: MonadRedis m => RedisList a b -> a -> m (Maybe b) Source #

Remove and return an item from the head of the list.

lrem :: MonadRedis m => RedisList a b -> a -> b -> m () Source #

Remove an item from the list. You should ensure that any Eq instance in Haskell respects the induced equality by your encoding scheme, as Redis will use the latter.

llen :: MonadRedis m => RedisList a b -> a -> m Integer Source #

Retrieve the length of a list.

HSet

hgetall :: MonadRedis m => RedisHSet a s b -> a -> m [(s, b)] Source #

Retrieve all elements of an HSet

hget :: MonadRedis m => RedisHSet a s b -> a -> s -> m (Maybe b) Source #

Lookup via key and subkey

hmget :: (MonadRedis m, Traversable t) => RedisHSet a s b -> a -> t s -> m (t (s, Maybe b)) Source #

Lookup via key and subkeys, pairing each given subkey with the lookup result

hset :: MonadRedis m => RedisHSet a s b -> a -> s -> b -> m (ActionPerformed Creation) Source #

Set via key and subkey

hmset :: (MonadRedis m, Traversable t) => RedisHSet a s b -> a -> t (s, b) -> m () Source #

Set via key and subkeys

hdel :: (MonadRedis m, Traversable t) => RedisHSet a s b -> a -> t s -> m (ActionPerformed Deletion) Source #

Delete via key and subkeys

hsetnx :: MonadRedis m => RedisHSet a s b -> a -> s -> b -> m (ActionPerformed Creation) Source #

Set a value only if it does not currently exist in the HSET

hscan :: RedisHSet a s b -> a -> Cursor -> Redis (Maybe Cursor, [(s, b)]) Source #

Use a cursor to iterate a collection

Set

smembers :: (MonadRedis m, Eq b, Hashable b) => RedisSet a b -> a -> m (HashSet b) Source #

Retrieve the elements of a set from Redis

sismember :: MonadRedis m => RedisSet a b -> a -> b -> m Bool Source #

Test if an item is a member of a set

sadd :: (MonadRedis m, Traversable t) => RedisSet a b -> a -> t b -> m () Source #

Add items to a set

srem :: (MonadRedis m, Traversable t) => RedisSet a b -> a -> t b -> m () Source #

Remove items from a set

scard :: MonadRedis m => RedisSet a b -> a -> m Integer Source #

Retrieve the cardinality of a set

srandmember :: MonadRedis m => RedisSet a b -> a -> m (Maybe b) Source #

Retrieve a random element from a set. The underlying Redis primitive uses a poor but efficient distribution, biased by the underlying hash bucket allocation.

srandmemberN :: MonadRedis m => RedisSet a b -> Integer -> a -> m [b] Source #

Retrieve up to N unique random elements, limited by the cardinality of the set.

sscan :: MonadRedis m => RedisSet a b -> a -> Cursor -> m (Maybe Cursor, [b]) Source #

Use a cursor to iterate a collection

SSet

zadd :: (MonadRedis m, Traversable t) => RedisSSet a b -> a -> t (Double, b) -> m (ActionPerformed Creation) Source #

Add items and scores

zscore :: MonadRedis m => RedisSSet a b -> a -> b -> m (Maybe Double) Source #

Lookup an element's score

zupdate :: MonadRedis m => RedisSSet a b -> a -> (Double -> Double) -> m () Source #

Read the scores from Redis, apply the given trasformation, and write the resulting data

zbest :: MonadRedis m => RedisSSet a b -> a -> Integer -> Integer -> m [b] Source #

Retrieve the given range of best-performing elements. Range is inclusive, just as with Haskell's [ 1 .. 5 ] notation, and it is 0-based, which means [ 0 .. 4 ] is what corresponds to the English phrase "Best 5."

zworst :: MonadRedis m => RedisSSet a b -> a -> Integer -> Integer -> m [b] Source #

Retrieve the given range of worst-performing elements. Range is inclusive, just as with Haskell's [ 1 .. 5 ] notation, and it is 0-based, which means [ 0 .. 4 ] is what corresponds to the English phrase "Worst 5."

zmember :: MonadRedis m => RedisSSet a b -> a -> b -> m Bool Source #

Test if an object is a member of the set.

zrank :: MonadRedis m => RedisSSet a b -> a -> b -> m (Maybe Integer) Source #

Calculate the rank of an item. The best item has rank 0.

zrevrank :: MonadRedis m => RedisSSet a b -> a -> b -> m (Maybe Integer) Source #

Calculate the rank of an item starting from the end, e.g., the worst item has rank 0.

zrem :: (MonadRedis m, Traversable t) => RedisSSet a b -> a -> t b -> m (ActionPerformed Deletion) Source #

Remove items from a sorted set

zincrby :: MonadRedis m => RedisSSet a b -> a -> (Integer, b) -> m Double Source #

Increment an item's score. If the item does not already exist, it is inserted with the given score.

zcard :: MonadRedis m => RedisSSet a b -> a -> m Integer Source #

The cardinality of a sorted set

zscan :: MonadRedis m => RedisSSet a b -> a -> Cursor -> m (Maybe Cursor, [(b, Double)]) Source #

Use a cursor to iterate a collection.

zrangebyscore :: MonadRedis m => RedisSSet a b -> a -> Maybe Double -> Maybe Double -> Maybe Integer -> Maybe Integer -> m [(b, Double)] Source #

Retrieve items in a score range; final parameters are min, max, offset, and limit

Universal

del :: (Traversable t, MonadRedis m) => RedisStructure v a b -> t a -> m (ActionPerformed Deletion) Source #

Delete all data for the given keys in Redis

persist :: MonadRedis m => RedisStructure v a b -> a -> m Bool Source #

Discard any pending expirations of this key. Returns True if the key both exists and had a timeout which was removed by the command.

expire :: MonadRedis m => RedisStructure v a b -> a -> Integer -> m Bool Source #

Expire after a given amount of time (in seconds). Returns True if the key existed and a timeout was set.

expireat :: MonadRedis m => RedisStructure v a b -> a -> UTCTime -> m Bool Source #

Expire at a given timestamp. Returns True if the key existed and a timeout was set.

Re-exports from hedis

data Redis a #

Context for normal command execution, outside of transactions. Use runRedis to run actions of this type.

In this context, each result is wrapped in an Either to account for the possibility of Redis returning an Error reply.

Instances
Monad Redis 
Instance details

Defined in Database.Redis.Core

Methods

(>>=) :: Redis a -> (a -> Redis b) -> Redis b #

(>>) :: Redis a -> Redis b -> Redis b #

return :: a -> Redis a #

fail :: String -> Redis a #

Functor Redis 
Instance details

Defined in Database.Redis.Core

Methods

fmap :: (a -> b) -> Redis a -> Redis b #

(<$) :: a -> Redis b -> Redis a #

Applicative Redis 
Instance details

Defined in Database.Redis.Core

Methods

pure :: a -> Redis a #

(<*>) :: Redis (a -> b) -> Redis a -> Redis b #

liftA2 :: (a -> b -> c) -> Redis a -> Redis b -> Redis c #

(*>) :: Redis a -> Redis b -> Redis b #

(<*) :: Redis a -> Redis b -> Redis a #

MonadIO Redis 
Instance details

Defined in Database.Redis.Core

Methods

liftIO :: IO a -> Redis a #

MonadRedis Redis 
Instance details

Defined in Database.Redis.Core

Methods

liftRedis :: Redis a -> Redis a #

RedisCtx Redis (Either Reply) 
Instance details

Defined in Database.Redis.Core

class Monad m => MonadRedis (m :: Type -> Type) #

Minimal complete definition

liftRedis

Instances
MonadRedis RedisTx 
Instance details

Defined in Database.Redis.Transactions

Methods

liftRedis :: Redis a -> RedisTx a #

MonadRedis Redis 
Instance details

Defined in Database.Redis.Core

Methods

liftRedis :: Redis a -> Redis a #

liftRedis :: MonadRedis m => Redis a -> m a #

data Cursor #

Instances
Eq Cursor 
Instance details

Defined in Database.Redis.ManualCommands

Methods

(==) :: Cursor -> Cursor -> Bool #

(/=) :: Cursor -> Cursor -> Bool #

Show Cursor 
Instance details

Defined in Database.Redis.ManualCommands

RedisArg Cursor 
Instance details

Defined in Database.Redis.ManualCommands

Methods

encode :: Cursor -> ByteString

RedisResult Cursor 
Instance details

Defined in Database.Redis.ManualCommands

HLRDB Primitive re-exports