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

Safe HaskellNone
LanguageHaskell2010

Database.Redis.Redis

Contents

Description

Main Redis API and protocol implementation

Synopsis

Types ans Constructors

data Redis Source #

Redis connection descriptor

Instances
Eq Redis Source # 
Instance details

Defined in Database.Redis.Internal

Methods

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

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

WithRedis RedisM Source # 
Instance details

Defined in Database.Redis.Monad.State

data Reply s Source #

Redis reply variants

Constructors

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

Instances
Eq s => Eq (Reply s) Source # 
Instance details

Defined in Database.Redis.Internal

Methods

(==) :: Reply s -> Reply s -> Bool #

(/=) :: Reply s -> Reply s -> Bool #

BS s => Show (Reply s) Source # 
Instance details

Defined in Database.Redis.Internal

Methods

showsPrec :: Int -> Reply s -> ShowS #

show :: Reply s -> String #

showList :: [Reply s] -> ShowS #

data Message s Source #

Constructors

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

Instances
Eq s => Eq (Message s) Source # 
Instance details

Defined in Database.Redis.Internal

Methods

(==) :: Message s -> Message s -> Bool #

(/=) :: Message s -> Message s -> Bool #

Show s => Show (Message s) Source # 
Instance details

Defined in Database.Redis.Internal

Methods

showsPrec :: Int -> Message s -> ShowS #

show :: Message s -> String #

showList :: [Message s] -> ShowS #

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) Source # 
Instance details

Defined in Database.Redis.Redis

Methods

showsPrec :: Int -> Interval a -> ShowS #

show :: Interval a -> String #

showList :: [Interval a] -> ShowS #

IsInterval (Interval a) a Source #

Trivial IsInterval instance

Instance details

Defined in Database.Redis.Redis

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)

Methods

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.

Instance details

Defined in Database.Redis.Redis

Methods

toInterval :: [a] -> Interval a Source #

IsInterval (Interval a) a Source #

Trivial IsInterval instance

Instance details

Defined in Database.Redis.Redis

IsInterval (a, a) a Source #

Pair (a, b) converted to open interval

Instance details

Defined in Database.Redis.Redis

Methods

toInterval :: (a, a) -> Interval a Source #

data SortOptions s Source #

Options data type for the sort command

Constructors

SortOptions 

Fields

data Aggregate Source #

Constructors

SUM 
MIN 
MAX 
Instances
Eq Aggregate Source # 
Instance details

Defined in Database.Redis.Redis

Show Aggregate Source # 
Instance details

Defined in Database.Redis.Redis

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

localhost :: String Source #

just a localhost

defaultPort :: String Source #

default Redis port

connect Source #

Arguments

:: String

hostname or path to the redis socket

-> String

port or null if unix sockets used

-> IO Redis 

Conects to Redis server and returns connection descriptor

disconnect :: Redis -> IO () Source #

Close connection

isConnected :: Redis -> IO Bool Source #

Returns True when connection handler is opened

getServer :: Redis -> IO (String, String) Source #

Returns connection host and port

getDatabase :: Redis -> IO Int Source #

Returns currently selected database

renameCommand Source #

Arguments

:: Redis 
-> ByteString

command to rename

-> ByteString

new name

-> IO () 

Adds command to renaming map

Redis commands

Generic

ping :: Redis -> IO (Reply ()) Source #

ping - pong

RPong returned if no errors happends

auth Source #

Arguments

:: BS s 
=> Redis 
-> s

password

-> IO (Reply ()) 

Password authentication

ROk returned

echo Source #

Arguments

:: BS s 
=> Redis 
-> s

what to echo

-> IO (Reply s) 

Echo the given string

RBulk returned

quit :: Redis -> IO () Source #

Quit and close connection

shutdown :: Redis -> IO () Source #

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

multi :: Redis -> IO (Reply ()) Source #

Begin the multi-exec block

ROk returned

exec :: BS s => Redis -> IO (Reply s) Source #

Execute queued commands

RMulti returned - replies for all executed commands

discard :: Redis -> IO (Reply ()) Source #

Discard queued commands without execution

ROk returned

run_multi Source #

Arguments

:: BS s 
=> Redis 
-> (Redis -> IO ())

IO action to run

