Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Redis = ProgramT Command
- type PubSub = ProgramT PubSubCommand
- data Command :: * -> * where
- 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
- Subscribe :: Resp -> PubSubCommand ()
- Unsubscribe :: Resp -> PubSubCommand ()
- PSubscribe :: Resp -> PubSubCommand ()
- PUnsubscribe :: Resp -> PubSubCommand ()
- data PushMessage
- = SubscribeMessage {
- channel :: !ByteString
- subscriptions :: !Int64
- | UnsubscribeMessage {
- channel :: !ByteString
- subscriptions :: !Int64
- | Message {
- channel :: !ByteString
- message :: !ByteString
- | PMessage {
- pattern :: !ByteString
- channel :: !ByteString
- message :: !ByteString
- = SubscribeMessage {
- type Result = Either RedisError
- data RedisError
- data RedisType
- data TTL
- data Side
- data Choose
- data Aggregate
- data Min
- = MinIncl !ByteString
- | MinExcl !ByteString
- | MinInf
- data Max
- = MaxIncl !ByteString
- | MaxExcl !ByteString
- | MaxInf
- data ScoreList a = ScoreList {}
- newtype Seconds = Seconds Int64
- newtype Milliseconds = Milliseconds Int64
- newtype Timestamp = Timestamp Int64
- type Field = ByteString
- type Index = Int64
- newtype Key = Key {
- key :: ByteString
- data Cursor
- zero :: Cursor
- one :: a -> NonEmpty a
- data Opts (a :: Symbol)
- none :: Monoid m => m
- data BitStart
- data BitEnd
- start :: Int64 -> BitStart
- end :: Int64 -> BitEnd
- auth :: Monad m => ByteString -> Redis m ()
- echo :: (Monad m, ToByteString a, FromByteString a) => a -> Redis m a
- ping :: Monad m => Redis m ()
- quit :: Monad m => Redis m ()
- select :: Monad m => Int64 -> Redis m ()
- bgrewriteaof :: Monad m => Redis m ()
- bgsave :: Monad m => Redis m ()
- dbsize :: Monad m => Redis m Int64
- flushall :: Monad m => Redis m ()
- flushdb :: Monad m => Redis m ()
- lastsave :: Monad m => Redis m Int64
- save :: Monad m => Redis m ()
- discard :: Monad m => Redis m ()
- exec :: Monad m => Redis m ()
- multi :: Monad m => Redis m ()
- unwatch :: Monad m => Redis m ()
- watch :: Monad m => NonEmpty Key -> Redis m ()
- del :: Monad m => NonEmpty Key -> Redis m Int64
- dump :: Monad m => Key -> Redis m (Maybe ByteString)
- exists :: Monad m => Key -> Redis m Bool
- expire :: Monad m => Key -> Seconds -> Redis m Bool
- expireat :: Monad m => Key -> Timestamp -> Redis m Bool
- keys :: Monad m => ByteString -> Redis m [Key]
- persist :: Monad m => Key -> Redis m Bool
- randomkey :: Monad m => Redis m (Maybe Key)
- rename :: Monad m => Key -> Key -> Redis m ()
- renamenx :: Monad m => Key -> Key -> Redis m Bool
- ttl :: Monad m => Key -> Redis m (Maybe TTL)
- typeof :: Monad m => Key -> Redis m (Maybe RedisType)
- append :: (Monad m, ToByteString a) => Key -> a -> Redis m Int64
- decr :: Monad m => Key -> Redis m Int64
- decrby :: Monad m => Key -> Int64 -> Redis m Int64
- get :: (Monad m, FromByteString a) => Key -> Redis m (Maybe a)
- getrange :: (Monad m, FromByteString a) => Key -> Int64 -> Int64 -> Redis m a
- getset :: (Monad m, ToByteString a, FromByteString b) => Key -> a -> Redis m (Maybe b)
- incr :: Monad m => Key -> Redis m Int64
- incrby :: Monad m => Key -> Int64 -> Redis m Int64
- incrbyfloat :: Monad m => Key -> Double -> Redis m Double
- mget :: (Monad m, FromByteString a) => NonEmpty Key -> Redis m [Maybe a]
- mset :: (Monad m, ToByteString a) => NonEmpty (Key, a) -> Redis m ()
- msetnx :: (Monad m, ToByteString a) => NonEmpty (Key, a) -> Redis m Bool
- set :: (Monad m, ToByteString a) => Key -> a -> Opts "SET" -> Redis m Bool
- ex :: Seconds -> Opts "SET"
- px :: Milliseconds -> Opts "SET"
- xx :: Opts "SET"
- nx :: Opts "SET"
- setrange :: (Monad m, ToByteString a) => Key -> Int64 -> a -> Redis m Int64
- strlen :: Monad m => Key -> Redis m Int64
- bitand :: Monad m => Key -> NonEmpty Key -> Redis m Int64
- bitcount :: Monad m => Key -> Opts "RANGE" -> Redis m Int64
- range :: Int64 -> Int64 -> Opts "RANGE"
- bitnot :: Monad m => Key -> Key -> Redis m Int64
- bitor :: Monad m => Key -> NonEmpty Key -> Redis m Int64
- bitpos :: Monad m => Key -> Bool -> BitStart -> BitEnd -> Redis m Int64
- bitxor :: Monad m => Key -> NonEmpty Key -> Redis m Int64
- getbit :: Monad m => Key -> Int64 -> Redis m Int64
- setbit :: Monad m => Key -> Int64 -> Bool -> Redis m Int64
- hdel :: Monad m => Key -> NonEmpty Field -> Redis m Int64
- hexists :: Monad m => Key -> Field -> Redis m Bool
- hget :: (Monad m, FromByteString a) => Key -> Field -> Redis m (Maybe a)
- hgetall :: (Monad m, FromByteString a) => Key -> Redis m [(Field, a)]
- hincrby :: Monad m => Key -> Field -> Int64 -> Redis m Int64
- hincrbyfloat :: Monad m => Key -> Field -> Double -> Redis m Double
- hkeys :: Monad m => Key -> Redis m [Field]
- hlen :: Monad m => Key -> Redis m Int64
- hmget :: (Monad m, FromByteString a) => Key -> NonEmpty Field -> Redis m [Maybe a]
- hmset :: (Monad m, ToByteString a) => Key -> NonEmpty (Field, a) -> Redis m ()
- hset :: (Monad m, ToByteString a) => Key -> Field -> a -> Redis m Bool
- hsetnx :: (Monad m, ToByteString a) => Key -> Field -> a -> Redis m Bool
- hvals :: (Monad m, FromByteString a) => Key -> Redis m [a]
- blpop :: (Monad m, FromByteString a) => NonEmpty Key -> Seconds -> Redis m (Maybe (Key, a))
- brpop :: (Monad m, FromByteString a) => NonEmpty Key -> Seconds -> Redis m (Maybe (Key, a))
- brpoplpush :: (Monad m, FromByteString a) => Key -> Key -> Seconds -> Redis m (Maybe a)
- lindex :: (Monad m, FromByteString a) => Key -> Index -> Redis m (Maybe a)
- linsert :: (Monad m, ToByteString a) => Key -> Side -> a -> a -> Redis m Int64
- llen :: Monad m => Key -> Redis m Int64
- lpop :: (Monad m, FromByteString a) => Key -> Redis m (Maybe a)
- lpush :: (Monad m, ToByteString a) => Key -> NonEmpty a -> Redis m Int64
- lpushx :: (Monad m, ToByteString a) => Key -> a -> Redis m Int64
- lrange :: (Monad m, FromByteString a) => Key -> Int64 -> Int64 -> Redis m [a]
- lrem :: (Monad m, ToByteString a) => Key -> Int64 -> a -> Redis m Int64
- lset :: (Monad m, ToByteString a) => Key -> Int64 -> a -> Redis m ()
- ltrim :: Monad m => Key -> Int64 -> Int64 -> Redis m ()
- rpop :: (Monad m, FromByteString a) => Key -> Redis m (Maybe a)
- rpoplpush :: (Monad m, FromByteString a) => Key -> Key -> Redis m (Maybe a)
- rpush :: (Monad m, ToByteString a) => Key -> NonEmpty a -> Redis m Int64
- rpushx :: (Monad m, ToByteString a) => Key -> a -> Redis m Int64
- sadd :: (Monad m, ToByteString a) => Key -> NonEmpty a -> Redis m Int64
- scard :: Monad m => Key -> Redis m Int64
- sdiff :: (Monad m, FromByteString a) => NonEmpty Key -> Redis m [a]
- sdiffstore :: Monad m => Key -> NonEmpty Key -> Redis m Int64
- sinter :: (Monad m, FromByteString a) => NonEmpty Key -> Redis m [a]
- sinterstore :: Monad m => Key -> NonEmpty Key -> Redis m Int64
- sismember :: (Monad m, ToByteString a) => Key -> a -> Redis m Bool
- smembers :: (Monad m, FromByteString a) => Key -> Redis m [a]
- smove :: (Monad m, ToByteString a) => Key -> Key -> a -> Redis m Bool
- spop :: (Monad m, FromByteString a) => Key -> Redis m (Maybe a)
- srandmember :: (Monad m, FromByteString a) => Key -> Choose -> Redis m [a]
- srem :: (Monad m, ToByteString a) => Key -> NonEmpty a -> Redis m Int64
- sunion :: (Monad m, FromByteString a) => NonEmpty Key -> Redis m [a]
- sunionstore :: Monad m => Key -> NonEmpty Key -> Redis m Int64
- zadd :: (Monad m, ToByteString a) => Key -> NonEmpty (Double, a) -> Redis m Int64
- zcard :: Monad m => Key -> Redis m Int64
- zcount :: Monad m => Key -> Double -> Double -> Redis m Int64
- zincrby :: (Monad m, ToByteString a) => Key -> Double -> a -> Redis m Double
- zinterstore :: Monad m => Key -> NonEmpty Key -> [Int64] -> Aggregate -> Redis m Int64
- zlexcount :: Monad m => Key -> Min -> Max -> Redis m Int64
- zrange :: (Monad m, FromByteString a) => Key -> Int64 -> Int64 -> Bool -> Redis m (ScoreList a)
- zrangebylex :: (Monad m, FromByteString a) => Key -> Min -> Max -> Opts "LIMIT" -> Redis m [a]
- zrangebyscore :: (Monad m, FromByteString a) => Key -> Double -> Double -> Bool -> Opts "LIMIT" -> Redis m (ScoreList a)
- zrank :: (Monad m, ToByteString a) => Key -> a -> Redis m (Maybe Int64)
- zrem :: (Monad m, ToByteString a) => Key -> NonEmpty a -> Redis m Int64
- zremrangebylex :: Monad m => Key -> Min -> Max -> Redis m Int64
- zremrangebyrank :: Monad m => Key -> Int64 -> Int64 -> Redis m Int64
- zremrangebyscore :: Monad m => Key -> Double -> Double -> Redis m Int64
- zrevrangebyscore :: (Monad m, FromByteString a) => Key -> Double -> Double -> Bool -> Opts "LIMIT" -> Redis m (ScoreList a)
- zrevrange :: (Monad m, FromByteString a) => Key -> Int64 -> Int64 -> Bool -> Redis m (ScoreList a)
- zrevrank :: (Monad m, ToByteString a) => Key -> a -> Redis m (Maybe Int64)
- zscore :: (Monad m, ToByteString a) => Key -> a -> Redis m (Maybe Double)
- zunionstore :: Monad m => Key -> NonEmpty Key -> [Int64] -> Aggregate -> Redis m Int64
- pfadd :: (Monad m, ToByteString a) => Key -> NonEmpty a -> Redis m Bool
- pfcount :: Monad m => NonEmpty Key -> Redis m Int64
- pfmerge :: Monad m => Key -> NonEmpty Key -> Redis m ()
- scan :: (Monad m, FromByteString a) => Cursor -> Opts "SCAN" -> Redis m (Cursor, [a])
- match :: ByteString -> Opts "SCAN"
- count :: Int64 -> Opts "SCAN"
- hscan :: (Monad m, FromByteString a) => Key -> Cursor -> Opts "SCAN" -> Redis m (Cursor, [a])
- sscan :: (Monad m, FromByteString a) => Key -> Cursor -> Opts "SCAN" -> Redis m (Cursor, [a])
- zscan :: (Monad m, FromByteString a) => Key -> Cursor -> Opts "SCAN" -> Redis m (Cursor, [a])
- sort :: (Monad m, FromByteString a) => Key -> Opts "SORT" -> Redis m [a]
- by :: ByteString -> Opts "SORT"
- limit :: Int64 -> Int64 -> Opts o
- getkey :: NonEmpty ByteString -> Opts "SORT"
- asc :: Opts "SORT"
- desc :: Opts "SORT"
- alpha :: Opts "SORT"
- store :: Key -> Opts "SORT"
- publish :: (Monad m, ToByteString a) => ByteString -> a -> Redis m Int64
- subscribe :: Monad m => NonEmpty ByteString -> PubSub m ()
- psubscribe :: Monad m => NonEmpty ByteString -> PubSub m ()
- unsubscribe :: Monad m => [ByteString] -> PubSub m ()
- punsubscribe :: Monad m => [ByteString] -> PubSub m ()
- readInt :: String -> Resp -> Result Int64
- readInt'Null :: String -> Resp -> Result (Maybe Int64)
- readBool :: String -> Resp -> Result Bool
- readTTL :: String -> Resp -> Result (Maybe TTL)
- readBulk'Null :: FromByteString a => String -> Resp -> Result (Maybe a)
- readBulk :: FromByteString a => String -> Resp -> Result a
- readListOfMaybes :: FromByteString a => String -> Resp -> Result [Maybe a]
- readList :: FromByteString a => String -> Resp -> Result [a]
- readScoreList :: FromByteString a => String -> Bool -> Resp -> Result (ScoreList a)
- readFields :: FromByteString a => String -> Resp -> Result [(Field, a)]
- readKeyValue :: FromByteString a => String -> Resp -> Result (Maybe (Key, a))
- readBulk'Array :: FromByteString a => String -> Choose -> Resp -> Result [a]
- readScan :: FromByteString a => String -> Resp -> Result (Cursor, [a])
- matchStr :: String -> ByteString -> Resp -> Result ()
- readType :: String -> Resp -> Result (Maybe RedisType)
- fromSet :: Resp -> Result Bool
- anyStr :: String -> Resp -> Result ()
- readPushMessage :: Resp -> Result PushMessage
- data NonEmpty a = a :| [a]
- nonEmpty :: [a] -> Maybe (NonEmpty a)
Types
type PubSub = ProgramT PubSubCommand Source #
data Command :: * -> * where Source #
Redis commands.
data PubSubCommand r where Source #
Pub/Sub commands.
Subscribe :: Resp -> PubSubCommand () | |
Unsubscribe :: Resp -> PubSubCommand () | |
PSubscribe :: Resp -> PubSubCommand () | |
PUnsubscribe :: Resp -> PubSubCommand () |
data PushMessage Source #
Messages which are published to subscribers.
SubscribeMessage | |
| |
UnsubscribeMessage | |
| |
Message | |
| |
PMessage | |
|
Instances
Eq PushMessage Source # | |
Defined in Data.Redis.Command (==) :: PushMessage -> PushMessage -> Bool # (/=) :: PushMessage -> PushMessage -> Bool # | |
Ord PushMessage Source # | |
Defined in Data.Redis.Command compare :: PushMessage -> PushMessage -> Ordering # (<) :: PushMessage -> PushMessage -> Bool # (<=) :: PushMessage -> PushMessage -> Bool # (>) :: PushMessage -> PushMessage -> Bool # (>=) :: PushMessage -> PushMessage -> Bool # max :: PushMessage -> PushMessage -> PushMessage # min :: PushMessage -> PushMessage -> PushMessage # | |
Show PushMessage Source # | |
Defined in Data.Redis.Command showsPrec :: Int -> PushMessage -> ShowS # show :: PushMessage -> String # showList :: [PushMessage] -> ShowS # |
type Result = Either RedisError Source #
data RedisError Source #
Redis error type.
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 |
Instances
Eq RedisError Source # | |
Defined in Data.Redis.Command (==) :: RedisError -> RedisError -> Bool # (/=) :: RedisError -> RedisError -> Bool # | |
Ord RedisError Source # | |
Defined in Data.Redis.Command compare :: RedisError -> RedisError -> Ordering # (<) :: RedisError -> RedisError -> Bool # (<=) :: RedisError -> RedisError -> Bool # (>) :: RedisError -> RedisError -> Bool # (>=) :: RedisError -> RedisError -> Bool # max :: RedisError -> RedisError -> RedisError # min :: RedisError -> RedisError -> RedisError # | |
Show RedisError Source # | |
Defined in Data.Redis.Command showsPrec :: Int -> RedisError -> ShowS # show :: RedisError -> String # showList :: [RedisError] -> ShowS # | |
Exception RedisError Source # | |
Defined in Data.Redis.Command toException :: RedisError -> SomeException # fromException :: SomeException -> Maybe RedisError # displayException :: RedisError -> String # |
The types redis reports via type.
A type representing time-to-live values.
Used in linsert
to specify the insertion point.
One | Exactly one element |
Dist !Int64 |
|
Arb !Int64 |
|
MinIncl !ByteString | lower bound (inclusive) |
MinExcl !ByteString | lower bound (exclusive) |
MinInf | infinite lower bound |
MaxIncl !ByteString | upper bound (inclusive) |
MaxExcl !ByteString | upper bound (exclusive) |
MaxInf | infinite upper bound |
Instances
Eq a => Eq (ScoreList a) Source # | |
Ord a => Ord (ScoreList a) Source # | |
Defined in Data.Redis.Command | |
Show a => Show (ScoreList a) Source # | |
newtype Milliseconds Source #
type Field = ByteString Source #
Redis key type
Key | |
|
Cursor
Non-empty lists
Options
data Opts (a :: Symbol) Source #
Command options
Bit
Commands
Connection
echo :: (Monad m, ToByteString a, FromByteString a) => a -> Redis m a Source #
Server
bgrewriteaof :: Monad m => Redis m () Source #
Transactions
multi :: Monad m => Redis m () Source #
Note that all commands following multi
and until exec
are queued by
a Redis server. Therefore the result of any such command is not available
until the exec command completes. For example, the following is an invalid
Redis
program:
multi x <- hexists "FOO" "BAR" unless x (void $ hset "FOO" "BAR" 1) exec
This pattern is usually indicative of the desire for a transactional check-and-set operation, which may be achieved instead by the following valid command sequence:
watch ("FOO" R.:| []) x <- hexists "FOO" "BAR" multi unless x (void $ hset "FOO" "BAR" 1) exec
For more information on Redis transactions and conditional updates, see https://redis.io/topics/transactions.
Keys
Strings
getset :: (Monad m, ToByteString a, FromByteString b) => Key -> a -> Redis m (Maybe b) Source #
px :: Milliseconds -> Opts "SET" Source #
Bits
Hashes
Lists
blpop :: (Monad m, FromByteString a) => NonEmpty Key -> Seconds -> Redis m (Maybe (Key, a)) Source #
brpop :: (Monad m, FromByteString a) => NonEmpty Key -> Seconds -> Redis m (Maybe (Key, a)) Source #
brpoplpush :: (Monad m, FromByteString a) => Key -> Key -> Seconds -> Redis m (Maybe a) Source #
Sets
srandmember :: (Monad m, FromByteString a) => Key -> Choose -> Redis m [a] Source #
Sorted Sets
zrange :: (Monad m, FromByteString a) => Key -> Int64 -> Int64 -> Bool -> Redis m (ScoreList a) 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 #
zrevrangebyscore :: (Monad m, FromByteString a) => Key -> Double -> Double -> Bool -> Opts "LIMIT" -> Redis m (ScoreList a) Source #
zrevrange :: (Monad m, FromByteString a) => Key -> Int64 -> Int64 -> Bool -> Redis m (ScoreList a) Source #
HyperLogLog
Scan
match :: ByteString -> 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
by :: ByteString -> Opts "SORT" Source #
Pub/Sub
publish :: (Monad m, ToByteString a) => ByteString -> a -> Redis m Int64 Source #
psubscribe :: Monad m => NonEmpty ByteString -> PubSub m () Source #
unsubscribe :: Monad m => [ByteString] -> PubSub m () Source #
punsubscribe :: Monad m => [ByteString] -> PubSub m () Source #
Response Reading
readBulk'Null :: FromByteString a => String -> Resp -> Result (Maybe a) Source #
readListOfMaybes :: FromByteString a => String -> Resp -> Result [Maybe a] Source #
readScoreList :: FromByteString a => String -> Bool -> Resp -> Result (ScoreList a) Source #
readFields :: FromByteString a => String -> Resp -> Result [(Field, a)] Source #
readKeyValue :: FromByteString a => String -> Resp -> Result (Maybe (Key, a)) Source #
readBulk'Array :: FromByteString a => String -> Choose -> Resp -> Result [a] Source #
readPushMessage :: Resp -> Result PushMessage Source #
Re-exports
Non-empty (and non-strict) list type.
Since: base-4.9.0.0
a :| [a] infixr 5 |
Instances
Monad NonEmpty | Since: base-4.9.0.0 |
Functor NonEmpty | Since: base-4.9.0.0 |
Applicative NonEmpty | Since: base-4.9.0.0 |
Foldable NonEmpty | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => NonEmpty m -> m # foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m # foldr :: (a -> b -> b) -> b -> NonEmpty a -> b # foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b # foldl :: (b -> a -> b) -> b -> NonEmpty a -> b # foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b # foldr1 :: (a -> a -> a) -> NonEmpty a -> a # foldl1 :: (a -> a -> a) -> NonEmpty a -> a # elem :: Eq a => a -> NonEmpty a -> Bool # maximum :: Ord a => NonEmpty a -> a # minimum :: Ord a => NonEmpty a -> a # | |
Traversable NonEmpty | Since: base-4.9.0.0 |
Eq1 NonEmpty | Since: base-4.10.0.0 |
Ord1 NonEmpty | Since: base-4.10.0.0 |
Defined in Data.Functor.Classes | |
Read1 NonEmpty | Since: base-4.10.0.0 |
Defined in Data.Functor.Classes | |
Show1 NonEmpty | Since: base-4.10.0.0 |
IsList (NonEmpty a) | Since: base-4.9.0.0 |
Eq a => Eq (NonEmpty a) | |
Ord a => Ord (NonEmpty a) | |
Read a => Read (NonEmpty a) | |
Show a => Show (NonEmpty a) | |
Semigroup (NonEmpty a) | Since: base-4.9.0.0 |
type Item (NonEmpty a) | |