redis-0.1: A driver for Redis key-value database

Database.Redis.Redis

Contents

Description

Main Redis API and protocol implementation

Synopsis

Types ans Constructors

data Redis Source

Redis connection descriptor

Constructors

Redis 

Fields

server :: (String, String)

hostname and port pair

handle :: Handle

real network connection

Instances

data Reply Source

Redis reply variants

Constructors

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

Instances

data Interval a Source

Interval representation

Constructors

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) 
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)

Methods

toInterval :: i -> Interval aSource

Instances

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

Constructors

SortOptions 

Fields

desc :: Bool

sort with descending order

limit :: (Int, Int)

return (from, to) elements

alpha :: Bool

sort alphabetically

sort_by :: String

sort by value from this key

get_obj :: [String]

return this keys values

store :: String

store result to this key

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

takeAll :: (Int, Int)Source

a (0, -1) range - takes all element from a list in lrange, zrange and so on

Database connection

localhost :: StringSource

just a localhost

defaultPort :: StringSource

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

ping :: Redis -> IO ReplySource

ping - pong

RPong returned if no errors happends

authSource

Arguments

:: Redis 
-> String

password

-> IO Reply 

Password authentication

ROk returned

quit :: Redis -> IO ()Source

Quit and close connection

shutdown :: Redis -> IO ReplySource

Stop all the clients, save the DB, then quit the server

multi :: Redis -> IO ReplySource

Begin the multi-exec block

ROk returned

exec :: Redis -> IO ReplySource

Execute queued commands

RMulti returned - replys for all executed commands

run_multiSource

Arguments

:: Redis 
-> [IO Reply]

IO actions to run

-> IO Reply 

Run commands within multi-exec block

RMulti returned - replys for all executed commands

existsSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Test if the key exists

(RInt 1) returned if the key exists and (RInt 0) otherwise

delSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Remove the key

(RInt 0) returned if no keys were removed or (RInt n) with removed keys count

getTypeSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Return the type of the value stored at key in form of a string

RInline with one of none, string, list, set, zset returned

keysSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Returns all the keys matching the glob-style pattern as space separated strings

RBulk returned

randomKey :: Redis -> IO ReplySource

Return random key name

RInline returned

renameSource

Arguments

:: Redis 
-> String

source key

-> String

destination key

-> IO Reply 

Rename the key. If key with that name exists it'll be overwritten.

ROk returned

renameNxSource

Arguments

:: Redis 
-> String

source key

-> String

destination key

-> IO Reply 

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

expireSource

Arguments

:: Redis 
-> String

target key

-> Int

timeout in seconds

-> IO Reply 

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

expireAtSource

Arguments

:: Redis 
-> String

target key

-> Int

timeout in seconds

-> IO Reply 

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

ttlSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Return the remining time to live of the key or -1 if key has no associated timeout

RInt returned

selectSource

Arguments

:: Redis 
-> Int

database number

-> IO Reply 

Select the DB with the specified zero-based numeric index

ROk returned

moveSource

Arguments

:: Redis 
-> String

target key

-> Int

destination database number

-> IO Reply 

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 ReplySource

Delete all the keys of the currently selected DB

ROk returned

flushAll :: Redis -> IO ReplySource

Delete all the keys of all the existing databases

ROk returned

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

setSource

Arguments

:: Redis 
-> String

target key

-> String

value

-> IO Reply 

Set the string value as value of the key

ROk returned

setNxSource

Arguments

:: Redis 
-> String

target key

-> String

value

-> IO Reply 

Set the key value if key does not exists

(RInt 1) returned if key was set and (RInt 0) otherwise

mSetSource

Arguments

:: Redis 
-> [(String, String)]

(key, value) pairs

-> IO Reply 

Atomically set multiple keys

ROk returned

mSetNxSource

Arguments

:: Redis 
-> [(String, String)]

(key, value) pairs

-> IO Reply 

Atomically set multiple keys if none of them exists.

(RInt 1) returned if all keys was set and (RInt 0) otherwise

getSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Get the value of the specified key.

RBulk returned

getSetSource

Arguments

:: Redis 
-> String

target key

-> String

value

-> IO Reply 

Atomically set this value and return the old value

RBulk returned

mGetSource

Arguments

:: Redis 
-> [String]

target keys

-> IO Reply 

Get the values of all specified keys

RMulti filled with RBulk replys returned

incrSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Increment the key value by one

RInt returned with new key value

incrBySource

Arguments

:: Redis 
-> String

target key

-> Int

increment

-> IO Reply 

Increment the key value by N

RInt returned with new key value

decrSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Decrement the key value by one

RInt returned with new key value

decrBySource

Arguments

:: Redis 
-> String

target key

-> Int

decrement

-> IO Reply 

Decrement the key value by N

RInt returned with new key value

appendSource

Arguments

:: Redis 
-> String

target key

-> String

value

-> IO Reply 

Append string to the string-typed key

RInt returned - the length of resulting string

Lists

rpushSource

Arguments

:: Redis 
-> String

target key

-> String

value

-> IO Reply 

Add string value to the head of the list-type key

ROk returned or RError if key is not a list

lpushSource

