Safe Haskell | None |
---|---|
Language | Haskell2010 |
Main Redis API and protocol implementation
Synopsis
- data Redis
- data Reply s
- data Message s
- = MSubscribe s Int
- | MUnsubscribe s Int
- | MPSubscribe s Int
- | MPUnsubscribe s Int
- | MMessage s s
- | MPMessage s s s
- data LInsertDirection
- data Interval a
- class IsInterval i a | i -> a where
- toInterval :: i -> Interval a
- data SortOptions s = SortOptions {}
- data Aggregate
- data RedisKeyType
- type RedisInfo = Map String String
- sortDefaults :: SortOptions ByteString
- fromRInline :: (Monad m, BS s) => Reply s -> m s
- fromRBulk :: (Monad m, BS s) => Reply s -> m (Maybe s)
- fromRBulk' :: (Monad m, BS s) => Reply s -> m s
- fromRMulti :: (Monad m, BS s) => Reply s -> m (Maybe [Reply s])
- fromRMultiBulk :: (Monad m, BS s) => Reply s -> m (Maybe [Maybe s])
- fromRMultiBulk' :: (Monad m, BS s) => Reply s -> m [s]
- fromRInt :: (Monad m, BS s) => Reply s -> m Int
- fromROk :: (Monad m, BS s) => Reply s -> m ()
- noError :: (Monad m, BS s) => Reply s -> m ()
- parseMessage :: (Monad m, BS s) => Reply ByteString -> m (Message s)
- takeAll :: (Int, Int)
- localhost :: String
- defaultPort :: String
- connect :: String -> String -> IO Redis
- disconnect :: Redis -> IO ()
- isConnected :: Redis -> IO Bool
- getServer :: Redis -> IO (String, String)
- getDatabase :: Redis -> IO Int
- renameCommand :: Redis -> ByteString -> ByteString -> IO ()
- ping :: Redis -> IO (Reply ())
- auth :: BS s => Redis -> s -> IO (Reply ())
- echo :: BS s => Redis -> s -> IO (Reply s)
- quit :: Redis -> IO ()
- shutdown :: Redis -> IO ()
- multi :: Redis -> IO (Reply ())
- exec :: BS s => Redis -> IO (Reply s)
- discard :: Redis -> IO (Reply ())
- run_multi :: BS s => Redis -> (Redis -> IO ()) -> IO (Reply s)
- watch :: BS s => Redis -> [s] -> IO (Reply ())
- unwatch :: Redis -> IO (Reply ())
- run_cas :: BS s1 => Redis -> [s1] -> (Redis -> IO a) -> IO a
- exists :: BS s => Redis -> s -> IO (Reply Int)
- del :: BS s => Redis -> s -> IO (Reply Int)
- del_ :: BS s => Redis -> [s] -> IO (Reply Int)
- getType :: BS s => Redis -> s -> IO RedisKeyType
- keys :: (BS s1, BS s2) => Redis -> s1 -> IO (Reply s2)
- randomKey :: BS s => Redis -> IO (Reply s)
- rename :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply ())
- renameNx :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- dbsize :: Redis -> IO (Reply Int)
- expire :: BS s => Redis -> s -> Int -> IO (Reply Int)
- expireAt :: BS s => Redis -> s -> Int -> IO (Reply Int)
- persist :: BS s => Redis -> s -> IO (Reply Int)
- ttl :: BS s => Redis -> s -> IO (Reply Int)
- select :: Redis -> Int -> IO (Reply ())
- move :: BS s => Redis -> s -> Int -> IO (Reply Int)
- flushDb :: Redis -> IO (Reply ())
- flushAll :: Redis -> IO (Reply ())
- info :: Redis -> IO RedisInfo
- set :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply ())
- setNx :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- setEx :: (BS s1, BS s2) => Redis -> s1 -> Int -> s2 -> IO (Reply ())
- mSet :: (BS s1, BS s2) => Redis -> [(s1, s2)] -> IO (Reply ())
- mSetNx :: (BS s1, BS s2) => Redis -> [(s1, s2)] -> IO (Reply Int)
- get :: (BS s1, BS s2) => Redis -> s1 -> IO (Reply s2)
- getSet :: (BS s1, BS s2, BS s3) => Redis -> s1 -> s2 -> IO (Reply s3)
- mGet :: (BS s1, BS s2) => Redis -> [s1] -> IO (Reply s2)
- incr :: BS s => Redis -> s -> IO (Reply Int)
- incrBy :: BS s => Redis -> s -> Int -> IO (Reply Int)
- incrByFloat :: BS s => Redis -> s -> Double -> IO (Reply Double)
- decr :: BS s => Redis -> s -> IO (Reply Int)
- decrBy :: BS s => Redis -> s -> Int -> IO (Reply Int)
- append :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- substr :: (BS s1, BS s2) => Redis -> s1 -> (Int, Int) -> IO (Reply s2)
- getrange :: (BS s1, BS s2) => Redis -> s1 -> (Int, Int) -> IO (Reply s2)
- setrange :: (BS s1, BS s2) => Redis -> s1 -> Int -> s2 -> IO (Reply Int)
- getbit :: BS s => Redis -> s -> Int -> IO (Reply Int)
- setbit :: BS s => Redis -> s -> Int -> Int -> IO (Reply Int)
- strlen :: BS s => Redis -> s -> IO (Reply Int)
- rpush :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- rpush_ :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> IO (Reply Int)
- lpush :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- lpush_ :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> IO (Reply Int)
- rpushx :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- lpushx :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- linsert :: (BS s1, BS s2, BS s3) => Redis -> s1 -> LInsertDirection -> s2 -> s3 -> IO (Reply Int)
- llen :: BS s => Redis -> s -> IO (Reply Int)
- lrange :: (BS s1, BS s2) => Redis -> s1 -> (Int, Int) -> IO (Reply s2)
- ltrim :: BS s => Redis -> s -> (Int, Int) -> IO (Reply ())
- lindex :: (BS s1, BS s2) => Redis -> s1 -> Int -> IO (Reply s2)
- lset :: (BS s1, BS s2) => Redis -> s1 -> Int -> s2 -> IO (Reply ())
- lrem :: (BS s1, BS s2) => Redis -> s1 -> Int -> s2 -> IO (Reply Int)
- lpop :: (BS s1, BS s2) => Redis -> s1 -> IO (Reply s2)
- rpop :: (BS s1, BS s2) => Redis -> s1 -> IO (Reply s2)
- rpoplpush :: (BS s1, BS s2, BS s3) => Redis -> s1 -> s2 -> IO (Reply s3)
- blpop :: (BS s1, BS s2) => Redis -> [s1] -> Int -> IO (Maybe (s1, s2))
- brpop :: (BS s1, BS s2) => Redis -> [s1] -> Int -> IO (Maybe (s1, s2))
- brpoplpush :: (BS s1, BS s2, BS s3) => Redis -> s1 -> s2 -> Int -> IO (Maybe (Maybe s3))
- sadd :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- sadd_ :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> IO (Reply Int)
- srem :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- srem_ :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> IO (Reply Int)
- spop :: (BS s1, BS s2) => Redis -> s1 -> IO (Reply s2)
- smove :: (BS s1, BS s2, BS s3) => Redis -> s1 -> s2 -> s3 -> IO (Reply Int)
- scard :: BS s => Redis -> s -> IO (Reply Int)
- sismember :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- smembers :: (BS s1, BS s2) => Redis -> s1 -> IO (Reply s2)
- srandmember :: (BS s1, BS s2) => Redis -> s1 -> IO (Reply s2)
- sinter :: (BS s1, BS s2) => Redis -> [s1] -> IO (Reply s2)
- sinterStore :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> IO (Reply ())
- sunion :: (BS s1, BS s2) => Redis -> [s1] -> IO (Reply s2)
- sunionStore :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> IO (Reply ())
- sdiff :: (BS s1, BS s2) => Redis -> [s1] -> IO (Reply s2)
- sdiffStore :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> IO (Reply ())
- zadd :: (BS s1, BS s2) => Redis -> s1 -> Double -> s2 -> IO (Reply Int)
- zadd_ :: (BS s1, BS s2) => Redis -> s1 -> [(Double, s2)] -> IO (Reply Int)
- zrem :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- zrem_ :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> IO (Reply Int)
- zincrBy :: (BS s1, BS s2, BS s3) => Redis -> s1 -> Double -> s2 -> IO (Reply s3)
- zrange :: (BS s1, BS s2) => Redis -> s1 -> (Int, Int) -> Bool -> IO (Reply s2)
- zrevrange :: (BS s1, BS s2) => Redis -> s1 -> (Int, Int) -> Bool -> IO (Reply s2)
- zrangebyscore :: (IsInterval i Double, BS s1, BS s2) => Redis -> s1 -> i -> Maybe (Int, Int) -> Bool -> IO (Reply s2)
- zrevrangebyscore :: (IsInterval i Double, BS s1, BS s2) => Redis -> s1 -> i -> Maybe (Int, Int) -> Bool -> IO (Reply s2)
- zcount :: (IsInterval i Double, BS s) => Redis -> s -> i -> IO (Reply Int)
- zremrangebyscore :: BS s => Redis -> s -> (Double, Double) -> IO (Reply Int)
- zcard :: BS s => Redis -> s -> IO (Reply Int)
- zscore :: (BS s1, BS s2, BS s3) => Redis -> s1 -> s2 -> IO (Reply s3)
- zrank :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- zrevrank :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- zremrangebyrank :: BS s => Redis -> s -> (Int, Int) -> IO (Reply Int)
- zunion :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> [Double] -> Aggregate -> IO (Reply Int)
- zinter :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> [Double] -> Aggregate -> IO (Reply Int)
- zunionStore :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> [Double] -> Aggregate -> IO (Reply Int)
- zinterStore :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> [Double] -> Aggregate -> IO (Reply Int)
- hset :: (BS s1, BS s2, BS s3) => Redis -> s1 -> s2 -> s3 -> IO (Reply Int)
- hget :: (BS s1, BS s2, BS s3) => Redis -> s1 -> s2 -> IO (Reply s3)
- hdel :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- hdel_ :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> IO (Reply Int)
- hmset :: (BS s1, BS s2, BS s3) => Redis -> s1 -> [(s2, s3)] -> IO (Reply ())
- hmget :: (BS s1, BS s2, BS s3) => Redis -> s1 -> [s2] -> IO (Reply s3)
- hincrBy :: (BS s1, BS s2) => Redis -> s1 -> s2 -> Int -> IO (Reply Int)
- hincrByFloat :: (BS s1, BS s2) => Redis -> s1 -> s2 -> Double -> IO (Reply Double)
- hexists :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- hlen :: BS s => Redis -> s -> IO (Reply Int)
- hkeys :: (BS s1, BS s2) => Redis -> s1 -> IO (Reply s2)
- hvals :: (BS s1, BS s2) => Redis -> s1 -> IO (Reply s2)
- hgetall :: (BS s1, BS s2) => Redis -> s1 -> IO (Reply s2)
- sort :: (BS s1, BS s2, BS s3) => Redis -> s1 -> SortOptions s2 -> IO (Reply s3)
- listRelated :: (BS s1, BS s2, BS s3) => Redis -> s1 -> s2 -> (Int, Int) -> IO (Reply s3)
- subscribed :: Redis -> IO Int
- subscribe :: (BS s1, BS s2) => Redis -> [s1] -> IO [Message s2]
- unsubscribe :: (BS s1, BS s2) => Redis -> [s1] -> IO [Message s2]
- psubscribe :: (BS s1, BS s2) => Redis -> [s1] -> IO [Message s2]
- punsubscribe :: (BS s1, BS s2) => Redis -> [s1] -> IO [Message s2]
- publish :: (BS s1, BS s2) => Redis -> s1 -> s2 -> IO (Reply Int)
- listen :: BS s => Redis -> Int -> IO (Maybe (Message s))
- save :: Redis -> IO (Reply ())
- bgsave :: Redis -> IO (Reply ())
- lastsave :: Redis -> IO (Reply Int)
- bgrewriteaof :: Redis -> IO (Reply ())
Types ans Constructors
Redis connection descriptor
Redis reply variants
RTimeout | Timeout. Currently unused |
RParseError String | Error converting value from ByteString. It's a client-side error. |
ROk | "Ok" reply |
RPong | Reply for the ping command |
RQueued | Used inside multi-exec block |
RError String | Some kind of server-side error |
RInline s | Simple oneline reply |
RInt Int | Integer reply |
RBulk (Maybe s) | Multiline reply |
RMulti (Maybe [Reply s]) | Complex reply. It may consists of various type of replys |
MSubscribe s Int | subscribed |
MUnsubscribe s Int | unsubscribed |
MPSubscribe s Int | pattern subscribed |
MPUnsubscribe s Int | pattern unsubscribed |
MMessage s s | message recieved |
MPMessage s s s | message recieved by pattern |
data LInsertDirection Source #
Instances
Show LInsertDirection Source # | |
Defined in Database.Redis.Redis showsPrec :: Int -> LInsertDirection -> ShowS # show :: LInsertDirection -> String # showList :: [LInsertDirection] -> ShowS # |
Interval representation
Closed a a | closed interval [a, b] |
Open a a | open interval (a, b) |
LeftOpen a a | left-open interval (a, b] |
RightOpen a a | right-open interval [a, b) |
Instances
Show a => Show (Interval a) Source # | |
IsInterval (Interval a) a Source # | Trivial IsInterval instance |
Defined in Database.Redis.Redis toInterval :: Interval a -> Interval a Source # |
class IsInterval i a | i -> a where Source #
Class for conversion value to Interval
Definied instances is:
- the Interval itself
- pair (a,b) for open interval
- two-member list [a, b] for closed interval (throws runtime error if the list length is different)
toInterval :: i -> Interval a Source #
Instances
IsInterval [a] a Source # | Two-element list [a, b] converted to closed interval. No static checking of list length performed. |
Defined in Database.Redis.Redis toInterval :: [a] -> Interval a Source # | |
IsInterval (Interval a) a Source # | Trivial IsInterval instance |
Defined in Database.Redis.Redis toInterval :: Interval a -> Interval a Source # | |
IsInterval (a, a) a Source # | Pair (a, b) converted to open interval |
Defined in Database.Redis.Redis toInterval :: (a, a) -> Interval a Source # |
data SortOptions s Source #
Options data type for the sort
command
data RedisKeyType Source #
Instances
Eq RedisKeyType Source # | |
Defined in Database.Redis.Redis (==) :: RedisKeyType -> RedisKeyType -> Bool # (/=) :: RedisKeyType -> RedisKeyType -> Bool # | |
Show RedisKeyType Source # | |
Defined in Database.Redis.Redis showsPrec :: Int -> RedisKeyType -> ShowS # show :: RedisKeyType -> String # showList :: [RedisKeyType] -> ShowS # |
sortDefaults :: SortOptions ByteString Source #
Default options for the sort
command
fromRInline :: (Monad m, BS s) => Reply s -> m s Source #
Unwraps RInline reply.
Throws an exception when called with something different from RInline
fromRBulk :: (Monad m, BS s) => Reply s -> m (Maybe s) Source #
Unwraps RBulk reply.
Throws an exception when called with something different from RBulk
fromRBulk' :: (Monad m, BS s) => Reply s -> m s Source #
The same as fromRBulk but with fromJust applied
fromRMulti :: (Monad m, BS s) => Reply s -> m (Maybe [Reply s]) Source #
Unwraps RMulti reply
Throws an exception when called with something different from RMulti
fromRMultiBulk :: (Monad m, BS s) => Reply s -> m (Maybe [Maybe s]) Source #
Unwraps RMulti reply filled with RBulk
Throws an exception when called with something different from RMulti
fromRMultiBulk' :: (Monad m, BS s) => Reply s -> m [s] Source #
The same as fromRMultiBulk but with fromJust applied
fromRInt :: (Monad m, BS s) => Reply s -> m Int Source #
Unwraps RInt reply
Throws an exception when called with something different from RInt
fromROk :: (Monad m, BS s) => Reply s -> m () Source #
Unwraps ROk reply
Throws an exception when called with something different from ROk
noError :: (Monad m, BS s) => Reply s -> m () Source #
Unwraps every non-error reply
Throws an exception when called with something different from RMulti
parseMessage :: (Monad m, BS s) => Reply ByteString -> m (Message s) Source #
Parse Reply as a Message
Throws an exception on parse error
takeAll :: (Int, Int) Source #
a (0, -1) range - takes all element from a list in lrange, zrange and so on
Database connection
defaultPort :: String Source #
default Redis port
Conects to Redis server and returns connection descriptor
disconnect :: Redis -> IO () Source #
Close connection
:: Redis | |
-> ByteString | command to rename |
-> ByteString | new name |
-> IO () |
Adds command to renaming map
Redis commands
Generic
exec :: BS s => Redis -> IO (Reply s) Source #
Execute queued commands
RMulti returned - replies for all executed commands
Run commands within multi-exec block
RMulti returned - replies for all executed commands
Add keys to a watch list for Check-and-Set operation.
For more information see http://redis.io/topics/transactions
ROk returned
unwatch :: Redis -> IO (Reply ()) Source #
Force unwatch all watched keys
For more information see http://redis.io/topics/transactions
ROk returned
Run actions in a CAS manner
You have to explicitly add multi/exec commands to an appropriate place in an action sequence. Command sequence will be explicitly terminated with unwatch command even if exec command was sent.
Result of user-defined action returned
Test if the key exists
(RInt 1) returned if the key exists and (RInt 0) otherwise
Remove the key
(RInt 0) returned if no keys were removed or (RInt n) with removed keys count
Variadic form of DEL
RInt returned - number of deleted keys
:: BS s | |
=> Redis | |
-> s | target key |
-> IO RedisKeyType |
Return the type of the value stored at key in form of a string
RedisKeyType returned
Returns all the keys matching the glob-style pattern
RMulti filled with RBulk returned
Rename the key. If key with that name exists it'll be overwritten.
ROk returned
Rename the key if no keys with destination name exists.
(RInt 1) returned if key was renamed and (RInt 0) otherwise
dbsize :: Redis -> IO (Reply Int) Source #
Get the number of keys in the currently selected database
RInt returned
Set an expiration timeout in seconds on the specified key.
For more information see http://redis.io/commands/expire
(RInt 1) returned if timeout was set and (RInt 0) otherwise
Set an expiration time in form of UNIX timestamp on the specified key
For more information see http://redis.io/commands/expireat
(RInt 1) returned if timeout was set and (RInt 0) otherwise
Remove the timeout from a key
(RInt 1) returned if the timeout was removed and (RInt 0) otherwise
Return the remining time to live of the key or -1 if key has no associated timeout
RInt returned
Select the DB with the specified zero-based numeric index
ROk returned
Move the specified key from the currently selected DB to the specified destination DB. If such a key is already exists in the target DB no data modification performed.
(RInt 1) returned if the key was moved and (RInt 0) otherwise
flushDb :: Redis -> IO (Reply ()) Source #
Delete all the keys of the currently selected DB
ROk returned
flushAll :: Redis -> IO (Reply ()) Source #
Delete all the keys of all the existing databases
ROk returned
info :: Redis -> IO RedisInfo Source #
Returns different information and statistics about the server
for more information see http://redis.io/commands/info
RedisInfo
returned
Strings
Set the string value as value of the key
ROk returned
Set the key value if key does not exists
(RInt 1) returned if key was set and (RInt 0) otherwise
Atomically sets target key value and assigns expiration time. The same as multi; set key val; expire key seconds; exec but faster.
Arguments order is the same as in Redis protocol.
ROk returned
Atomically set multiple keys
ROk returned
Atomically set multiple keys if none of them exists.
(RInt 1) returned if all keys was set and (RInt 0) otherwise
Get the value of the specified key.
RBulk returned
Atomically set this value and return the old value
RBulk returned
Get the values of all specified keys
RMulti filled with RBulk replies returned
Increment the key value by one
RInt returned with new key value
Increment the key value by N
RInt returned with new key value
Increment the key value by N
(RBulk Double) returned with new key value
Decrement the key value by one
RInt returned with new key value
Decrement the key value by N
RInt returned with new key value
Append string to the string-typed key
RInt returned - the length of resulting string
Returns the substring of the string value stored at key, determined by the offsets start and end (both are inclusive). Negative offsets can be used in order to provide an offset starting from the end of the string.
RBulk returned
Returns the substring of the string value stored at key, determined by the offsets start and end (both are inclusive). Negative offsets can be used in order to provide an offset starting from the end of the string.
RBulk returned
Overwrites part of the string stored at key, starting at the specified offset, for the entire length of value. If the offset is larger than the current length of the string at key, the string is padded with zero-bytes to make offset fit. Non-existing keys are considered as empty strings, so this command will make sure it holds a string large enough to be able to set value at offset.
RInt returned - resulting string length.
Returns the bit value at offset in the string value stored at key. When offset is beyond the string length, the string is assumed to be a contiguous space with 0 bits. When key does not exist it is assumed to be an empty string, so offset is always out of range and the value is also assumed to be a contiguous space with 0 bits.
RInt returned
Sets or clears the bit at offset in the string value stored at key. For more information see http://redis.io/commands/setbit
RInt returned - the original bit value stored at offset.
Returns a length of a string-typed key
RInt returned
Lists
Add string value to the tail of the list-type key. New list length returned
RInt returned
Variadic form of rpush
RInt returned
Add string value to the head of the list-type key. New list length returned
RInt returned
Variadic form of LPUSH
RInt returned
Add string value to the tail of existing list-type key. New list length returned. If such a key was not exists, list is not created and (RInt 0) returned.
RInt returned
Add string value to the head of existing list-type key. New list length returned. If such a key was not exists, list is not created and (RInt 0) returned.
RInt returned
:: (BS s1, BS s2, BS s3) | |
=> Redis | |
-> s1 | target list |
-> LInsertDirection | where to insert - before or after |
-> s2 | target element |
-> s3 | inserted value |
-> IO (Reply Int) |
Inserts value in the list stored at key either before or after the reference value pivot.
RInt returned - resulting list length or (RInt -1) if target element was not found.
Return lenght of the list. Note that for not-existing keys it returns zero length.
RInt returned or RError if key is not a list
Return the specified range of list elements. List indexed from 0 to (llen - 1). lrange returns slice including "from" and "to" elements, eg. lrange 0 2 will return the first three elements of the list.
Parameters "from" and "to" may also be negative. If so it will counts as offset from end ot the list. eg. -1 - is the last element of the list, -2 - is the second from the end and so on.
RMulti filled with RBulk returned
Trim list so that it will contain only the specified range of elements.
ROk returned
Return the specified element of the list by its index
RBulk returned
Set the list's value indexed by an index to the new value
ROk returned if element was set and RError if index is out of range or key is not a list
Remove the first count occurrences of the value element from the list
RInt returned - the number of elements removed
Atomically return and remove the first element of the list
RBulk returned
Atomically return and remove the last element of the list
RBulk returned
Atomically return and remove the last (tail) element of the source list, and push the element as the first (head) element of the destination list
RBulk returned
Blocking lpop
For more information see http://redis.io/commands/blpop
Return (Just (key, value)) if value was successfully popped from key list or Nothing of timeout exceeded.
Blocking rpop
For more information see http://redis.io/commands/brpop
Return (Just (key, value)) if value was successfully popped from key list or Nothing of timeout exceeded.
:: (BS s1, BS s2, BS s3) | |
=> Redis | |
-> s1 | source key |
-> s2 | destination key |
-> Int | timeout |
-> IO (Maybe (Maybe s3)) |
Blocking rpoplpush
For more information see http://redis.io/commands/brpoplpush
Return (Just $ Maybe value) if value was successfully popped or Nothing if timeout exceeded.
Sets
Add the specified member to the set value stored at key
(RInt 1) returned if element was added and (RInt 0) if element was already a member of the set
Variadic form of SADD
RInt returned - number of actualy added elements
Remove the specified member from the set value stored at key
(RInt 1) returned if element was removed and (RInt 0) if element is not a member of the set
Variadic form of SREM
RInt returned - number of removed values
Remove a random element from a Set returning it as return value
RBulk returned
Move the specifided member from one set to another
(RInt 1) returned if element was moved and (RInt 0) if element is not a member of the source set
Return the number of elements of the set. If key doesn't exists 0 returned.
RInt returned
Test if element is member of the set. If key doesn't exists 0 returned.
(RInt 1) returned if element is member of the set and (RInt 0) otherwise
Return all the members (elements) of the set
RMulti filled with RBulk returned
Return a random element from a set
RBulk returned
Return the members of a set resulting from the intersection of all the specifided sets
RMulti filled with RBulk returned
The same as sinter
but instead of being returned the resulting set
is stored
RInt returned - resulting set cardinality.
Return the members of a set resulting from the union of all the specifided sets
RMulti filled with RBulk returned
The same as sunion
but instead of being returned the resulting set
is stored
RInt returned - resulting set cardinality.
Return the members of a set resulting from the difference between the first set provided and all the successive sets
RMulti filled with RBulk returned
The same as sdiff
but instead of being returned the resulting
set is stored
RInt returned - resulting set cardinality.
Sorted sets
Add the specified member having the specifeid score to the sorted set
(RInt 1) returned if new element was added and (RInt 0) if that element was already a member of the sortet set and the score was updated
:: (BS s1, BS s2) | |
=> Redis | |
-> s1 | target key |
-> [(Double, s2)] | list of score-value pairs |
-> IO (Reply Int) |
Variadic form of zadd
RInt returned - the number of elements actually added. Not including elements which scores was just updated.
Remove the specified member from the sorted set
(RInt 1) returned if element was removed and (RInt 0) if element was not a member of the sorted set
Variadic form of zrem RInt returned - the number of removed elements
If member already in the sorted set adds the increment to its score and updates the position of the element in the sorted set accordingly. If member does not exist in the sorted set it is added with increment as score (that is, like if the previous score was virtually zero). The new score of the member is returned.
RBulk returned
:: (BS s1, BS s2) | |
=> Redis | |
-> s1 | target key |
-> (Int, Int) | (from, to) pair |
-> Bool | withscores option |
-> IO (Reply s2) |
Return the specified elements of the sorted set. Start and end are zero-based indexes. WITHSCORES paramenter indicates if it's needed to return elements with its scores or not. If WITHSCORES is True then the resulting list will be composed of value1, score1, value2, score2 and so on.
RMulti filled with RBulk returned
:: (BS s1, BS s2) | |
=> Redis | |
-> s1 | target key |
-> (Int, Int) | (from, to) pair |
-> Bool | withscores option |
-> IO (Reply s2) |
Return the specified elements of the sorted set at the specified key. The elements are considered sorted from the highest to the lowerest score
RMulti filled with RBulk returned
:: (IsInterval i Double, BS s1, BS s2) | |
=> Redis | |
-> s1 | target key |
-> i | scores interval |
-> Maybe (Int, Int) | limits (offset, count) |
-> Bool | withscores option |
-> IO (Reply s2) |
Return the all the elements in the sorted set with a score that lays within a given interval
RMulti filled with RBulk returned
zrevrangebyscore :: (IsInterval i Double, BS s1, BS s2) => Redis -> s1 -> i -> Maybe (Int, Int) -> Bool -> IO (Reply s2) Source #
Return the all the elements in the sorted set with a score that lays within a given interval. Elements is ordered from greater score to lower. Interval passed into command must be reversed (first value is greater then second)
RMulti filled with RBulk returned
Count a number of elements of the sorted set with a score that lays within a given interval
RInt returned
:: BS s | |
=> Redis | |
-> s | target key |
-> (Double, Double) | (from, to) pair. zremrangebyscore currently doesn't supports open intervals |
-> IO (Reply Int) |
Remove all the elements in the sorted set with a score that lays within a given interval. For now this command doesn't supports open and semi-open intervals
RInt returned - the number of elements removed
Return the sorted set cardinality (number of elements)
RInt returned
Return the score of the specified element of the sorted set
RBulk returned
Returns the rank of member in the sorted set stored at key, with the scores ordered from low to high.
RInt returned or (RBulk Nothing) if value is not found in set.
Returns the rank of member in the sorted set stored at key, with the scores ordered from high to low.
RInt returned or (RBulk Nothing) if value is not found in set.
zremrangebyrank :: BS s => Redis -> s -> (Int, Int) -> IO (Reply Int) Source #
Remove elements from the sorted set with rank lays within a given interval.
RInt returned - the number of elements removed
zunion :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> [Double] -> Aggregate -> IO (Reply Int) Source #
Deprecated: ZUNION command was renamed to ZUNIONSTORE
zinter :: (BS s1, BS s2) => Redis -> s1 -> [s2] -> [Double] -> Aggregate -> IO (Reply Int) Source #
Deprecated: ZINTER command was renamed to ZINTERSTORE
:: (BS s1, BS s2) | |
=> Redis | |
-> s1 | destination key |
-> [s2] | sources keys |
-> [Double] | weights |
-> Aggregate | aggregate |
-> IO (Reply Int) |
Create a union of provided sorted sets and store it at destination key
If weights is not null then scores of sorted sets used with corresponding weights. If so lenght of weights must be the same as length of sources.
Aggregate is an option how to aggregate resulting scores.
RInt returned - the number of elements in the resulting set.
:: (BS s1, BS s2) | |
=> Redis | |
-> s1 | destination key |
-> [s2] | sources keys |
-> [Double] | weights |
-> Aggregate | aggregate |
-> IO (Reply Int) |
Create an intersectoin of provided sorted sets and store it at destination key
If weights is not null then scores of sorted sets used with corresponding weights. If so lenght of weights must be the same as length of sources.
Aggregate is an option how to aggregate resulting scores.
RInt returned - the number of elements in the resulting set.
Hashes
Set the specified hash field to the specified value
(RInt 0 returned if field value was updated and (RInt 1) if new field created
Return value associated with specified field from hash
RBulk returned
Remove field from a hash
(RInt 1) returned if field was removed and (RInt 0) otherwise
Variadic form of HDEL
RInt returned - number of fields deleted
Atomically sets multiple fields within a hash-typed key
ROk returned
Get the values of all specified fields from the hash-typed key
RMulti filled with RBulk replies returned
Increment the field value within a hash by N
RInt returned with new key value
Increment the field value within a hash by N
(RBulk Double) returned with new key value
Test if hash contains the specified field
(RInt 1) returned if fiels exists and (RInt 0) otherwise
hlen :: BS s => Redis -> s -> IO (Reply Int) Source #
Return the number of fields contained in the specified hash
RInt returned
hkeys :: (BS s1, BS s2) => Redis -> s1 -> IO (Reply s2) Source #
Return all the field names the hash holding
RMulti field with RBulk returned
hvals :: (BS s1, BS s2) => Redis -> s1 -> IO (Reply s2) Source #
Return all the associated values the hash holding
RMulti field with RBulk returned
Return all the field names and associated values the hash holding in form of [field1, value1, field2, value2...]
RMulti field with RBulk returned. If key doesn't exists (RMulti []) returned.
Sorting
Sort the elements contained in the List, Set, or Sorted Set
for more information see http://redis.io/commands/sort
RMulti filled with RBulk returned
Publish/Subscribe
subscribed :: Redis -> IO Int Source #
Get a number of subscribed channels on this connection
It doesn't run any redis commands, number of subscribtions is taken from internal connection state
Subscribe to channels
list of Message with subscribtion information returned
Unsubscribe from channels. If called with an empty list then unsubscribe all channels
list of Message with subscribtion information returned
Subscribe to patterns
list of Message with subscribtion information returned
Unsubscribe from patterns. If called with an empty list then unsubscribe all patterns
list of Message with subscribtion information returned
Publish message to target channel
RInt returned - a number of clients that recieves the message
Wait for a messages.
Just Message returned or Nothing if timeout exceeded