-- Generated by GenCmds.hs. DO NOT EDIT. {-# LANGUAGE OverloadedStrings, FlexibleContexts #-} module Database.Redis.Commands ( -- ** Connection auth, -- |Authenticate to the server (). echo, -- |Echo the given string (). ping, -- |Ping the server (). quit, -- |Close the connection (). select, -- |Change the selected database for the current connection (). -- ** Keys del, -- |Delete a key (). dump, -- |Return a serialized version of the value stored at the specified key. (). exists, -- |Determine if a key exists (). expire, -- |Set a key's time to live in seconds (). expireat, -- |Set the expiration for a key as a UNIX timestamp (). keys, -- |Find all keys matching the given pattern (). migrate, -- |Atomically transfer a key from a Redis instance to another one. (). move, -- |Move a key to another database (). objectRefcount, -- |Inspect the internals of Redis objects (). The Redis command @OBJECT@ is split up into 'objectRefcount', 'objectEncoding', 'objectIdletime'. objectEncoding, -- |Inspect the internals of Redis objects (). The Redis command @OBJECT@ is split up into 'objectRefcount', 'objectEncoding', 'objectIdletime'. objectIdletime, -- |Inspect the internals of Redis objects (). The Redis command @OBJECT@ is split up into 'objectRefcount', 'objectEncoding', 'objectIdletime'. persist, -- |Remove the expiration from a key (). pexpire, -- |Set a key's time to live in milliseconds (). pexpireat, -- |Set the expiration for a key as a UNIX timestamp specified in milliseconds (). pttl, -- |Get the time to live for a key in milliseconds (). randomkey, -- |Return a random key from the keyspace (). rename, -- |Rename a key (). renamenx, -- |Rename a key, only if the new key does not exist (). restore, -- |Create a key using the provided serialized value, previously obtained using DUMP. (). SortOpts(..), defaultSortOpts, SortOrder(..), sort, -- |Sort the elements in a list, set or sorted set (). The Redis command @SORT@ is split up into 'sort', 'sortStore'. sortStore, -- |Sort the elements in a list, set or sorted set (). The Redis command @SORT@ is split up into 'sort', 'sortStore'. ttl, -- |Get the time to live for a key (). RedisType(..), getType, -- |Determine the type stored at key (). -- ** Hashes hdel, -- |Delete one or more hash fields (). hexists, -- |Determine if a hash field exists (). hget, -- |Get the value of a hash field (). hgetall, -- |Get all the fields and values in a hash (). hincrby, -- |Increment the integer value of a hash field by the given number (). hincrbyfloat, -- |Increment the float value of a hash field by the given amount (). hkeys, -- |Get all the fields in a hash (). hlen, -- |Get the number of fields in a hash (). hmget, -- |Get the values of all the given hash fields (). hmset, -- |Set multiple hash fields to multiple values (). hset, -- |Set the string value of a hash field (). hsetnx, -- |Set the value of a hash field, only if the field does not exist (). hvals, -- |Get all the values in a hash (). -- ** Lists blpop, -- |Remove and get the first element in a list, or block until one is available (). brpop, -- |Remove and get the last element in a list, or block until one is available (). brpoplpush, -- |Pop a value from a list, push it to another list and return it; or block until one is available (). lindex, -- |Get an element from a list by its index (). linsertBefore, -- |Insert an element before or after another element in a list (). The Redis command @LINSERT@ is split up into 'linsertBefore', 'linsertAfter'. linsertAfter, -- |Insert an element before or after another element in a list (). The Redis command @LINSERT@ is split up into 'linsertBefore', 'linsertAfter'. llen, -- |Get the length of a list (). lpop, -- |Remove and get the first element in a list (). lpush, -- |Prepend one or multiple values to a list (). lpushx, -- |Prepend a value to a list, only if the list exists (). lrange, -- |Get a range of elements from a list (). lrem, -- |Remove elements from a list (). lset, -- |Set the value of an element in a list by its index (). ltrim, -- |Trim a list to the specified range (). rpop, -- |Remove and get the last element in a list (). rpoplpush, -- |Remove the last element in a list, append it to another list and return it (). rpush, -- |Append one or multiple values to a list (). rpushx, -- |Append a value to a list, only if the list exists (). -- ** Scripting eval, -- |Execute a Lua script server side (). evalsha, -- |Execute a Lua script server side (). scriptExists, -- |Check existence of scripts in the script cache. (). scriptFlush, -- |Remove all the scripts from the script cache. (). scriptKill, -- |Kill the script currently in execution. (). scriptLoad, -- |Load the specified Lua script into the script cache. (). -- ** Server bgrewriteaof, -- |Asynchronously rewrite the append-only file (). bgsave, -- |Asynchronously save the dataset to disk (). configGet, -- |Get the value of a configuration parameter (). configResetstat, -- |Reset the stats returned by INFO (). configSet, -- |Set a configuration parameter to the given value (). dbsize, -- |Return the number of keys in the selected database (). debugObject, -- |Get debugging information about a key (). flushall, -- |Remove all keys from all databases (). flushdb, -- |Remove all keys from the current database (). info, -- |Get information and statistics about the server (). lastsave, -- |Get the UNIX time stamp of the last successful save to disk (). save, -- |Synchronously save the dataset to disk (). slaveof, -- |Make the server a slave of another instance, or promote it as master (). Slowlog(..), slowlogGet, -- |Manages the Redis slow queries log (). The Redis command @SLOWLOG@ is split up into 'slowlogGet', 'slowlogLen', 'slowlogReset'. slowlogLen, -- |Manages the Redis slow queries log (). The Redis command @SLOWLOG@ is split up into 'slowlogGet', 'slowlogLen', 'slowlogReset'. slowlogReset, -- |Manages the Redis slow queries log (). The Redis command @SLOWLOG@ is split up into 'slowlogGet', 'slowlogLen', 'slowlogReset'. time, -- |Return the current server time (). -- ** Sets sadd, -- |Add one or more members to a set (). scard, -- |Get the number of members in a set (). sdiff, -- |Subtract multiple sets (). sdiffstore, -- |Subtract multiple sets and store the resulting set in a key (). sinter, -- |Intersect multiple sets (). sinterstore, -- |Intersect multiple sets and store the resulting set in a key (). sismember, -- |Determine if a given value is a member of a set (). smembers, -- |Get all the members in a set (). smove, -- |Move a member from one set to another (). spop, -- |Remove and return a random member from a set (). srandmember, -- |Get a random member from a set (). srem, -- |Remove one or more members from a set (). sunion, -- |Add multiple sets (). sunionstore, -- |Add multiple sets and store the resulting set in a key (). -- ** Sorted Sets zadd, -- |Add one or more members to a sorted set, or update its score if it already exists (). zcard, -- |Get the number of members in a sorted set (). zcount, -- |Count the members in a sorted set with scores within the given values (). zincrby, -- |Increment the score of a member in a sorted set (). Aggregate(..), zinterstore, -- |Intersect multiple sorted sets and store the resulting sorted set in a new key (). The Redis command @ZINTERSTORE@ is split up into 'zinterstore', 'zinterstoreWeights'. zinterstoreWeights, -- |Intersect multiple sorted sets and store the resulting sorted set in a new key (). The Redis command @ZINTERSTORE@ is split up into 'zinterstore', 'zinterstoreWeights'. zrange, -- |Return a range of members in a sorted set, by index (). The Redis command @ZRANGE@ is split up into 'zrange', 'zrangeWithscores'. zrangeWithscores, -- |Return a range of members in a sorted set, by index (). The Redis command @ZRANGE@ is split up into 'zrange', 'zrangeWithscores'. zrangebyscore, -- |Return a range of members in a sorted set, by score (). The Redis command @ZRANGEBYSCORE@ is split up into 'zrangebyscore', 'zrangebyscoreWithscores', 'zrangebyscoreLimit', 'zrangebyscoreWithscoresLimit'. zrangebyscoreWithscores, -- |Return a range of members in a sorted set, by score (). The Redis command @ZRANGEBYSCORE@ is split up into 'zrangebyscore', 'zrangebyscoreWithscores', 'zrangebyscoreLimit', 'zrangebyscoreWithscoresLimit'. zrangebyscoreLimit, -- |Return a range of members in a sorted set, by score (). The Redis command @ZRANGEBYSCORE@ is split up into 'zrangebyscore', 'zrangebyscoreWithscores', 'zrangebyscoreLimit', 'zrangebyscoreWithscoresLimit'. zrangebyscoreWithscoresLimit, -- |Return a range of members in a sorted set, by score (). The Redis command @ZRANGEBYSCORE@ is split up into 'zrangebyscore', 'zrangebyscoreWithscores', 'zrangebyscoreLimit', 'zrangebyscoreWithscoresLimit'. zrank, -- |Determine the index of a member in a sorted set (). zrem, -- |Remove one or more members from a sorted set (). zremrangebyrank, -- |Remove all members in a sorted set within the given indexes (). zremrangebyscore, -- |Remove all members in a sorted set within the given scores (). zrevrange, -- |Return a range of members in a sorted set, by index, with scores ordered from high to low (). The Redis command @ZREVRANGE@ is split up into 'zrevrange', 'zrevrangeWithscores'. zrevrangeWithscores, -- |Return a range of members in a sorted set, by index, with scores ordered from high to low (). The Redis command @ZREVRANGE@ is split up into 'zrevrange', 'zrevrangeWithscores'. zrevrangebyscore, -- |Return a range of members in a sorted set, by score, with scores ordered from high to low (). The Redis command @ZREVRANGEBYSCORE@ is split up into 'zrevrangebyscore', 'zrevrangebyscoreWithscores', 'zrevrangebyscoreLimit', 'zrevrangebyscoreWithscoresLimit'. zrevrangebyscoreWithscores, -- |Return a range of members in a sorted set, by score, with scores ordered from high to low (). The Redis command @ZREVRANGEBYSCORE@ is split up into 'zrevrangebyscore', 'zrevrangebyscoreWithscores', 'zrevrangebyscoreLimit', 'zrevrangebyscoreWithscoresLimit'. zrevrangebyscoreLimit, -- |Return a range of members in a sorted set, by score, with scores ordered from high to low (). The Redis command @ZREVRANGEBYSCORE@ is split up into 'zrevrangebyscore', 'zrevrangebyscoreWithscores', 'zrevrangebyscoreLimit', 'zrevrangebyscoreWithscoresLimit'. zrevrangebyscoreWithscoresLimit, -- |Return a range of members in a sorted set, by score, with scores ordered from high to low (). The Redis command @ZREVRANGEBYSCORE@ is split up into 'zrevrangebyscore', 'zrevrangebyscoreWithscores', 'zrevrangebyscoreLimit', 'zrevrangebyscoreWithscoresLimit'. zrevrank, -- |Determine the index of a member in a sorted set, with scores ordered from high to low (). zscore, -- |Get the score associated with the given member in a sorted set (). zunionstore, -- |Add multiple sorted sets and store the resulting sorted set in a new key (). The Redis command @ZUNIONSTORE@ is split up into 'zunionstore', 'zunionstoreWeights'. zunionstoreWeights, -- |Add multiple sorted sets and store the resulting sorted set in a new key (). The Redis command @ZUNIONSTORE@ is split up into 'zunionstore', 'zunionstoreWeights'. -- ** Strings append, -- |Append a value to a key (). bitcount, -- |Count set bits in a string (). The Redis command @BITCOUNT@ is split up into 'bitcount', 'bitcountRange'. bitcountRange, -- |Count set bits in a string (). The Redis command @BITCOUNT@ is split up into 'bitcount', 'bitcountRange'. bitopAnd, -- |Perform bitwise operations between strings (). The Redis command @BITOP@ is split up into 'bitopAnd', 'bitopOr', 'bitopXor', 'bitopNot'. bitopOr, -- |Perform bitwise operations between strings (). The Redis command @BITOP@ is split up into 'bitopAnd', 'bitopOr', 'bitopXor', 'bitopNot'. bitopXor, -- |Perform bitwise operations between strings (). The Redis command @BITOP@ is split up into 'bitopAnd', 'bitopOr', 'bitopXor', 'bitopNot'. bitopNot, -- |Perform bitwise operations between strings (). The Redis command @BITOP@ is split up into 'bitopAnd', 'bitopOr', 'bitopXor', 'bitopNot'. decr, -- |Decrement the integer value of a key by one (). decrby, -- |Decrement the integer value of a key by the given number (). get, -- |Get the value of a key (). getbit, -- |Returns the bit value at offset in the string value stored at key (). getrange, -- |Get a substring of the string stored at a key (). getset, -- |Set the string value of a key and return its old value (). incr, -- |Increment the integer value of a key by one (). incrby, -- |Increment the integer value of a key by the given amount (). incrbyfloat, -- |Increment the float value of a key by the given amount (). mget, -- |Get the values of all the given keys (). mset, -- |Set multiple keys to multiple values (). msetnx, -- |Set multiple keys to multiple values, only if none of the keys exist (). psetex, -- |Set the value and expiration in milliseconds of a key (). set, -- |Set the string value of a key (). setbit, -- |Sets or clears the bit at offset in the string value stored at key (). setex, -- |Set the value and expiration of a key (). setnx, -- |Set the value of a key, only if the key does not exist (). setrange, -- |Overwrite part of a string at key starting at the specified offset (). strlen, -- |Get the length of the value stored in a key (). -- * 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 () -- -- -- * SYNC () -- -- -- * SHUTDOWN () -- -- -- * DEBUG SEGFAULT () -- ) where import Prelude hiding (min,max) import Data.ByteString (ByteString) import Database.Redis.ManualCommands import Database.Redis.Types import Database.Redis.Core flushall :: (RedisCtx m f) => m (f Status) flushall = sendRequest (["FLUSHALL"] ) time :: (RedisCtx m f) => m (f (Integer,Integer)) time = sendRequest (["TIME"] ) hdel :: (RedisCtx m f) => ByteString -- ^ key -> [ByteString] -- ^ field -> m (f Integer) hdel key field = sendRequest (["HDEL"] ++ [encode key] ++ map encode field ) hincrby :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ field -> Integer -- ^ increment -> m (f Integer) hincrby key field increment = sendRequest (["HINCRBY"] ++ [encode key] ++ [encode field] ++ [encode increment] ) hincrbyfloat :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ field -> Double -- ^ increment -> m (f Double) hincrbyfloat key field increment = sendRequest (["HINCRBYFLOAT"] ++ [encode key] ++ [encode field] ++ [encode increment] ) getset :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ value -> m (f (Maybe ByteString)) getset key value = sendRequest (["GETSET"] ++ [encode key] ++ [encode value] ) rpushx :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ value -> m (f Integer) rpushx key value = sendRequest (["RPUSHX"] ++ [encode key] ++ [encode value] ) setnx :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ value -> m (f Bool) setnx key value = sendRequest (["SETNX"] ++ [encode key] ++ [encode value] ) keys :: (RedisCtx m f) => ByteString -- ^ pattern -> m (f [ByteString]) keys pattern = sendRequest (["KEYS"] ++ [encode pattern] ) bgsave :: (RedisCtx m f) => m (f Status) bgsave = sendRequest (["BGSAVE"] ) slaveof :: (RedisCtx m f) => ByteString -- ^ host -> ByteString -- ^ port -> m (f Status) slaveof host port = sendRequest (["SLAVEOF"] ++ [encode host] ++ [encode port] ) debugObject :: (RedisCtx m f) => ByteString -- ^ key -> m (f ByteString) debugObject key = sendRequest (["DEBUG","OBJECT"] ++ [encode key] ) bgrewriteaof :: (RedisCtx m f) => m (f Status) bgrewriteaof = sendRequest (["BGREWRITEAOF"] ) zincrby :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ increment -> ByteString -- ^ member -> m (f Double) zincrby key increment member = sendRequest (["ZINCRBY"] ++ [encode key] ++ [encode increment] ++ [encode member] ) sinter :: (RedisCtx m f) => [ByteString] -- ^ key -> m (f [ByteString]) sinter key = sendRequest (["SINTER"] ++ map encode key ) hmset :: (RedisCtx m f) => ByteString -- ^ key -> [(ByteString,ByteString)] -- ^ fieldValue -> m (f Status) hmset key fieldValue = sendRequest (["HMSET"] ++ [encode key] ++ concatMap (\(x,y) -> [encode x,encode y])fieldValue ) scard :: (RedisCtx m f) => ByteString -- ^ key -> m (f Integer) scard key = sendRequest (["SCARD"] ++ [encode key] ) get :: (RedisCtx m f) => ByteString -- ^ key -> m (f (Maybe ByteString)) get key = sendRequest (["GET"] ++ [encode key] ) lrem :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ count -> ByteString -- ^ value -> m (f Integer) lrem key count value = sendRequest (["LREM"] ++ [encode key] ++ [encode count] ++ [encode value] ) expireat :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ timestamp -> m (f Bool) expireat key timestamp = sendRequest (["EXPIREAT"] ++ [encode key] ++ [encode timestamp] ) incr :: (RedisCtx m f) => ByteString -- ^ key -> m (f Integer) incr key = sendRequest (["INCR"] ++ [encode key] ) renamenx :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ newkey -> m (f Bool) renamenx key newkey = sendRequest (["RENAMENX"] ++ [encode key] ++ [encode newkey] ) pexpireat :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ millisecondsTimestamp -> m (f Bool) pexpireat key millisecondsTimestamp = sendRequest (["PEXPIREAT"] ++ [encode key] ++ [encode millisecondsTimestamp] ) save :: (RedisCtx m f) => m (f Status) save = sendRequest (["SAVE"] ) echo :: (RedisCtx m f) => ByteString -- ^ message -> m (f ByteString) echo message = sendRequest (["ECHO"] ++ [encode message] ) blpop :: (RedisCtx m f) => [ByteString] -- ^ key -> Integer -- ^ timeout -> m (f (Maybe (ByteString,ByteString))) blpop key timeout = sendRequest (["BLPOP"] ++ map encode key ++ [encode timeout] ) sdiffstore :: (RedisCtx m f) => ByteString -- ^ destination -> [ByteString] -- ^ key -> m (f Integer) sdiffstore destination key = sendRequest (["SDIFFSTORE"] ++ [encode destination] ++ map encode key ) migrate :: (RedisCtx m f) => ByteString -- ^ host -> ByteString -- ^ port -> ByteString -- ^ key -> Integer -- ^ destinationDb -> Integer -- ^ timeout -> m (f Status) migrate host port key destinationDb timeout = sendRequest (["MIGRATE"] ++ [encode host] ++ [encode port] ++ [encode key] ++ [encode destinationDb] ++ [encode timeout] ) move :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ db -> m (f Bool) move key db = sendRequest (["MOVE"] ++ [encode key] ++ [encode db] ) hvals :: (RedisCtx m f) => ByteString -- ^ key -> m (f [ByteString]) hvals key = sendRequest (["HVALS"] ++ [encode key] ) exists :: (RedisCtx m f) => ByteString -- ^ key -> m (f Bool) exists key = sendRequest (["EXISTS"] ++ [encode key] ) smembers :: (RedisCtx m f) => ByteString -- ^ key -> m (f [ByteString]) smembers key = sendRequest (["SMEMBERS"] ++ [encode key] ) decr :: (RedisCtx m f) => ByteString -- ^ key -> m (f Integer) decr key = sendRequest (["DECR"] ++ [encode key] ) rename :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ newkey -> m (f Status) rename key newkey = sendRequest (["RENAME"] ++ [encode key] ++ [encode newkey] ) sunion :: (RedisCtx m f) => [ByteString] -- ^ key -> m (f [ByteString]) sunion key = sendRequest (["SUNION"] ++ map encode key ) ping :: (RedisCtx m f) => m (f Status) ping = sendRequest (["PING"] ) zrem :: (RedisCtx m f) => ByteString -- ^ key -> [ByteString] -- ^ member -> m (f Integer) zrem key member = sendRequest (["ZREM"] ++ [encode key] ++ map encode member ) hmget :: (RedisCtx m f) => ByteString -- ^ key -> [ByteString] -- ^ field -> m (f [Maybe ByteString]) hmget key field = sendRequest (["HMGET"] ++ [encode key] ++ map encode field ) pexpire :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ milliseconds -> m (f Bool) pexpire key milliseconds = sendRequest (["PEXPIRE"] ++ [encode key] ++ [encode milliseconds] ) dbsize :: (RedisCtx m f) => m (f Integer) dbsize = sendRequest (["DBSIZE"] ) lrange :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ start -> Integer -- ^ stop -> m (f [ByteString]) lrange key start stop = sendRequest (["LRANGE"] ++ [encode key] ++ [encode start] ++ [encode stop] ) lpop :: (RedisCtx m f) => ByteString -- ^ key -> m (f (Maybe ByteString)) lpop key = sendRequest (["LPOP"] ++ [encode key] ) expire :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ seconds -> m (f Bool) expire key seconds = sendRequest (["EXPIRE"] ++ [encode key] ++ [encode seconds] ) flushdb :: (RedisCtx m f) => m (f Status) flushdb = sendRequest (["FLUSHDB"] ) smove :: (RedisCtx m f) => ByteString -- ^ source -> ByteString -- ^ destination -> ByteString -- ^ member -> m (f Bool) smove source destination member = sendRequest (["SMOVE"] ++ [encode source] ++ [encode destination] ++ [encode member] ) zremrangebyrank :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ start -> Integer -- ^ stop -> m (f Integer) zremrangebyrank key start stop = sendRequest (["ZREMRANGEBYRANK"] ++ [encode key] ++ [encode start] ++ [encode stop] ) sadd :: (RedisCtx m f) => ByteString -- ^ key -> [ByteString] -- ^ member -> m (f Integer) sadd key member = sendRequest (["SADD"] ++ [encode key] ++ map encode member ) lpush :: (RedisCtx m f) => ByteString -- ^ key -> [ByteString] -- ^ value -> m (f Integer) lpush key value = sendRequest (["LPUSH"] ++ [encode key] ++ map encode value ) strlen :: (RedisCtx m f) => ByteString -- ^ key -> m (f Integer) strlen key = sendRequest (["STRLEN"] ++ [encode key] ) set :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ value -> m (f Status) set key value = sendRequest (["SET"] ++ [encode key] ++ [encode value] ) lindex :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ index -> m (f (Maybe ByteString)) lindex key index = sendRequest (["LINDEX"] ++ [encode key] ++ [encode index] ) zscore :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ member -> m (f (Maybe Double)) zscore key member = sendRequest (["ZSCORE"] ++ [encode key] ++ [encode member] ) configResetstat :: (RedisCtx m f) => m (f Status) configResetstat = sendRequest (["CONFIG","RESETSTAT"] ) del :: (RedisCtx m f) => [ByteString] -- ^ key -> m (f Integer) del key = sendRequest (["DEL"] ++ map encode key ) zrevrank :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ member -> m (f (Maybe Integer)) zrevrank key member = sendRequest (["ZREVRANK"] ++ [encode key] ++ [encode member] ) scriptKill :: (RedisCtx m f) => m (f Status) scriptKill = sendRequest (["SCRIPT","KILL"] ) incrby :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ increment -> m (f Integer) incrby key increment = sendRequest (["INCRBY"] ++ [encode key] ++ [encode increment] ) setbit :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ offset -> ByteString -- ^ value -> m (f Integer) setbit key offset value = sendRequest (["SETBIT"] ++ [encode key] ++ [encode offset] ++ [encode value] ) incrbyfloat :: (RedisCtx m f) => ByteString -- ^ key -> Double -- ^ increment -> m (f Double) incrbyfloat key increment = sendRequest (["INCRBYFLOAT"] ++ [encode key] ++ [encode increment] ) brpoplpush :: (RedisCtx m f) => ByteString -- ^ source -> ByteString -- ^ destination -> Integer -- ^ timeout -> m (f (Maybe ByteString)) brpoplpush source destination timeout = sendRequest (["BRPOPLPUSH"] ++ [encode source] ++ [encode destination] ++ [encode timeout] ) rpop :: (RedisCtx m f) => ByteString -- ^ key -> m (f (Maybe ByteString)) rpop key = sendRequest (["RPOP"] ++ [encode key] ) setrange :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ offset -> ByteString -- ^ value -> m (f Integer) setrange key offset value = sendRequest (["SETRANGE"] ++ [encode key] ++ [encode offset] ++ [encode value] ) ttl :: (RedisCtx m f) => ByteString -- ^ key -> m (f Integer) ttl key = sendRequest (["TTL"] ++ [encode key] ) zremrangebyscore :: (RedisCtx m f) => ByteString -- ^ key -> Double -- ^ min -> Double -- ^ max -> m (f Integer) zremrangebyscore key min max = sendRequest (["ZREMRANGEBYSCORE"] ++ [encode key] ++ [encode min] ++ [encode max] ) zrank :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ member -> m (f (Maybe Integer)) zrank key member = sendRequest (["ZRANK"] ++ [encode key] ++ [encode member] ) hkeys :: (RedisCtx m f) => ByteString -- ^ key -> m (f [ByteString]) hkeys key = sendRequest (["HKEYS"] ++ [encode key] ) dump :: (RedisCtx m f) => ByteString -- ^ key -> m (f ByteString) dump key = sendRequest (["DUMP"] ++ [encode key] ) rpush :: (RedisCtx m f) => ByteString -- ^ key -> [ByteString] -- ^ value -> m (f Integer) rpush key value = sendRequest (["RPUSH"] ++ [encode key] ++ map encode value ) pttl :: (RedisCtx m f) => ByteString -- ^ key -> m (f Integer) pttl key = sendRequest (["PTTL"] ++ [encode key] ) spop :: (RedisCtx m f) => ByteString -- ^ key -> m (f (Maybe ByteString)) spop key = sendRequest (["SPOP"] ++ [encode key] ) randomkey :: (RedisCtx m f) => m (f (Maybe ByteString)) randomkey = sendRequest (["RANDOMKEY"] ) hsetnx :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ field -> ByteString -- ^ value -> m (f Bool) hsetnx key field value = sendRequest (["HSETNX"] ++ [encode key] ++ [encode field] ++ [encode value] ) configGet :: (RedisCtx m f) => ByteString -- ^ parameter -> m (f [(ByteString,ByteString)]) configGet parameter = sendRequest (["CONFIG","GET"] ++ [encode parameter] ) mset :: (RedisCtx m f) => [(ByteString,ByteString)] -- ^ keyValue -> m (f Status) mset keyValue = sendRequest (["MSET"] ++ concatMap (\(x,y) -> [encode x,encode y])keyValue ) setex :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ seconds -> ByteString -- ^ value -> m (f Status) setex key seconds value = sendRequest (["SETEX"] ++ [encode key] ++ [encode seconds] ++ [encode value] ) sunionstore :: (RedisCtx m f) => ByteString -- ^ destination -> [ByteString] -- ^ key -> m (f Integer) sunionstore destination key = sendRequest (["SUNIONSTORE"] ++ [encode destination] ++ map encode key ) scriptExists :: (RedisCtx m f) => [ByteString] -- ^ script -> m (f [Bool]) scriptExists script = sendRequest (["SCRIPT","EXISTS"] ++ map encode script ) brpop :: (RedisCtx m f) => [ByteString] -- ^ key -> Integer -- ^ timeout -> m (f (Maybe (ByteString,ByteString))) brpop key timeout = sendRequest (["BRPOP"] ++ map encode key ++ [encode timeout] ) psetex :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ milliseconds -> ByteString -- ^ value -> m (f Status) psetex key milliseconds value = sendRequest (["PSETEX"] ++ [encode key] ++ [encode milliseconds] ++ [encode value] ) rpoplpush :: (RedisCtx m f) => ByteString -- ^ source -> ByteString -- ^ destination -> m (f (Maybe ByteString)) rpoplpush source destination = sendRequest (["RPOPLPUSH"] ++ [encode source] ++ [encode destination] ) hlen :: (RedisCtx m f) => ByteString -- ^ key -> m (f Integer) hlen key = sendRequest (["HLEN"] ++ [encode key] ) hgetall :: (RedisCtx m f) => ByteString -- ^ key -> m (f [(ByteString,ByteString)]) hgetall key = sendRequest (["HGETALL"] ++ [encode key] ) zcard :: (RedisCtx m f) => ByteString -- ^ key -> m (f Integer) zcard key = sendRequest (["ZCARD"] ++ [encode key] ) ltrim :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ start -> Integer -- ^ stop -> m (f Status) ltrim key start stop = sendRequest (["LTRIM"] ++ [encode key] ++ [encode start] ++ [encode stop] ) lset :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ index -> ByteString -- ^ value -> m (f Status) lset key index value = sendRequest (["LSET"] ++ [encode key] ++ [encode index] ++ [encode value] ) append :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ value -> m (f Integer) append key value = sendRequest (["APPEND"] ++ [encode key] ++ [encode value] ) info :: (RedisCtx m f) => m (f ByteString) info = sendRequest (["INFO"] ) hget :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ field -> m (f (Maybe ByteString)) hget key field = sendRequest (["HGET"] ++ [encode key] ++ [encode field] ) sdiff :: (RedisCtx m f) => [ByteString] -- ^ key -> m (f [ByteString]) sdiff key = sendRequest (["SDIFF"] ++ map encode key ) getrange :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ start -> Integer -- ^ end -> m (f ByteString) getrange key start end = sendRequest (["GETRANGE"] ++ [encode key] ++ [encode start] ++ [encode end] ) zcount :: (RedisCtx m f) => ByteString -- ^ key -> Double -- ^ min -> Double -- ^ max -> m (f Integer) zcount key min max = sendRequest (["ZCOUNT"] ++ [encode key] ++ [encode min] ++ [encode max] ) srem :: (RedisCtx m f) => ByteString -- ^ key -> [ByteString] -- ^ member -> m (f Integer) srem key member = sendRequest (["SREM"] ++ [encode key] ++ map encode member ) quit :: (RedisCtx m f) => m (f Status) quit = sendRequest (["QUIT"] ) scriptLoad :: (RedisCtx m f) => ByteString -- ^ script -> m (f ByteString) scriptLoad script = sendRequest (["SCRIPT","LOAD"] ++ [encode script] ) getbit :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ offset -> m (f Integer) getbit key offset = sendRequest (["GETBIT"] ++ [encode key] ++ [encode offset] ) msetnx :: (RedisCtx m f) => [(ByteString,ByteString)] -- ^ keyValue -> m (f Bool) msetnx keyValue = sendRequest (["MSETNX"] ++ concatMap (\(x,y) -> [encode x,encode y])keyValue ) sismember :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ member -> m (f Bool) sismember key member = sendRequest (["SISMEMBER"] ++ [encode key] ++ [encode member] ) select :: (RedisCtx m f) => Integer -- ^ index -> m (f Status) select index = sendRequest (["SELECT"] ++ [encode index] ) sinterstore :: (RedisCtx m f) => ByteString -- ^ destination -> [ByteString] -- ^ key -> m (f Integer) sinterstore destination key = sendRequest (["SINTERSTORE"] ++ [encode destination] ++ map encode key ) restore :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ timeToLive -> ByteString -- ^ serializedValue -> m (f Status) restore key timeToLive serializedValue = sendRequest (["RESTORE"] ++ [encode key] ++ [encode timeToLive] ++ [encode serializedValue] ) configSet :: (RedisCtx m f) => ByteString -- ^ parameter -> ByteString -- ^ value -> m (f Status) configSet parameter value = sendRequest (["CONFIG","SET"] ++ [encode parameter] ++ [encode value] ) hexists :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ field -> m (f Bool) hexists key field = sendRequest (["HEXISTS"] ++ [encode key] ++ [encode field] ) scriptFlush :: (RedisCtx m f) => m (f Status) scriptFlush = sendRequest (["SCRIPT","FLUSH"] ) llen :: (RedisCtx m f) => ByteString -- ^ key -> m (f Integer) llen key = sendRequest (["LLEN"] ++ [encode key] ) lastsave :: (RedisCtx m f) => m (f Integer) lastsave = sendRequest (["LASTSAVE"] ) mget :: (RedisCtx m f) => [ByteString] -- ^ key -> m (f [Maybe ByteString]) mget key = sendRequest (["MGET"] ++ map encode key ) zadd :: (RedisCtx m f) => ByteString -- ^ key -> [(Double,ByteString)] -- ^ scoreMember -> m (f Integer) zadd key scoreMember = sendRequest (["ZADD"] ++ [encode key] ++ concatMap (\(x,y) -> [encode x,encode y])scoreMember ) decrby :: (RedisCtx m f) => ByteString -- ^ key -> Integer -- ^ decrement -> m (f Integer) decrby key decrement = sendRequest (["DECRBY"] ++ [encode key] ++ [encode decrement] ) hset :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ field -> ByteString -- ^ value -> m (f Bool) hset key field value = sendRequest (["HSET"] ++ [encode key] ++ [encode field] ++ [encode value] ) srandmember :: (RedisCtx m f) => ByteString -- ^ key -> m (f (Maybe ByteString)) srandmember key = sendRequest (["SRANDMEMBER"] ++ [encode key] ) lpushx :: (RedisCtx m f) => ByteString -- ^ key -> ByteString -- ^ value -> m (f Integer) lpushx key value = sendRequest (["LPUSHX"] ++ [encode key] ++ [encode value] ) persist :: (RedisCtx m f) => ByteString -- ^ key -> m (f Bool) persist key = sendRequest (["PERSIST"] ++ [encode key] )