Main Redis API and protocol implementation
- data Redis = Redis {}
- data Reply
- data Interval a
- class IsInterval i a | i -> a where
- toInterval :: i -> Interval a
- data SortOptions = SortOptions {}
- sortDefaults :: SortOptions
- fromRInline :: Monad m => Reply -> m String
- fromRBulk :: Monad m => Reply -> m (Maybe String)
- fromRMulti :: Monad m => Reply -> m (Maybe [Reply])
- fromRMultiBulk :: Monad m => Reply -> m (Maybe [Maybe String])
- fromRInt :: Monad m => Reply -> m Int
- fromROk :: Monad m => Reply -> m ()
- noError :: Monad m => Reply -> m ()
- takeAll :: (Int, Int)
- localhost :: String
- defaultPort :: String
- connect :: String -> String -> IO Redis
- disconnect :: Redis -> IO ()
- isConnected :: Redis -> IO Bool
- ping :: Redis -> IO Reply
- auth :: Redis -> String -> IO Reply
- quit :: Redis -> IO ()
- shutdown :: Redis -> IO Reply
- multi :: Redis -> IO Reply
- exec :: Redis -> IO Reply
- discard :: Redis -> IO Reply
- run_multi :: Redis -> [IO Reply] -> IO Reply
- exists :: Redis -> String -> IO Reply
- del :: Redis -> String -> IO Reply
- getType :: Redis -> String -> IO Reply
- keys :: Redis -> String -> IO Reply
- randomKey :: Redis -> IO Reply
- rename :: Redis -> String -> String -> IO Reply
- renameNx :: Redis -> String -> String -> IO Reply
- dbsize :: Redis -> IO Reply
- expire :: Redis -> String -> Int -> IO Reply
- expireAt :: Redis -> String -> Int -> IO Reply
- ttl :: Redis -> String -> IO Reply
- select :: Redis -> Int -> IO Reply
- move :: Redis -> String -> Int -> IO Reply
- flushDb :: Redis -> IO Reply
- flushAll :: Redis -> IO Reply
- info :: Redis -> IO Reply
- set :: Redis -> String -> String -> IO Reply
- setNx :: Redis -> String -> String -> IO Reply
- mSet :: Redis -> [(String, String)] -> IO Reply
- mSetNx :: Redis -> [(String, String)] -> IO Reply
- get :: Redis -> String -> IO Reply
- getSet :: Redis -> String -> String -> IO Reply
- mGet :: Redis -> [String] -> IO Reply
- incr :: Redis -> String -> IO Reply
- incrBy :: Redis -> String -> Int -> IO Reply
- decr :: Redis -> String -> IO Reply
- decrBy :: Redis -> String -> Int -> IO Reply
- append :: Redis -> String -> String -> IO Reply
- rpush :: Redis -> String -> String -> IO Reply
- lpush :: Redis -> String -> String -> IO Reply
- llen :: Redis -> String -> IO Reply
- lrange :: Redis -> String -> (Int, Int) -> IO Reply
- ltrim :: Redis -> String -> (Int, Int) -> IO Reply
- lindex :: Redis -> String -> Int -> IO Reply
- lset :: Redis -> String -> Int -> String -> IO Reply
- lrem :: Redis -> String -> Int -> String -> IO Reply
- lpop :: Redis -> String -> IO Reply
- rpop :: Redis -> String -> IO Reply
- rpoplpush :: Redis -> String -> String -> IO Reply
- blpop :: Redis -> [String] -> Int -> IO Reply
- brpop :: Redis -> [String] -> Int -> IO Reply
- sadd :: Redis -> String -> String -> IO Reply
- srem :: Redis -> String -> String -> IO Reply
- spop :: Redis -> String -> IO Reply
- smove :: Redis -> String -> String -> String -> IO Reply
- scard :: Redis -> String -> IO Reply
- sismember :: Redis -> String -> IO Reply
- smembers :: Redis -> String -> IO Reply
- srandmember :: Redis -> String -> IO Reply
- sinter :: Redis -> [String] -> IO Reply
- sinterStore :: Redis -> String -> [String] -> IO Reply
- sunion :: Redis -> [String] -> IO Reply
- sunionStore :: Redis -> String -> [String] -> IO Reply
- sdiff :: Redis -> [String] -> IO Reply
- sdiffStore :: Redis -> String -> [String] -> IO Reply
- zadd :: Redis -> String -> Double -> String -> IO Reply
- zrem :: Redis -> String -> String -> IO Reply
- zincrBy :: Redis -> String -> Double -> String -> IO Reply
- zrange :: Redis -> String -> (Int, Int) -> Bool -> IO Reply
- zrevrange :: Redis -> String -> (Int, Int) -> Bool -> IO Reply
- zrangebyscore :: IsInterval i Double => Redis -> String -> i -> Bool -> IO Reply
- zcount :: IsInterval i Double => Redis -> String -> i -> IO Reply
- zremrangebyscore :: Redis -> String -> (Double, Double) -> IO Reply
- zcard :: Redis -> String -> IO Reply
- zscore :: Redis -> String -> String -> IO Reply
- sort :: Redis -> String -> SortOptions -> IO Reply
- listRelated :: Redis -> String -> String -> (Int, Int) -> IO Reply
- save :: Redis -> IO Reply
- bgsave :: Redis -> IO Reply
- lastsave :: Redis -> IO Reply
- bgrewriteaof :: Redis -> IO Reply
Types ans Constructors
Redis connection descriptor
Redis reply variants
RTimeout | Timeout. Currently unused |
ROk | "Ok" reply |
RPong | Reply for the ping command |
RQueued | Used inside multi-exec block |
RError String | Some kind of server-side error |
RInline String | Simple oneline reply |
RInt Int | Integer reply |
RBulk (Maybe String) | Multiline reply |
RMulti (Maybe [Reply]) | Complex reply. It may consists of various type of replys |
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) |
Show a => Show (Interval a) | |
IsInterval (Interval a) a | Trivial IsInterval instance |
class IsInterval i a | i -> a whereSource
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 aSource
IsInterval [a] a | Two-element list [a, b] converted to closed interval. No static checking of list length performed. |
IsInterval (Interval a) a | Trivial IsInterval instance |
IsInterval (a, a) a | Pair (a, b) converted to open interval |
data SortOptions Source
Options data type for the sort
command
sortDefaults :: SortOptionsSource
Default options for the sort
command
fromRInline :: Monad m => Reply -> m StringSource
Unwraps RInline reply.
Throws an exception when called with something different from RInline
fromRBulk :: Monad m => Reply -> m (Maybe String)Source
Unwraps RBulk reply.
Throws an exception when called with something different from RBulk
fromRMulti :: Monad m => Reply -> m (Maybe [Reply])Source
Unwraps RMulti reply
Throws an exception when called with something different from RMulti
fromRMultiBulk :: Monad m => Reply -> m (Maybe [Maybe String])Source
Unwraps RMulti reply filled with RBulk
Throws an exception when called with something different from RMulti
fromRInt :: Monad m => Reply -> m IntSource
Unwraps RInt reply
Throws an exception when called with something different from RInt
fromROk :: Monad m => Reply -> m ()Source
Unwraps ROk reply
Throws an exception when called with something different from ROk
noError :: Monad m => Reply -> m ()Source
Unwraps every non-error reply
Throws an exception when called with something different from RMulti
a (0, -1) range - takes all element from a list in lrange, zrange and so on
Database connection
default Redis port
connect :: String -> String -> IO RedisSource
Conects to Redis server and returns connection descriptor
disconnect :: Redis -> IO ()Source
Close connection
isConnected :: Redis -> IO BoolSource
Returns True when connection handler is opened
Redis commands
Generic
exec :: Redis -> IO ReplySource
Execute queued commands
RMulti returned - replys for all executed commands
Run commands within multi-exec block
RMulti returned - replys for all executed commands
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
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 ReplySource
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://code.google.com/p/redis/wiki/ExpireCommand
(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://code.google.com/p/redis/wiki/ExpireCommand
(RInt 1) returned if timeout was set 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
info :: Redis -> IO ReplySource
Returns different information and statistics about the server
for more information see http://code.google.com/p/redis/wiki/InfoCommand
RBulk 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 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 replys 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
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
Lists
Add string value to the head of the list-type key
ROk returned or RError if key is not a list
Add string value to the tail of the list-type key
ROk returned or RError if key is not a list
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
lset :: Redis -> String -> Int -> String -> IO ReplySource
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://code.google.com/p/redis/wiki/BlpopCommand
RMulti returned filled with key name and popped value
Blocking rpop
For more information see http://code.google.com/p/redis/wiki/BlpopCommand
RMulti returned filled with key name and popped value
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
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
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
ROk returned
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
ROk returned
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
ROk returned
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
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
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
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
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 | |
=> Redis | |
-> String | target key |
-> i | scores interval |
-> Bool | withscores option |
-> IO Reply |
Return the all the elements in the sorted set with a score that lays within a given interval
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
:: Redis | |
-> String | target key |
-> (Double, Double) | (from, to) pair. zremrangebyscore currently doesn't supports open intervals |
-> IO Reply |
Remove all the elements in the sorted set with a score that lays within a given interval
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
Sorting
:: Redis | |
-> String | target key |
-> SortOptions | options |
-> IO Reply |
Sort the elements contained in the List, Set, or Sorted Set
for more information see http://code.google.com/p/redis/wiki/SortCommand
RMulti filled with RBulk returned
Persistent control
lastsave :: Redis -> IO ReplySource
Return the UNIX TIME of the last DB save executed with success
RInt returned
bgrewriteaof :: Redis -> IO ReplySource
Rewrites the Append Only File in background
ROk returned