-> IO (Reply s) 

Run commands within multi-exec block

RMulti returned - replies for all executed commands

watch Source #

Arguments

:: BS s 
=> Redis 
-> [s]

keys to watch for

-> IO (Reply ()) 

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_cas Source #

Arguments

:: BS s1 
=> Redis 
-> [s1]

keys watched

-> (Redis -> IO a)

action to run

-> IO a 

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

exists Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> IO (Reply Int) 

Test if the key exists

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

del Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> IO (Reply Int) 

Remove the key

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

del_ Source #

Arguments

:: BS s 
=> Redis 
-> [s]

target keys list

-> IO (Reply Int) 

Variadic form of DEL

RInt returned - number of deleted keys

getType Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> IO RedisKeyType 

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

RedisKeyType returned

keys Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target keys pattern

-> IO (Reply s2) 

Returns all the keys matching the glob-style pattern

RMulti filled with RBulk returned

randomKey :: BS s => Redis -> IO (Reply s) Source #

Return random key name

RBulk returned

rename Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

source key

-> s2

destination key

-> IO (Reply ()) 

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

ROk returned

renameNx Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

source key

-> s2

destination key

-> IO (Reply Int) 

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

expire Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> Int

timeout in seconds

-> IO (Reply Int) 

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

expireAt Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> Int

expiration time

-> IO (Reply Int) 

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

persist Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> IO (Reply Int) 

Remove the timeout from a key

(RInt 1) returned if the timeout was removed and (RInt 0) otherwise

ttl Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> IO (Reply Int) 

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

RInt returned

select Source #

Arguments

:: Redis 
-> Int

database number

-> IO (Reply ()) 

Select the DB with the specified zero-based numeric index

ROk returned

move Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> Int

destination database number

-> IO (Reply Int) 

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 Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

value

-> IO (Reply ()) 

Set the string value as value of the key

ROk returned

setNx Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

value

-> IO (Reply Int) 

Set the key value if key does not exists

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

setEx Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> Int

timeout in seconds

-> s2

value

-> IO (Reply ()) 

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

mSet Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> [(s1, s2)]

(key, value) pairs

-> IO (Reply ()) 

Atomically set multiple keys

ROk returned

mSetNx Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> [(s1, s2)]

(key, value) pairs

-> IO (Reply Int) 

Atomically set multiple keys if none of them exists.

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

get Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> IO (Reply s2) 

Get the value of the specified key.

RBulk returned

getSet Source #

Arguments

:: (BS s1, BS s2, BS s3) 
=> Redis 
-> s1

target key

-> s2

value

-> IO (Reply s3) 

Atomically set this value and return the old value

RBulk returned

mGet Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> [s1]

target keys

-> IO (Reply s2) 

Get the values of all specified keys

RMulti filled with RBulk replies returned

incr Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> IO (Reply Int) 

Increment the key value by one

RInt returned with new key value

incrBy Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> Int

increment

-> IO (Reply Int) 

Increment the key value by N

RInt returned with new key value

incrByFloat Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> Double

increment

-> IO (Reply Double) 

Increment the key value by N

(RBulk Double) returned with new key value

decr Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> IO (Reply Int) 

Decrement the key value by one

RInt returned with new key value

decrBy Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> Int

decrement

-> IO (Reply Int) 

Decrement the key value by N

RInt returned with new key value

append Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

value

-> IO (Reply Int) 

Append string to the string-typed key

RInt returned - the length of resulting string

substr Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> (Int, Int)

(start, end)

-> IO (Reply s2) 

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

getrange Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> (Int, Int)

(start, end)

-> IO (Reply s2) 

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

setrange Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> Int

offset

-> s2

value

-> IO (Reply Int) 

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.

getbit Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> Int

bit offset

-> IO (Reply Int) 

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

setbit Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> Int

bit offset

-> Int

bit value - 0 or 1

-> IO (Reply Int) 

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.

strlen Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> IO (Reply Int) 

Returns a length of a string-typed key

RInt returned

Lists

rpush Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

value

-> IO (Reply Int) 

Add string value to the tail of the list-type key. New list length returned

RInt returned

rpush_ Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> [s2]

values list

-> IO (Reply Int) 

Variadic form of rpush

RInt returned

lpush Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

value

-> IO (Reply Int) 

