Monadic wrapper for Database.Redis.Redis
- class MonadIO m => WithRedis m where
- data Redis = Redis {}
- data Reply
- data Interval a
- class IsInterval i a | i -> a where
- toInterval :: i -> Interval a
- data SortOptions = SortOptions {}
- sortDefaults :: SortOptions
- fromRInline :: Monad m => Reply -> m String
- fromRBulk :: Monad m => Reply -> m (Maybe String)
- fromRMulti :: Monad m => Reply -> m (Maybe [Reply])
- fromRMultiBulk :: Monad m => Reply -> m (Maybe [Maybe String])
- fromRInt :: Monad m => Reply -> m Int
- fromROk :: Monad m => Reply -> m ()
- noError :: Monad m => Reply -> m ()
- takeAll :: (Int, Int)
- localhost :: String
- defaultPort :: String
- connect :: WithRedis m => String -> String -> m ()
- disconnect :: WithRedis m => m ()
- isConnected :: WithRedis m => m Bool
- ping :: WithRedis m => m Reply
- auth :: WithRedis m => String -> m Reply
- quit :: WithRedis m => m ()
- shutdown :: WithRedis m => m Reply
- multi :: WithRedis m => m Reply
- exec :: WithRedis m => m Reply
- discard :: WithRedis m => m Reply
- run_multi :: WithRedis m => [m Reply] -> m Reply
- exists :: WithRedis m => String -> m Reply
- del :: WithRedis m => String -> m Reply
- getType :: WithRedis m => String -> m Reply
- keys :: WithRedis m => String -> m Reply
- randomKey :: WithRedis m => m Reply
- rename :: WithRedis m => String -> String -> m Reply
- renameNx :: WithRedis m => String -> String -> m Reply
- dbsize :: WithRedis m => m Reply
- expire :: WithRedis m => String -> Int -> m Reply
- expireAt :: WithRedis m => String -> Int -> m Reply
- ttl :: WithRedis m => String -> m Reply
- select :: WithRedis m => Int -> m Reply
- move :: WithRedis m => String -> Int -> m Reply
- flushDb :: WithRedis m => m Reply
- flushAll :: WithRedis m => m Reply
- info :: WithRedis m => m Reply
- set :: WithRedis m => String -> String -> m Reply
- setNx :: WithRedis m => String -> String -> m Reply
- mSet :: WithRedis m => [(String, String)] -> m Reply
- mSetNx :: WithRedis m => [(String, String)] -> m Reply
- get :: WithRedis m => String -> m Reply
- getSet :: WithRedis m => String -> String -> m Reply
- mGet :: WithRedis m => [String] -> m Reply
- incr :: WithRedis m => String -> m Reply
- incrBy :: WithRedis m => String -> Int -> m Reply
- decr :: WithRedis m => String -> m Reply
- decrBy :: WithRedis m => String -> Int -> m Reply
- append :: WithRedis m => String -> String -> m Reply
- rpush :: WithRedis m => String -> String -> m Reply
- lpush :: WithRedis m => String -> String -> m Reply
- llen :: WithRedis m => String -> m Reply
- lrange :: WithRedis m => String -> (Int, Int) -> m Reply
- ltrim :: WithRedis m => String -> (Int, Int) -> m Reply
- lindex :: WithRedis m => String -> Int -> m Reply
- lset :: WithRedis m => String -> Int -> String -> m Reply
- lrem :: WithRedis m => String -> Int -> String -> m Reply
- lpop :: WithRedis m => String -> m Reply
- rpop :: WithRedis m => String -> m Reply
- rpoplpush :: WithRedis m => String -> String -> m Reply
- blpop :: WithRedis m => [String] -> Int -> m Reply
- brpop :: WithRedis m => [String] -> Int -> m Reply
- sadd :: WithRedis m => String -> String -> m Reply
- srem :: WithRedis m => String -> String -> m Reply
- spop :: WithRedis m => String -> m Reply
- smove :: WithRedis m => String -> String -> String -> m Reply
- scard :: WithRedis m => String -> m Reply
- sismember :: WithRedis m => String -> m Reply
- smembers :: WithRedis m => String -> m Reply
- srandmember :: WithRedis m => String -> m Reply
- sinter :: WithRedis m => [String] -> m Reply
- sinterStore :: WithRedis m => String -> [String] -> m Reply
- sunion :: WithRedis m => [String] -> m Reply
- sunionStore :: WithRedis m => String -> [String] -> m Reply
- sdiff :: WithRedis m => [String] -> m Reply
- sdiffStore :: WithRedis m => String -> [String] -> m Reply
- zadd :: WithRedis m => String -> Double -> String -> m Reply
- zrem :: WithRedis m => String -> String -> m Reply
- zincrBy :: WithRedis m => String -> Double -> String -> m Reply
- zrange :: WithRedis m => String -> (Int, Int) -> Bool -> m Reply
- zrevrange :: WithRedis m => String -> (Int, Int) -> Bool -> m Reply
- zrangebyscore :: (WithRedis m, IsInterval i Double) => String -> i -> Bool -> m Reply
- zcount :: (WithRedis m, IsInterval i Double) => String -> i -> m Reply
- zremrangebyscore :: WithRedis m => String -> (Double, Double) -> m Reply
- zcard :: WithRedis m => String -> m Reply
- zscore :: WithRedis m => String -> String -> m Reply
- sort :: WithRedis m => String -> SortOptions -> m Reply
- listRelated :: WithRedis m => String -> String -> (Int, Int) -> m Reply
- save :: WithRedis m => m Reply
- bgsave :: WithRedis m => m Reply
- lastsave :: WithRedis m => m Reply
- bgrewriteaof :: WithRedis m => m Reply
Types ans Constructors
Redis connection descriptor
Redis reply variants
RTimeout | Timeout. Currently unused |
ROk | "Ok" reply |
RPong | Reply for the ping command |
RQueued | Used inside multi-exec block |
RError String | Some kind of server-side error |
RInline String | Simple oneline reply |
RInt Int | Integer reply |
RBulk (Maybe String) | Multiline reply |
RMulti (Maybe [Reply]) | Complex reply. It may consists of various type of replys |
Interval representation
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) |
Show a => Show (Interval a) | |
IsInterval (Interval a) a | Trivial IsInterval instance |
class IsInterval i a | i -> a whereSource
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)
toInterval :: i -> Interval aSource
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 Source
Options data type for the sort
command
sortDefaults :: SortOptionsSource
Default options for the sort
command
fromRInline :: Monad m => Reply -> m StringSource
Unwraps RInline reply.
Throws an exception when called with something different from RInline
fromRBulk :: Monad m => Reply -> m (Maybe String)Source
Unwraps RBulk reply.
Throws an exception when called with something different from RBulk
fromRMulti :: Monad m => Reply -> m (Maybe [Reply])Source
Unwraps RMulti reply
Throws an exception when called with something different from RMulti
fromRMultiBulk :: Monad m => Reply -> m (Maybe [Maybe String])Source
Unwraps RMulti reply filled with RBulk
Throws an exception when called with something different from RMulti
fromRInt :: Monad m => Reply -> m IntSource
Unwraps RInt reply
Throws an exception when called with something different from RInt
fromROk :: Monad m => Reply -> m ()Source
Unwraps ROk reply
Throws an exception when called with something different from ROk
noError :: Monad m => Reply -> m ()Source
Unwraps every non-error reply
Throws an exception when called with something different from RMulti
a (0, -1) range - takes all element from a list in lrange, zrange and so on
Database connection
default Redis port
disconnect :: WithRedis m => m ()Source
isConnected :: WithRedis m => m BoolSource
Redis commands
Generic
Strings
Lists
Sets
srandmember :: WithRedis m => String -> m ReplySource
Sorted sets
zrangebyscore :: (WithRedis m, IsInterval i Double) => String -> i -> Bool -> m ReplySource
Sorting
Persistent control
bgrewriteaof :: WithRedis m => m ReplySource