-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Client library for the Redis datastore: supports full command set, -- pipelining. -- -- Redis is an open source, advanced key-value store. It is often -- referred to as a data structure server since keys can contain strings, -- hashes, lists, sets and sorted sets. This library is a Haskell client -- for the Redis datastore. Compared to other Haskell client libraries it -- has some advantages: -- -- -- -- For detailed documentation, see the Database.Redis module. @package hedis @version 0.8.3 module Database.Redis -- | Context for normal command execution, outside of transactions. Use -- runRedis to run actions of this type. -- -- In this context, each result is wrapped in an Either to account -- for the possibility of Redis returning an Error reply. data Redis a -- | Interact with a Redis datastore specified by the given -- Connection. -- -- Each call of runRedis takes a network connection from the -- Connection pool and runs the given Redis action. Calls -- to runRedis may thus block while all connections from the pool -- are in use. runRedis :: Connection -> Redis a -> IO a -- | Deconstruct Redis constructor. -- -- unRedis and reRedis can be used to define instances for -- arbitrary typeclasses. -- -- WARNING! These functions are considered internal and no guarantee is -- given at this point that they will not break in future. unRedis :: Redis a -> ReaderT RedisEnv IO a -- | Reconstruct Redis constructor. reRedis :: ReaderT RedisEnv IO a -> Redis a -- | This class captures the following behaviour: In a context m, -- a command will return it's result wrapped in a "container" of type -- f. -- -- Please refer to the Command Type Signatures section of this page for -- more information. class (MonadRedis m) => RedisCtx m f | m -> f class (Monad m) => MonadRedis m liftRedis :: MonadRedis m => Redis a -> m a -- | A threadsafe pool of network connections to a Redis server. Use the -- connect function to create one. data Connection -- | Opens a Connection to a Redis server designated by the given -- ConnectInfo. connect :: ConnectInfo -> IO Connection -- | Information for connnecting to a Redis server. -- -- It is recommended to not use the ConnInfo data constructor -- directly. Instead use defaultConnectInfo and update it with -- record syntax. For example to connect to a password protected Redis -- server running on localhost and listening to the default port: -- --
--   myConnectInfo :: ConnectInfo
--   myConnectInfo = defaultConnectInfo {connectAuth = Just "secret"}
--   
data ConnectInfo ConnInfo :: HostName -> PortID -> Maybe ByteString -> Integer -> Int -> NominalDiffTime -> ConnectInfo [connectHost] :: ConnectInfo -> HostName [connectPort] :: ConnectInfo -> PortID -- | When the server is protected by a password, set connectAuth to -- Just the password. Each connection will then authenticate by -- the auth command. [connectAuth] :: ConnectInfo -> Maybe ByteString -- | Each connection will select the database with the given index. [connectDatabase] :: ConnectInfo -> Integer -- | Maximum number of connections to keep open. The smallest acceptable -- value is 1. [connectMaxConnections] :: ConnectInfo -> Int -- | Amount of time for which an unused connection is kept open. The -- smallest acceptable value is 0.5 seconds. If the timeout -- value in your redis.conf file is non-zero, it should be larger than -- connectMaxIdleTime. [connectMaxIdleTime] :: ConnectInfo -> NominalDiffTime -- | Default information for connecting: -- --
--   connectHost           = "localhost"
--   connectPort           = PortNumber 6379 -- Redis default port
--   connectAuth           = Nothing         -- No password
--   connectDatabase       = 0               -- SELECT database 0
--   connectMaxConnections = 50              -- Up to 50 connections
--   connectMaxIdleTime    = 30              -- Keep open for 30 seconds
--   
defaultConnectInfo :: ConnectInfo -- | Either a host name e.g., "haskell.org" or a numeric host -- address string consisting of a dotted decimal IPv4 address or an IPv6 -- address e.g., "192.168.0.1". type HostName = String data PortID :: * Service :: String -> PortID PortNumber :: PortNumber -> PortID UnixSocket :: String -> PortID auth :: ByteString -> Redis (Either Reply Status) echo :: (RedisCtx m f) => ByteString -> m (f ByteString) ping :: (RedisCtx m f) => m (f Status) quit :: (RedisCtx m f) => m (f Status) select :: RedisCtx m f => Integer -> m (f Status) del :: (RedisCtx m f) => [ByteString] -> m (f Integer) dump :: (RedisCtx m f) => ByteString -> m (f ByteString) exists :: (RedisCtx m f) => ByteString -> m (f Bool) expire :: (RedisCtx m f) => ByteString -> Integer -> m (f Bool) expireat :: (RedisCtx m f) => ByteString -> Integer -> m (f Bool) keys :: (RedisCtx m f) => ByteString -> m (f [ByteString]) migrate :: (RedisCtx m f) => ByteString -> ByteString -> ByteString -> Integer -> Integer -> m (f Status) move :: (RedisCtx m f) => ByteString -> Integer -> m (f Bool) objectRefcount :: (RedisCtx m f) => ByteString -> m (f Integer) objectEncoding :: (RedisCtx m f) => ByteString -> m (f ByteString) objectIdletime :: (RedisCtx m f) => ByteString -> m (f Integer) persist :: (RedisCtx m f) => ByteString -> m (f Bool) pexpire :: (RedisCtx m f) => ByteString -> Integer -> m (f Bool) pexpireat :: (RedisCtx m f) => ByteString -> Integer -> m (f Bool) pttl :: (RedisCtx m f) => ByteString -> m (f Integer) randomkey :: (RedisCtx m f) => m (f (Maybe ByteString)) rename :: (RedisCtx m f) => ByteString -> ByteString -> m (f Status) renamenx :: (RedisCtx m f) => ByteString -> ByteString -> m (f Bool) restore :: (RedisCtx m f) => ByteString -> Integer -> ByteString -> m (f Status) -- | Options for the sort command. data SortOpts SortOpts :: Maybe ByteString -> (Integer, Integer) -> [ByteString] -> SortOrder -> Bool -> SortOpts [sortBy] :: SortOpts -> Maybe ByteString [sortLimit] :: SortOpts -> (Integer, Integer) [sortGet] :: SortOpts -> [ByteString] [sortOrder] :: SortOpts -> SortOrder [sortAlpha] :: SortOpts -> Bool -- | Redis default SortOpts. Equivalent to omitting all optional -- parameters. -- --
--   SortOpts
--       { sortBy    = Nothing -- omit the BY option
--       , sortLimit = (0,-1)  -- return entire collection
--       , sortGet   = []      -- omit the GET option
--       , sortOrder = Asc     -- sort in ascending order
--       , sortAlpha = False   -- sort numerically, not lexicographically
--       }
--   
defaultSortOpts :: SortOpts data SortOrder Asc :: SortOrder Desc :: SortOrder sort :: (RedisCtx m f) => ByteString -> SortOpts -> m (f [ByteString]) sortStore :: (RedisCtx m f) => ByteString -> ByteString -> SortOpts -> m (f Integer) ttl :: (RedisCtx m f) => ByteString -> m (f Integer) data RedisType None :: RedisType String :: RedisType Hash :: RedisType List :: RedisType Set :: RedisType ZSet :: RedisType getType :: (RedisCtx m f) => ByteString -> m (f RedisType) hdel :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f Integer) hexists :: (RedisCtx m f) => ByteString -> ByteString -> m (f Bool) hget :: (RedisCtx m f) => ByteString -> ByteString -> m (f (Maybe ByteString)) hgetall :: (RedisCtx m f) => ByteString -> m (f [(ByteString, ByteString)]) hincrby :: (RedisCtx m f) => ByteString -> ByteString -> Integer -> m (f Integer) hincrbyfloat :: (RedisCtx m f) => ByteString -> ByteString -> Double -> m (f Double) hkeys :: (RedisCtx m f) => ByteString -> m (f [ByteString]) hlen :: (RedisCtx m f) => ByteString -> m (f Integer) hmget :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f [Maybe ByteString]) hmset :: (RedisCtx m f) => ByteString -> [(ByteString, ByteString)] -> m (f Status) hset :: (RedisCtx m f) => ByteString -> ByteString -> ByteString -> m (f Bool) hsetnx :: (RedisCtx m f) => ByteString -> ByteString -> ByteString -> m (f Bool) hvals :: (RedisCtx m f) => ByteString -> m (f [ByteString]) pfadd :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f Integer) pfcount :: (RedisCtx m f) => [ByteString] -> m (f Integer) pfmerge :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f ByteString) blpop :: (RedisCtx m f) => [ByteString] -> Integer -> m (f (Maybe (ByteString, ByteString))) brpop :: (RedisCtx m f) => [ByteString] -> Integer -> m (f (Maybe (ByteString, ByteString))) brpoplpush :: (RedisCtx m f) => ByteString -> ByteString -> Integer -> m (f (Maybe ByteString)) lindex :: (RedisCtx m f) => ByteString -> Integer -> m (f (Maybe ByteString)) linsertBefore :: (RedisCtx m f) => ByteString -> ByteString -> ByteString -> m (f Integer) linsertAfter :: (RedisCtx m f) => ByteString -> ByteString -> ByteString -> m (f Integer) llen :: (RedisCtx m f) => ByteString -> m (f Integer) lpop :: (RedisCtx m f) => ByteString -> m (f (Maybe ByteString)) lpush :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f Integer) lpushx :: (RedisCtx m f) => ByteString -> ByteString -> m (f Integer) lrange :: (RedisCtx m f) => ByteString -> Integer -> Integer -> m (f [ByteString]) lrem :: (RedisCtx m f) => ByteString -> Integer -> ByteString -> m (f Integer) lset :: (RedisCtx m f) => ByteString -> Integer -> ByteString -> m (f Status) ltrim :: (RedisCtx m f) => ByteString -> Integer -> Integer -> m (f Status) rpop :: (RedisCtx m f) => ByteString -> m (f (Maybe ByteString)) rpoplpush :: (RedisCtx m f) => ByteString -> ByteString -> m (f (Maybe ByteString)) rpush :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f Integer) rpushx :: (RedisCtx m f) => ByteString -> ByteString -> m (f Integer) eval :: (RedisCtx m f, RedisResult a) => ByteString -> [ByteString] -> [ByteString] -> m (f a) evalsha :: (RedisCtx m f, RedisResult a) => ByteString -> [ByteString] -> [ByteString] -> m (f a) scriptExists :: (RedisCtx m f) => [ByteString] -> m (f [Bool]) scriptFlush :: (RedisCtx m f) => m (f Status) scriptKill :: (RedisCtx m f) => m (f Status) scriptLoad :: (RedisCtx m f) => ByteString -> m (f ByteString) bgrewriteaof :: (RedisCtx m f) => m (f Status) bgsave :: (RedisCtx m f) => m (f Status) configGet :: (RedisCtx m f) => ByteString -> m (f [(ByteString, ByteString)]) configResetstat :: (RedisCtx m f) => m (f Status) configSet :: (RedisCtx m f) => ByteString -> ByteString -> m (f Status) dbsize :: (RedisCtx m f) => m (f Integer) debugObject :: (RedisCtx m f) => ByteString -> m (f ByteString) flushall :: (RedisCtx m f) => m (f Status) flushdb :: (RedisCtx m f) => m (f Status) info :: (RedisCtx m f) => m (f ByteString) lastsave :: (RedisCtx m f) => m (f Integer) save :: (RedisCtx m f) => m (f Status) slaveof :: (RedisCtx m f) => ByteString -> ByteString -> m (f Status) -- | A single entry from the slowlog. data Slowlog Slowlog :: Integer -> Integer -> Integer -> [ByteString] -> Slowlog -- | A unique progressive identifier for every slow log entry. [slowlogId] :: Slowlog -> Integer -- | The unix timestamp at which the logged command was processed. [slowlogTimestamp] :: Slowlog -> Integer -- | The amount of time needed for its execution, in microseconds. [slowlogMicros] :: Slowlog -> Integer -- | The command and it's arguments. [slowlogCmd] :: Slowlog -> [ByteString] slowlogGet :: (RedisCtx m f) => Integer -> m (f [Slowlog]) slowlogLen :: (RedisCtx m f) => m (f Integer) slowlogReset :: (RedisCtx m f) => m (f Status) time :: (RedisCtx m f) => m (f (Integer, Integer)) sadd :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f Integer) scard :: (RedisCtx m f) => ByteString -> m (f Integer) sdiff :: (RedisCtx m f) => [ByteString] -> m (f [ByteString]) sdiffstore :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f Integer) sinter :: (RedisCtx m f) => [ByteString] -> m (f [ByteString]) sinterstore :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f Integer) sismember :: (RedisCtx m f) => ByteString -> ByteString -> m (f Bool) smembers :: (RedisCtx m f) => ByteString -> m (f [ByteString]) smove :: (RedisCtx m f) => ByteString -> ByteString -> ByteString -> m (f Bool) spop :: (RedisCtx m f) => ByteString -> m (f (Maybe ByteString)) srandmember :: (RedisCtx m f) => ByteString -> m (f (Maybe ByteString)) srem :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f Integer) sunion :: (RedisCtx m f) => [ByteString] -> m (f [ByteString]) sunionstore :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f Integer) zadd :: (RedisCtx m f) => ByteString -> [(Double, ByteString)] -> m (f Integer) zcard :: (RedisCtx m f) => ByteString -> m (f Integer) zcount :: (RedisCtx m f) => ByteString -> Double -> Double -> m (f Integer) zincrby :: (RedisCtx m f) => ByteString -> Integer -> ByteString -> m (f Double) data Aggregate Sum :: Aggregate Min :: Aggregate Max :: Aggregate zinterstore :: (RedisCtx m f) => ByteString -> [ByteString] -> Aggregate -> m (f Integer) zinterstoreWeights :: (RedisCtx m f) => ByteString -> [(ByteString, Double)] -> Aggregate -> m (f Integer) zrange :: (RedisCtx m f) => ByteString -> Integer -> Integer -> m (f [ByteString]) zrangeWithscores :: (RedisCtx m f) => ByteString -> Integer -> Integer -> m (f [(ByteString, Double)]) zrangebyscore :: (RedisCtx m f) => ByteString -> Double -> Double -> m (f [ByteString]) zrangebyscoreWithscores :: (RedisCtx m f) => ByteString -> Double -> Double -> m (f [(ByteString, Double)]) zrangebyscoreLimit :: (RedisCtx m f) => ByteString -> Double -> Double -> Integer -> Integer -> m (f [ByteString]) zrangebyscoreWithscoresLimit :: (RedisCtx m f) => ByteString -> Double -> Double -> Integer -> Integer -> m (f [(ByteString, Double)]) zrank :: (RedisCtx m f) => ByteString -> ByteString -> m (f (Maybe Integer)) zrem :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f Integer) zremrangebyrank :: (RedisCtx m f) => ByteString -> Integer -> Integer -> m (f Integer) zremrangebyscore :: (RedisCtx m f) => ByteString -> Double -> Double -> m (f Integer) zrevrange :: (RedisCtx m f) => ByteString -> Integer -> Integer -> m (f [ByteString]) zrevrangeWithscores :: (RedisCtx m f) => ByteString -> Integer -> Integer -> m (f [(ByteString, Double)]) zrevrangebyscore :: (RedisCtx m f) => ByteString -> Double -> Double -> m (f [ByteString]) zrevrangebyscoreWithscores :: (RedisCtx m f) => ByteString -> Double -> Double -> m (f [(ByteString, Double)]) zrevrangebyscoreLimit :: (RedisCtx m f) => ByteString -> Double -> Double -> Integer -> Integer -> m (f [ByteString]) zrevrangebyscoreWithscoresLimit :: (RedisCtx m f) => ByteString -> Double -> Double -> Integer -> Integer -> m (f [(ByteString, Double)]) zrevrank :: (RedisCtx m f) => ByteString -> ByteString -> m (f (Maybe Integer)) zscore :: (RedisCtx m f) => ByteString -> ByteString -> m (f (Maybe Double)) zunionstore :: (RedisCtx m f) => ByteString -> [ByteString] -> Aggregate -> m (f Integer) zunionstoreWeights :: (RedisCtx m f) => ByteString -> [(ByteString, Double)] -> Aggregate -> m (f Integer) append :: (RedisCtx m f) => ByteString -> ByteString -> m (f Integer) bitcount :: (RedisCtx m f) => ByteString -> m (f Integer) bitcountRange :: (RedisCtx m f) => ByteString -> Integer -> Integer -> m (f Integer) bitopAnd :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f Integer) bitopOr :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f Integer) bitopXor :: (RedisCtx m f) => ByteString -> [ByteString] -> m (f Integer) bitopNot :: (RedisCtx m f) => ByteString -> ByteString -> m (f Integer) decr :: (RedisCtx m f) => ByteString -> m (f Integer) decrby :: (RedisCtx m f) => ByteString -> Integer -> m (f Integer) get :: (RedisCtx m f) => ByteString -> m (f (Maybe ByteString)) getbit :: (RedisCtx m f) => ByteString -> Integer -> m (f Integer) getrange :: (RedisCtx m f) => ByteString -> Integer -> Integer -> m (f ByteString) getset :: (RedisCtx m f) => ByteString -> ByteString -> m (f (Maybe ByteString)) incr :: (RedisCtx m f) => ByteString -> m (f Integer) incrby :: (RedisCtx m f) => ByteString -> Integer -> m (f Integer) incrbyfloat :: (RedisCtx m f) => ByteString -> Double -> m (f Double) mget :: (RedisCtx m f) => [ByteString] -> m (f [Maybe ByteString]) mset :: (RedisCtx m f) => [(ByteString, ByteString)] -> m (f Status) msetnx :: (RedisCtx m f) => [(ByteString, ByteString)] -> m (f Bool) psetex :: (RedisCtx m f) => ByteString -> Integer -> ByteString -> m (f Status) set :: (RedisCtx m f) => ByteString -> ByteString -> m (f Status) setbit :: (RedisCtx m f) => ByteString -> Integer -> ByteString -> m (f Integer) setex :: (RedisCtx m f) => ByteString -> Integer -> ByteString -> m (f Status) setnx :: (RedisCtx m f) => ByteString -> ByteString -> m (f Bool) setrange :: (RedisCtx m f) => ByteString -> Integer -> ByteString -> m (f Integer) strlen :: (RedisCtx m f) => ByteString -> m (f Integer) -- | Watch the given keys to determine execution of the MULTI/EXEC block -- (http://redis.io/commands/watch). watch :: [ByteString] -> Redis (Either Reply Status) -- | Forget about all watched keys -- (http://redis.io/commands/unwatch). unwatch :: Redis (Either Reply Status) -- | Run commands inside a transaction. For documentation on the semantics -- of Redis transaction see http://redis.io/topics/transactions. -- -- Inside the transaction block, command functions return their result -- wrapped in a Queued. The Queued result is a proxy object -- for the actual command's result, which will only be available after -- EXECing the transaction. -- -- Example usage (note how Queued 's Applicative instance -- is used to combine the two individual results): -- --
--   runRedis conn $ do
--       set "hello" "hello"
--       set "world" "world"
--       helloworld <- multiExec $ do
--           hello <- get "hello"
--           world <- get "world"
--           return $ (,) <$> hello <*> world
--       liftIO (print helloworld)
--   
--   
multiExec :: RedisTx (Queued a) -> Redis (TxResult a) -- | A Queued value represents the result of a command inside a -- transaction. It is a proxy object for the actual result, which -- will only be available after returning from a multiExec -- transaction. -- -- Queued values are composable by utilizing the Functor, -- Applicative or Monad interfaces. data Queued a -- | Result of a multiExec transaction. data TxResult a -- | Transaction completed successfully. The wrapped value corresponds to -- the Queued value returned from the multiExec argument -- action. TxSuccess :: a -> TxResult a -- | Transaction aborted due to an earlier watch command. TxAborted :: TxResult a -- | At least one of the commands returned an Error reply. TxError :: String -> TxResult a -- | Command-context inside of MULTI/EXEC transactions. Use -- multiExec to run actions of this type. -- -- In the RedisTx context, all commands return a Queued -- value. It is a proxy object for the actual result, which will -- only be available after finishing the transaction. data RedisTx a -- | Post a message to a channel (http://redis.io/commands/publish). publish :: (RedisCtx m f) => ByteString -> ByteString -> m (f Integer) -- | Listens to published messages on subscribed channels and channels -- matching the subscribed patterns. For documentation on the semantics -- of Redis Pub/Sub see http://redis.io/topics/pubsub. -- -- The given callback function is called for each received message. -- Subscription changes are triggered by the returned PubSub. To -- keep subscriptions unchanged, the callback can return mempty. -- -- Example: Subscribe to the "news" channel indefinitely. -- --
--   pubSub (subscribe ["news"]) $ \msg -> do
--       putStrLn $ "Message from " ++ show (msgChannel msg)
--       return mempty
--   
--   
-- -- Example: Receive a single message from the "chat" channel. -- --
--   pubSub (subscribe ["chat"]) $ \msg -> do
--       putStrLn $ "Message from " ++ show (msgChannel msg)
--       return $ unsubscribe ["chat"]
--   
--   
-- -- It should be noted that Redis Pub/Sub by its nature is asynchronous so -- returning unsubscribe does not mean that callback won't be able -- to receive any further messages. And to guarantee that you won't won't -- process messages after unsubscription and won't unsubscribe from the -- same channel more than once you need to use IORef or -- something similar pubSub :: PubSub -> (Message -> IO PubSub) -> Redis () data Message Message :: ByteString -> Message [msgChannel, msgMessage] :: Message -> ByteString PMessage :: ByteString -> Message [msgPattern, msgChannel, msgMessage] :: Message -> ByteString -- | Encapsulates subscription changes. Use subscribe, -- unsubscribe, psubscribe, punsubscribe or -- mempty to construct a value. Combine values by using the -- Monoid interface, i.e. mappend and mconcat. data PubSub -- | Listen for messages published to the given channels -- (http://redis.io/commands/subscribe). subscribe :: [ByteString] -> PubSub -- | Stop listening for messages posted to the given channels -- (http://redis.io/commands/unsubscribe). unsubscribe :: [ByteString] -> PubSub -- | Listen for messages published to channels matching the given patterns -- (http://redis.io/commands/psubscribe). psubscribe :: [ByteString] -> PubSub -- | Stop listening for messages posted to channels matching the given -- patterns (http://redis.io/commands/punsubscribe). punsubscribe :: [ByteString] -> PubSub -- | sendRequest can be used to implement commands from experimental -- versions of Redis. An example of how to implement a command is given -- below. -- --
--   -- |Redis DEBUG OBJECT command
--   debugObject :: ByteString -> Redis (Either Reply ByteString)
--   debugObject key = sendRequest ["DEBUG", "OBJECT", key]
--   
sendRequest :: (RedisCtx m f, RedisResult a) => [ByteString] -> m (f a) -- | Low-level representation of replies from the Redis server. data Reply SingleLine :: ByteString -> Reply Error :: ByteString -> Reply Integer :: Integer -> Reply Bulk :: (Maybe ByteString) -> Reply MultiBulk :: (Maybe [Reply]) -> Reply data Status Ok :: Status Pong :: Status Status :: ByteString -> Status class RedisResult a decode :: RedisResult a => Reply -> Either Reply a data ConnectionLostException ConnectionLost :: ConnectionLostException