redis-resp-0.4.0: REdis Serialization Protocol (RESP) implementation.

Safe HaskellNone
LanguageHaskell2010

Data.Redis.Command

Contents

Synopsis

Types

data Command :: * -> * where Source

Redis commands.

Constructors

Ping :: Resp -> Command () 
Echo :: FromByteString a => Resp -> Command a 
Auth :: Resp -> Command () 
Quit :: Resp -> Command () 
Select :: Resp -> Command () 
BgRewriteAOF :: Resp -> Command () 
BgSave :: Resp -> Command () 
Save :: Resp -> Command () 
DbSize :: Resp -> Command Int64 
FlushAll :: Resp -> Command () 
FlushDb :: Resp -> Command () 
LastSave :: Resp -> Command Int64 
Multi :: Resp -> Command () 
Watch :: Resp -> Command () 
Unwatch :: Resp -> Command () 
Discard :: Resp -> Command () 
Exec :: Resp -> Command () 
Del :: Resp -> Command Int64 
Dump :: Resp -> Command (Maybe ByteString) 
Exists :: Resp -> Command Bool 
Expire :: Resp -> Command Bool 
ExpireAt :: Resp -> Command Bool 
Persist :: Resp -> Command Bool 
Keys :: Resp -> Command [Key] 
RandomKey :: Resp -> Command (Maybe Key) 
Rename :: Resp -> Command () 
RenameNx :: Resp -> Command Bool 
Sort :: FromByteString a => Resp -> Command [a] 
Ttl :: Resp -> Command (Maybe TTL) 
Type :: Resp -> Command (Maybe RedisType) 
Scan :: FromByteString a => Resp -> Command (Cursor, [a]) 
Append :: Resp -> Command Int64 
Get :: FromByteString a => Resp -> Command (Maybe a) 
GetRange :: FromByteString a => Resp -> Command a 
GetSet :: FromByteString a => Resp -> Command (Maybe a) 
MGet :: FromByteString a => Resp -> Command [Maybe a] 
MSet :: Resp -> Command () 
MSetNx :: Resp -> Command Bool 
Set :: Resp -> Command Bool 
SetRange :: Resp -> Command Int64 
StrLen :: Resp -> Command Int64 
BitAnd :: Resp -> Command Int64 
BitCount :: Resp -> Command Int64 
BitNot :: Resp -> Command Int64 
BitOr :: Resp -> Command Int64 
BitPos :: Resp -> Command Int64 
BitXOr :: Resp -> Command Int64 
GetBit :: Resp -> Command Int64 
SetBit :: Resp -> Command Int64 
Decr :: Resp -> Command Int64 
DecrBy :: Resp -> Command Int64 
Incr :: Resp -> Command Int64 
IncrBy :: Resp -> Command Int64 
IncrByFloat :: Resp -> Command Double 
HDel :: Resp -> Command Int64 
HExists :: Resp -> Command Bool 
HGet :: FromByteString a => Resp -> Command (Maybe a) 
HGetAll :: FromByteString a => Resp -> Command [(Field, a)] 
HIncrBy :: Resp -> Command Int64 
HIncrByFloat :: Resp -> Command Double 
HKeys :: Resp -> Command [Field] 
HLen :: Resp -> Command Int64 
HMGet :: FromByteString a => Resp -> Command [Maybe a] 
HMSet :: Resp -> Command () 
HSet :: Resp -> Command Bool 
HSetNx :: Resp -> Command Bool 
HVals :: FromByteString a => Resp -> Command [a] 
HScan :: FromByteString a => Resp -> Command (Cursor, [a]) 
BLPop :: FromByteString a => Int64 -> Resp -> Command (Maybe (Key, a)) 
BRPop :: FromByteString a => Int64 -> Resp -> Command (Maybe (Key, a)) 
BRPopLPush :: FromByteString a => Int64 -> Resp -> Command (Maybe a) 
LIndex :: FromByteString a => Resp -> Command (Maybe a) 
LInsert :: Resp -> Command Int64 
LLen :: Resp -> Command Int64 
LPop :: FromByteString a => Resp -> Command (Maybe a) 
LPush :: Resp -> Command Int64 
LPushX :: Resp -> Command Int64 
LRange :: FromByteString a => Resp -> Command [a] 
LRem :: Resp -> Command Int64 
LSet :: Resp -> Command () 
LTrim :: Resp -> Command () 
RPop :: FromByteString a => Resp -> Command (Maybe a) 
RPopLPush :: FromByteString a => Resp -> Command (Maybe a) 
RPush :: Resp -> Command Int64 
RPushX :: Resp -> Command Int64 
SAdd :: Resp -> Command Int64 
SCard :: Resp -> Command Int64 
SDiff :: FromByteString a => Resp -> Command [a] 
SDiffStore :: Resp -> Command Int64 
SInter :: FromByteString a => Resp -> Command [a] 
SInterStore :: Resp -> Command Int64 
SIsMember :: Resp -> Command Bool 
SMembers :: FromByteString a => Resp -> Command [a] 
SMove :: Resp -> Command Bool 
SPop :: FromByteString a => Resp -> Command (Maybe a) 
SRandMember :: FromByteString a => Choose -> Resp -> Command [a] 
SRem :: Resp -> Command Int64 
SScan :: FromByteString a => Resp -> Command (Cursor, [a]) 
SUnion :: FromByteString a => Resp -> Command [a] 
SUnionStore :: Resp -> Command Int64 
ZAdd :: Resp -> Command Int64 
ZCard :: Resp -> Command Int64 
ZCount :: Resp -> Command Int64 
ZIncrBy :: Resp -> Command Double 
ZInterStore :: Resp -> Command Int64 
ZLexCount :: Resp -> Command Int64 
ZRange :: FromByteString a => Bool -> Resp -> Command (ScoreList a) 
ZRangeByLex :: FromByteString a => Resp -> Command [a] 
ZRangeByScore :: FromByteString a => Bool -> Resp -> Command (ScoreList a) 
ZRank :: Resp -> Command (Maybe Int64) 
ZRem :: Resp -> Command Int64 
ZRemRangeByLex :: Resp -> Command Int64 
ZRemRangeByRank :: Resp -> Command Int64 
ZRemRangeByScore :: Resp -> Command Int64 
ZRevRange :: FromByteString a => Bool -> Resp -> Command (ScoreList a) 
ZRevRangeByScore :: FromByteString a => Bool -> Resp -> Command (ScoreList a) 
ZRevRank :: Resp -> Command (Maybe Int64) 
ZScan :: FromByteString a => Resp -> Command (Cursor, [a]) 
ZScore :: Resp -> Command (Maybe Double) 
ZUnionStore :: Resp -> Command Int64 
PfAdd :: Resp -> Command Bool 
PfCount :: Resp -> Command Int64 
PfMerge :: Resp -> Command () 
Publish :: Resp -> Command Int64 

