redis-0.14: A driver for Redis key-value database

Safe HaskellNone
LanguageHaskell98

Database.Redis.Monad

Contents

Description

Monadic wrapper for Database.Redis.Redis

Synopsis

Types ans Constructors

class MonadIO m => WithRedis m where Source

Methods

getRedis :: m Redis Source

setRedis :: Redis -> m () Source

Instances

data Redis Source

Redis connection descriptor

Constructors

Redis 

Fields

r_lock :: RLock
 
r_st :: IORef RedisState
 

Instances

data Reply s Source

Redis reply variants

Constructors

RTimeout

Timeout. Currently unused

RParseError String

Error converting value from ByteString. It's a client-side error.

ROk

"Ok" reply

RPong

Reply for the ping command

RQueued

Used inside multi-exec block

RError String

Some kind of server-side error

RInline s

Simple oneline reply

RInt Int

Integer reply

RBulk (Maybe s)

Multiline reply

RMulti (Maybe [Reply s])

Complex reply. It may consists of various type of replys

Instances

Eq s => Eq (Reply s) 
BS s => Show (Reply s) 

data Message s Source

Constructors

MSubscribe s Int

subscribed

MUnsubscribe s Int

unsubscribed

MPSubscribe s Int

pattern subscribed

MPUnsubscribe s Int

pattern unsubscribed

MMessage s s

message recieved

MPMessage s s s

message recieved by pattern

Instances

Eq s => Eq (Message s) 
Show s => Show (Message s) 

data Interval a Source

Interval representation

Constructors

Closed a a

closed interval [a, b]

Open a a

open interval (a, b)

LeftOpen a a

left-open interval (a, b]

RightOpen a a

right-open interval [a, b)

Instances

Show a => Show (Interval a) 
IsInterval (Interval a) a

Trivial IsInterval instance

class IsInterval i a | i -> a where Source

Class for conversion value to Interval

Definied instances is:

  • the Interval itself
  • pair (a,b) for open interval
  • two-member list [a, b] for closed interval (throws runtime error if the list length is different)

Methods

toInterval :: i -> Interval a Source

Instances

IsInterval [a] a

Two-element list [a, b] converted to closed interval. No static checking of list length performed.

IsInterval (Interval a) a

Trivial IsInterval instance

IsInterval (a, a) a

Pair (a, b) converted to open interval

data SortOptions s Source

Options data type for the sort command

Constructors

SortOptions 

Fields

desc :: Bool

sort with descending order

limit :: (Int, Int)

return (from, to) elements

alpha :: Bool

sort alphabetically

sort_by :: s

sort by value from this key

get_obj :: [s]

return this keys values

store :: s

store result to this key

data Aggregate Source

Constructors

SUM 
MIN 
MAX 

sortDefaults :: SortOptions ByteString Source

Default options for the sort command

fromRInline :: (Monad m, BS s) => Reply s -> m s Source

Unwraps RInline reply.

Throws an exception when called with something different from RInline

fromRBulk :: (Monad m, BS s) => Reply s -> m (Maybe s) Source

Unwraps RBulk reply.

Throws an exception when called with something different from RBulk

fromRMulti :: (Monad m, BS s) => Reply s -> m (Maybe [Reply s]) Source

Unwraps RMulti reply

Throws an exception when called with something different from RMulti

fromRMultiBulk :: (Monad m, BS s) => Reply s -> m (Maybe [Maybe s]) Source

Unwraps RMulti reply filled with RBulk

Throws an exception when called with something different from RMulti

fromRMultiBulk' :: (Monad m, BS s) => Reply s -> m [s] Source

The same as fromRMultiBulk but with fromJust applied

fromRInt :: (Monad m, BS s) => Reply s -> m Int Source

Unwraps RInt reply

Throws an exception when called with something different from RInt

fromROk :: (Monad m, BS s) => Reply s -> m () Source

Unwraps ROk reply

Throws an exception when called with something different from ROk

noError :: (Monad m, BS s) => Reply s -> m () Source