Add string value to the head of the list-type key. New list length returned

RInt returned

lpush_ Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> [s2]

values list

-> IO (Reply Int) 

Variadic form of LPUSH

RInt returned

rpushx Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

value to push

-> IO (Reply Int) 

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

lpushx Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

value to push

-> IO (Reply Int) 

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

linsert Source #

Arguments

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

llen Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> IO (Reply Int) 

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

lrange Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> (Int, Int)

(from, to) pair

-> IO (Reply s2) 

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

ltrim Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> (Int, Int)

(from, to) pair

-> IO (Reply ()) 

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

ROk returned

lindex Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> Int

index

-> IO (Reply s2) 

Return the specified element of the list by its index

RBulk returned

lset Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> Int

index

-> s2

new value

-> IO (Reply ()) 

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

lrem Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> Int

occurrences

-> s2

value

-> IO (Reply Int) 

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

RInt returned - the number of elements removed

lpop Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> IO (Reply s2) 

Atomically return and remove the first element of the list

RBulk returned

rpop Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> IO (Reply s2) 

Atomically return and remove the last element of the list

RBulk returned

rpoplpush Source #

Arguments

:: (BS s1, BS s2, BS s3) 
=> Redis 
-> s1

source key

-> s2

destination key

-> IO (Reply s3) 

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

blpop Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> [s1]

keys list

-> Int

timeout

-> IO (Maybe (s1, s2)) 

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.

brpop Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> [s1]

keys list

-> Int

timeout

-> IO (Maybe (s1, s2)) 

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.

brpoplpush Source #

Arguments

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

sadd Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

value

-> IO (Reply Int) 

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

sadd_ Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> [s2]

values list

-> IO (Reply Int) 

Variadic form of SADD

RInt returned - number of actualy added elements

srem Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

value

-> IO (Reply Int) 

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

srem_ Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> [s2]

values list

-> IO (Reply Int) 

Variadic form of SREM

RInt returned - number of removed values

spop Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> IO (Reply s2) 

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

RBulk returned

smove Source #

Arguments

:: (BS s1, BS s2, BS s3) 
=> Redis 
-> s1

source key

-> s2

destination key

-> s3

value

-> IO (Reply Int) 

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

scard Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> IO (Reply Int) 

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

RInt returned

sismember Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

value to test

-> IO (Reply Int) 

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

smembers Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> IO (Reply s2) 

Return all the members (elements) of the set

RMulti filled with RBulk returned

srandmember Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> IO (Reply s2) 

Return a random element from a set

RBulk returned

sinter Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> [s1]

keys list

-> IO (Reply s2) 

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

RMulti filled with RBulk returned

sinterStore Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

where to store resulting set

-> [s2]

sets list

-> IO (Reply ()) 

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

RInt returned - resulting set cardinality.

sunion Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> [s1]

keys list

-> IO (Reply s2) 

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

RMulti filled with RBulk returned

sunionStore Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

where to store resulting set

-> [s2]

sets list

-> IO (Reply ()) 

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

RInt returned - resulting set cardinality.

sdiff Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> [s1]

keys list

-> IO (Reply s2) 

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

sdiffStore Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

where to store resulting set

-> [s2]

sets list

-> IO (Reply ()) 

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

RInt returned - resulting set cardinality.

Sorted sets

zadd Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> Double

score

-> s2

value

-> IO (Reply Int) 

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

zadd_ Source #

Arguments

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

zrem Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

value

-> IO (Reply Int) 

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

zrem_ Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> [s2]

values list

-> IO (Reply Int) 

Variadic form of zrem RInt returned - the number of removed elements

zincrBy Source #

Arguments

:: (BS s1, BS s2, BS s3) 
=> Redis 
-> s1

target key

-> Double

increment

-> s2

value

-> IO (Reply s3) 

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

zrange Source #

Arguments

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

zrevrange Source #

Arguments

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

zrangebyscore Source #

Arguments

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

zcount Source #

Arguments

:: (IsInterval i Double, BS s) 
=> Redis 
-> s

target key

-> i

scores interval

-> IO (Reply Int) 

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

RInt returned

zremrangebyscore Source #

Arguments

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

zcard Source #

Arguments

:: BS s 
=> Redis 
-> s

target key

-> IO (Reply Int) 

Return the sorted set cardinality (number of elements)