data PubSubCommand r where Source

Pub/Sub commands.

data RedisError Source

Redis error type.

Constructors

RedisError !ByteString

General error case.

InvalidResponse !String

The received response is invalid or unexpected (e.g. a bulk string instead of an integer).

InvalidConversion !String

ByteString conversion using FromByteString failed.

data TTL Source

A type representing time-to-live values.

Constructors

NoTTL 
TTL !Int64 

data Side Source

Used in linsert to specify the insertion point.

Constructors

Before 
After 

data Choose Source

Constructors

One

Exactly one element

Dist !Int64

n distint elements

Arb !Int64

n arbitrary (i.e. potentially repeated) elements

data Aggregate Source

Constructors

None

no aggregation

Min

take the minimum score

Max

take the maximum score

Sum

addition of scores

data Min Source

Constructors

MinIncl !ByteString

lower bound (inclusive)

MinExcl !ByteString

lower bound (exclusive)

MinInf

infinite lower bound

data Max Source

Constructors

MaxIncl !ByteString

upper bound (inclusive)

MaxExcl !ByteString

upper bound (exclusive)

MaxInf

infinite upper bound

data ScoreList a Source

Constructors

ScoreList 

Fields

scores :: [Double]
 
elements :: [a]
 

Instances

Eq a => Eq (ScoreList a) Source 
Ord a => Ord (ScoreList a) Source 
Show a => Show (ScoreList a) Source 

newtype Seconds Source

Constructors

Seconds Int64 

newtype Milliseconds Source

Constructors

Milliseconds Int64 

newtype Timestamp Source

Constructors

Timestamp Int64 

newtype Key Source

Redis key type

Constructors

Key 

Fields

key :: ByteString
 

Cursor

Non-empty lists

one :: a -> NonEmpty a Source

Options

data Opts a Source

Command options

Instances

none :: Monoid m => m Source

Bit

Commands

Connection

auth :: Monad m => ByteString -> Redis m () Source

ping :: Monad m => Redis m () Source

quit :: Monad m => Redis m () Source

select :: Monad m => Int64 -> Redis m () Source

Server

bgsave :: Monad m => Redis m () Source

flushall :: Monad m => Redis m () Source

flushdb :: Monad m => Redis m () Source

save :: Monad m => Redis m () Source

Transactions

discard :: Monad m => Redis m () Source

exec :: Monad m => Redis m () Source

multi :: Monad m => Redis m () Source

unwatch :: Monad m => Redis m () Source

Keys

rename :: Monad m => Key -> Key -> Redis m () Source

ttl :: Monad m => Key -> Redis m (Maybe TTL) Source

Strings

append :: (Monad m, ToByteString a) => Key -> a -> Redis m Int64 Source