Unwraps every non-error reply

Throws an exception when called with something different from RMulti

parseMessage :: (Monad m, BS s) => Reply ByteString -> m (Message s) Source

Parse Reply as a Message

Throws an exception on parse error

takeAll :: (Int, Int) Source

a (0, -1) range - takes all element from a list in lrange, zrange and so on

Database connection

localhost :: String Source

just a localhost

defaultPort :: String Source

default Redis port

connect :: WithRedis m => String -> String -> m () Source

Redis commands

Generic

ping :: WithRedis m => m (Reply ()) Source

auth :: WithRedis m => String -> m (Reply ()) Source

echo :: (WithRedis m, BS s) => s -> m (Reply s) Source

quit :: WithRedis m => m () Source

multi :: WithRedis m => m (Reply ()) Source

exec :: (WithRedis m, BS s) => m (Reply s) Source

discard :: WithRedis m => m (Reply ()) Source

run_multi :: (MonadCatch m, MonadMask m, WithRedis m, BS s) => m () -> m (Reply s) Source

watch :: (WithRedis m, BS s) => [s] -> m (Reply ()) Source

unwatch :: WithRedis m => m (Reply ()) Source

run_cas :: (MonadCatch m, MonadMask m, WithRedis m, BS s1) => [s1] -> m a -> m a Source

exists :: (WithRedis m, BS s) => s -> m (Reply Int) Source

del :: (WithRedis m, BS s) => s -> m (Reply Int) Source

del_ :: (WithRedis m, BS s) => [s] -> m (Reply Int) Source

getType :: (WithRedis m, BS s1) => s1 -> m RedisKeyType Source

keys :: (WithRedis m, BS s1, BS s2) => s1 -> m (Reply s2) Source

randomKey :: (WithRedis m, BS s) => m (Reply s) Source

rename :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply ()) Source

renameNx :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

expire :: (WithRedis m, BS s) => s -> Int -> m (Reply Int) Source

expireAt :: (WithRedis m, BS s) => s -> Int -> m (Reply Int) Source

persist :: (WithRedis m, BS s) => s -> m (Reply Int) Source

ttl :: (WithRedis m, BS s) => s -> m (Reply Int) Source

select :: WithRedis m => Int -> m (Reply ()) Source

move :: (WithRedis m, BS s) => s -> Int -> m (Reply Int) Source

flushDb :: WithRedis m => m (Reply ()) Source

Strings

set :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply ()) Source

setNx :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

setEx :: (WithRedis m, BS s1, BS s2) => s1 -> Int -> s2 -> m (Reply ()) Source

mSet :: (WithRedis m, BS s1, BS s2) => [(s1, s2)] -> m (Reply ()) Source

mSetNx :: (WithRedis m, BS s1, BS s2) => [(s1, s2)] -> m (Reply Int) Source

get :: (WithRedis m, BS s1, BS s2) => s1 -> m (Reply s2) Source

getSet :: (WithRedis m, BS s1, BS s2, BS s3) => s1 -> s2 -> m (Reply s3) Source

mGet :: (WithRedis m, BS s1, BS s2) => [s1] -> m (Reply s2) Source

incr :: (WithRedis m, BS s) => s -> m (Reply Int) Source

incrBy :: (WithRedis m, BS s) => s -> Int -> m (Reply Int) Source

incrByFloat :: (WithRedis m, BS s) => s -> Double -> m (Reply Double) Source

decr :: (WithRedis m, BS s) => s -> m (Reply Int) Source

decrBy :: (WithRedis m, BS s) => s -> Int -> m (Reply Int) Source

append :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

substr :: (WithRedis m, BS s1, BS s2) => s1 -> (Int, Int) -> m (Reply s2) Source

getrange :: (WithRedis m, BS s1, BS s2) => s1 -> (Int, Int) -> m (Reply s2) Source

setrange :: (WithRedis m, BS s1, BS s2) => s1 -> Int -> s2 -> m (Reply Int) Source

getbit :: (WithRedis m, BS s) => s -> Int -> m (Reply Int) Source

