Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
- get :: MonadRedis m => RedisStructure (BASIC w) a b -> a -> m b
- liftq :: RedisStructure (BASIC w) a b -> a ⟿ b
- mget :: MonadRedis m => (a ⟿ b) -> a -> m b
- set :: MonadRedis m => RedisStructure (BASIC w) a b -> a -> b -> m ()
- set' :: MonadRedis m => RedisBasic a (Maybe b) -> a -> b -> m ()
- incr :: MonadRedis m => RedisIntegral a b -> a -> m b
- incrby :: MonadRedis m => RedisIntegral a b -> a -> b -> m b
- decr :: MonadRedis m => RedisIntegral a b -> a -> m b
- decrby :: MonadRedis m => RedisIntegral a b -> a -> b -> m b
- lrange :: MonadRedis m => RedisList a b -> a -> Integer -> Integer -> m [b]
- lprepend :: (MonadRedis m, Traversable t) => RedisList a b -> a -> t b -> m ()
- lappend :: (MonadRedis m, Traversable t) => RedisList a b -> a -> t b -> m ()
- lpop :: MonadRedis m => RedisList a b -> a -> m (Maybe b)
- lrem :: MonadRedis m => RedisList a b -> a -> b -> m ()
- llen :: MonadRedis m => RedisList a b -> a -> m Integer
- hgetall :: MonadRedis m => RedisHSet a s b -> a -> m [(s, b)]
- hget :: MonadRedis m => RedisHSet a s b -> a -> s -> m (Maybe b)
- hmget :: (MonadRedis m, Traversable t) => RedisHSet a s b -> a -> t s -> m (t (s, Maybe b))
- hset :: MonadRedis m => RedisHSet a s b -> a -> s -> b -> m (ActionPerformed Creation)
- hmset :: (MonadRedis m, Traversable t) => RedisHSet a s b -> a -> t (s, b) -> m ()
- hdel :: (MonadRedis m, Traversable t) => RedisHSet a s b -> a -> t s -> m (ActionPerformed Deletion)
- hsetnx :: MonadRedis m => RedisHSet a s b -> a -> s -> b -> m (ActionPerformed Creation)
- hscan :: RedisHSet a s b -> a -> Cursor -> Redis (Maybe Cursor, [(s, b)])
- smembers :: (MonadRedis m, Eq b, Hashable b) => RedisSet a b -> a -> m (HashSet b)
- sismember :: MonadRedis m => RedisSet a b -> a -> b -> m Bool
- sadd :: (MonadRedis m, Traversable t) => RedisSet a b -> a -> t b -> m ()
- srem :: (MonadRedis m, Traversable t) => RedisSet a b -> a -> t b -> m ()
- scard :: MonadRedis m => RedisSet a b -> a -> m Integer
- srandmember :: MonadRedis m => RedisSet a b -> a -> m (Maybe b)
- sscan :: MonadRedis m => RedisSet a b -> a -> Cursor -> m (Maybe Cursor, [b])
- zadd :: (MonadRedis m, Traversable t) => RedisSSet a b -> a -> t (Double, b) -> m (ActionPerformed Creation)
- zscore :: MonadRedis m => RedisSSet a b -> a -> b -> m (Maybe Double)
- zupdate :: MonadRedis m => RedisSSet a b -> a -> (Double -> Double) -> m ()
- zbest :: MonadRedis m => RedisSSet a b -> a -> Integer -> Integer -> m [b]
- zworst :: MonadRedis m => RedisSSet a b -> a -> Integer -> Integer -> m [b]
- zmember :: MonadRedis m => RedisSSet a b -> a -> b -> m Bool
- zrank :: MonadRedis m => RedisSSet a b -> a -> b -> m (Maybe Integer)
- zrevrank :: MonadRedis m => RedisSSet a b -> a -> b -> m (Maybe Integer)
- zrem :: (MonadRedis m, Traversable t) => RedisSSet a b -> a -> t b -> m (ActionPerformed Deletion)
- zincrby :: MonadRedis m => RedisSSet a b -> a -> (Integer, b) -> m Double
- zcard :: MonadRedis m => RedisSSet a b -> a -> m Integer
- zscan :: MonadRedis m => RedisSSet a b -> a -> Cursor -> m (Maybe Cursor, [(b, Double)])
- del :: (Traversable t, MonadRedis m) => RedisStructure v a b -> t a -> m (ActionPerformed Deletion)
- persist :: MonadRedis m => RedisStructure v a b -> a -> m Bool
- expire :: MonadRedis m => RedisStructure v a b -> a -> Integer -> m Bool
- expireat :: MonadRedis m => RedisStructure v a b -> a -> UTCTime -> m Bool
- data Redis a :: * -> *
- class Monad m => MonadRedis (m :: * -> *) where
- liftRedis :: MonadRedis m => forall a. Redis a -> m a
- data Cursor :: *
- cursor0 :: Cursor
- module HLRDB.Primitives.Aggregate
- module HLRDB.Primitives.Redis
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
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.
HSet
hgetall :: MonadRedis m => RedisHSet a s b -> a -> m [(s, b)] Source #
Retrieve all elements of an HSet
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
srandmember :: MonadRedis m => RedisSet a b -> a -> m (Maybe b) Source #
Retrieve a random element from a 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.
zscan :: MonadRedis m => RedisSSet a b -> a -> Cursor -> m (Maybe Cursor, [(b, Double)]) Source #
Use a cursor to iterate a collection.
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
class Monad m => MonadRedis (m :: * -> *) where #
liftRedis :: MonadRedis m => forall a. Redis a -> m a #
HLRDB Primitive re-exports
module HLRDB.Primitives.Aggregate
module HLRDB.Primitives.Redis