get :: (Monad m, FromByteString a) => Key -> Redis m (Maybe a) Source

mset :: (Monad m, ToByteString a) => NonEmpty (Key, a) -> Redis m () Source

set :: (Monad m, ToByteString a) => Key -> a -> Opts "SET" -> Redis m Bool Source

ex :: Seconds -> Opts "SET" Source

xx :: Opts "SET" Source

nx :: Opts "SET" Source

setrange :: (Monad m, ToByteString a) => Key -> Int64 -> a -> Redis m Int64 Source

Bits

bitcount :: Monad m => Key -> Opts "RANGE" -> Redis m Int64 Source

range :: Int64 -> Int64 -> Opts "RANGE" Source

bitnot :: Monad m => Key -> Key -> Redis m Int64 Source

setbit :: Monad m => Key -> Int64 -> Bool -> Redis m Int64 Source

Hashes

hget :: (Monad m, FromByteString a) => Key -> Field -> Redis m (Maybe a) Source

hgetall :: (Monad m, FromByteString a) => Key -> Redis m [(Field, a)] Source

hkeys :: Monad m => Key -> Redis m [Field] Source

hmset :: (Monad m, ToByteString a) => Key -> NonEmpty (Field, a) -> Redis m () Source

hset :: (Monad m, ToByteString a) => Key -> Field -> a -> Redis m Bool Source

hsetnx :: (Monad m, ToByteString a) => Key -> Field -> a -> Redis m Bool Source

hvals :: (Monad m, FromByteString a) => Key -> Redis m [a] Source

Lists

linsert :: (Monad m, ToByteString a) => Key -> Side -> a -> a -> Redis m Int64 Source

lpop :: (Monad m, FromByteString a) => Key -> Redis m (Maybe a) Source

lpushx :: (Monad m, ToByteString a) => Key -> a -> Redis m Int64 Source

lrange :: (Monad m, FromByteString a) => Key -> Int64 -> Int64 -> Redis m [a] Source

lrem :: (Monad m, ToByteString a) => Key -> Int64 -> a -> Redis m Int64 Source

lset :: (Monad m, ToByteString a) => Key -> Int64 -> a -> Redis m () Source

ltrim :: Monad m => Key -> Int64 -> Int64 -> Redis m () Source

rpop :: (Monad m, FromByteString a) => Key -> Redis m (Maybe a) Source

rpushx :: (Monad m, ToByteString a) => Key -> a -> Redis m Int64 Source

Sets

smove :: (Monad m, ToByteString a) => Key -> Key -> a -> Redis m Bool Source

spop :: (Monad m, FromByteString a) => Key -> Redis m (Maybe a) Source

Sorted Sets

zlexcount :: Monad m => Key -> Min -> Max -> Redis m Int64 Source

zrangebylex :: (Monad m, FromByteString a) => Key -> Min -> Max -> Opts "LIMIT" -> Redis m [a] Source

zrangebyscore :: (Monad m, FromByteString a) => Key -> Double -> Double -> Bool -> Opts "LIMIT" -> Redis m (ScoreList a) Source

zrank :: (Monad m, ToByteString a) => Key -> a -> Redis m (Maybe Int64) Source

zrevrangebyscore :: (Monad m, FromByteString a) => Key -> Double -> Double -> Bool -> Opts "LIMIT" -> Redis m (ScoreList a) Source

zscore :: (Monad m, ToByteString a) => Key -> a -> Redis m (Maybe Double) Source

HyperLogLog

pfmerge :: Monad m => Key -> NonEmpty Key -> Redis m () Source

Scan

scan :: (Monad m, FromByteString a) => Cursor -> Opts "SCAN" -> Redis m (Cursor, [a]) Source

count :: Int64 -> Opts "SCAN" Source

hscan :: (Monad m, FromByteString a) => Key -> Cursor -> Opts "SCAN" -> Redis m (Cursor, [a]) Source

sscan :: (Monad m, FromByteString a) => Key -> Cursor -> Opts "SCAN" -> Redis m (Cursor, [a]) Source

zscan :: (Monad m, FromByteString a) => Key -> Cursor -> Opts "SCAN" -> Redis m (Cursor, [a]) Source

Sort

sort :: (Monad m, FromByteString a) => Key -> Opts "SORT" -> Redis m [a] Source

by :: ByteString -> Opts "SORT" Source

asc :: Opts "SORT" Source

desc :: Opts "SORT" Source

alpha :: Opts "SORT" Source

store :: Key -> Opts "SORT" Source

Pub/Sub

Response Reading

Re-exports

data NonEmpty a :: * -> *

Constructors

a :| [a] infixr 5 

Instances

nonEmpty :: [a] -> Maybe (NonEmpty a)

nonEmpty efficiently turns a normal list into a NonEmpty stream, producing Nothing if the input is empty.