Arguments

:: Redis 
-> String

target key

-> String

value

-> IO Reply 

Add string value to the tail of the list-type key

ROk returned or RError if key is not a list

llenSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

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

lrangeSource

Arguments

:: Redis 
-> String

traget key

-> (Int, Int)

(from, to) pair

-> IO Reply 

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

ltrimSource

Arguments

:: Redis 
-> String

target key

-> (Int, Int)

(from, to) pair

-> IO Reply 

Trim list so that it will contain only the specified range of elements.

ROk returned

lindexSource

Arguments

:: Redis 
-> String

target key

-> Int

index

-> IO Reply 

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

lremSource

Arguments

:: Redis 
-> String

target key

-> Int

occurrences

-> String

value

-> IO Reply 

Remove the first count occurrences of the value element from the list

RInt returned - the number of elements removed

lpopSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Atomically return and remove the first element of the list

RBulk returned

rpopSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Atomically return and remove the last element of the list

RBulk returned

rpoplpushSource

Arguments

:: Redis 
-> String

source key

-> String

destination key

-> IO Reply 

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

blpopSource

Arguments

:: Redis 
-> [String]

keys list

-> Int

timeout

-> IO Reply 

Blocking lpop

For more information see http://code.google.com/p/redis/wiki/BlpopCommand

RMulti returned filled with key name and popped value

brpopSource

Arguments

:: Redis 
-> [String]

keys list

-> Int

timeout

-> IO Reply 

Blocking rpop

For more information see http://code.google.com/p/redis/wiki/BlpopCommand

RMulti returned filled with key name and popped value

Sets

saddSource

Arguments

:: Redis 
-> String

target key

-> String

value

-> IO Reply 

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

sremSource

Arguments

:: Redis 
-> String

target key

-> String

value

-> IO Reply 

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

spopSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Remove a random element from a Set returning it as return value

RBulk returned

smoveSource

Arguments

:: Redis 
-> String

source key

-> String

destination key

-> String

value

-> IO Reply 

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

scardSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Return the number of elements of the set. If key doesn't exists 0 returned.

RInt returned

sismemberSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

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

smembersSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Return all the members (elements) of the set

RMulti filled with RBulk returned

srandmemberSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Return a random element from a set

RBulk returned

sinterSource

Arguments

:: Redis 
-> [String]

keys list

-> IO Reply 

Return the members of a set resulting from the intersection of all the specifided sets

RMulti filled with RBulk returned

sinterStoreSource

Arguments

:: Redis 
-> String

where to store resulting set

-> [String]

sets list

-> IO Reply 

The same as sinter but instead of being returned the resulting set is stored

ROk returned

sunionSource

Arguments

:: Redis 
-> [String]

keys list

-> IO Reply 

Return the members of a set resulting from the union of all the specifided sets

RMulti filled with RBulk returned

sunionStoreSource

Arguments

:: Redis 
-> String

where to store resulting set

-> [String]

sets list

-> IO Reply 

The same as sunion but instead of being returned the resulting set is stored

ROk returned

sdiffSource

Arguments

:: Redis 
-> [String]

keys list

-> IO Reply 

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

sdiffStoreSource

Arguments

:: Redis 
-> String

where to store resulting set

-> [String]

sets list

-> IO Reply 

The same as sdiff but instead of being returned the resulting set is stored

ROk returned

Sorted sets

zaddSource

Arguments

:: Redis 
-> String

target key

-> Double

score

-> String

value

-> IO Reply 

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

zremSource

Arguments

:: Redis 
-> String

target key

-> String

value

-> IO Reply 

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

zincrBySource

Arguments

:: Redis 
-> String

target key

-> Double

increment

-> String

value

-> IO Reply 

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

zrangeSource

Arguments

:: Redis 
-> String

target key

-> (Int, Int)

(from, to) pair

-> Bool

withscores option

-> IO Reply 

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

zrevrangeSource

Arguments

:: Redis 
-> String

target key

-> (Int, Int)

(from, to) pair

-> Bool

withscores option

-> IO Reply 

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

zrangebyscoreSource

Arguments

:: 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

zcountSource

Arguments

:: IsInterval i Double 
=> Redis 
-> String

target key

-> i

scores interval

-> IO Reply 

Count a number of elements of the sorted set with a score that lays within a given interval

RInt returned

zremrangebyscoreSource

Arguments

:: 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

zcardSource

Arguments

:: Redis 
-> String

target key

-> IO Reply 

Return the sorted set cardinality (number of elements)

RInt returned

zscoreSource

Arguments

:: Redis 
-> String

target key

-> String

value

-> IO Reply 

Return the score of the specified element of the sorted set

RBulk returned

Sorting

sortSource

Arguments

:: 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

listRelatedSource

Arguments

:: Redis 
-> String

target key

-> String

key returned

-> (Int, Int)

range

-> IO Reply 

Shortcut for the sort with some get_obj and constant sort_by options

RMulti filled with RBulk returned

Persistent control

save :: Redis -> IO ReplySource

Save the whole dataset on disk

ROk returned

bgsave :: Redis -> IO ReplySource

Save the DB in background

ROk returned

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