Safe Haskell | None |
---|
- data Redis a
- runRedis :: Connection -> Redis a -> IO a
- class MonadRedis m => RedisCtx m f | m -> f
- class Monad m => MonadRedis m
- data Connection
- connect :: ConnectInfo -> IO Connection
- data ConnectInfo = ConnInfo {}
- defaultConnectInfo :: ConnectInfo
- type HostName = String
- data PortID
- auth :: ByteString -> Redis (Either Reply Status)
- echo :: RedisCtx m f => ByteString -> m (f ByteString)
- ping :: RedisCtx m f => m (f Status)
- quit :: RedisCtx m f => m (f Status)
- select :: RedisCtx m f => Integer -> m (f Status)
- del :: RedisCtx m f => [ByteString] -> m (f Integer)
- dump :: RedisCtx m f => ByteString -> m (f ByteString)
- exists :: RedisCtx m f => ByteString -> m (f Bool)
- expire :: RedisCtx m f => ByteString -> Integer -> m (f Bool)
- expireat :: RedisCtx m f => ByteString -> Integer -> m (f Bool)
- keys :: RedisCtx m f => ByteString -> m (f [ByteString])
- migrate :: RedisCtx m f => ByteString -> ByteString -> ByteString -> Integer -> Integer -> m (f Status)
- move :: RedisCtx m f => ByteString -> Integer -> m (f Bool)
- objectRefcount :: RedisCtx m f => ByteString -> m (f Integer)
- objectEncoding :: RedisCtx m f => ByteString -> m (f ByteString)
- objectIdletime :: RedisCtx m f => ByteString -> m (f Integer)
- persist :: RedisCtx m f => ByteString -> m (f Bool)
- pexpire :: RedisCtx m f => ByteString -> Integer -> m (f Bool)
- pexpireat :: RedisCtx m f => ByteString -> Integer -> m (f Bool)
- pttl :: RedisCtx m f => ByteString -> m (f Integer)
- randomkey :: RedisCtx m f => m (f (Maybe ByteString))
- rename :: RedisCtx m f => ByteString -> ByteString -> m (f Status)
- renamenx :: RedisCtx m f => ByteString -> ByteString -> m (f Bool)
- restore :: RedisCtx m f => ByteString -> Integer -> ByteString -> m (f Status)
- data SortOpts = SortOpts {}
- defaultSortOpts :: SortOpts
- data SortOrder
- sort :: RedisCtx m f => ByteString -> SortOpts -> m (f [ByteString])
- sortStore :: RedisCtx m f => ByteString -> ByteString -> SortOpts -> m (f Integer)
- ttl :: RedisCtx m f => ByteString -> m (f Integer)
- data RedisType
- getType :: RedisCtx m f => ByteString -> m (f RedisType)
- hdel :: RedisCtx m f => ByteString -> [ByteString] -> m (f Integer)
- hexists :: RedisCtx m f => ByteString -> ByteString -> m (f Bool)
- hget :: RedisCtx m f => ByteString -> ByteString -> m (f (Maybe ByteString))
- hgetall :: RedisCtx m f => ByteString -> m (f [(ByteString, ByteString)])
- hincrby :: RedisCtx m f => ByteString -> ByteString -> Integer -> m (f Integer)
- hincrbyfloat :: RedisCtx m f => ByteString -> ByteString -> Double -> m (f Double)
- hkeys :: RedisCtx m f => ByteString -> m (f [ByteString])
- hlen :: RedisCtx m f => ByteString -> m (f Integer)
- hmget :: RedisCtx m f => ByteString -> [ByteString] -> m (f [Maybe ByteString])
- hmset :: RedisCtx m f => ByteString -> [(ByteString, ByteString)] -> m (f Status)
- hset :: RedisCtx m f => ByteString -> ByteString -> ByteString -> m (f Bool)
- hsetnx :: RedisCtx m f => ByteString -> ByteString -> ByteString -> m (f Bool)
- hvals :: RedisCtx m f => ByteString -> m (f [ByteString])
- blpop :: RedisCtx m f => [ByteString] -> Integer -> m (f (Maybe (ByteString, ByteString)))
- brpop :: RedisCtx m f => [ByteString] -> Integer -> m (f (Maybe (ByteString, ByteString)))
- brpoplpush :: RedisCtx m f => ByteString -> ByteString -> Integer -> m (f (Maybe ByteString))
- lindex :: RedisCtx m f => ByteString -> Integer -> m (f (Maybe ByteString))
- linsertBefore :: RedisCtx m f => ByteString -> ByteString -> ByteString -> m (f Integer)
- linsertAfter :: RedisCtx m f => ByteString -> ByteString -> ByteString -> m (f Integer)
- llen :: RedisCtx m f => ByteString -> m (f Integer)
- lpop :: RedisCtx m f => ByteString -> m (f (Maybe ByteString))
- lpush :: RedisCtx m f => ByteString -> [ByteString] -> m (f Integer)
- lpushx :: RedisCtx m f => ByteString -> ByteString -> m (f Integer)
- lrange :: RedisCtx m f => ByteString -> Integer -> Integer -> m (f [ByteString])
- lrem :: RedisCtx m f => ByteString -> Integer -> ByteString -> m (f Integer)
- lset :: RedisCtx m f => ByteString -> Integer -> ByteString -> m (f Status)
- ltrim :: RedisCtx m f => ByteString -> Integer -> Integer -> m (f Status)
- rpop :: RedisCtx m f => ByteString -> m (f (Maybe ByteString))
- rpoplpush :: RedisCtx m f => ByteString -> ByteString -> m (f (Maybe ByteString))
- rpush :: RedisCtx m f => ByteString -> [ByteString] -> m (f Integer)
- rpushx :: RedisCtx m f => ByteString -> ByteString -> m (f Integer)
- eval :: (RedisCtx m f, RedisResult a) => ByteString -> [ByteString] -> [ByteString] -> m (f a)
- evalsha :: (RedisCtx m f, RedisResult a) => ByteString -> [ByteString] -> [ByteString] -> m (f a)
- scriptExists :: RedisCtx m f => [ByteString] -> m (f [Bool])
- scriptFlush :: RedisCtx m f => m (f Status)
- scriptKill :: RedisCtx m f => m (f Status)
- scriptLoad :: RedisCtx m f => ByteString -> m (f ByteString)
- bgrewriteaof :: RedisCtx m f => m (f Status)
- bgsave :: RedisCtx m f => m (f Status)
- configGet :: RedisCtx m f => ByteString -> m (f [(ByteString, ByteString)])
- configResetstat :: RedisCtx m f => m (f Status)
- configSet :: RedisCtx m f => ByteString -> ByteString -> m (f Status)
- dbsize :: RedisCtx m f => m (f Integer)
- debugObject :: RedisCtx m f => ByteString -> m (f ByteString)
- flushall :: RedisCtx m f => m (f Status)
- flushdb :: RedisCtx m f => m (f Status)
- info :: RedisCtx m f => m (f ByteString)
- lastsave :: RedisCtx m f => m (f Integer)
- save :: RedisCtx m f => m (f Status)
- slaveof :: RedisCtx m f => ByteString -> ByteString -> m (f Status)
- data Slowlog = Slowlog {}
- slowlogGet :: RedisCtx m f => Integer -> m (f [Slowlog])
- slowlogLen :: RedisCtx m f => m (f Integer)
- slowlogReset :: RedisCtx m f => m (f Status)
- time :: RedisCtx m f => m (f (Integer, Integer))
- sadd :: RedisCtx m f => ByteString -> [ByteString] -> m (f Integer)
- scard :: RedisCtx m f => ByteString -> m (f Integer)
- sdiff :: RedisCtx m f => [ByteString] -> m (f [ByteString])
- sdiffstore :: RedisCtx m f => ByteString -> [ByteString] -> m (f Integer)
- sinter :: RedisCtx m f => [ByteString] -> m (f [ByteString])
- sinterstore :: RedisCtx m f => ByteString -> [ByteString] -> m (f Integer)
- sismember :: RedisCtx m f => ByteString -> ByteString -> m (f Bool)
- smembers :: RedisCtx m f => ByteString -> m (f [ByteString])
- smove :: RedisCtx m f => ByteString -> ByteString -> ByteString -> m (f Bool)
- spop :: RedisCtx m f => ByteString -> m (f (Maybe ByteString))
- srandmember :: RedisCtx m f => ByteString -> m (f (Maybe ByteString))
- srem :: RedisCtx m f => ByteString -> [ByteString] -> m (f Integer)
- sunion :: RedisCtx m f => [ByteString] -> m (f [ByteString])
- sunionstore :: RedisCtx m f => ByteString -> [ByteString] -> m (f Integer)
- zadd :: RedisCtx m f => ByteString -> [(Double, ByteString)] -> m (f Integer)
- zcard :: RedisCtx m f => ByteString -> m (f Integer)
- zcount :: RedisCtx m f => ByteString -> Double -> Double -> m (f Integer)
- zincrby :: RedisCtx m f => ByteString -> Integer -> ByteString -> m (f Double)
- data Aggregate
- zinterstore :: RedisCtx m f => ByteString -> [ByteString] -> Aggregate -> m (f Integer)
- zinterstoreWeights :: RedisCtx m f => ByteString -> [(ByteString, Double)] -> Aggregate -> m (f Integer)
- zrange :: RedisCtx m f => ByteString -> Integer -> Integer -> m (f [ByteString])
- zrangeWithscores :: RedisCtx m f => ByteString -> Integer -> Integer -> m (f [(ByteString, Double)])
- zrangebyscore :: RedisCtx m f => ByteString -> Double -> Double -> m (f [ByteString])
- zrangebyscoreWithscores :: RedisCtx m f => ByteString -> Double -> Double -> m (f [(ByteString, Double)])
- zrangebyscoreLimit :: RedisCtx m f => ByteString -> Double -> Double -> Integer -> Integer -> m (f [ByteString])
- zrangebyscoreWithscoresLimit :: RedisCtx m f => ByteString -> Double -> Double -> Integer -> Integer -> m (f [(ByteString, Double)])
- zrank :: RedisCtx m f => ByteString -> ByteString -> m (f (Maybe Integer))
- zrem :: RedisCtx m f => ByteString -> [ByteString] -> m (f Integer)
- zremrangebyrank :: RedisCtx m f => ByteString -> Integer -> Integer -> m (f Integer)
- zremrangebyscore :: RedisCtx m f => ByteString -> Double -> Double -> m (f Integer)
- zrevrange :: RedisCtx m f => ByteString -> Integer -> Integer -> m (f [ByteString])
- zrevrangeWithscores :: RedisCtx m f => ByteString -> Integer -> Integer -> m (f [(ByteString, Double)])
- zrevrangebyscore :: RedisCtx m f => ByteString -> Double -> Double -> m (f [ByteString])
- zrevrangebyscoreWithscores :: RedisCtx m f => ByteString -> Double -> Double -> m (f [(ByteString, Double)])
- zrevrangebyscoreLimit :: RedisCtx m f => ByteString -> Double -> Double -> Integer -> Integer -> m (f [ByteString])
- zrevrangebyscoreWithscoresLimit :: RedisCtx m f => ByteString -> Double -> Double -> Integer -> Integer -> m (f [(ByteString, Double)])
- zrevrank :: RedisCtx m f => ByteString -> ByteString -> m (f (Maybe Integer))
- zscore :: RedisCtx m f => ByteString -> ByteString -> m (f (Maybe Double))
- zunionstore :: RedisCtx m f => ByteString -> [ByteString] -> Aggregate -> m (f Integer)
- zunionstoreWeights :: RedisCtx m f => ByteString -> [(ByteString, Double)] -> Aggregate -> m (f Integer)
- append :: RedisCtx m f => ByteString -> ByteString -> m (f Integer)
- bitcount :: RedisCtx m f => ByteString -> m (f Integer)
- bitcountRange :: RedisCtx m f => ByteString -> Integer -> Integer -> m (f Integer)
- bitopAnd :: RedisCtx m f => ByteString -> [ByteString] -> m (f Integer)
- bitopOr :: RedisCtx m f => ByteString -> [ByteString] -> m (f Integer)
- bitopXor :: RedisCtx m f => ByteString -> [ByteString] -> m (f Integer)
- bitopNot :: RedisCtx m f => ByteString -> ByteString -> m (f Integer)
- decr :: RedisCtx m f => ByteString -> m (f Integer)
- decrby :: RedisCtx m f => ByteString -> Integer -> m (f Integer)
- get :: RedisCtx m f => ByteString -> m (f (Maybe ByteString))
- getbit :: RedisCtx m f => ByteString -> Integer -> m (f Integer)
- getrange :: RedisCtx m f => ByteString -> Integer -> Integer -> m (f ByteString)
- getset :: RedisCtx m f => ByteString -> ByteString -> m (f (Maybe ByteString))
- incr :: RedisCtx m f => ByteString -> m (f Integer)
- incrby :: RedisCtx m f => ByteString -> Integer -> m (f Integer)
- incrbyfloat :: RedisCtx m f => ByteString -> Double -> m (f Double)
- mget :: RedisCtx m f => [ByteString] -> m (f [Maybe ByteString])
- mset :: RedisCtx m f => [(ByteString, ByteString)] -> m (f Status)
- msetnx :: RedisCtx m f => [(ByteString, ByteString)] -> m (f Bool)
- psetex :: RedisCtx m f => ByteString -> Integer -> ByteString -> m (f Status)
- set :: RedisCtx m f => ByteString -> ByteString -> m (f Status)
- setbit :: RedisCtx m f => ByteString -> Integer -> ByteString -> m (f Integer)
- setex :: RedisCtx m f => ByteString -> Integer -> ByteString -> m (f Status)
- setnx :: RedisCtx m f => ByteString -> ByteString -> m (f Bool)
- setrange :: RedisCtx m f => ByteString -> Integer -> ByteString -> m (f Integer)
- strlen :: RedisCtx m f => ByteString -> m (f Integer)
- watch :: [ByteString] -> Redis (Either Reply Status)
- unwatch :: Redis (Either Reply Status)
- multiExec :: RedisTx (Queued a) -> Redis (TxResult a)
- data Queued a
- data TxResult a
- data RedisTx a
- publish :: RedisCtx m f => ByteString -> ByteString -> m (f Integer)
- pubSub :: PubSub -> (Message -> IO PubSub) -> Redis ()
- data Message
- data PubSub
- subscribe :: [ByteString] -> PubSub
- unsubscribe :: [ByteString] -> PubSub
- psubscribe :: [ByteString] -> PubSub
- punsubscribe :: [ByteString] -> PubSub
- sendRequest :: (RedisCtx m f, RedisResult a) => [ByteString] -> m (f a)
- data Reply
- = SingleLine ByteString
- | Error ByteString
- | Integer Integer
- | Bulk (Maybe ByteString)
- | MultiBulk (Maybe [Reply])
- data Status
- = Ok
- | Pong
- | Status ByteString
- class RedisResult a where
- data ConnectionLostException = ConnectionLost
How To Use This Module
Connect to a Redis server:
-- connects to localhost:6379 conn <-connect
defaultConnectInfo
Send commands to the server:
{-# LANGUAGE OverloadedStrings #-} ...runRedis
conn $ doset
"hello" "hello" set "world" "world" hello <-get
"hello" world <- get "world" liftIO $ print (hello,world)
Command Type Signatures
Redis commands behave differently when issued in- or outside of a transaction. To make them work in both contexts, most command functions have a type signature similar to the following:
echo
:: (RedisCtx
m f) => ByteString -> m (f ByteString)
Here is how to interpret this type signature:
- The argument types are independent of the execution context.
echo
always takes aByteString
parameter, whether in- or outside of a transaction. This is true for all command functions. - All Redis commands return their result wrapped in some "container".
The type
f
of this container depends on the commands execution contextm
. TheByteString
return type in the example is specific to theecho
command. For other commands, it will often be another type. - In the "normal" context
Redis
, outside of any transactions, results are wrapped in an
.Either
Reply
- Inside a transaction, in the
RedisTx
context, results are wrapped in aQueued
.
In short, you can view any command with a RedisCtx
constraint in the
type signature, to "have two types". For example echo
"has both
types":
echo :: ByteString -> Redis (Either Reply ByteString) echo :: ByteString -> RedisTx (Queued ByteString)
Lua Scripting
Lua values returned from the eval
and evalsha
functions will be
converted to Haskell values by the decode
function from the
RedisResult
type class.
Lua Type | Haskell Type | Conversion Example --------------|--------------------|----------------------------- Number | Integer | 1.23 => 1 String | ByteString, Double | "1.23" => "1.23" or 1.23 Boolean | Bool | false => False Table | List | {1,2} => [1,2]
Additionally, any of the Haskell types from the table above can be
wrapped in a Maybe
:
42 => Just 42 :: Maybe Integer nil => Nothing :: Maybe Integer
Note that Redis imposes some limitations on the possible conversions:
- Lua numbers can only be converted to Integers. Only Lua strings can be interpreted as Doubles.
- Associative Lua tables can not be converted at all. Returned tables must be "arrays", i.e. indexed only by integers.
The Redis Scripting website (http://redis.io/commands/eval) documents the exact semantics of the scripting commands and value conversion.
Automatic Pipelining
Commands are automatically pipelined as much as possible. For example, in the above "hello world" example, all four commands are pipelined. Automatic pipelining makes use of Haskell's laziness. As long as a previous reply is not evaluated, subsequent commands can be pipelined.
Automatic pipelining also works across several calls to runRedis
, as
long as replies are only evaluated outside the runRedis
block.
To keep memory usage low, the number of requests "in the pipeline" is limited (per connection) to 1000. After that number, the next command is sent only when at least one reply has been received. That means, command functions may block until there are less than 1000 outstanding replies.
Error Behavior
- Operations against keys holding the wrong kind of value:
- Outside of a
transaction, if the Redis server returns an
Error
, command functions will returnLeft
theReply
. The library user can inspect the error message to gain information on what kind of error occured. - Connection to the server lost:
- In case of a lost connection, command
functions throw a
ConnectionLostException
. It can only be caught outside ofrunRedis
. - Exceptions:
- Any exceptions can only be caught outside of
runRedis
. This way the connection pool can properly close the connection, making sure it is not left in an unusable state, e.g. closed or inside a transaction.
The Redis Monad
runRedis :: Connection -> Redis a -> IO aSource
Interact with a Redis datastore specified by the given Connection
.
Each call of runRedis
takes a network connection from the Connection
pool and runs the given Redis
action. Calls to runRedis
may thus block
while all connections from the pool are in use.
class MonadRedis m => RedisCtx m f | m -> fSource
This class captures the following behaviour: In a context m
, a command
will return it's result wrapped in a "container" of type f
.
Please refer to the Command Type Signatures section of this page for more information.
class Monad m => MonadRedis m Source
Connection
data Connection Source
A threadsafe pool of network connections to a Redis server. Use the
connect
function to create one.
connect :: ConnectInfo -> IO ConnectionSource
Opens a Connection
to a Redis server designated by the given
ConnectInfo
.
data ConnectInfo Source
Information for connnecting to a Redis server.
It is recommended to not use the ConnInfo
data constructor directly.
Instead use defaultConnectInfo
and update it with record syntax. For
example to connect to a password protected Redis server running on localhost
and listening to the default port:
myConnectInfo :: ConnectInfo myConnectInfo = defaultConnectInfo {connectAuth = Just "secret"}
ConnInfo | |
|
defaultConnectInfo :: ConnectInfoSource
Default information for connecting:
connectHost = "localhost" connectPort = PortNumber 6379 -- Redis default port connectAuth = Nothing -- No password connectMaxConnections = 50 -- Up to 50 connections connectMaxIdleTime = 30 -- Keep open for 30 seconds
Either a host name e.g., "haskell.org"
or a numeric host
address string consisting of a dotted decimal IPv4 address or an
IPv6 address e.g., "192.168.0.1"
.
Commands
Connection
Authenticate to the server (http://redis.io/commands/auth).
:: RedisCtx m f | |
=> ByteString | message |
-> m (f ByteString) |
Echo the given string (http://redis.io/commands/echo).
Ping the server (http://redis.io/commands/ping).
Close the connection (http://redis.io/commands/quit).
Change the selected database for the current connection (http://redis.io/commands/select).
Keys
:: RedisCtx m f | |
=> [ByteString] | key |
-> m (f Integer) |
Delete a key (http://redis.io/commands/del).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f ByteString) |
Return a serialized version of the value stored at the specified key. (http://redis.io/commands/dump).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f Bool) |
Determine if a key exists (http://redis.io/commands/exists).
Set a key's time to live in seconds (http://redis.io/commands/expire).
Set the expiration for a key as a UNIX timestamp (http://redis.io/commands/expireat).
:: RedisCtx m f | |
=> ByteString | pattern |
-> m (f [ByteString]) |
Find all keys matching the given pattern (http://redis.io/commands/keys).
:: RedisCtx m f | |
=> ByteString | host |
-> ByteString | port |
-> ByteString | key |
-> Integer | destinationDb |
-> Integer | timeout |
-> m (f Status) |
Atomically transfer a key from a Redis instance to another one. (http://redis.io/commands/migrate).
Move a key to another database (http://redis.io/commands/move).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f Integer) |
Inspect the internals of Redis objects (http://redis.io/commands/object). The Redis command OBJECT
is split up into objectRefcount
, objectEncoding
, objectIdletime
.
:: RedisCtx m f | |
=> ByteString | key |
-> m (f ByteString) |
Inspect the internals of Redis objects (http://redis.io/commands/object). The Redis command OBJECT
is split up into objectRefcount
, objectEncoding
, objectIdletime
.
:: RedisCtx m f | |
=> ByteString | key |
-> m (f Integer) |
Inspect the internals of Redis objects (http://redis.io/commands/object). The Redis command OBJECT
is split up into objectRefcount
, objectEncoding
, objectIdletime
.
:: RedisCtx m f | |
=> ByteString | key |
-> m (f Bool) |
Remove the expiration from a key (http://redis.io/commands/persist).
Set a key's time to live in milliseconds (http://redis.io/commands/pexpire).
Set the expiration for a key as a UNIX timestamp specified in milliseconds (http://redis.io/commands/pexpireat).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f Integer) |
Get the time to live for a key in milliseconds (http://redis.io/commands/pttl).
randomkey :: RedisCtx m f => m (f (Maybe ByteString))Source
Return a random key from the keyspace (http://redis.io/commands/randomkey).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | newkey |
-> m (f Status) |
Rename a key (http://redis.io/commands/rename).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | newkey |
-> m (f Bool) |
Rename a key, only if the new key does not exist (http://redis.io/commands/renamenx).
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | timeToLive |
-> ByteString | serializedValue |
-> m (f Status) |
Create a key using the provided serialized value, previously obtained using DUMP. (http://redis.io/commands/restore).
defaultSortOpts :: SortOptsSource
Redis default SortOpts
. Equivalent to omitting all optional parameters.
SortOpts { sortBy = Nothing -- omit the BY option , sortLimit = (0,-1) -- return entire collection , sortGet = [] -- omit the GET option , sortOrder = Asc -- sort in ascending order , sortAlpha = False -- sort numerically, not lexicographically }
:: RedisCtx m f | |
=> ByteString | key |
-> SortOpts | |
-> m (f [ByteString]) |
Sort the elements in a list, set or sorted set (http://redis.io/commands/sort). The Redis command SORT
is split up into sort
, sortStore
.
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | destination |
-> SortOpts | |
-> m (f Integer) |
Sort the elements in a list, set or sorted set (http://redis.io/commands/sort). The Redis command SORT
is split up into sort
, sortStore
.
:: RedisCtx m f | |
=> ByteString | key |
-> m (f Integer) |
Get the time to live for a key (http://redis.io/commands/ttl).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f RedisType) |
Determine the type stored at key (http://redis.io/commands/type).
Hashes
:: RedisCtx m f | |
=> ByteString | key |
-> [ByteString] | field |
-> m (f Integer) |
Delete one or more hash fields (http://redis.io/commands/hdel).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | field |
-> m (f Bool) |
Determine if a hash field exists (http://redis.io/commands/hexists).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | field |
-> m (f (Maybe ByteString)) |
Get the value of a hash field (http://redis.io/commands/hget).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f [(ByteString, ByteString)]) |
Get all the fields and values in a hash (http://redis.io/commands/hgetall).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | field |
-> Integer | increment |
-> m (f Integer) |
Increment the integer value of a hash field by the given number (http://redis.io/commands/hincrby).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | field |
-> Double | increment |
-> m (f Double) |
Increment the float value of a hash field by the given amount (http://redis.io/commands/hincrbyfloat).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f [ByteString]) |
Get all the fields in a hash (http://redis.io/commands/hkeys).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f Integer) |
Get the number of fields in a hash (http://redis.io/commands/hlen).
:: RedisCtx m f | |
=> ByteString | key |
-> [ByteString] | field |
-> m (f [Maybe ByteString]) |
Get the values of all the given hash fields (http://redis.io/commands/hmget).
:: RedisCtx m f | |
=> ByteString | key |
-> [(ByteString, ByteString)] | fieldValue |
-> m (f Status) |
Set multiple hash fields to multiple values (http://redis.io/commands/hmset).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | field |
-> ByteString | value |
-> m (f Bool) |
Set the string value of a hash field (http://redis.io/commands/hset).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | field |
-> ByteString | value |
-> m (f Bool) |
Set the value of a hash field, only if the field does not exist (http://redis.io/commands/hsetnx).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f [ByteString]) |
Get all the values in a hash (http://redis.io/commands/hvals).
Lists
:: RedisCtx m f | |
=> [ByteString] | key |
-> Integer | timeout |
-> m (f (Maybe (ByteString, ByteString))) |
Remove and get the first element in a list, or block until one is available (http://redis.io/commands/blpop).
:: RedisCtx m f | |
=> [ByteString] | key |
-> Integer | timeout |
-> m (f (Maybe (ByteString, ByteString))) |
Remove and get the last element in a list, or block until one is available (http://redis.io/commands/brpop).
:: RedisCtx m f | |
=> ByteString | source |
-> ByteString | destination |
-> Integer | timeout |
-> m (f (Maybe ByteString)) |
Pop a value from a list, push it to another list and return it; or block until one is available (http://redis.io/commands/brpoplpush).
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | index |
-> m (f (Maybe ByteString)) |
Get an element from a list by its index (http://redis.io/commands/lindex).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | pivot |
-> ByteString | value |
-> m (f Integer) |
Insert an element before or after another element in a list (http://redis.io/commands/linsert). The Redis command LINSERT
is split up into linsertBefore
, linsertAfter
.
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | pivot |
-> ByteString | value |
-> m (f Integer) |
Insert an element before or after another element in a list (http://redis.io/commands/linsert). The Redis command LINSERT
is split up into linsertBefore
, linsertAfter
.
:: RedisCtx m f | |
=> ByteString | key |
-> m (f Integer) |
Get the length of a list (http://redis.io/commands/llen).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f (Maybe ByteString)) |
Remove and get the first element in a list (http://redis.io/commands/lpop).
:: RedisCtx m f | |
=> ByteString | key |
-> [ByteString] | value |
-> m (f Integer) |
Prepend one or multiple values to a list (http://redis.io/commands/lpush).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | value |
-> m (f Integer) |
Prepend a value to a list, only if the list exists (http://redis.io/commands/lpushx).
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | start |
-> Integer | stop |
-> m (f [ByteString]) |
Get a range of elements from a list (http://redis.io/commands/lrange).
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | count |
-> ByteString | value |
-> m (f Integer) |
Remove elements from a list (http://redis.io/commands/lrem).
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | index |
-> ByteString | value |
-> m (f Status) |
Set the value of an element in a list by its index (http://redis.io/commands/lset).
Trim a list to the specified range (http://redis.io/commands/ltrim).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f (Maybe ByteString)) |
Remove and get the last element in a list (http://redis.io/commands/rpop).
:: RedisCtx m f | |
=> ByteString | source |
-> ByteString | destination |
-> m (f (Maybe ByteString)) |
Remove the last element in a list, append it to another list and return it (http://redis.io/commands/rpoplpush).
:: RedisCtx m f | |
=> ByteString | key |
-> [ByteString] | value |
-> m (f Integer) |
Append one or multiple values to a list (http://redis.io/commands/rpush).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | value |
-> m (f Integer) |
Append a value to a list, only if the list exists (http://redis.io/commands/rpushx).
Scripting
:: (RedisCtx m f, RedisResult a) | |
=> ByteString | script |
-> [ByteString] | keys |
-> [ByteString] | args |
-> m (f a) |
Execute a Lua script server side (http://redis.io/commands/eval).
:: (RedisCtx m f, RedisResult a) | |
=> ByteString | script |
-> [ByteString] | keys |
-> [ByteString] | args |
-> m (f a) |
Execute a Lua script server side (http://redis.io/commands/evalsha).
:: RedisCtx m f | |
=> [ByteString] | script |
-> m (f [Bool]) |
Check existence of scripts in the script cache. (http://redis.io/commands/script-exists).
scriptFlush :: RedisCtx m f => m (f Status)Source
Remove all the scripts from the script cache. (http://redis.io/commands/script-flush).
scriptKill :: RedisCtx m f => m (f Status)Source
Kill the script currently in execution. (http://redis.io/commands/script-kill).
:: RedisCtx m f | |
=> ByteString | script |
-> m (f ByteString) |
Load the specified Lua script into the script cache. (http://redis.io/commands/script-load).
Server
bgrewriteaof :: RedisCtx m f => m (f Status)Source
Asynchronously rewrite the append-only file (http://redis.io/commands/bgrewriteaof).
Asynchronously save the dataset to disk (http://redis.io/commands/bgsave).
:: RedisCtx m f | |
=> ByteString | parameter |
-> m (f [(ByteString, ByteString)]) |
Get the value of a configuration parameter (http://redis.io/commands/config-get).
configResetstat :: RedisCtx m f => m (f Status)Source
Reset the stats returned by INFO (http://redis.io/commands/config-resetstat).
:: RedisCtx m f | |
=> ByteString | parameter |
-> ByteString | value |
-> m (f Status) |
Set a configuration parameter to the given value (http://redis.io/commands/config-set).
Return the number of keys in the selected database (http://redis.io/commands/dbsize).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f ByteString) |
Get debugging information about a key (http://redis.io/commands/debug-object).
Remove all keys from all databases (http://redis.io/commands/flushall).
Remove all keys from the current database (http://redis.io/commands/flushdb).
info :: RedisCtx m f => m (f ByteString)Source
Get information and statistics about the server (http://redis.io/commands/info).
Get the UNIX time stamp of the last successful save to disk (http://redis.io/commands/lastsave).
Synchronously save the dataset to disk (http://redis.io/commands/save).
:: RedisCtx m f | |
=> ByteString | host |
-> ByteString | port |
-> m (f Status) |
Make the server a slave of another instance, or promote it as master (http://redis.io/commands/slaveof).
A single entry from the slowlog.
Slowlog | |
|
Manages the Redis slow queries log (http://redis.io/commands/slowlog). The Redis command SLOWLOG
is split up into slowlogGet
, slowlogLen
, slowlogReset
.
slowlogLen :: RedisCtx m f => m (f Integer)Source
Manages the Redis slow queries log (http://redis.io/commands/slowlog). The Redis command SLOWLOG
is split up into slowlogGet
, slowlogLen
, slowlogReset
.
slowlogReset :: RedisCtx m f => m (f Status)Source
Manages the Redis slow queries log (http://redis.io/commands/slowlog). The Redis command SLOWLOG
is split up into slowlogGet
, slowlogLen
, slowlogReset
.
Return the current server time (http://redis.io/commands/time).
Sets
:: RedisCtx m f | |
=> ByteString | key |
-> [ByteString] | member |
-> m (f Integer) |
Add one or more members to a set (http://redis.io/commands/sadd).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f Integer) |
Get the number of members in a set (http://redis.io/commands/scard).
:: RedisCtx m f | |
=> [ByteString] | key |
-> m (f [ByteString]) |
Subtract multiple sets (http://redis.io/commands/sdiff).
:: RedisCtx m f | |
=> ByteString | destination |
-> [ByteString] | key |
-> m (f Integer) |
Subtract multiple sets and store the resulting set in a key (http://redis.io/commands/sdiffstore).
:: RedisCtx m f | |
=> [ByteString] | key |
-> m (f [ByteString]) |
Intersect multiple sets (http://redis.io/commands/sinter).
:: RedisCtx m f | |
=> ByteString | destination |
-> [ByteString] | key |
-> m (f Integer) |
Intersect multiple sets and store the resulting set in a key (http://redis.io/commands/sinterstore).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | member |
-> m (f Bool) |
Determine if a given value is a member of a set (http://redis.io/commands/sismember).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f [ByteString]) |
Get all the members in a set (http://redis.io/commands/smembers).
:: RedisCtx m f | |
=> ByteString | source |
-> ByteString | destination |
-> ByteString | member |
-> m (f Bool) |
Move a member from one set to another (http://redis.io/commands/smove).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f (Maybe ByteString)) |
Remove and return a random member from a set (http://redis.io/commands/spop).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f (Maybe ByteString)) |
Get a random member from a set (http://redis.io/commands/srandmember).
:: RedisCtx m f | |
=> ByteString | key |
-> [ByteString] | member |
-> m (f Integer) |
Remove one or more members from a set (http://redis.io/commands/srem).
:: RedisCtx m f | |
=> [ByteString] | key |
-> m (f [ByteString]) |
Add multiple sets (http://redis.io/commands/sunion).
:: RedisCtx m f | |
=> ByteString | destination |
-> [ByteString] | key |
-> m (f Integer) |
Add multiple sets and store the resulting set in a key (http://redis.io/commands/sunionstore).
Sorted Sets
:: RedisCtx m f | |
=> ByteString | key |
-> [(Double, ByteString)] | scoreMember |
-> m (f Integer) |
Add one or more members to a sorted set, or update its score if it already exists (http://redis.io/commands/zadd).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f Integer) |
Get the number of members in a sorted set (http://redis.io/commands/zcard).
Count the members in a sorted set with scores within the given values (http://redis.io/commands/zcount).
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | increment |
-> ByteString | member |
-> m (f Double) |
Increment the score of a member in a sorted set (http://redis.io/commands/zincrby).
:: RedisCtx m f | |
=> ByteString | destination |
-> [ByteString] | keys |
-> Aggregate | |
-> m (f Integer) |
Intersect multiple sorted sets and store the resulting sorted set in a new key (http://redis.io/commands/zinterstore). The Redis command ZINTERSTORE
is split up into zinterstore
, zinterstoreWeights
.
:: RedisCtx m f | |
=> ByteString | destination |
-> [(ByteString, Double)] | weighted keys |
-> Aggregate | |
-> m (f Integer) |
Intersect multiple sorted sets and store the resulting sorted set in a new key (http://redis.io/commands/zinterstore). The Redis command ZINTERSTORE
is split up into zinterstore
, zinterstoreWeights
.
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | start |
-> Integer | stop |
-> m (f [ByteString]) |
Return a range of members in a sorted set, by index (http://redis.io/commands/zrange). The Redis command ZRANGE
is split up into zrange
, zrangeWithscores
.
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | start |
-> Integer | stop |
-> m (f [(ByteString, Double)]) |
Return a range of members in a sorted set, by index (http://redis.io/commands/zrange). The Redis command ZRANGE
is split up into zrange
, zrangeWithscores
.
:: RedisCtx m f | |
=> ByteString | key |
-> Double | min |
-> Double | max |
-> m (f [ByteString]) |
Return a range of members in a sorted set, by score (http://redis.io/commands/zrangebyscore). The Redis command ZRANGEBYSCORE
is split up into zrangebyscore
, zrangebyscoreWithscores
, zrangebyscoreLimit
, zrangebyscoreWithscoresLimit
.
:: RedisCtx m f | |
=> ByteString | key |
-> Double | min |
-> Double | max |
-> m (f [(ByteString, Double)]) |
Return a range of members in a sorted set, by score (http://redis.io/commands/zrangebyscore). The Redis command ZRANGEBYSCORE
is split up into zrangebyscore
, zrangebyscoreWithscores
, zrangebyscoreLimit
, zrangebyscoreWithscoresLimit
.
:: RedisCtx m f | |
=> ByteString | key |
-> Double | min |
-> Double | max |
-> Integer | offset |
-> Integer | count |
-> m (f [ByteString]) |
Return a range of members in a sorted set, by score (http://redis.io/commands/zrangebyscore). The Redis command ZRANGEBYSCORE
is split up into zrangebyscore
, zrangebyscoreWithscores
, zrangebyscoreLimit
, zrangebyscoreWithscoresLimit
.
zrangebyscoreWithscoresLimitSource
:: RedisCtx m f | |
=> ByteString | key |
-> Double | min |
-> Double | max |
-> Integer | offset |
-> Integer | count |
-> m (f [(ByteString, Double)]) |
Return a range of members in a sorted set, by score (http://redis.io/commands/zrangebyscore). The Redis command ZRANGEBYSCORE
is split up into zrangebyscore
, zrangebyscoreWithscores
, zrangebyscoreLimit
, zrangebyscoreWithscoresLimit
.
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | member |
-> m (f (Maybe Integer)) |
Determine the index of a member in a sorted set (http://redis.io/commands/zrank).
:: RedisCtx m f | |
=> ByteString | key |
-> [ByteString] | member |
-> m (f Integer) |
Remove one or more members from a sorted set (http://redis.io/commands/zrem).
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | start |
-> Integer | stop |
-> m (f Integer) |
Remove all members in a sorted set within the given indexes (http://redis.io/commands/zremrangebyrank).
:: RedisCtx m f | |
=> ByteString | key |
-> Double | min |
-> Double | max |
-> m (f Integer) |
Remove all members in a sorted set within the given scores (http://redis.io/commands/zremrangebyscore).
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | start |
-> Integer | stop |
-> m (f [ByteString]) |
Return a range of members in a sorted set, by index, with scores ordered from high to low (http://redis.io/commands/zrevrange). The Redis command ZREVRANGE
is split up into zrevrange
, zrevrangeWithscores
.
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | start |
-> Integer | stop |
-> m (f [(ByteString, Double)]) |
Return a range of members in a sorted set, by index, with scores ordered from high to low (http://redis.io/commands/zrevrange). The Redis command ZREVRANGE
is split up into zrevrange
, zrevrangeWithscores
.
:: RedisCtx m f | |
=> ByteString | key |
-> Double | max |
-> Double | min |
-> m (f [ByteString]) |
Return a range of members in a sorted set, by score, with scores ordered from high to low (http://redis.io/commands/zrevrangebyscore). The Redis command ZREVRANGEBYSCORE
is split up into zrevrangebyscore
, zrevrangebyscoreWithscores
, zrevrangebyscoreLimit
, zrevrangebyscoreWithscoresLimit
.
zrevrangebyscoreWithscoresSource
:: RedisCtx m f | |
=> ByteString | key |
-> Double | max |
-> Double | min |
-> m (f [(ByteString, Double)]) |
Return a range of members in a sorted set, by score, with scores ordered from high to low (http://redis.io/commands/zrevrangebyscore). The Redis command ZREVRANGEBYSCORE
is split up into zrevrangebyscore
, zrevrangebyscoreWithscores
, zrevrangebyscoreLimit
, zrevrangebyscoreWithscoresLimit
.
:: RedisCtx m f | |
=> ByteString | key |
-> Double | max |
-> Double | min |
-> Integer | offset |
-> Integer | count |
-> m (f [ByteString]) |
Return a range of members in a sorted set, by score, with scores ordered from high to low (http://redis.io/commands/zrevrangebyscore). The Redis command ZREVRANGEBYSCORE
is split up into zrevrangebyscore
, zrevrangebyscoreWithscores
, zrevrangebyscoreLimit
, zrevrangebyscoreWithscoresLimit
.
zrevrangebyscoreWithscoresLimitSource
:: RedisCtx m f | |
=> ByteString | key |
-> Double | max |
-> Double | min |
-> Integer | offset |
-> Integer | count |
-> m (f [(ByteString, Double)]) |
Return a range of members in a sorted set, by score, with scores ordered from high to low (http://redis.io/commands/zrevrangebyscore). The Redis command ZREVRANGEBYSCORE
is split up into zrevrangebyscore
, zrevrangebyscoreWithscores
, zrevrangebyscoreLimit
, zrevrangebyscoreWithscoresLimit
.
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | member |
-> m (f (Maybe Integer)) |
Determine the index of a member in a sorted set, with scores ordered from high to low (http://redis.io/commands/zrevrank).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | member |
-> m (f (Maybe Double)) |
Get the score associated with the given member in a sorted set (http://redis.io/commands/zscore).
:: RedisCtx m f | |
=> ByteString | destination |
-> [ByteString] | keys |
-> Aggregate | |
-> m (f Integer) |
Add multiple sorted sets and store the resulting sorted set in a new key (http://redis.io/commands/zunionstore). The Redis command ZUNIONSTORE
is split up into zunionstore
, zunionstoreWeights
.
:: RedisCtx m f | |
=> ByteString | destination |
-> [(ByteString, Double)] | weighted keys |
-> Aggregate | |
-> m (f Integer) |
Add multiple sorted sets and store the resulting sorted set in a new key (http://redis.io/commands/zunionstore). The Redis command ZUNIONSTORE
is split up into zunionstore
, zunionstoreWeights
.
Strings
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | value |
-> m (f Integer) |
Append a value to a key (http://redis.io/commands/append).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f Integer) |
Count set bits in a string (http://redis.io/commands/bitcount). The Redis command BITCOUNT
is split up into bitcount
, bitcountRange
.
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | start |
-> Integer | end |
-> m (f Integer) |
Count set bits in a string (http://redis.io/commands/bitcount). The Redis command BITCOUNT
is split up into bitcount
, bitcountRange
.
:: RedisCtx m f | |
=> ByteString | destkey |
-> [ByteString] | srckeys |
-> m (f Integer) |
Perform bitwise operations between strings (http://redis.io/commands/bitop). The Redis command BITOP
is split up into bitopAnd
, bitopOr
, bitopXor
, bitopNot
.
:: RedisCtx m f | |
=> ByteString | destkey |
-> [ByteString] | srckeys |
-> m (f Integer) |
Perform bitwise operations between strings (http://redis.io/commands/bitop). The Redis command BITOP
is split up into bitopAnd
, bitopOr
, bitopXor
, bitopNot
.
:: RedisCtx m f | |
=> ByteString | destkey |
-> [ByteString] | srckeys |
-> m (f Integer) |
Perform bitwise operations between strings (http://redis.io/commands/bitop). The Redis command BITOP
is split up into bitopAnd
, bitopOr
, bitopXor
, bitopNot
.
:: RedisCtx m f | |
=> ByteString | destkey |
-> ByteString | srckey |
-> m (f Integer) |
Perform bitwise operations between strings (http://redis.io/commands/bitop). The Redis command BITOP
is split up into bitopAnd
, bitopOr
, bitopXor
, bitopNot
.
:: RedisCtx m f | |
=> ByteString | key |
-> m (f Integer) |
Decrement the integer value of a key by one (http://redis.io/commands/decr).
Decrement the integer value of a key by the given number (http://redis.io/commands/decrby).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f (Maybe ByteString)) |
Get the value of a key (http://redis.io/commands/get).
Returns the bit value at offset in the string value stored at key (http://redis.io/commands/getbit).
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | start |
-> Integer | end |
-> m (f ByteString) |
Get a substring of the string stored at a key (http://redis.io/commands/getrange).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | value |
-> m (f (Maybe ByteString)) |
Set the string value of a key and return its old value (http://redis.io/commands/getset).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f Integer) |
Increment the integer value of a key by one (http://redis.io/commands/incr).
Increment the integer value of a key by the given amount (http://redis.io/commands/incrby).
:: RedisCtx m f | |
=> ByteString | key |
-> Double | increment |
-> m (f Double) |
Increment the float value of a key by the given amount (http://redis.io/commands/incrbyfloat).
:: RedisCtx m f | |
=> [ByteString] | key |
-> m (f [Maybe ByteString]) |
Get the values of all the given keys (http://redis.io/commands/mget).
:: RedisCtx m f | |
=> [(ByteString, ByteString)] | keyValue |
-> m (f Status) |
Set multiple keys to multiple values (http://redis.io/commands/mset).
:: RedisCtx m f | |
=> [(ByteString, ByteString)] | keyValue |
-> m (f Bool) |
Set multiple keys to multiple values, only if none of the keys exist (http://redis.io/commands/msetnx).
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | milliseconds |
-> ByteString | value |
-> m (f Status) |
Set the value and expiration in milliseconds of a key (http://redis.io/commands/psetex).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | value |
-> m (f Status) |
Set the string value of a key (http://redis.io/commands/set).
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | offset |
-> ByteString | value |
-> m (f Integer) |
Sets or clears the bit at offset in the string value stored at key (http://redis.io/commands/setbit).
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | seconds |
-> ByteString | value |
-> m (f Status) |
Set the value and expiration of a key (http://redis.io/commands/setex).
:: RedisCtx m f | |
=> ByteString | key |
-> ByteString | value |
-> m (f Bool) |
Set the value of a key, only if the key does not exist (http://redis.io/commands/setnx).
:: RedisCtx m f | |
=> ByteString | key |
-> Integer | offset |
-> ByteString | value |
-> m (f Integer) |
Overwrite part of a string at key starting at the specified offset (http://redis.io/commands/setrange).
:: RedisCtx m f | |
=> ByteString | key |
-> m (f Integer) |
Get the length of the value stored in a key (http://redis.io/commands/strlen).
Unimplemented Commands
These commands are not implemented, as of now. Library
users can implement these or other commands from
experimental Redis versions by using the sendRequest
function.
- MONITOR (http://redis.io/commands/monitor)
- SYNC (http://redis.io/commands/sync)
- SHUTDOWN (http://redis.io/commands/shutdown)
- DEBUG SEGFAULT (http://redis.io/commands/debug-segfault)
Transactions
:: [ByteString] | key |
-> Redis (Either Reply Status) |
Watch the given keys to determine execution of the MULTI/EXEC block (http://redis.io/commands/watch).
unwatch :: Redis (Either Reply Status)Source
Forget about all watched keys (http://redis.io/commands/unwatch).
multiExec :: RedisTx (Queued a) -> Redis (TxResult a)Source
Run commands inside a transaction. For documentation on the semantics of Redis transaction see http://redis.io/topics/transactions.
Inside the transaction block, command functions return their result wrapped
in a Queued
. The Queued
result is a proxy object for the actual
command's result, which will only be available after EXEC
ing the
transaction.
Example usage (note how Queued
's Applicative
instance is used to
combine the two individual results):
runRedis conn $ do
set "hello" "hello"
set "world" "world"
helloworld <- multiExec
$ do
hello <- get "hello"
world <- get "world"
return $ (,) <$> hello <*> world
liftIO (print helloworld)
Result of a multiExec
transaction.
Pub/Sub
:: RedisCtx m f | |
=> ByteString | channel |
-> ByteString | message |
-> m (f Integer) |
Post a message to a channel (http://redis.io/commands/publish).
Listens to published messages on subscribed channels and channels matching the subscribed patterns. For documentation on the semantics of Redis Pub/Sub see http://redis.io/topics/pubsub.
The given callback function is called for each received message.
Subscription changes are triggered by the returned PubSub
. To keep
subscriptions unchanged, the callback can return mempty
.
Example: Subscribe to the "news" channel indefinitely.
pubSub (subscribe ["news"]) $ \msg -> do putStrLn $ "Message from " ++ show (msgChannel msg) return mempty
Example: Receive a single message from the "chat" channel.
pubSub (subscribe ["chat"]) $ \msg -> do putStrLn $ "Message from " ++ show (msgChannel msg) return $ unsubscribe ["chat"]
Encapsulates subscription changes. Use subscribe
, unsubscribe
,
psubscribe
, punsubscribe
or mempty
to construct a value. Combine
values by using the Monoid
interface, i.e. mappend
and mconcat
.
:: [ByteString] | channel |
-> PubSub |
Listen for messages published to the given channels (http://redis.io/commands/subscribe).
:: [ByteString] | channel |
-> PubSub |
Stop listening for messages posted to the given channels (http://redis.io/commands/unsubscribe).
:: [ByteString] | pattern |
-> PubSub |
Listen for messages published to channels matching the given patterns (http://redis.io/commands/psubscribe).
:: [ByteString] | pattern |
-> PubSub |
Stop listening for messages posted to channels matching the given patterns (http://redis.io/commands/punsubscribe).
Low-Level Command API
sendRequest :: (RedisCtx m f, RedisResult a) => [ByteString] -> m (f a)Source
sendRequest
can be used to implement commands from experimental
versions of Redis. An example of how to implement a command is given
below.
-- |Redis DEBUG OBJECT command debugObject :: ByteString ->Redis
(EitherReply
ByteString) debugObject key =sendRequest
["DEBUG", "OBJECT", key]
Low-level representation of replies from the Redis server.
class RedisResult a whereSource
RedisResult Bool | |
RedisResult Double | |
RedisResult Integer | |
RedisResult ByteString | |
RedisResult Reply | |
RedisResult RedisType | |
RedisResult Status | |
RedisResult Slowlog | |
(RedisResult k, RedisResult v) => RedisResult [(k, v)] | |
RedisResult a => RedisResult [a] | |
RedisResult a => RedisResult (Maybe a) | |
(RedisResult a, RedisResult b) => RedisResult (a, b) |