setbit :: (WithRedis m, BS s) => s -> Int -> Int -> m (Reply Int) Source

strlen :: (WithRedis m, BS s) => s -> m (Reply Int) Source

Lists

rpush :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

rpush_ :: (WithRedis m, BS s1, BS s2) => s1 -> [s2] -> m (Reply Int) Source

lpush :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

rpushx :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

lpushx :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

llen :: (WithRedis m, BS s) => s -> m (Reply Int) Source

lrange :: (WithRedis m, BS s1, BS s2) => s1 -> (Int, Int) -> m (Reply s2) Source

ltrim :: (WithRedis m, BS s) => s -> (Int, Int) -> m (Reply ()) Source

lindex :: (WithRedis m, BS s1, BS s2) => s1 -> Int -> m (Reply s2) Source

lset :: (WithRedis m, BS s1, BS s2) => s1 -> Int -> s2 -> m (Reply ()) Source

lrem :: (WithRedis m, BS s1, BS s2) => s1 -> Int -> s2 -> m (Reply Int) Source

lpop :: (WithRedis m, BS s1, BS s2) => s1 -> m (Reply s2) Source

rpop :: (WithRedis m, BS s1, BS s2) => s1 -> m (Reply s2) Source

rpoplpush :: (WithRedis m, BS s1, BS s2, BS s3) => s1 -> s2 -> m (Reply s3) Source

blpop :: (WithRedis m, BS s1, BS s2) => [s1] -> Int -> m (Maybe (s1, s2)) Source

brpop :: (WithRedis m, BS s1, BS s2) => [s1] -> Int -> m (Maybe (s1, s2)) Source

brpoplpush :: (WithRedis m, BS s1, BS s2, BS s3) => s1 -> s2 -> Int -> m (Maybe (Maybe s3)) Source

Sets

sadd :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

sadd_ :: (WithRedis m, BS s1, BS s2) => s1 -> [s2] -> m (Reply Int) Source

srem :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

srem_ :: (WithRedis m, BS s1, BS s2) => s1 -> [s2] -> m (Reply Int) Source

spop :: (WithRedis m, BS s1, BS s2) => s1 -> m (Reply s2) Source

smove :: (WithRedis m, BS s1, BS s2, BS s3) => s1 -> s2 -> s3 -> m (Reply Int) Source

scard :: (WithRedis m, BS s) => s -> m (Reply Int) Source

sismember :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

smembers :: (WithRedis m, BS s1, BS s2) => s1 -> m (Reply s2) Source

srandmember :: (WithRedis m, BS s1, BS s2) => s1 -> m (Reply s2) Source

sinter :: (WithRedis m, BS s1, BS s2) => [s1] -> m (Reply s2) Source

sinterStore :: (WithRedis m, BS s1, BS s2) => s1 -> [s2] -> m (Reply ()) Source

sunion :: (WithRedis m, BS s1, BS s2) => [s1] -> m (Reply s2) Source

sunionStore :: (WithRedis m, BS s1, BS s2) => s1 -> [s2] -> m (Reply ()) Source

sdiff :: (WithRedis m, BS s1, BS s2) => [s1] -> m (Reply s2) Source

sdiffStore :: (WithRedis m, BS s1, BS s2) => s1 -> [s2] -> m (Reply ()) Source

Sorted sets

zadd :: (WithRedis m, BS s1, BS s2) => s1 -> Double -> s2 -> m (Reply Int) Source

zadd_ :: (WithRedis m, BS s1, BS s2) => s1 -> [(Double, s2)] -> m (Reply Int) Source

zrem :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

zrem_ :: (WithRedis m, BS s1, BS s2) => s1 -> [s2] -> m (Reply Int) Source

zincrBy :: (WithRedis m, BS s1, BS s2, BS s3) => s1 -> Double -> s2 -> m (Reply s3) Source

zrange :: (WithRedis m, BS s1, BS s2) => s1 -> (Int, Int) -> Bool -> m (Reply s2) Source

