hedis-0.14.2: Client library for the Redis datastore: supports full command set, pipelining.
Safe HaskellNone
LanguageHaskell2010

Database.Redis

Synopsis

How To Use This Module

Connect to a Redis server:

-- connects to localhost:6379
conn <- checkedConnect defaultConnectInfo

Connect to a Redis server using TLS:

-- connects to foobar.redis.cache.windows.net:6380
import Network.TLS
import Network.TLS.Extra.Cipher
import Data.X509.CertificateStore
import Data.Default.Class (def)
(Just certStore) <- readCertificateStore "azure-redis.crt"
let tlsParams = (defaultParamsClient "foobar.redis.cache.windows.net" "") { clientSupported = def { supportedCiphers = ciphersuite_strong }, clientShared = def { sharedCAStore = certStore } }
let redisConnInfo = defaultConnectInfo { connectHost = "foobar.redis.cache.windows.net", connectPort = PortNumber 6380, connectTLSParams = Just tlsParams, connectAuth = Just "Foobar!" }
conn <- checkedConnect redisConnInfo

Send commands to the server:

{-# LANGUAGE OverloadedStrings #-}
...
runRedis conn $ do
     set "hello" "hello"
     set "world" "world"
     hello <- get "hello"
     world <- get "world"
     liftIO $ print (hello,world)

disconnect all idle resources in the connection pool:

disconnect conn

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 a ByteString 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 context m. The ByteString return type in the example is specific to the echo 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 a Queued.

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)
 
Exercise
What are the types of expire inside a transaction and lindex outside of a transaction? The solutions are at the very bottom of this page.

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 is limited to the scope of runRedis call and it is guaranteed that every reply expected as a part of runRedis execution gets received after runRedis invocation.

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 return Left the Reply. 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 of runRedis.
Trying to connect to an unreachable server:
When trying to connect to a server that does not exist or can't be reached, the connection pool only starts the first connection when actually executing a call to the server. This can lead to discovering very late that the server is not available, for example when running a server that logs to Redis. To prevent this, run a ping command directly after connecting or use the checkedConnect function which encapsulates this behavior.
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

data Redis a Source #

Context for normal command execution, outside of transactions. Use runRedis to run actions of this type.

In this context, each result is wrapped in an Either to account for the possibility of Redis returning an Error reply.

Instances

Instances details
Monad Redis Source # 
Instance details

Defined in Database.Redis.Core.Internal

Methods

(>>=) :: Redis a -> (a -> Redis b) -> Redis b #

(>>) :: Redis a -> Redis b -> Redis b #

return :: a -> Redis a #

Functor Redis Source # 
Instance details

Defined in Database.Redis.Core.Internal

Methods

fmap :: (a -> b) -> Redis a -> Redis b #

(<$) :: a -> Redis b -> Redis a #

MonadFail Redis Source # 
Instance details

Defined in Database.Redis.Core.Internal

Methods

fail :: String -> Redis a #

Applicative Redis Source # 
Instance details

Defined in Database.Redis.Core.Internal

Methods

pure :: a -> Redis a #

(<*>) :: Redis (a -> b) -> Redis a -> Redis b #

liftA2 :: (a -> b -> c) -> Redis a -> Redis b -> Redis c #

(*>) :: Redis a -> Redis b -> Redis b #

(<*) :: Redis a -> Redis b -> Redis a #

MonadIO Redis Source # 
Instance details

Defined in Database.Redis.Core.Internal

Methods

liftIO :: IO a -> Redis a #

MonadRedis Redis Source # 
Instance details

Defined in Database.Redis.Core

Methods

liftRedis :: Redis a -> Redis a Source #

RedisCtx Redis (Either Reply) Source # 
Instance details

Defined in Database.Redis.Core

runRedis :: Connection -> Redis a -> IO a Source #

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.

unRedis :: Redis a -> ReaderT RedisEnv IO a Source #

Deconstruct Redis constructor.

unRedis and reRedis can be used to define instances for arbitrary typeclasses.

WARNING! These functions are considered internal and no guarantee is given at this point that they will not break in future.

reRedis :: ReaderT RedisEnv IO a -> Redis a Source #

Reconstruct Redis constructor.

class MonadRedis m => RedisCtx m f | m -> f where Source #

This class captures the following behaviour: In a context m, a command will return its result wrapped in a "container" of type f.

Please refer to the Command Type Signatures section of this page for more information.

Methods

returnDecode :: RedisResult a => Reply -> m (f a) Source #

Instances

Instances details
RedisCtx RedisTx Queued Source # 
Instance details

Defined in Database.Redis.Transactions

RedisCtx Redis (Either Reply) Source # 
Instance details

Defined in Database.Redis.Core

class Monad m => MonadRedis m where Source #

Methods

liftRedis :: Redis a -> m a Source #

Instances

Instances details
MonadRedis Redis Source # 
Instance details

Defined in Database.Redis.Core

Methods

liftRedis :: Redis a -> Redis a Source #

MonadRedis RedisTx Source # 
Instance details

Defined in Database.Redis.Transactions

Methods

liftRedis :: Redis a -> RedisTx a 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 Connection Source #

Constructs a Connection pool to a Redis server designated by the given ConnectInfo. The first connection is not actually established until the first call to the server.

checkedConnect :: ConnectInfo -> IO Connection Source #

Constructs a Connection pool to a Redis server designated by the given ConnectInfo, then tests if the server is actually there. Throws an exception if the connection to the Redis server can't be established.

disconnect :: Connection -> IO () Source #

Destroy all idle resources in the pool.

withConnect :: (MonadMask m, MonadIO m) => ConnectInfo -> (Connection -> m c) -> m c Source #

Memory bracket around connect and disconnect.

withCheckedConnect :: ConnectInfo -> (Connection -> IO c) -> IO c Source #

Memory bracket around checkedConnect and disconnect

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"}

Constructors

ConnInfo 

Fields

Instances

Instances details
Show ConnectInfo Source # 
Instance details

Defined in Database.Redis.Connection

defaultConnectInfo :: ConnectInfo Source #

Default information for connecting:

 connectHost           = "localhost"
 connectPort           = PortNumber 6379 -- Redis default port
 connectAuth           = Nothing         -- No password
 connectDatabase       = 0               -- SELECT database 0
 connectMaxConnections = 50              -- Up to 50 connections
 connectMaxIdleTime    = 30              -- Keep open for 30 seconds
 connectTimeout        = Nothing         -- Don't add timeout logic
 connectTLSParams      = Nothing         -- Do not use TLS

parseConnectInfo :: String -> Either String ConnectInfo Source #

Parse a ConnectInfo from a URL

Username is ignored, path is used to specify the database:

>>> parseConnectInfo "redis://username:password@host:42/2"
Right (ConnInfo {connectHost = "host", connectPort = PortNumber 42, connectAuth = Just "password", connectDatabase = 2, connectMaxConnections = 50, connectMaxIdleTime = 30s, connectTimeout = Nothing, connectTLSParams = Nothing})
>>> parseConnectInfo "redis://username:password@host:42/db"
Left "Invalid port: db"

The scheme is validated, to prevent mixing up configurations:

>>> parseConnectInfo "postgres://"
Left "Wrong scheme"

Beyond that, all values are optional. Omitted values are taken from defaultConnectInfo:

>>> parseConnectInfo "redis://"
Right (ConnInfo {connectHost = "localhost", connectPort = PortNumber 6379, connectAuth = Nothing, connectDatabase = 0, connectMaxConnections = 50, connectMaxIdleTime = 30s, connectTimeout = Nothing, connectTLSParams = Nothing})

connectCluster :: ConnectInfo -> IO Connection Source #

Constructs a ShardMap of connections to clustered nodes. The argument is a ConnectInfo for any node in the cluster

Some Redis commands are currently not supported in cluster mode - CONFIG, AUTH - SCAN - MOVE, SELECT - PUBLISH, SUBSCRIBE, PSUBSCRIBE, UNSUBSCRIBE, PUNSUBSCRIBE, RESET

data PortID Source #

Instances

Instances details
Eq PortID Source # 
Instance details

Defined in Database.Redis.ConnectionContext

Methods

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

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

Show PortID Source # 
Instance details

Defined in Database.Redis.ConnectionContext

Commands

Connection

auth Source #

Arguments

:: RedisCtx m f 
=> ByteString

password

-> m (f Status) 

