{-# LANGUAGE OverloadedStrings, FlexibleContexts #-}
module Database.Redis.Commands (
auth,
echo,
ping,
quit,
select,
del,
dump,
exists,
expire,
expireat,
keys,
MigrateOpts(..),
defaultMigrateOpts,
migrate,
migrateMultiple,
move,
objectRefcount,
objectEncoding,
objectIdletime,
persist,
pexpire,
pexpireat,
pttl,
randomkey,
rename,
renamenx,
restore,
restoreReplace,
Cursor,
cursor0,
ScanOpts(..),
defaultScanOpts,
scan,
scanOpts,
SortOpts(..),
defaultSortOpts,
SortOrder(..),
sort,
sortStore,
ttl,
RedisType(..),
getType,
wait,
hdel,
hexists,
hget,
hgetall,
hincrby,
hincrbyfloat,
hkeys,
hlen,
hmget,
hmset,
hscan,
hscanOpts,
hset,
hsetnx,
hstrlen,
hvals,
pfadd,
pfcount,
pfmerge,
blpop,
brpop,
brpoplpush,
lindex,
linsertBefore,
linsertAfter,
llen,
lpop,
lpush,
lpushx,
lrange,
lrem,
lset,
ltrim,
rpop,
rpoplpush,
rpush,
rpushx,
eval,
evalsha,
DebugMode,
scriptDebug,
scriptExists,
scriptFlush,
scriptKill,
scriptLoad,
bgrewriteaof,
bgsave,
clientGetname,
clientList,
clientPause,
ReplyMode,
clientReply,
clientSetname,
commandCount,
commandInfo,
configGet,
configResetstat,
configRewrite,
configSet,
dbsize,
debugObject,
flushall,
flushdb,
info,
infoSection,
lastsave,
save,
slaveof,
Slowlog(..),
slowlogGet,
slowlogLen,
slowlogReset,
time,
sadd,
scard,
sdiff,
sdiffstore,
sinter,
sinterstore,
sismember,
smembers,
smove,
spop,
spopN,
srandmember,
srandmemberN,
srem,
sscan,
sscanOpts,
sunion,
sunionstore,
ZaddOpts(..),
defaultZaddOpts,
zadd,
zaddOpts,
zcard,
zcount,
zincrby,
Aggregate(..),
zinterstore,
zinterstoreWeights,
zlexcount,
zrange,
zrangeWithscores,
RangeLex(..),
zrangebylex, zrangebylexLimit,
zrangebyscore,
zrangebyscoreWithscores,
zrangebyscoreLimit,
zrangebyscoreWithscoresLimit,
zrank,
zrem,
zremrangebylex,
zremrangebyrank,
zremrangebyscore,
zrevrange,
zrevrangeWithscores,
zrevrangebyscore,
zrevrangebyscoreWithscores,
zrevrangebyscoreLimit,
zrevrangebyscoreWithscoresLimit,
zrevrank,
zscan,
zscanOpts,
zscore,
zunionstore,
zunionstoreWeights,
append,
bitcount,
bitcountRange,
bitopAnd,
bitopOr,
bitopXor,
bitopNot,
bitpos,
decr,
decrby,
get,
getbit,
getrange,
getset,
incr,
incrby,
incrbyfloat,
mget,
mset,
msetnx,
psetex,
Condition(..),
SetOpts(..),
set,
setOpts,
setbit,
setex,
setnx,
setrange,
strlen,
XReadOpts(..),
defaultXreadOpts,
XReadResponse(..),
StreamsRecord(..),
TrimOpts(..),
xadd,
xaddOpts,
xread,
xreadOpts,
xreadGroup,
xreadGroupOpts,
xack,
xgroupCreate,
xgroupSetId,
xgroupDestroy,
xgroupDelConsumer,
xrange,
xrevRange,
xlen,
XPendingSummaryResponse(..),
xpendingSummary,
XPendingDetailRecord(..),
xpendingDetail,
XClaimOpts(..),
defaultXClaimOpts,
xclaim,
xclaimJustIds,
XInfoConsumersResponse(..),
xinfoConsumers,
XInfoGroupsResponse(..),
xinfoGroups,
XInfoStreamResponse(..),
xinfoStream,
xdel,
xtrim,
inf,
ClusterNodesResponse(..),
ClusterNodesResponseEntry(..),
ClusterNodesResponseSlotSpec(..),
clusterNodes,
ClusterSlotsResponse(..),
ClusterSlotsResponseEntry(..),
ClusterSlotsNode(..),
clusterSlots,
clusterSetSlotNode,
clusterSetSlotStable,
clusterSetSlotImporting,
clusterSetSlotMigrating,
clusterGetKeysInSlot,
command
) where
import Prelude hiding (min,max)
import Data.ByteString (ByteString)
import Database.Redis.ManualCommands
import Database.Redis.Types
import Database.Redis.Core(sendRequest, RedisCtx)
ttl
:: (RedisCtx m f)
=> ByteString
-> m (f Integer)
ttl :: ByteString -> m (f Integer)
ttl ByteString
key = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"TTL"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
setnx
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f Bool)
setnx :: ByteString -> ByteString -> m (f Bool)
setnx ByteString
key ByteString
value = [ByteString] -> m (f Bool)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SETNX"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
value] )
pttl
:: (RedisCtx m f)
=> ByteString
-> m (f Integer)
pttl :: ByteString -> m (f Integer)
pttl ByteString
key = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"PTTL"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
commandCount
:: (RedisCtx m f)
=> m (f Integer)
commandCount :: m (f Integer)
commandCount = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"COMMAND",ByteString
"COUNT"] )
clientSetname
:: (RedisCtx m f)
=> ByteString
-> m (f ByteString)
clientSetname :: ByteString -> m (f ByteString)
clientSetname ByteString
connectionName = [ByteString] -> m (f ByteString)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"CLIENT",ByteString
"SETNAME"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
connectionName] )
zrank
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f (Maybe Integer))
zrank :: ByteString -> ByteString -> m (f (Maybe Integer))
zrank ByteString
key ByteString
member = [ByteString] -> m (f (Maybe Integer))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"ZRANK"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
member] )
zremrangebyscore
:: (RedisCtx m f)
=> ByteString
-> Double
-> Double
-> m (f Integer)
zremrangebyscore :: ByteString -> Double -> Double -> m (f Integer)
zremrangebyscore ByteString
key Double
min Double
max = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"ZREMRANGEBYSCORE"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Double -> ByteString
forall a. RedisArg a => a -> ByteString
encode Double
min] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Double -> ByteString
forall a. RedisArg a => a -> ByteString
encode Double
max] )
hkeys
:: (RedisCtx m f)
=> ByteString
-> m (f [ByteString])
hkeys :: ByteString -> m (f [ByteString])
hkeys ByteString
key = [ByteString] -> m (f [ByteString])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"HKEYS"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
slaveof
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f Status)
slaveof :: ByteString -> ByteString -> m (f Status)
slaveof ByteString
host ByteString
port = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SLAVEOF"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
host] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
port] )
rpushx
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f Integer)
rpushx :: ByteString -> ByteString -> m (f Integer)
rpushx ByteString
key ByteString
value = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"RPUSHX"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
value] )
debugObject
:: (RedisCtx m f)
=> ByteString
-> m (f ByteString)
debugObject :: ByteString -> m (f ByteString)
debugObject ByteString
key = [ByteString] -> m (f ByteString)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"DEBUG",ByteString
"OBJECT"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
bgsave
:: (RedisCtx m f)
=> m (f Status)
bgsave :: m (f Status)
bgsave = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"BGSAVE"] )
hlen
:: (RedisCtx m f)
=> ByteString
-> m (f Integer)
hlen :: ByteString -> m (f Integer)
hlen ByteString
key = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"HLEN"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
rpoplpush
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f (Maybe ByteString))
rpoplpush :: ByteString -> ByteString -> m (f (Maybe ByteString))
rpoplpush ByteString
source ByteString
destination = [ByteString] -> m (f (Maybe ByteString))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"RPOPLPUSH"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
source] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
destination] )
brpop
:: (RedisCtx m f)
=> [ByteString]
-> Integer
-> m (f (Maybe (ByteString,ByteString)))
brpop :: [ByteString] -> Integer -> m (f (Maybe (ByteString, ByteString)))
brpop [ByteString]
key Integer
timeout = [ByteString] -> m (f (Maybe (ByteString, ByteString)))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"BRPOP"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
key [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
timeout] )
bgrewriteaof
:: (RedisCtx m f)
=> m (f Status)
bgrewriteaof :: m (f Status)
bgrewriteaof = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"BGREWRITEAOF"] )
zincrby
:: (RedisCtx m f)
=> ByteString
-> Integer
-> ByteString
-> m (f Double)
zincrby :: ByteString -> Integer -> ByteString -> m (f Double)
zincrby ByteString
key Integer
increment ByteString
member = [ByteString] -> m (f Double)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"ZINCRBY"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
increment] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
member] )
hgetall
:: (RedisCtx m f)
=> ByteString
-> m (f [(ByteString,ByteString)])
hgetall :: ByteString -> m (f [(ByteString, ByteString)])
hgetall ByteString
key = [ByteString] -> m (f [(ByteString, ByteString)])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"HGETALL"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
hmset
:: (RedisCtx m f)
=> ByteString
-> [(ByteString,ByteString)]
-> m (f Status)
hmset :: ByteString -> [(ByteString, ByteString)] -> m (f Status)
hmset ByteString
key [(ByteString, ByteString)]
fieldValue = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"HMSET"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ ((ByteString, ByteString) -> [ByteString])
-> [(ByteString, ByteString)] -> [ByteString]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(ByteString
x,ByteString
y) -> [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
x,ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
y])[(ByteString, ByteString)]
fieldValue )
sinter
:: (RedisCtx m f)
=> [ByteString]
-> m (f [ByteString])
sinter :: [ByteString] -> m (f [ByteString])
sinter [ByteString]
key = [ByteString] -> m (f [ByteString])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SINTER"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
key )
pfadd
:: (RedisCtx m f)
=> ByteString
-> [ByteString]
-> m (f Integer)
pfadd :: ByteString -> [ByteString] -> m (f Integer)
pfadd ByteString
key [ByteString]
value = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"PFADD"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
value )
zremrangebyrank
:: (RedisCtx m f)
=> ByteString
-> Integer
-> Integer
-> m (f Integer)
zremrangebyrank :: ByteString -> Integer -> Integer -> m (f Integer)
zremrangebyrank ByteString
key Integer
start Integer
stop = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"ZREMRANGEBYRANK"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
start] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
stop] )
flushdb
:: (RedisCtx m f)
=> m (f Status)
flushdb :: m (f Status)
flushdb = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"FLUSHDB"] )
sadd
:: (RedisCtx m f)
=> ByteString
-> [ByteString]
-> m (f Integer)
sadd :: ByteString -> [ByteString] -> m (f Integer)
sadd ByteString
key [ByteString]
member = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SADD"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
member )
lindex
:: (RedisCtx m f)
=> ByteString
-> Integer
-> m (f (Maybe ByteString))
lindex :: ByteString -> Integer -> m (f (Maybe ByteString))
lindex ByteString
key Integer
index = [ByteString] -> m (f (Maybe ByteString))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"LINDEX"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
index] )
lpush
:: (RedisCtx m f)
=> ByteString
-> [ByteString]
-> m (f Integer)
lpush :: ByteString -> [ByteString] -> m (f Integer)
lpush ByteString
key [ByteString]
value = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"LPUSH"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
value )
hstrlen
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f Integer)
hstrlen :: ByteString -> ByteString -> m (f Integer)
hstrlen ByteString
key ByteString
field = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"HSTRLEN"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
field] )
smove
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> ByteString
-> m (f Bool)
smove :: ByteString -> ByteString -> ByteString -> m (f Bool)
smove ByteString
source ByteString
destination ByteString
member = [ByteString] -> m (f Bool)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SMOVE"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
source] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
destination] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
member] )
zscore
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f (Maybe Double))
zscore :: ByteString -> ByteString -> m (f (Maybe Double))
zscore ByteString
key ByteString
member = [ByteString] -> m (f (Maybe Double))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"ZSCORE"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
member] )
configResetstat
:: (RedisCtx m f)
=> m (f Status)
configResetstat :: m (f Status)
configResetstat = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"CONFIG",ByteString
"RESETSTAT"] )
pfcount
:: (RedisCtx m f)
=> [ByteString]
-> m (f Integer)
pfcount :: [ByteString] -> m (f Integer)
pfcount [ByteString]
key = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"PFCOUNT"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
key )
hdel
:: (RedisCtx m f)
=> ByteString
-> [ByteString]
-> m (f Integer)
hdel :: ByteString -> [ByteString] -> m (f Integer)
hdel ByteString
key [ByteString]
field = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"HDEL"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
field )
incrbyfloat
:: (RedisCtx m f)
=> ByteString
-> Double
-> m (f Double)
incrbyfloat :: ByteString -> Double -> m (f Double)
incrbyfloat ByteString
key Double
increment = [ByteString] -> m (f Double)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"INCRBYFLOAT"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Double -> ByteString
forall a. RedisArg a => a -> ByteString
encode Double
increment] )
setbit
:: (RedisCtx m f)
=> ByteString
-> Integer
-> ByteString
-> m (f Integer)
setbit :: ByteString -> Integer -> ByteString -> m (f Integer)
setbit ByteString
key Integer
offset ByteString
value = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SETBIT"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
offset] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
value] )
flushall
:: (RedisCtx m f)
=> m (f Status)
flushall :: m (f Status)
flushall = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"FLUSHALL"] )
incrby
:: (RedisCtx m f)
=> ByteString
-> Integer
-> m (f Integer)
incrby :: ByteString -> Integer -> m (f Integer)
incrby ByteString
key Integer
increment = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"INCRBY"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
increment] )
time
:: (RedisCtx m f)
=> m (f (Integer,Integer))
time :: m (f (Integer, Integer))
time = [ByteString] -> m (f (Integer, Integer))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"TIME"] )
smembers
:: (RedisCtx m f)
=> ByteString
-> m (f [ByteString])
smembers :: ByteString -> m (f [ByteString])
smembers ByteString
key = [ByteString] -> m (f [ByteString])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SMEMBERS"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
zlexcount
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> ByteString
-> m (f Integer)
zlexcount :: ByteString -> ByteString -> ByteString -> m (f Integer)
zlexcount ByteString
key ByteString
min ByteString
max = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"ZLEXCOUNT"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
min] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
max] )
sunion
:: (RedisCtx m f)
=> [ByteString]
-> m (f [ByteString])
sunion :: [ByteString] -> m (f [ByteString])
sunion [ByteString]
key = [ByteString] -> m (f [ByteString])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SUNION"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
key )
sinterstore
:: (RedisCtx m f)
=> ByteString
-> [ByteString]
-> m (f Integer)
sinterstore :: ByteString -> [ByteString] -> m (f Integer)
sinterstore ByteString
destination [ByteString]
key = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SINTERSTORE"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
destination] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
key )
hvals
:: (RedisCtx m f)
=> ByteString
-> m (f [ByteString])
hvals :: ByteString -> m (f [ByteString])
hvals ByteString
key = [ByteString] -> m (f [ByteString])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"HVALS"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
configSet
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f Status)
configSet :: ByteString -> ByteString -> m (f Status)
configSet ByteString
parameter ByteString
value = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"CONFIG",ByteString
"SET"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
parameter] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
value] )
scriptFlush
:: (RedisCtx m f)
=> m (f Status)
scriptFlush :: m (f Status)
scriptFlush = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SCRIPT",ByteString
"FLUSH"] )
dbsize
:: (RedisCtx m f)
=> m (f Integer)
dbsize :: m (f Integer)
dbsize = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"DBSIZE"] )
wait
:: (RedisCtx m f)
=> Integer
-> Integer
-> m (f Integer)
wait :: Integer -> Integer -> m (f Integer)
wait Integer
numslaves Integer
timeout = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"WAIT"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
numslaves] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
timeout] )
lpop
:: (RedisCtx m f)
=> ByteString
-> m (f (Maybe ByteString))
lpop :: ByteString -> m (f (Maybe ByteString))
lpop ByteString
key = [ByteString] -> m (f (Maybe ByteString))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"LPOP"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
clientPause
:: (RedisCtx m f)
=> Integer
-> m (f Status)
clientPause :: Integer -> m (f Status)
clientPause Integer
timeout = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"CLIENT",ByteString
"PAUSE"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
timeout] )
expire
:: (RedisCtx m f)
=> ByteString
-> Integer
-> m (f Bool)
expire :: ByteString -> Integer -> m (f Bool)
expire ByteString
key Integer
seconds = [ByteString] -> m (f Bool)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"EXPIRE"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
seconds] )
mget
:: (RedisCtx m f)
=> [ByteString]
-> m (f [Maybe ByteString])
mget :: [ByteString] -> m (f [Maybe ByteString])
mget [ByteString]
key = [ByteString] -> m (f [Maybe ByteString])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"MGET"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
key )
bitpos
:: (RedisCtx m f)
=> ByteString
-> Integer
-> Integer
-> Integer
-> m (f Integer)
bitpos :: ByteString -> Integer -> Integer -> Integer -> m (f Integer)
bitpos ByteString
key Integer
bit Integer
start Integer
end = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"BITPOS"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
bit] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
start] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
end] )
lastsave
:: (RedisCtx m f)
=> m (f Integer)
lastsave :: m (f Integer)
lastsave = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"LASTSAVE"] )
pexpire
:: (RedisCtx m f)
=> ByteString
-> Integer
-> m (f Bool)
pexpire :: ByteString -> Integer -> m (f Bool)
pexpire ByteString
key Integer
milliseconds = [ByteString] -> m (f Bool)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"PEXPIRE"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
milliseconds] )
clientList
:: (RedisCtx m f)
=> m (f [ByteString])
clientList :: m (f [ByteString])
clientList = [ByteString] -> m (f [ByteString])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"CLIENT",ByteString
"LIST"] )
renamenx
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f Bool)
renamenx :: ByteString -> ByteString -> m (f Bool)
renamenx ByteString
key ByteString
newkey = [ByteString] -> m (f Bool)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"RENAMENX"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
newkey] )
pfmerge
:: (RedisCtx m f)
=> ByteString
-> [ByteString]
-> m (f ByteString)
pfmerge :: ByteString -> [ByteString] -> m (f ByteString)
pfmerge ByteString
destkey [ByteString]
sourcekey = [ByteString] -> m (f ByteString)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"PFMERGE"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
destkey] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
sourcekey )
lrem
:: (RedisCtx m f)
=> ByteString
-> Integer
-> ByteString
-> m (f Integer)
lrem :: ByteString -> Integer -> ByteString -> m (f Integer)
lrem ByteString
key Integer
count ByteString
value = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"LREM"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
count] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
value] )
sdiff
:: (RedisCtx m f)
=> [ByteString]
-> m (f [ByteString])
sdiff :: [ByteString] -> m (f [ByteString])
sdiff [ByteString]
key = [ByteString] -> m (f [ByteString])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SDIFF"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
key )
get
:: (RedisCtx m f)
=> ByteString
-> m (f (Maybe ByteString))
get :: ByteString -> m (f (Maybe ByteString))
get ByteString
key = [ByteString] -> m (f (Maybe ByteString))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"GET"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
getrange
:: (RedisCtx m f)
=> ByteString
-> Integer
-> Integer
-> m (f ByteString)
getrange :: ByteString -> Integer -> Integer -> m (f ByteString)
getrange ByteString
key Integer
start Integer
end = [ByteString] -> m (f ByteString)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"GETRANGE"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
start] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
end] )
sdiffstore
:: (RedisCtx m f)
=> ByteString
-> [ByteString]
-> m (f Integer)
sdiffstore :: ByteString -> [ByteString] -> m (f Integer)
sdiffstore ByteString
destination [ByteString]
key = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SDIFFSTORE"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
destination] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
key )
zcount
:: (RedisCtx m f)
=> ByteString
-> Double
-> Double
-> m (f Integer)
zcount :: ByteString -> Double -> Double -> m (f Integer)
zcount ByteString
key Double
min Double
max = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"ZCOUNT"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Double -> ByteString
forall a. RedisArg a => a -> ByteString
encode Double
min] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Double -> ByteString
forall a. RedisArg a => a -> ByteString
encode Double
max] )
scriptLoad
:: (RedisCtx m f)
=> ByteString
-> m (f ByteString)
scriptLoad :: ByteString -> m (f ByteString)
scriptLoad ByteString
script = [ByteString] -> m (f ByteString)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SCRIPT",ByteString
"LOAD"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
script] )
getset
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f (Maybe ByteString))
getset :: ByteString -> ByteString -> m (f (Maybe ByteString))
getset ByteString
key ByteString
value = [ByteString] -> m (f (Maybe ByteString))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"GETSET"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
value] )
dump
:: (RedisCtx m f)
=> ByteString
-> m (f ByteString)
dump :: ByteString -> m (f ByteString)
dump ByteString
key = [ByteString] -> m (f ByteString)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"DUMP"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
keys
:: (RedisCtx m f)
=> ByteString
-> m (f [ByteString])
keys :: ByteString -> m (f [ByteString])
keys ByteString
pattern = [ByteString] -> m (f [ByteString])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"KEYS"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
pattern] )
configGet
:: (RedisCtx m f)
=> ByteString
-> m (f [(ByteString,ByteString)])
configGet :: ByteString -> m (f [(ByteString, ByteString)])
configGet ByteString
parameter = [ByteString] -> m (f [(ByteString, ByteString)])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"CONFIG",ByteString
"GET"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
parameter] )
rpush
:: (RedisCtx m f)
=> ByteString
-> [ByteString]
-> m (f Integer)
rpush :: ByteString -> [ByteString] -> m (f Integer)
rpush ByteString
key [ByteString]
value = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"RPUSH"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
value )
randomkey
:: (RedisCtx m f)
=> m (f (Maybe ByteString))
randomkey :: m (f (Maybe ByteString))
randomkey = [ByteString] -> m (f (Maybe ByteString))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"RANDOMKEY"] )
hsetnx
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> ByteString
-> m (f Bool)
hsetnx :: ByteString -> ByteString -> ByteString -> m (f Bool)
hsetnx ByteString
key ByteString
field ByteString
value = [ByteString] -> m (f Bool)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"HSETNX"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
field] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
value] )
mset
:: (RedisCtx m f)
=> [(ByteString,ByteString)]
-> m (f Status)
mset :: [(ByteString, ByteString)] -> m (f Status)
mset [(ByteString, ByteString)]
keyValue = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"MSET"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ ((ByteString, ByteString) -> [ByteString])
-> [(ByteString, ByteString)] -> [ByteString]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(ByteString
x,ByteString
y) -> [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
x,ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
y])[(ByteString, ByteString)]
keyValue )
setex
:: (RedisCtx m f)
=> ByteString
-> Integer
-> ByteString
-> m (f Status)
setex :: ByteString -> Integer -> ByteString -> m (f Status)
setex ByteString
key Integer
seconds ByteString
value = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SETEX"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
seconds] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
value] )
psetex
:: (RedisCtx m f)
=> ByteString
-> Integer
-> ByteString
-> m (f Status)
psetex :: ByteString -> Integer -> ByteString -> m (f Status)
psetex ByteString
key Integer
milliseconds ByteString
value = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"PSETEX"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
milliseconds] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
value] )
scard
:: (RedisCtx m f)
=> ByteString
-> m (f Integer)
scard :: ByteString -> m (f Integer)
scard ByteString
key = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SCARD"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
scriptExists
:: (RedisCtx m f)
=> [ByteString]
-> m (f [Bool])
scriptExists :: [ByteString] -> m (f [Bool])
scriptExists [ByteString]
script = [ByteString] -> m (f [Bool])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SCRIPT",ByteString
"EXISTS"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
script )
sunionstore
:: (RedisCtx m f)
=> ByteString
-> [ByteString]
-> m (f Integer)
sunionstore :: ByteString -> [ByteString] -> m (f Integer)
sunionstore ByteString
destination [ByteString]
key = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SUNIONSTORE"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
destination] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
key )
persist
:: (RedisCtx m f)
=> ByteString
-> m (f Bool)
persist :: ByteString -> m (f Bool)
persist ByteString
key = [ByteString] -> m (f Bool)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"PERSIST"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
strlen
:: (RedisCtx m f)
=> ByteString
-> m (f Integer)
strlen :: ByteString -> m (f Integer)
strlen ByteString
key = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"STRLEN"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
lpushx
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f Integer)
lpushx :: ByteString -> ByteString -> m (f Integer)
lpushx ByteString
key ByteString
value = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"LPUSHX"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
value] )
hset
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> ByteString
-> m (f Integer)
hset :: ByteString -> ByteString -> ByteString -> m (f Integer)
hset ByteString
key ByteString
field ByteString
value = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"HSET"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
field] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
value] )
brpoplpush
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> Integer
-> m (f (Maybe ByteString))
brpoplpush :: ByteString -> ByteString -> Integer -> m (f (Maybe ByteString))
brpoplpush ByteString
source ByteString
destination Integer
timeout = [ByteString] -> m (f (Maybe ByteString))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"BRPOPLPUSH"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
source] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
destination] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
timeout] )
zrevrank
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f (Maybe Integer))
zrevrank :: ByteString -> ByteString -> m (f (Maybe Integer))
zrevrank ByteString
key ByteString
member = [ByteString] -> m (f (Maybe Integer))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"ZREVRANK"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
member] )
scriptKill
:: (RedisCtx m f)
=> m (f Status)
scriptKill :: m (f Status)
scriptKill = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SCRIPT",ByteString
"KILL"] )
setrange
:: (RedisCtx m f)
=> ByteString
-> Integer
-> ByteString
-> m (f Integer)
setrange :: ByteString -> Integer -> ByteString -> m (f Integer)
setrange ByteString
key Integer
offset ByteString
value = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SETRANGE"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
offset] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
value] )
del
:: (RedisCtx m f)
=> [ByteString]
-> m (f Integer)
del :: [ByteString] -> m (f Integer)
del [ByteString]
key = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"DEL"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
key )
hincrbyfloat
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> Double
-> m (f Double)
hincrbyfloat :: ByteString -> ByteString -> Double -> m (f Double)
hincrbyfloat ByteString
key ByteString
field Double
increment = [ByteString] -> m (f Double)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"HINCRBYFLOAT"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
field] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Double -> ByteString
forall a. RedisArg a => a -> ByteString
encode Double
increment] )
hincrby
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> Integer
-> m (f Integer)
hincrby :: ByteString -> ByteString -> Integer -> m (f Integer)
hincrby ByteString
key ByteString
field Integer
increment = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"HINCRBY"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
field] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
increment] )
zremrangebylex
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> ByteString
-> m (f Integer)
zremrangebylex :: ByteString -> ByteString -> ByteString -> m (f Integer)
zremrangebylex ByteString
key ByteString
min ByteString
max = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"ZREMRANGEBYLEX"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
min] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
max] )
rpop
:: (RedisCtx m f)
=> ByteString
-> m (f (Maybe ByteString))
rpop :: ByteString -> m (f (Maybe ByteString))
rpop ByteString
key = [ByteString] -> m (f (Maybe ByteString))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"RPOP"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
rename
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f Status)
rename :: ByteString -> ByteString -> m (f Status)
rename ByteString
key ByteString
newkey = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"RENAME"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
newkey] )
zrem
:: (RedisCtx m f)
=> ByteString
-> [ByteString]
-> m (f Integer)
zrem :: ByteString -> [ByteString] -> m (f Integer)
zrem ByteString
key [ByteString]
member = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"ZREM"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
member )
hexists
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f Bool)
hexists :: ByteString -> ByteString -> m (f Bool)
hexists ByteString
key ByteString
field = [ByteString] -> m (f Bool)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"HEXISTS"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
field] )
clientGetname
:: (RedisCtx m f)
=> m (f Status)
clientGetname :: m (f Status)
clientGetname = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"CLIENT",ByteString
"GETNAME"] )
configRewrite
:: (RedisCtx m f)
=> m (f Status)
configRewrite :: m (f Status)
configRewrite = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"CONFIG",ByteString
"REWRITE"] )
decr
:: (RedisCtx m f)
=> ByteString
-> m (f Integer)
decr :: ByteString -> m (f Integer)
decr ByteString
key = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"DECR"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
hmget
:: (RedisCtx m f)
=> ByteString
-> [ByteString]
-> m (f [Maybe ByteString])
hmget :: ByteString -> [ByteString] -> m (f [Maybe ByteString])
hmget ByteString
key [ByteString]
field = [ByteString] -> m (f [Maybe ByteString])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"HMGET"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
field )
lrange
:: (RedisCtx m f)
=> ByteString
-> Integer
-> Integer
-> m (f [ByteString])
lrange :: ByteString -> Integer -> Integer -> m (f [ByteString])
lrange ByteString
key Integer
start Integer
stop = [ByteString] -> m (f [ByteString])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"LRANGE"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
start] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
stop] )
decrby
:: (RedisCtx m f)
=> ByteString
-> Integer
-> m (f Integer)
decrby :: ByteString -> Integer -> m (f Integer)
decrby ByteString
key Integer
decrement = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"DECRBY"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
decrement] )
llen
:: (RedisCtx m f)
=> ByteString
-> m (f Integer)
llen :: ByteString -> m (f Integer)
llen ByteString
key = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"LLEN"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
append
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f Integer)
append :: ByteString -> ByteString -> m (f Integer)
append ByteString
key ByteString
value = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"APPEND"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
value] )
incr
:: (RedisCtx m f)
=> ByteString
-> m (f Integer)
incr :: ByteString -> m (f Integer)
incr ByteString
key = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"INCR"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
hget
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f (Maybe ByteString))
hget :: ByteString -> ByteString -> m (f (Maybe ByteString))
hget ByteString
key ByteString
field = [ByteString] -> m (f (Maybe ByteString))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"HGET"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
field] )
pexpireat
:: (RedisCtx m f)
=> ByteString
-> Integer
-> m (f Bool)
pexpireat :: ByteString -> Integer -> m (f Bool)
pexpireat ByteString
key Integer
millisecondsTimestamp = [ByteString] -> m (f Bool)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"PEXPIREAT"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
millisecondsTimestamp] )
ltrim
:: (RedisCtx m f)
=> ByteString
-> Integer
-> Integer
-> m (f Status)
ltrim :: ByteString -> Integer -> Integer -> m (f Status)
ltrim ByteString
key Integer
start Integer
stop = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"LTRIM"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
start] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
stop] )
zcard
:: (RedisCtx m f)
=> ByteString
-> m (f Integer)
zcard :: ByteString -> m (f Integer)
zcard ByteString
key = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"ZCARD"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] )
lset
:: (RedisCtx m f)
=> ByteString
-> Integer
-> ByteString
-> m (f Status)
lset :: ByteString -> Integer -> ByteString -> m (f Status)
lset ByteString
key Integer
index ByteString
value = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"LSET"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
index] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
value] )
expireat
:: (RedisCtx m f)
=> ByteString
-> Integer
-> m (f Bool)
expireat :: ByteString -> Integer -> m (f Bool)
expireat ByteString
key Integer
timestamp = [ByteString] -> m (f Bool)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"EXPIREAT"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
timestamp] )
save
:: (RedisCtx m f)
=> m (f Status)
save :: m (f Status)
save = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SAVE"] )
move
:: (RedisCtx m f)
=> ByteString
-> Integer
-> m (f Bool)
move :: ByteString -> Integer -> m (f Bool)
move ByteString
key Integer
db = [ByteString] -> m (f Bool)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"MOVE"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
db] )
getbit
:: (RedisCtx m f)
=> ByteString
-> Integer
-> m (f Integer)
getbit :: ByteString -> Integer -> m (f Integer)
getbit ByteString
key Integer
offset = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"GETBIT"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
offset] )
msetnx
:: (RedisCtx m f)
=> [(ByteString,ByteString)]
-> m (f Bool)
msetnx :: [(ByteString, ByteString)] -> m (f Bool)
msetnx [(ByteString, ByteString)]
keyValue = [ByteString] -> m (f Bool)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"MSETNX"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ ((ByteString, ByteString) -> [ByteString])
-> [(ByteString, ByteString)] -> [ByteString]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\(ByteString
x,ByteString
y) -> [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
x,ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
y])[(ByteString, ByteString)]
keyValue )
commandInfo
:: (RedisCtx m f)
=> [ByteString]
-> m (f [ByteString])
commandInfo :: [ByteString] -> m (f [ByteString])
commandInfo [ByteString]
commandName = [ByteString] -> m (f [ByteString])
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"COMMAND",ByteString
"INFO"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
commandName )
quit
:: (RedisCtx m f)
=> m (f Status)
quit :: m (f Status)
quit = [ByteString] -> m (f Status)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"QUIT"] )
blpop
:: (RedisCtx m f)
=> [ByteString]
-> Integer
-> m (f (Maybe (ByteString,ByteString)))
blpop :: [ByteString] -> Integer -> m (f (Maybe (ByteString, ByteString)))
blpop [ByteString]
key Integer
timeout = [ByteString] -> m (f (Maybe (ByteString, ByteString)))
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"BLPOP"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
key [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [Integer -> ByteString
forall a. RedisArg a => a -> ByteString
encode Integer
timeout] )
srem
:: (RedisCtx m f)
=> ByteString
-> [ByteString]
-> m (f Integer)
srem :: ByteString -> [ByteString] -> m (f Integer)
srem ByteString
key [ByteString]
member = [ByteString] -> m (f Integer)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SREM"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode [ByteString]
member )
echo
:: (RedisCtx m f)
=> ByteString
-> m (f ByteString)
echo :: ByteString -> m (f ByteString)
echo ByteString
message = [ByteString] -> m (f ByteString)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"ECHO"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
message] )
sismember
:: (RedisCtx m f)
=> ByteString
-> ByteString
-> m (f Bool)
sismember :: ByteString -> ByteString -> m (f Bool)
sismember ByteString
key ByteString
member = [ByteString] -> m (f Bool)
forall (m :: * -> *) (f :: * -> *) a.
(RedisCtx m f, RedisResult a) =>
[ByteString] -> m (f a)
sendRequest ([ByteString
"SISMEMBER"] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
key] [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ [ByteString -> ByteString
forall a. RedisArg a => a -> ByteString
encode ByteString
member] )