zrevrange :: (WithRedis m, BS s1, BS s2) => s1 -> (Int, Int) -> Bool -> m (Reply s2) Source

zrangebyscore :: (WithRedis m, IsInterval i Double, BS s1, BS s2) => s1 -> i -> Maybe (Int, Int) -> Bool -> m (Reply s2) Source

zrevrangebyscore :: (WithRedis m, IsInterval i Double, BS s1, BS s2) => s1 -> i -> Maybe (Int, Int) -> Bool -> m (Reply s2) Source

zcount :: (WithRedis m, IsInterval i Double, BS s) => s -> i -> m (Reply Int) Source

zcard :: (WithRedis m, BS s) => s -> m (Reply Int) Source

zscore :: (WithRedis m, BS s1, BS s2, BS s3) => s1 -> s2 -> m (Reply s3) Source

zrank :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

zrevrank :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

zremrangebyrank :: (WithRedis m, BS s) => s -> (Int, Int) -> m (Reply Int) Source

zunion :: (WithRedis m, BS s1, BS s2) => s1 -> [s2] -> [Double] -> Aggregate -> m (Reply Int) Source

Deprecated: ZUNION command was renamed to ZUNIONSTORE

zinter :: (WithRedis m, BS s1, BS s2) => s1 -> [s2] -> [Double] -> Aggregate -> m (Reply Int) Source

Deprecated: ZINTER command was renamed to ZINTERSTORE

zunionStore :: (WithRedis m, BS s1, BS s2) => s1 -> [s2] -> [Double] -> Aggregate -> m (Reply Int) Source

zinterStore :: (WithRedis m, BS s1, BS s2) => s1 -> [s2] -> [Double] -> Aggregate -> m (Reply Int) Source

Hashes

hset :: (WithRedis m, BS s1, BS s2, BS s3) => s1 -> s2 -> s3 -> m (Reply Int) Source

hget :: (WithRedis m, BS s1, BS s2, BS s3) => s1 -> s2 -> m (Reply s3) Source

hdel :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

hdel_ :: (WithRedis m, BS s1, BS s2) => s1 -> [s2] -> m (Reply Int) Source

hmset :: (WithRedis m, BS s1, BS s2, BS s3) => s1 -> [(s2, s3)] -> m (Reply ()) Source

hmget :: (WithRedis m, BS s1, BS s2, BS s3) => s1 -> [s2] -> m (Reply s3) Source

hincrBy :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> Int -> m (Reply Int) Source

hincrByFloat :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> Double -> m (Reply Double) Source

hexists :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

hlen :: (WithRedis m, BS s) => s -> m (Reply Int) Source

hkeys :: (WithRedis m, BS s1, BS s2) => s1 -> m (Reply s2) Source

hvals :: (WithRedis m, BS s1, BS s2) => s1 -> m (Reply s2) Source

hgetall :: (WithRedis m, BS s1, BS s2) => s1 -> m (Reply s2) Source

Sorting

sort :: (WithRedis m, BS s1, BS s2, BS s3) => s1 -> SortOptions s2 -> m (Reply s3) Source

listRelated :: (WithRedis m, BS s1, BS s2, BS s3) => s1 -> s2 -> (Int, Int) -> m (Reply s3) Source

Publish/Subscribe

subscribe :: (WithRedis m, BS s1, BS s2) => [s1] -> m [Message s2] Source

unsubscribe :: (WithRedis m, BS s1, BS s2) => [s1] -> m [Message s2] Source

psubscribe :: (WithRedis m, BS s1, BS s2) => [s1] -> m [Message s2] Source

punsubscribe :: (WithRedis m, BS s1, BS s2) => [s1] -> m [Message s2] Source

publish :: (WithRedis m, BS s1, BS s2) => s1 -> s2 -> m (Reply Int) Source

listen :: (WithRedis m, BS s) => Int -> m (Maybe (Message s)) Source

Persistent control

save :: WithRedis m => m (Reply ()) Source

bgsave :: WithRedis m => m (Reply ()) Source