Authenticate to the server (http://redis.io/commands/auth). Since Redis 1.0.0

echo Source #

Arguments

:: RedisCtx m f 
=> ByteString

message

-> m (f ByteString) 

Echo the given string (http://redis.io/commands/echo). Since Redis 1.0.0

ping :: RedisCtx m f => m (f Status) Source #

Ping the server (http://redis.io/commands/ping). Since Redis 1.0.0

quit :: RedisCtx m f => m (f Status) Source #

Close the connection (http://redis.io/commands/quit). Since Redis 1.0.0

select Source #

Arguments

:: RedisCtx m f 
=> Integer

index

-> m (f Status) 

Change the selected database for the current connection (http://redis.io/commands/select). Since Redis 1.0.0

Keys

del Source #

Arguments

:: RedisCtx m f 
=> [ByteString]

key

-> m (f Integer) 

Delete a key (http://redis.io/commands/del). Since Redis 1.0.0

dump Source #

Arguments

:: 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). Since Redis 2.6.0

exists Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f Bool) 

Determine if a key exists (http://redis.io/commands/exists). Since Redis 1.0.0

expire Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Integer

seconds

-> m (f Bool) 

Set a key's time to live in seconds (http://redis.io/commands/expire). Since Redis 1.0.0

expireat Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Integer

timestamp

-> m (f Bool) 

Set the expiration for a key as a UNIX timestamp (http://redis.io/commands/expireat). Since Redis 1.2.0

keys Source #

Arguments

:: RedisCtx m f 
=> ByteString

pattern

-> m (f [ByteString]) 

Find all keys matching the given pattern (http://redis.io/commands/keys). Since Redis 1.0.0

data MigrateOpts Source #

Options for the migrate command.

Constructors

MigrateOpts 

Instances

Instances details
Eq MigrateOpts Source # 
Instance details

Defined in Database.Redis.ManualCommands

Show MigrateOpts Source # 
Instance details

Defined in Database.Redis.ManualCommands

defaultMigrateOpts :: MigrateOpts Source #

Redis default MigrateOpts. Equivalent to omitting all optional parameters.

MigrateOpts
    { migrateCopy    = False -- remove the key from the local instance
    , migrateReplace = False -- don't replace existing key on the remote instance
    }

migrate Source #

Arguments

:: 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). The Redis command MIGRATE is split up into migrate, migrateMultiple. Since Redis 2.6.0

migrateMultiple Source #

Arguments

:: RedisCtx m f 
=> ByteString

host

-> ByteString

port

-> Integer

destinationDb

-> Integer

timeout

-> MigrateOpts 
-> [ByteString]

keys

-> m (f Status) 

Atomically transfer a key from a Redis instance to another one (http://redis.io/commands/migrate). The Redis command MIGRATE is split up into migrate, migrateMultiple. Since Redis 2.6.0

move Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Integer

db

-> m (f Bool) 

Move a key to another database (http://redis.io/commands/move). Since Redis 1.0.0

objectRefcount Source #

Arguments

:: 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. Since Redis 2.2.3

objectEncoding Source #

Arguments

:: 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. Since Redis 2.2.3

objectIdletime Source #

Arguments

:: 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. Since Redis 2.2.3

persist Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f Bool) 

Remove the expiration from a key (http://redis.io/commands/persist). Since Redis 2.2.0

pexpire Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Integer

milliseconds

-> m (f Bool) 

Set a key's time to live in milliseconds (http://redis.io/commands/pexpire). Since Redis 2.6.0

pexpireat Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Integer

millisecondsTimestamp

-> m (f Bool) 

Set the expiration for a key as a UNIX timestamp specified in milliseconds (http://redis.io/commands/pexpireat). Since Redis 2.6.0

pttl Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f Integer) 

Get the time to live for a key in milliseconds (http://redis.io/commands/pttl). Since Redis 2.6.0

Return a random key from the keyspace (http://redis.io/commands/randomkey). Since Redis 1.0.0

rename Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> ByteString

newkey

-> m (f Status) 

Rename a key (http://redis.io/commands/rename). Since Redis 1.0.0

renamenx Source #

Arguments

:: 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). Since Redis 1.0.0

restore Source #

Arguments

:: 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). The Redis command RESTORE is split up into restore, restoreReplace. Since Redis 2.6.0

restoreReplace Source #

Arguments

:: 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). The Redis command RESTORE is split up into restore, restoreReplace. Since Redis 2.6.0

data Cursor Source #

Instances

Instances details
Eq Cursor Source # 
Instance details

Defined in Database.Redis.ManualCommands

Methods

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

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

Show Cursor Source # 
Instance details

Defined in Database.Redis.ManualCommands

RedisResult Cursor Source # 
Instance details

Defined in Database.Redis.ManualCommands

data ScanOpts Source #

Instances

Instances details
Eq ScanOpts Source # 
Instance details

Defined in Database.Redis.ManualCommands

Show ScanOpts Source # 
Instance details

Defined in Database.Redis.ManualCommands

defaultScanOpts :: ScanOpts Source #

Redis default ScanOpts. Equivalent to omitting all optional parameters.

ScanOpts
    { scanMatch = Nothing -- don't match any pattern
    , scanCount = Nothing -- don't set any requirements on number elements returned (works like value COUNT 10)
    }

scan Source #

Arguments

:: RedisCtx m f 
=> Cursor 
-> m (f (Cursor, [ByteString]))

next cursor and values

Incrementally iterate the keys space (http://redis.io/commands/scan). The Redis command SCAN is split up into scan, scanOpts. Since Redis 2.8.0

scanOpts Source #

Arguments

:: RedisCtx m f 
=> Cursor 
-> ScanOpts 
-> m (f (Cursor, [ByteString]))

next cursor and values

Incrementally iterate the keys space (http://redis.io/commands/scan). The Redis command SCAN is split up into scan, scanOpts. Since Redis 2.8.0

data SortOpts Source #

Options for the sort command.

Instances

Instances details
Eq SortOpts Source # 
Instance details

Defined in Database.Redis.ManualCommands

Show SortOpts Source # 
Instance details

Defined in Database.Redis.ManualCommands

defaultSortOpts :: SortOpts Source #

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
    }

data SortOrder Source #

Constructors

Asc 
Desc 

Instances

Instances details
Eq SortOrder Source # 
Instance details

Defined in Database.Redis.ManualCommands

Show SortOrder Source # 
Instance details

Defined in Database.Redis.ManualCommands

sort Source #

Arguments

:: 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. Since Redis 1.0.0

sortStore Source #

Arguments

:: 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. Since Redis 1.0.0

ttl Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f Integer) 

Get the time to live for a key (http://redis.io/commands/ttl). Since Redis 1.0.0

data RedisType Source #

Constructors

None 
String 
Hash 
List 
Set 
ZSet 

Instances

Instances details
Eq RedisType Source # 
Instance details

Defined in Database.Redis.Types

Show RedisType Source # 
Instance details

Defined in Database.Redis.Types

RedisResult RedisType Source # 
Instance details

Defined in Database.Redis.Types

getType Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f RedisType) 

Determine the type stored at key (http://redis.io/commands/type). Since Redis 1.0.0

wait Source #

Arguments

:: RedisCtx m f 
=> Integer

numslaves

-> Integer

timeout

-> m (f Integer) 

Wait for the synchronous replication of all the write commands sent in the context of the current connection (http://redis.io/commands/wait). Since Redis 3.0.0

Hashes

hdel Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> [ByteString]

field

-> m (f Integer) 

Delete one or more hash fields (http://redis.io/commands/hdel). Since Redis 2.0.0

hexists Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> ByteString

field

-> m (f Bool) 

Determine if a hash field exists (http://redis.io/commands/hexists). Since Redis 2.0.0

hget Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> ByteString

field

-> m (f (Maybe ByteString)) 

Get the value of a hash field (http://redis.io/commands/hget). Since Redis 2.0.0

hgetall Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f [(ByteString, ByteString)]) 

Get all the fields and values in a hash (http://redis.io/commands/hgetall). Since Redis 2.0.0

hincrby Source #

Arguments

:: 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). Since Redis 2.0.0

hincrbyfloat Source #

Arguments

:: 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). Since Redis 2.6.0

hkeys Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f [ByteString]) 

Get all the fields in a hash (http://redis.io/commands/hkeys). Since Redis 2.0.0

hlen Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f Integer) 

Get the number of fields in a hash (http://redis.io/commands/hlen). Since Redis 2.0.0

hmget Source #

Arguments

:: 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). Since Redis 2.0.0

hmset Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> [(ByteString, ByteString)]

fieldValue

-> m (f Status) 

Set multiple hash fields to multiple values (http://redis.io/commands/hmset). Since Redis 2.0.0

hscan Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Cursor 
-> m (f (Cursor, [(ByteString, ByteString)]))

next cursor and values

Incrementally iterate hash fields and associated values (http://redis.io/commands/hscan). The Redis command HSCAN is split up into hscan, hscanOpts. Since Redis 2.8.0

hscanOpts Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Cursor 
-> ScanOpts 
-> m (f (Cursor, [(ByteString, ByteString)]))

next cursor and values

Incrementally iterate hash fields and associated values (http://redis.io/commands/hscan). The Redis command HSCAN is split up into hscan, hscanOpts. Since Redis 2.8.0

hset Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> ByteString

field

-> ByteString

value

-> m (f Integer) 

Set the string value of a hash field (http://redis.io/commands/hset). Since Redis 2.0.0

hsetnx Source #

Arguments

:: 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). Since Redis 2.0.0

hstrlen Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> ByteString

field

-> m (f Integer) 

Get the length of the value of a hash field (http://redis.io/commands/hstrlen). Since Redis 3.2.0

hvals Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f [ByteString]) 

Get all the values in a hash (http://redis.io/commands/hvals). Since Redis 2.0.0

HyperLogLogs

pfadd Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> [ByteString]

value

-> m (f Integer) 

Adds all the elements arguments to the HyperLogLog data structure stored at the variable name specified as first argument (http://redis.io/commands/pfadd). Since Redis 2.8.9

pfcount Source #

Arguments

:: RedisCtx m f 
=> [ByteString]

key

-> m (f Integer) 

Return the approximated cardinality of the set(s) observed by the HyperLogLog at key(s) (http://redis.io/commands/pfcount). Since Redis 2.8.9

pfmerge Source #

Arguments

:: RedisCtx m f 
=> ByteString

destkey

-> [ByteString]

sourcekey

-> m (f ByteString) 

Merge N different HyperLogLogs into a single one (http://redis.io/commands/pfmerge). Since Redis 2.8.9

Lists

blpop Source #

Arguments

:: 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). Since Redis 2.0.0

brpop Source #

Arguments

:: 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). Since Redis 2.0.0

brpoplpush Source #

Arguments

:: 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). Since Redis 2.2.0

lindex Source #

Arguments

:: 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). Since Redis 1.0.0

linsertBefore Source #

Arguments

:: 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. Since Redis 2.2.0

linsertAfter Source #

Arguments

:: 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. Since Redis 2.2.0

llen Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f Integer) 

Get the length of a list (http://redis.io/commands/llen). Since Redis 1.0.0

lpop Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f (Maybe ByteString)) 

Remove and get the first element in a list (http://redis.io/commands/lpop). Since Redis 1.0.0

lpush Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> [ByteString]

value

-> m (f Integer) 

Prepend one or multiple values to a list (http://redis.io/commands/lpush). Since Redis 1.0.0

lpushx Source #

Arguments

:: 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). Since Redis 2.2.0

lrange Source #

Arguments

:: 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). Since Redis 1.0.0

lrem Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Integer

count

-> ByteString

value

-> m (f Integer) 

Remove elements from a list (http://redis.io/commands/lrem). Since Redis 1.0.0

lset Source #

Arguments

:: 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). Since Redis 1.0.0

ltrim Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Integer

start

-> Integer

stop

-> m (f Status) 

Trim a list to the specified range (http://redis.io/commands/ltrim). Since Redis 1.0.0

rpop Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f (Maybe ByteString)) 

Remove and get the last element in a list (http://redis.io/commands/rpop). Since Redis 1.0.0

rpoplpush Source #

Arguments

:: RedisCtx m f 
=> ByteString

source

-> ByteString

destination

-> m (f (Maybe ByteString)) 

Remove the last element in a list, prepend it to another list and return it (http://redis.io/commands/rpoplpush). Since Redis 1.2.0

rpush Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> [ByteString]

value

-> m (f Integer) 

Append one or multiple values to a list (http://redis.io/commands/rpush). Since Redis 1.0.0

rpushx Source #

Arguments

:: 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). Since Redis 2.2.0

Scripting

eval Source #

Arguments

:: (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). Since Redis 2.6.0

evalsha Source #

Arguments

:: (RedisCtx m f, RedisResult a) 
=> ByteString

base16-encoded sha1 hash of the script

-> [ByteString]

keys

-> [ByteString]

args

-> m (f a) 

Works like eval, but sends the SHA1 hash of the script instead of the script itself. Fails if the server does not recognise the hash, in which case, eval should be used instead.

Execute a Lua script server side (http://redis.io/commands/evalsha). Since Redis 2.6.0

data DebugMode Source #

Instances

Instances details
Eq DebugMode Source # 
Instance details

Defined in Database.Redis.ManualCommands

Show DebugMode Source # 
Instance details

Defined in Database.Redis.ManualCommands

Set the debug mode for executed scripts (http://redis.io/commands/script-debug). Since Redis 3.2.0

scriptExists Source #

Arguments

:: RedisCtx m f 
=> [ByteString]

script

-> m (f [Bool]) 

Check existence of scripts in the script cache (http://redis.io/commands/script-exists). Since Redis 2.6.0

Remove all the scripts from the script cache (http://redis.io/commands/script-flush). Since Redis 2.6.0

Kill the script currently in execution (http://redis.io/commands/script-kill). Since Redis 2.6.0

scriptLoad Source #

Arguments

:: RedisCtx m f 
=> ByteString

script

-> m (f ByteString) 

Load the specified Lua script into the script cache (http://redis.io/commands/script-load). Since Redis 2.6.0

Server

Asynchronously rewrite the append-only file (http://redis.io/commands/bgrewriteaof). Since Redis 1.0.0

bgsave :: RedisCtx m f => m (f Status) Source #

Asynchronously save the dataset to disk (http://redis.io/commands/bgsave). Since Redis 1.0.0

Get the current connection name (http://redis.io/commands/client-getname). Since Redis 2.6.9

Get the list of client connections (http://redis.io/commands/client-list). Since Redis 2.4.0

clientPause Source #

Arguments

:: RedisCtx m f 
=> Integer

timeout

-> m (f Status) 

Stop processing commands from clients for some time (http://redis.io/commands/client-pause). Since Redis 2.9.50

data ReplyMode Source #

Instances

Instances details
Eq ReplyMode Source # 
Instance details

Defined in Database.Redis.ManualCommands

Show ReplyMode Source # 
Instance details

Defined in Database.Redis.ManualCommands

Instruct the server whether to reply to commands (http://redis.io/commands/client-reply). Since Redis 3.2

clientSetname Source #

Arguments

:: RedisCtx m f 
=> ByteString

connectionName

-> m (f ByteString) 

Set the current connection name (http://redis.io/commands/client-setname). Since Redis 2.6.9

Get total number of Redis commands (http://redis.io/commands/command-count). Since Redis 2.8.13

commandInfo Source #

Arguments

:: RedisCtx m f 
=> [ByteString]

commandName

-> m (f [ByteString]) 

Get array of specific Redis command details (http://redis.io/commands/command-info). Since Redis 2.8.13

configGet Source #

Arguments

:: RedisCtx m f 
=> ByteString

parameter

-> m (f [(ByteString, ByteString)]) 

Get the value of a configuration parameter (http://redis.io/commands/config-get). Since Redis 2.0.0

Reset the stats returned by INFO (http://redis.io/commands/config-resetstat). Since Redis 2.0.0

Rewrite the configuration file with the in memory configuration (http://redis.io/commands/config-rewrite). Since Redis 2.8.0

configSet Source #

Arguments

:: RedisCtx m f 
=> ByteString

parameter

-> ByteString

value

-> m (f Status) 

Set a configuration parameter to the given value (http://redis.io/commands/config-set). Since Redis 2.0.0

dbsize :: RedisCtx m f => m (f Integer) Source #

Return the number of keys in the selected database (http://redis.io/commands/dbsize). Since Redis 1.0.0

debugObject Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f ByteString) 

Get debugging information about a key (http://redis.io/commands/debug-object). Since Redis 1.0.0

flushall :: RedisCtx m f => m (f Status) Source #

Remove all keys from all databases (http://redis.io/commands/flushall). Since Redis 1.0.0

flushdb :: RedisCtx m f => m (f Status) Source #

Remove all keys from the current database (http://redis.io/commands/flushdb). Since Redis 1.0.0

info :: RedisCtx m f => m (f ByteString) Source #

Get information and statistics about the server (http://redis.io/commands/info). The Redis command INFO is split up into info, infoSection. Since Redis 1.0.0

infoSection Source #

Arguments

:: RedisCtx m f 
=> ByteString

section

-> m (f ByteString) 

Get information and statistics about the server (http://redis.io/commands/info). The Redis command INFO is split up into info, infoSection. Since Redis 1.0.0

lastsave :: RedisCtx m f => m (f Integer) Source #

Get the UNIX time stamp of the last successful save to disk (http://redis.io/commands/lastsave). Since Redis 1.0.0

save :: RedisCtx m f => m (f Status) Source #

Synchronously save the dataset to disk (http://redis.io/commands/save). Since Redis 1.0.0

slaveof Source #

Arguments

:: 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). Since Redis 1.0.0

data Slowlog Source #

A single entry from the slowlog.

Constructors

Slowlog 

Fields

Instances

Instances details
Eq Slowlog Source # 
Instance details

Defined in Database.Redis.ManualCommands

Methods

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

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

Show Slowlog Source # 
Instance details

Defined in Database.Redis.ManualCommands

RedisResult Slowlog Source # 
Instance details

Defined in Database.Redis.ManualCommands

slowlogGet Source #

Arguments

:: RedisCtx m f 
=> Integer

cnt

-> m (f [Slowlog]) 

Manages the Redis slow queries log (http://redis.io/commands/slowlog). The Redis command SLOWLOG is split up into slowlogGet, slowlogLen, slowlogReset. Since Redis 2.2.12

Manages the Redis slow queries log (http://redis.io/commands/slowlog). The Redis command SLOWLOG is split up into slowlogGet, slowlogLen, slowlogReset. Since Redis 2.2.12

Manages the Redis slow queries log (http://redis.io/commands/slowlog). The Redis command SLOWLOG is split up into slowlogGet, slowlogLen, slowlogReset. Since Redis 2.2.12

time :: RedisCtx m f => m (f (Integer, Integer)) Source #

Return the current server time (http://redis.io/commands/time). Since Redis 2.6.0

Sets

sadd Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> [ByteString]

member

-> m (f Integer) 

Add one or more members to a set (http://redis.io/commands/sadd). Since Redis 1.0.0

scard Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f Integer) 

Get the number of members in a set (http://redis.io/commands/scard). Since Redis 1.0.0

sdiff Source #

Arguments

:: RedisCtx m f 
=> [ByteString]

key

-> m (f [ByteString]) 

Subtract multiple sets (http://redis.io/commands/sdiff). Since Redis 1.0.0

sdiffstore Source #

Arguments

:: 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). Since Redis 1.0.0

sinter Source #

Arguments

:: RedisCtx m f 
=> [ByteString]

key

-> m (f [ByteString]) 

Intersect multiple sets (http://redis.io/commands/sinter). Since Redis 1.0.0

sinterstore Source #

Arguments

:: 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). Since Redis 1.0.0

sismember Source #

Arguments

:: 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). Since Redis 1.0.0

smembers Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f [ByteString]) 

Get all the members in a set (http://redis.io/commands/smembers). Since Redis 1.0.0

smove Source #

Arguments

:: 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). Since Redis 1.0.0

spop Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f (Maybe ByteString)) 

Remove and return one or multiple random members from a set (http://redis.io/commands/spop). The Redis command SPOP is split up into spop, spopN. Since Redis 1.0.0

spopN Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Integer

count

-> m (f [ByteString]) 

Remove and return one or multiple random members from a set (http://redis.io/commands/spop). The Redis command SPOP is split up into spop, spopN. Since Redis 1.0.0

srandmember Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f (Maybe ByteString)) 

Get one or multiple random members from a set (http://redis.io/commands/srandmember). The Redis command SRANDMEMBER is split up into srandmember, srandmemberN. Since Redis 1.0.0

srandmemberN Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Integer

count

-> m (f [ByteString]) 

Get one or multiple random members from a set (http://redis.io/commands/srandmember). The Redis command SRANDMEMBER is split up into srandmember, srandmemberN. Since Redis 1.0.0

srem Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> [ByteString]

member

-> m (f Integer) 

Remove one or more members from a set (http://redis.io/commands/srem). Since Redis 1.0.0

sscan Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Cursor 
-> m (f (Cursor, [ByteString]))

next cursor and values

Incrementally iterate Set elements (http://redis.io/commands/sscan). The Redis command SSCAN is split up into sscan, sscanOpts. Since Redis 2.8.0

sscanOpts Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Cursor 
-> ScanOpts 
-> m (f (Cursor, [ByteString]))

next cursor and values

Incrementally iterate Set elements (http://redis.io/commands/sscan). The Redis command SSCAN is split up into sscan, sscanOpts. Since Redis 2.8.0

sunion Source #

Arguments

:: RedisCtx m f 
=> [ByteString]

key

-> m (f [ByteString]) 

Add multiple sets (http://redis.io/commands/sunion). Since Redis 1.0.0

sunionstore Source #

Arguments

:: 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). Since Redis 1.0.0

Sorted Sets

data ZaddOpts Source #

Instances

Instances details
Eq ZaddOpts Source # 
Instance details

Defined in Database.Redis.ManualCommands

Show ZaddOpts Source # 
Instance details

Defined in Database.Redis.ManualCommands

defaultZaddOpts :: ZaddOpts Source #

Redis default ZaddOpts. Equivalent to omitting all optional parameters.

ZaddOpts
    { zaddCondition = Nothing -- omit NX and XX options
    , zaddChange    = False   -- don't modify the return value from the number of new elements added, to the total number of elements changed
    , zaddIncrement = False   -- don't add like ZINCRBY
    }

zadd Source #

Arguments

:: 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). The Redis command ZADD is split up into zadd, zaddOpts. Since Redis 1.2.0

zaddOpts Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> [(Double, ByteString)]

scoreMember

-> ZaddOpts

options

-> 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). The Redis command ZADD is split up into zadd, zaddOpts. Since Redis 1.2.0

zcard Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f Integer) 

Get the number of members in a sorted set (http://redis.io/commands/zcard). Since Redis 1.2.0

zcount Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Double

min

-> Double

max

-> m (f Integer) 

Count the members in a sorted set with scores within the given values (http://redis.io/commands/zcount). Since Redis 2.0.0

zincrby Source #

Arguments

:: 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). Since Redis 1.2.0

data Aggregate Source #

Constructors

Sum 
Min 
Max 

Instances

Instances details
Eq Aggregate Source # 
Instance details

Defined in Database.Redis.ManualCommands

Show Aggregate Source # 
Instance details

Defined in Database.Redis.ManualCommands

zinterstore Source #

Arguments

:: 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. Since Redis 2.0.0

zinterstoreWeights Source #

Arguments

:: 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. Since Redis 2.0.0

zlexcount Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> ByteString

min

-> ByteString

max

-> m (f Integer) 

Count the number of members in a sorted set between a given lexicographical range (http://redis.io/commands/zlexcount). Since Redis 2.8.9

zrange Source #

Arguments

:: 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. Since Redis 1.2.0

zrangeWithscores Source #

Arguments

:: 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. Since Redis 1.2.0

data RangeLex a Source #

Constructors

Incl a 
Excl a 
Minr 
Maxr 

zrangebylexLimit Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> RangeLex ByteString

min

-> RangeLex ByteString

max

-> Integer

offset

-> Integer

count

-> m (f [ByteString]) 

Return a range of members in a sorted set, by lexicographical range (http://redis.io/commands/zrangebylex). Since Redis 2.8.9

zrangebyscore Source #

Arguments

:: 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. Since Redis 1.0.5

zrangebyscoreWithscores Source #

Arguments

:: 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. Since Redis 1.0.5

zrangebyscoreLimit Source #

Arguments

:: 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. Since Redis 1.0.5

zrangebyscoreWithscoresLimit Source #

Arguments

:: 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. Since Redis 1.0.5

zrank Source #

Arguments

:: 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). Since Redis 2.0.0

zrem Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> [ByteString]

member

-> m (f Integer) 

Remove one or more members from a sorted set (http://redis.io/commands/zrem). Since Redis 1.2.0

zremrangebylex Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> ByteString

min

-> ByteString

max

-> m (f Integer) 

Remove all members in a sorted set between the given lexicographical range (http://redis.io/commands/zremrangebylex). Since Redis 2.8.9

zremrangebyrank Source #

Arguments

:: 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). Since Redis 2.0.0

zremrangebyscore Source #

Arguments

:: 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). Since Redis 1.2.0

zrevrange Source #

Arguments

:: 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. Since Redis 1.2.0

zrevrangeWithscores Source #

Arguments

:: 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. Since Redis 1.2.0

zrevrangebyscore Source #

Arguments

:: 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. Since Redis 2.2.0

zrevrangebyscoreWithscores Source #

Arguments

:: 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. Since Redis 2.2.0

zrevrangebyscoreLimit Source #

Arguments

:: 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. Since Redis 2.2.0

zrevrangebyscoreWithscoresLimit Source #

Arguments

:: 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. Since Redis 2.2.0

zrevrank Source #

Arguments

:: 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). Since Redis 2.0.0

zscan Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Cursor 
-> m (f (Cursor, [(ByteString, Double)]))

next cursor and values

Incrementally iterate sorted sets elements and associated scores (http://redis.io/commands/zscan). The Redis command ZSCAN is split up into zscan, zscanOpts. Since Redis 2.8.0

zscanOpts Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Cursor 
-> ScanOpts 
-> m (f (Cursor, [(ByteString, Double)]))

next cursor and values

Incrementally iterate sorted sets elements and associated scores (http://redis.io/commands/zscan). The Redis command ZSCAN is split up into zscan, zscanOpts. Since Redis 2.8.0

zscore Source #

Arguments

:: 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). Since Redis 1.2.0

zunionstore Source #

Arguments

:: 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. Since Redis 2.0.0

zunionstoreWeights Source #

Arguments

:: 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. Since Redis 2.0.0

Strings

append Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> ByteString

value

-> m (f Integer) 

Append a value to a key (http://redis.io/commands/append). Since Redis 2.0.0

bitcount Source #

Arguments

:: 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. Since Redis 2.6.0

bitcountRange Source #

Arguments

:: 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. Since Redis 2.6.0

bitopAnd Source #

Arguments

:: 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. Since Redis 2.6.0

bitopOr Source #

Arguments

:: 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. Since Redis 2.6.0

bitopXor Source #

Arguments

:: 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. Since Redis 2.6.0

bitopNot Source #

Arguments

:: 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. Since Redis 2.6.0

bitpos Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Integer

bit

-> Integer

start

-> Integer

end

-> m (f Integer) 

Find first bit set or clear in a string (http://redis.io/commands/bitpos). Since Redis 2.8.7

decr Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f Integer) 

Decrement the integer value of a key by one (http://redis.io/commands/decr). Since Redis 1.0.0

decrby Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Integer

decrement

-> m (f Integer) 

Decrement the integer value of a key by the given number (http://redis.io/commands/decrby). Since Redis 1.0.0

get Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f (Maybe ByteString)) 

Get the value of a key (http://redis.io/commands/get). Since Redis 1.0.0

getbit Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Integer

offset

-> m (f Integer) 

Returns the bit value at offset in the string value stored at key (http://redis.io/commands/getbit). Since Redis 2.2.0

getrange Source #

Arguments

:: 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). Since Redis 2.4.0

getset Source #

Arguments

:: 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). Since Redis 1.0.0

incr Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f Integer) 

Increment the integer value of a key by one (http://redis.io/commands/incr). Since Redis 1.0.0

incrby Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> Integer

increment

-> m (f Integer) 

Increment the integer value of a key by the given amount (http://redis.io/commands/incrby). Since Redis 1.0.0

incrbyfloat Source #

Arguments

:: 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). Since Redis 2.6.0

mget Source #

Arguments

:: RedisCtx m f 
=> [ByteString]

key

-> m (f [Maybe ByteString]) 

Get the values of all the given keys (http://redis.io/commands/mget). Since Redis 1.0.0

mset Source #

Arguments

:: RedisCtx m f 
=> [(ByteString, ByteString)]

keyValue

-> m (f Status) 

Set multiple keys to multiple values (http://redis.io/commands/mset). Since Redis 1.0.1

msetnx Source #

Arguments

:: 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). Since Redis 1.0.1

psetex Source #

Arguments

:: 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). Since Redis 2.6.0

data Condition Source #

Constructors

Nx 
Xx 

Instances

Instances details
Eq Condition Source # 
Instance details

Defined in Database.Redis.ManualCommands

Show Condition Source # 
Instance details

Defined in Database.Redis.ManualCommands

data SetOpts Source #

Instances

Instances details
Eq SetOpts Source # 
Instance details

Defined in Database.Redis.ManualCommands

Methods

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

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

Show SetOpts Source # 
Instance details

Defined in Database.Redis.ManualCommands

set Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> ByteString

value

-> m (f Status) 

Set the string value of a key (http://redis.io/commands/set). The Redis command SET is split up into set, setOpts. Since Redis 1.0.0

setOpts Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> ByteString

value

-> SetOpts 
-> m (f Status) 

Set the string value of a key (http://redis.io/commands/set). The Redis command SET is split up into set, setOpts. Since Redis 1.0.0

setbit Source #

Arguments

:: 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). Since Redis 2.2.0

setex Source #

Arguments

:: 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). Since Redis 2.0.0

setnx Source #

Arguments

:: 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). Since Redis 1.0.0

setrange Source #

Arguments

:: 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). Since Redis 2.2.0

strlen Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> m (f Integer) 

Get the length of the value stored in a key (http://redis.io/commands/strlen). Since Redis 2.2.0

Streams

data XReadOpts Source #

Constructors

XReadOpts 

Instances

Instances details
Eq XReadOpts Source # 
Instance details

Defined in Database.Redis.ManualCommands

Show XReadOpts Source # 
Instance details

Defined in Database.Redis.ManualCommands

defaultXreadOpts :: XReadOpts Source #

Redis default XReadOpts. Equivalent to omitting all optional parameters.

XReadOpts
    { block = Nothing -- Don't block waiting for more records
    , recordCount    = Nothing   -- no record count
    }

xadd Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> ByteString

id

-> [(ByteString, ByteString)]

(field, value)

-> m (f ByteString) 

Add a value to a stream (https://redis.io/commands/xadd). Since Redis 5.0.0

xaddOpts Source #

Arguments

:: RedisCtx m f 
=> ByteString

key

-> ByteString

id

-> [(ByteString, ByteString)]

(field, value)

-> TrimOpts 
-> m (f ByteString) 

Add a value to a stream (https://redis.io/commands/xadd). The Redis command XADD is split up into xadd, xaddOpts. Since Redis 5.0.0

xread Source #

Arguments

:: RedisCtx m f 
=> [(ByteString, ByteString)]

(stream, id) pairs

-> m (f (Maybe [XReadResponse])) 

Read values from a stream (https://redis.io/commands/xread). The Redis command XREAD is split up into xread, xreadOpts. Since Redis 5.0.0

xreadOpts Source #

Arguments

:: RedisCtx m f 
=> [(ByteString, ByteString)]

(stream, id) pairs

-> XReadOpts

Options

-> m (f (Maybe [XReadResponse])) 

Read values from a stream (https://redis.io/commands/xread). The Redis command XREAD is split up into xread, xreadOpts. Since Redis 5.0.0

xreadGroup Source #

Arguments

:: RedisCtx m f 
=> ByteString

group name

-> ByteString

consumer name

-> [(ByteString, ByteString)]

(stream, id) pairs

-> m (f (Maybe [XReadResponse])) 

Read values from a stream as part of a consumer group (https:/redis.iocommands/xreadgroup). The redis command XREADGROUP is split up into xreadGroup and xreadGroupOpts. Since Redis 5.0.0

xreadGroupOpts Source #

Arguments

:: RedisCtx m f 
=> ByteString

group name

-> ByteString

consumer name

-> [(ByteString, ByteString)]

(stream, id) pairs

-> XReadOpts

Options

-> m (f (Maybe [XReadResponse])) 

Read values from a stream as part of a consumer group (https:/redis.iocommands/xreadgroup). The redis command XREADGROUP is split up into xreadGroup and xreadGroupOpts. Since Redis 5.0.0

xack Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> ByteString

group name

-> [ByteString]

message IDs

-> m (f Integer) 

Acknowledge receipt of a message as part of a consumer group. Since Redis 5.0.0

xgroupCreate Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> ByteString

group name

-> ByteString

start ID

-> m (f Status) 

Create a consumer group. The redis command XGROUP is split up into xgroupCreate, xgroupSetId, xgroupDestroy, and xgroupDelConsumer. Since Redis 5.0.0

xgroupSetId Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> ByteString

group

-> ByteString

id

-> m (f Status) 

Set the id for a consumer group. The redis command XGROUP is split up into xgroupCreate, xgroupSetId, xgroupDestroy, and xgroupDelConsumer. Since Redis 5.0.0

xgroupDestroy Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> ByteString

group

-> m (f Bool) 

Destroy a consumer group. The redis command XGROUP is split up into xgroupCreate, xgroupSetId, xgroupDestroy, and xgroupDelConsumer. Since Redis 5.0.0

xgroupDelConsumer Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> ByteString

group

-> ByteString

consumer

-> m (f Integer) 

Delete a consumer. The redis command XGROUP is split up into xgroupCreate, xgroupSetId, xgroupDestroy, and xgroupDelConsumer. Since Redis 5.0.0

xrange Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> ByteString

start

-> ByteString

end

-> Maybe Integer

COUNT

-> m (f [StreamsRecord]) 

Read values from a stream within a range (https:/redis.iocommands/xrange). Since Redis 5.0.0

xrevRange Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> ByteString

end

-> ByteString

start

-> Maybe Integer

COUNT

-> m (f [StreamsRecord]) 

Read values from a stream within a range in reverse order (https:/redis.iocommands/xrevrange). Since Redis 5.0.0

xlen Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> m (f Integer) 

Get the number of entries in a stream (https:/redis.iocommands/xlen). Since Redis 5.0.0

xpendingSummary Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> ByteString

group

-> Maybe ByteString

consumer

-> m (f XPendingSummaryResponse) 

Get information about pending messages (https:/redis.iocommands/xpending). The Redis XPENDING command is split into xpendingSummary and xpendingDetail. Since Redis 5.0.0

xpendingDetail Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> ByteString

group

-> ByteString

startId

-> ByteString

endId

-> Integer

count

-> Maybe ByteString

consumer

-> m (f [XPendingDetailRecord]) 

Get detailed information about pending messages (https:/redis.iocommands/xpending). The Redis XPENDING command is split into xpendingSummary and xpendingDetail. Since Redis 5.0.0

xclaim Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> ByteString

group

-> ByteString

consumer

-> Integer

min idle time

-> XClaimOpts

optional arguments

-> [ByteString]

message IDs

-> m (f [StreamsRecord]) 

Change ownership of some messages to the given consumer, returning the updated messages. The Redis XCLAIM command is split into xclaim and xclaimJustIds. Since Redis 5.0.0

xclaimJustIds Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> ByteString

group

-> ByteString

consumer

-> Integer

min idle time

-> XClaimOpts

optional arguments

-> [ByteString]

message IDs

-> m (f [ByteString]) 

Change ownership of some messages to the given consumer, returning only the changed message IDs. The Redis XCLAIM command is split into xclaim and xclaimJustIds. Since Redis 5.0.0

xinfoConsumers Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> ByteString

group

-> m (f [XInfoConsumersResponse]) 

Get info about consumers in a group. The Redis command XINFO is split into xinfoConsumers, xinfoGroups, and xinfoStream. Since Redis 5.0.0

xinfoGroups Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> m (f [XInfoGroupsResponse]) 

Get info about groups consuming from a stream. The Redis command XINFO is split into xinfoConsumers, xinfoGroups, and xinfoStream. Since Redis 5.0.0

xinfoStream Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> m (f XInfoStreamResponse) 

Get info about a stream. The Redis command XINFO is split into xinfoConsumers, xinfoGroups, and xinfoStream. Since Redis 5.0.0

xdel Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> [ByteString]

message IDs

-> m (f Integer) 

Delete messages from a stream. Since Redis 5.0.0

xtrim Source #

Arguments

:: RedisCtx m f 
=> ByteString

stream

-> TrimOpts 
-> m (f Integer) 

Set the upper bound for number of messages in a stream. Since Redis 5.0.0

inf :: RealFloat a => a Source #

Constructor for inf Redis argument values

command :: RedisCtx m f => m (f [CommandInfo]) Source #

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.

Transactions

watch Source #

Arguments

:: [ByteString]

key

-> Redis (Either Reply Status) 

Watch the given keys to determine execution of the MULTI/EXEC block (http://redis.io/commands/watch).

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

data Queued a Source #

A Queued value represents the result of a command inside a transaction. It is a proxy object for the actual result, which will only be available after returning from a multiExec transaction.

Queued values are composable by utilizing the Functor, Applicative or Monad interfaces.

Instances

Instances details
Monad Queued Source # 
Instance details

Defined in Database.Redis.Transactions

Methods

(>>=) :: Queued a -> (a -> Queued b) -> Queued b #

(>>) :: Queued a -> Queued b -> Queued b #

return :: a -> Queued a #

Functor Queued Source # 
Instance details

Defined in Database.Redis.Transactions

Methods

fmap :: (a -> b) -> Queued a -> Queued b #

(<$) :: a -> Queued b -> Queued a #

Applicative Queued Source # 
Instance details

Defined in Database.Redis.Transactions

Methods

pure :: a -> Queued a #

(<*>) :: Queued (a -> b) -> Queued a -> Queued b #

liftA2 :: (a -> b -> c) -> Queued a -> Queued b -> Queued c #

(*>) :: Queued a -> Queued b -> Queued b #

(<*) :: Queued a -> Queued b -> Queued a #

RedisCtx RedisTx Queued Source # 
Instance details

Defined in Database.Redis.Transactions

data TxResult a Source #

Result of a multiExec transaction.

Constructors

TxSuccess a

Transaction completed successfully. The wrapped value corresponds to the Queued value returned from the multiExec argument action.

TxAborted

Transaction aborted due to an earlier watch command.

TxError String

At least one of the commands returned an Error reply.

Instances

Instances details
Eq a => Eq (TxResult a) Source # 
Instance details

Defined in Database.Redis.Transactions

Methods

(==) :: TxResult a -> TxResult a -> Bool #

(/=) :: TxResult a -> TxResult a -> Bool #

Show a => Show (TxResult a) Source # 
Instance details

Defined in Database.Redis.Transactions

Methods

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

show :: TxResult a -> String #

showList :: [TxResult a] -> ShowS #

Generic (TxResult a) Source # 
Instance details

Defined in Database.Redis.Transactions

Associated Types

type Rep (TxResult a) :: Type -> Type #

Methods

from :: TxResult a -> Rep (TxResult a) x #

to :: Rep (TxResult a) x -> TxResult a #

NFData a => NFData (TxResult a) Source # 
Instance details

Defined in Database.Redis.Transactions

Methods

rnf :: TxResult a -> () #

type Rep (TxResult a) Source # 
Instance details

Defined in Database.Redis.Transactions

type Rep (TxResult a) = D1 ('MetaData "TxResult" "Database.Redis.Transactions" "hedis-0.14.2-6awqAJzDqBjD7lj5RyLFIN" 'False) (C1 ('MetaCons "TxSuccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: (C1 ('MetaCons "TxAborted" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TxError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))

data RedisTx a Source #

Command-context inside of MULTI/EXEC transactions. Use multiExec to run actions of this type.

In the RedisTx context, all commands return a Queued value. It is a proxy object for the actual result, which will only be available after finishing the transaction.

Instances

Instances details
Monad RedisTx Source # 
Instance details

Defined in Database.Redis.Transactions

Methods

(>>=) :: RedisTx a -> (a -> RedisTx b) -> RedisTx b #

(>>) :: RedisTx a -> RedisTx b -> RedisTx b #

return :: a -> RedisTx a #

Functor RedisTx Source # 
Instance details

Defined in Database.Redis.Transactions

Methods

fmap :: (a -> b) -> RedisTx a -> RedisTx b #

(<$) :: a -> RedisTx b -> RedisTx a #

Applicative RedisTx Source # 
Instance details

Defined in Database.Redis.Transactions

Methods

pure :: a -> RedisTx a #

(<*>) :: RedisTx (a -> b) -> RedisTx a -> RedisTx b #

liftA2 :: (a -> b -> c) -> RedisTx a -> RedisTx b -> RedisTx c #

(*>) :: RedisTx a -> RedisTx b -> RedisTx b #

(<*) :: RedisTx a -> RedisTx b -> RedisTx a #

MonadIO RedisTx Source # 
Instance details

Defined in Database.Redis.Transactions

Methods

liftIO :: IO a -> RedisTx a #

MonadRedis RedisTx Source # 
Instance details

Defined in Database.Redis.Transactions

Methods

liftRedis :: Redis a -> RedisTx a Source #

RedisCtx RedisTx Queued Source # 
Instance details

Defined in Database.Redis.Transactions

Pub/Sub

publish Source #

Arguments

:: RedisCtx m f 
=> ByteString

channel

-> ByteString

message

-> m (f Integer) 

Post a message to a channel (http://redis.io/commands/publish).

Subscribing to channels

There are two Pub/Sub implementations. First, there is a single-threaded implementation pubSub which is simpler to use but has the restriction that subscription changes can only be made in response to a message. Secondly, there is a more complicated Pub/Sub controller pubSubForever that uses concurrency to support changing subscriptions at any time but requires more setup. You should only use one or the other. In addition, no types or utility functions (that are part of the public API) are shared, so functions or types in one of the following sections cannot be used for the other. In particular, be aware that they use different utility functions to subscribe and unsubscribe to channels.

Single-thread Pub/Sub

pubSub Source #

Arguments

:: PubSub

Initial subscriptions.

-> (Message -> IO PubSub)

Callback function.

-> Redis () 

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"]
 

It should be noted that Redis Pub/Sub by its nature is asynchronous so returning unsubscribe does not mean that callback won't be able to receive any further messages. And to guarantee that you won't won't process messages after unsubscription and won't unsubscribe from the same channel more than once you need to use IORef or something similar

data Message Source #

Instances

Instances details
Show Message Source # 
Instance details

Defined in Database.Redis.PubSub

data PubSub Source #

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.

Instances

Instances details
Eq PubSub Source # 
Instance details

Defined in Database.Redis.PubSub

Methods

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

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

Semigroup PubSub Source # 
Instance details

Defined in Database.Redis.PubSub

Monoid PubSub Source # 
Instance details

Defined in Database.Redis.PubSub

subscribe Source #

Arguments

:: [ByteString]

channel

-> PubSub 

Listen for messages published to the given channels (http://redis.io/commands/subscribe).

unsubscribe Source #

Arguments

:: [ByteString]

channel

-> PubSub 

Stop listening for messages posted to the given channels (http://redis.io/commands/unsubscribe).

psubscribe Source #

Arguments

:: [ByteString]

pattern

-> PubSub 

Listen for messages published to channels matching the given patterns (http://redis.io/commands/psubscribe).

punsubscribe Source #

Arguments

:: [ByteString]

pattern

-> PubSub 

Stop listening for messages posted to channels matching the given patterns (http://redis.io/commands/punsubscribe).

Continuous Pub/Sub message controller

pubSubForever Source #

Arguments

:: Connection

The connection pool

-> PubSubController

The controller which keeps track of all subscriptions and handlers

-> IO ()

This action is executed once Redis acknowledges that all the subscriptions in the controller are now subscribed. You can use this after an exception (such as ConnectionLost) to signal that all subscriptions are now reactivated.

-> IO () 

Open a connection to the Redis server, register to all channels in the PubSubController, and process messages and subscription change requests forever. The only way this will ever exit is if there is an exception from the network code or an unhandled exception in a MessageCallback or PMessageCallback. For example, if the network connection to Redis dies, pubSubForever will throw a ConnectionLost. When such an exception is thrown, you can recall pubSubForever with the same PubSubController which will open a new connection and resubscribe to all the channels which are tracked in the PubSubController.

The general pattern is therefore during program startup create a PubSubController and fork a thread which calls pubSubForever in a loop (using an exponential backoff algorithm such as the retry package to not hammer the Redis server if it does die). For example,

myhandler :: ByteString -> IO ()
myhandler msg = putStrLn $ unpack $ decodeUtf8 msg

onInitialComplete :: IO ()
onInitialComplete = putStrLn "Redis acknowledged that mychannel is now subscribed"

main :: IO ()
main = do
  conn <- connect defaultConnectInfo
  pubSubCtrl <- newPubSubController [("mychannel", myhandler)] []
  forkIO $ forever $
      pubSubForever conn pubSubCtrl onInitialComplete
        `catch` (\(e :: SomeException) -> do
          putStrLn $ "Got error: " ++ show e
          threadDelay $ 50*1000) -- TODO: use exponential backoff

  {- elsewhere in your program, use pubSubCtrl to change subscriptions -}

At most one active pubSubForever can be running against a single PubSubController at any time. If two active calls to pubSubForever share a single PubSubController there will be deadlocks. If you do want to process messages using multiple connections to Redis, you can create more than one PubSubController. For example, create one PubSubController for each getNumCapabilities and then create a Haskell thread bound to each capability each calling pubSubForever in a loop. This will create one network connection per controller/capability and allow you to register separate channels and callbacks for each controller, spreading the load across the capabilities.

type RedisChannel = ByteString Source #

A Redis channel name

type RedisPChannel = ByteString Source #

A Redis pattern channel name

type MessageCallback = ByteString -> IO () Source #

A handler for a message from a subscribed channel. The callback is passed the message content.

Messages are processed synchronously in the receiving thread, so if the callback takes a long time it will block other callbacks and other messages from being received. If you need to move long-running work to a different thread, we suggest you use TBQueue with a reasonable bound, so that if messages are arriving faster than you can process them, you do eventually block.

If the callback throws an exception, the exception will be thrown from pubSubForever which will cause the entire Redis connection for all subscriptions to be closed. As long as you call pubSubForever in a loop you will reconnect to your subscribed channels, but you should probably add an exception handler to each callback to prevent this.

type PMessageCallback = RedisChannel -> ByteString -> IO () Source #

A handler for a message from a psubscribed channel. The callback is passed the channel the message was sent on plus the message content.

Similar to MessageCallback, callbacks are executed synchronously and any exceptions are rethrown from pubSubForever.

data PubSubController Source #

A controller that stores a set of channels, pattern channels, and callbacks. It allows you to manage Pub/Sub subscriptions and pattern subscriptions and alter them at any time throughout the life of your program. You should typically create the controller at the start of your program and then store it through the life of your program, using addChannels and removeChannels to update the current subscriptions.

newPubSubController Source #

Arguments

:: MonadIO m 
=> [(RedisChannel, MessageCallback)]

the initial subscriptions

-> [(RedisPChannel, PMessageCallback)]

the initial pattern subscriptions

-> m PubSubController 

Create a new PubSubController. Note that this does not subscribe to any channels, it just creates the controller. The subscriptions will happen once pubSubForever is called.

currentChannels :: MonadIO m => PubSubController -> m [RedisChannel] Source #

Get the list of current channels in the PubSubController. WARNING! This might not exactly reflect the subscribed channels in the Redis server, because there is a delay between adding or removing a channel in the PubSubController and when Redis receives and processes the subscription change request.

currentPChannels :: MonadIO m => PubSubController -> m [RedisPChannel] Source #

Get the list of current pattern channels in the PubSubController. WARNING! This might not exactly reflect the subscribed channels in the Redis server, because there is a delay between adding or removing a channel in the PubSubController and when Redis receives and processes the subscription change request.

addChannels Source #

Arguments

:: MonadIO m 
=> PubSubController 
-> [(RedisChannel, MessageCallback)]

the channels to subscribe to

-> [(RedisPChannel, PMessageCallback)]

the channels to pattern subscribe to

-> m UnregisterCallbacksAction 

Add channels into the PubSubController, and if there is an active pubSubForever, send the subscribe and psubscribe commands to Redis. The addChannels function is thread-safe. This function does not wait for Redis to acknowledge that the channels have actually been subscribed; use addChannelsAndWait for that.

You can subscribe to the same channel or pattern channel multiple times; the PubSubController keeps a list of callbacks and executes each callback in response to a message.

The return value is an action UnregisterCallbacksAction which will unregister the callbacks, which should typically used with bracket.

addChannelsAndWait Source #

Arguments

:: MonadIO m 
=> PubSubController 
-> [(RedisChannel, MessageCallback)]

the channels to subscribe to

-> [(RedisPChannel, PMessageCallback)]

the channels to psubscribe to

-> m UnregisterCallbacksAction 

Call addChannels and then wait for Redis to acknowledge that the channels are actually subscribed.

Note that this function waits for all pending subscription change requests, so if you for example call addChannelsAndWait from multiple threads simultaneously, they all will wait for all pending subscription changes to be acknowledged by Redis (this is due to the fact that we just track the total number of pending change requests sent to Redis and just wait until that count reaches zero).

This also correctly waits if the network connection dies during the subscription change. Say that the network connection dies right after we send a subscription change to Redis. pubSubForever will throw ConnectionLost and addChannelsAndWait will continue to wait. Once you recall pubSubForever with the same PubSubController, pubSubForever will open a new connection, send subscription commands for all channels in the PubSubController (which include the ones we are waiting for), and wait for the responses from Redis. Only once we receive the response from Redis that it has subscribed to all channels in PubSubController will addChannelsAndWait unblock and return.

removeChannels :: MonadIO m => PubSubController -> [RedisChannel] -> [RedisPChannel] -> m () Source #

Remove channels from the PubSubController, and if there is an active pubSubForever, send the unsubscribe commands to Redis. Note that as soon as this function returns, no more callbacks will be executed even if more messages arrive during the period when we request to unsubscribe from the channel and Redis actually processes the unsubscribe request. This function is thread-safe.

If you remove all channels, the connection in pubSubForever to redis will stay open and waiting for any new channels from a call to addChannels. If you really want to close the connection, use killThread or cancel to kill the thread running pubSubForever.

removeChannelsAndWait :: MonadIO m => PubSubController -> [RedisChannel] -> [RedisPChannel] -> m () Source #

Call removeChannels and then wait for all pending subscription change requests to be acknowledged by Redis. This uses the same waiting logic as addChannelsAndWait. Since removeChannels immediately notifies the PubSubController to start discarding messages, you likely don't need this function and can just use removeChannels.

type UnregisterCallbacksAction = IO () Source #

An action that when executed will unregister the callbacks. It is returned from addChannels or addChannelsAndWait and typically you would use it in bracket to guarantee that you unsubscribe from channels. For example, if you are using websockets to distribute messages to clients, you could use something such as:

websocketConn <- Network.WebSockets.acceptRequest pending
let mycallback msg = Network.WebSockets.sendTextData websocketConn msg
bracket (addChannelsAndWait ctrl [("hello", mycallback)] []) id $ const $ do
  {- loop here calling Network.WebSockets.receiveData -}

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 (Either Reply ByteString)
debugObject key = sendRequest ["DEBUG", "OBJECT", key]

data Reply Source #

Low-level representation of replies from the Redis server.

Instances

Instances details
Eq Reply Source # 
Instance details

Defined in Database.Redis.Protocol

Methods

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

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

Show Reply Source # 
Instance details

Defined in Database.Redis.Protocol

Methods

showsPrec :: Int -> Reply -> ShowS #

show :: Reply -> String #

showList :: [Reply] -> ShowS #

Generic Reply Source # 
Instance details

Defined in Database.Redis.Protocol

Associated Types

type Rep Reply :: Type -> Type #

Methods

from :: Reply -> Rep Reply x #

to :: Rep Reply x -> Reply #

NFData Reply Source # 
Instance details

Defined in Database.Redis.Protocol

Methods

rnf :: Reply -> () #

RedisResult Reply Source # 
Instance details

Defined in Database.Redis.Types

RedisCtx Redis (Either Reply) Source # 
Instance details

Defined in Database.Redis.Core

type Rep Reply Source # 
Instance details

Defined in Database.Redis.Protocol

data Status Source #

Constructors

Ok 
Pong 
Status ByteString 

Instances

Instances details
Eq Status Source # 
Instance details

Defined in Database.Redis.Types

Methods

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

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

Show Status Source # 
Instance details

Defined in Database.Redis.Types

Generic Status Source # 
Instance details

Defined in Database.Redis.Types

Associated Types

type Rep Status :: Type -> Type #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

NFData Status Source # 
Instance details

Defined in Database.Redis.Types

Methods

rnf :: Status -> () #

RedisResult Status Source # 
Instance details

Defined in Database.Redis.Types

type Rep Status Source # 
Instance details

Defined in Database.Redis.Types

type Rep Status = D1 ('MetaData "Status" "Database.Redis.Types" "hedis-0.14.2-6awqAJzDqBjD7lj5RyLFIN" 'False) (C1 ('MetaCons "Ok" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Pong" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Status" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))))

class RedisResult a where Source #

Methods

decode :: Reply -> Either Reply a Source #

Instances

Instances details
RedisResult Bool Source # 
Instance details

Defined in Database.Redis.Types

RedisResult Double Source # 
Instance details

Defined in Database.Redis.Types

RedisResult Integer Source # 
Instance details

Defined in Database.Redis.Types

RedisResult ByteString Source # 
Instance details

Defined in Database.Redis.Types

RedisResult Reply Source # 
Instance details

Defined in Database.Redis.Types

RedisResult RedisType Source # 
Instance details

Defined in Database.Redis.Types

RedisResult Status Source # 
Instance details

Defined in Database.Redis.Types

RedisResult ClusterSlotsResponseEntry Source # 
Instance details

Defined in Database.Redis.ManualCommands

RedisResult ClusterSlotsNode Source # 
Instance details

Defined in Database.Redis.ManualCommands

RedisResult ClusterSlotsResponse Source # 
Instance details

Defined in Database.Redis.ManualCommands

RedisResult ClusterNodesResponse Source # 
Instance details

Defined in Database.Redis.ManualCommands

RedisResult XInfoStreamResponse Source # 
Instance details

Defined in Database.Redis.ManualCommands

RedisResult XInfoGroupsResponse Source # 
Instance details

Defined in Database.Redis.ManualCommands

RedisResult XInfoConsumersResponse Source # 
Instance details

Defined in Database.Redis.ManualCommands

RedisResult XPendingDetailRecord Source # 
Instance details

Defined in Database.Redis.ManualCommands

RedisResult XPendingSummaryResponse Source # 
Instance details

Defined in Database.Redis.ManualCommands

RedisResult XReadResponse Source # 
Instance details

Defined in Database.Redis.ManualCommands

RedisResult StreamsRecord Source # 
Instance details

Defined in Database.Redis.ManualCommands

RedisResult Cursor Source # 
Instance details

Defined in Database.Redis.ManualCommands

RedisResult Slowlog Source # 
Instance details

Defined in Database.Redis.ManualCommands

(RedisResult k, RedisResult v) => RedisResult [(k, v)] Source # 
Instance details

Defined in Database.Redis.Types

Methods

decode :: Reply -> Either Reply [(k, v)] Source #

RedisResult a => RedisResult [a] Source # 
Instance details

Defined in Database.Redis.Types

Methods

decode :: Reply -> Either Reply [a] Source #

RedisResult a => RedisResult (Maybe a) Source # 
Instance details

Defined in Database.Redis.Types

Methods

decode :: Reply -> Either Reply (Maybe a) Source #

(RedisResult a, RedisResult b) => RedisResult (a, b) Source # 
Instance details

Defined in Database.Redis.Types

Methods

decode :: Reply -> Either Reply (a, b) Source #

Solution to Exercise

Type of expire inside a transaction:

expire :: ByteString -> Integer -> RedisTx (Queued Bool)

Type of lindex outside of a transaction:

lindex :: ByteString -> Integer -> Redis (Either Reply ByteString)

data HashSlot Source #

Instances

Instances details
Enum HashSlot Source # 
Instance details

Defined in Database.Redis.Cluster.HashSlot

Eq HashSlot Source # 
Instance details

Defined in Database.Redis.Cluster.HashSlot

Integral HashSlot Source # 
Instance details

Defined in Database.Redis.Cluster.HashSlot

Num HashSlot Source # 
Instance details

Defined in Database.Redis.Cluster.HashSlot

Ord HashSlot Source # 
Instance details

Defined in Database.Redis.Cluster.HashSlot

Real HashSlot Source # 
Instance details

Defined in Database.Redis.Cluster.HashSlot

Show HashSlot Source # 
Instance details

Defined in Database.Redis.Cluster.HashSlot

keyToSlot :: ByteString -> HashSlot Source #

Compute the hashslot associated with a key