RInt returned

zscore Source #

Arguments

:: (BS s1, BS s2, BS s3) 
=> Redis 
-> s1

target key

-> s2

value

-> IO (Reply s3) 

Return the score of the specified element of the sorted set

RBulk returned

zrank Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

value

-> IO (Reply Int) 

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.

zrevrank Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

value

-> IO (Reply Int) 

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

zunionStore Source #

Arguments

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

zinterStore Source #

Arguments

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

hset Source #

Arguments

:: (BS s1, BS s2, BS s3) 
=> Redis 
-> s1

target key

-> s2

field name

-> s3

value

-> IO (Reply Int) 

Set the specified hash field to the specified value

(RInt 0 returned if field value was updated and (RInt 1) if new field created

hget Source #

Arguments

:: (BS s1, BS s2, BS s3) 
=> Redis 
-> s1

key

-> s2

field name

-> IO (Reply s3) 

Return value associated with specified field from hash

RBulk returned

hdel Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

key

-> s2

field name

-> IO (Reply Int) 

Remove field from a hash

(RInt 1) returned if field was removed and (RInt 0) otherwise

hdel_ Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

key

-> [s2]

field name

-> IO (Reply Int) 

Variadic form of HDEL

RInt returned - number of fields deleted

hmset Source #

Arguments

:: (BS s1, BS s2, BS s3) 
=> Redis 
-> s1

target key

-> [(s2, s3)]

(field, value) pairs

-> IO (Reply ()) 

Atomically sets multiple fields within a hash-typed key

ROk returned

hmget Source #

Arguments

:: (BS s1, BS s2, BS s3) 
=> Redis 
-> s1

target key

-> [s2]

field names

-> IO (Reply s3) 

Get the values of all specified fields from the hash-typed key

RMulti filled with RBulk replies returned

hincrBy Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

field name

-> Int

increment

-> IO (Reply Int) 

Increment the field value within a hash by N

RInt returned with new key value

hincrByFloat Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> s2

field name

-> Double

increment

-> IO (Reply Double) 

Increment the field value within a hash by N

(RBulk Double) returned with new key value

hexists Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

key

-> s2

field name

-> IO (Reply Int) 

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

hgetall Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

target key

-> IO (Reply s2) 

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 Source #

Arguments

:: (BS s1, BS s2, BS s3) 
=> Redis 
-> s1

target key

-> SortOptions s2

options

-> IO (Reply s3) 

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

listRelated Source #

Arguments

:: (BS s1, BS s2, BS s3) 
=> Redis 
-> s1

related key

-> s2

index key

-> (Int, Int)

range

-> IO (Reply s3) 

Shortcut for the sort with some get_obj and constant sort_by options

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 Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> [s1]

channels to subscribe

-> IO [Message s2] 

Subscribe to channels

list of Message with subscribtion information returned

unsubscribe Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> [s1]

channels to unsubscribe

-> IO [Message s2] 

Unsubscribe from channels. If called with an empty list then unsubscribe all channels

list of Message with subscribtion information returned

psubscribe Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> [s1]

patterns to subscribe

-> IO [Message s2] 

Subscribe to patterns

list of Message with subscribtion information returned

punsubscribe Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> [s1]

patterns to unsubscribe

-> IO [Message s2] 

Unsubscribe from patterns. If called with an empty list then unsubscribe all patterns

list of Message with subscribtion information returned

publish Source #

Arguments

:: (BS s1, BS s2) 
=> Redis 
-> s1

channel

-> s2

message

-> IO (Reply Int) 

Publish message to target channel

RInt returned - a number of clients that recieves the message

listen Source #

Arguments

:: BS s 
=> Redis 
-> Int

timeout

-> IO (Maybe (Message s)) 

Wait for a messages.

Just Message returned or Nothing if timeout exceeded

Persistent control

save :: Redis -> IO (Reply ()) Source #

Save the whole dataset on disk

ROk returned

bgsave :: Redis -> IO (Reply ()) Source #

Save the DB in background

ROk returned

lastsave :: Redis -> IO (Reply Int) Source #

Return the UNIX TIME of the last DB save executed with success

RInt returned

bgrewriteaof :: Redis -> IO (Reply ()) Source #

Rewrites the Append Only File in background

ROk returned