Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Client a
- class (Functor m, Applicative m, Monad m, MonadIO m, MonadCatch m) => MonadClient m where
- liftClient :: Client a -> m a
- runRedis :: MonadIO m => Pool -> Client a -> m a
- stepwise :: MonadClient m => Redis IO a -> m a
- pipelined :: MonadClient m => Redis IO a -> m a
- pubSub :: MonadClient m => (ByteString -> ByteString -> PubSub IO ()) -> PubSub IO () -> m ()
- data Pool
- mkPool :: MonadIO m => Logger -> Settings -> m Pool
- shutdown :: MonadIO m => Pool -> m ()
- data Settings
- defSettings :: Settings
- setHost :: String -> Settings -> Settings
- setPort :: Word16 -> Settings -> Settings
- setIdleTimeout :: NominalDiffTime -> Settings -> Settings
- setMaxConnections :: Int -> Settings -> Settings
- setPoolStripes :: Int -> Settings -> Settings
- setConnectTimeout :: NominalDiffTime -> Settings -> Settings
- setSendRecvTimeout :: NominalDiffTime -> Settings -> Settings
- data ConnectionError
- newtype InternalError = InternalError String
- newtype Timeout = Timeout String
- module Data.Redis.Command
Redis client
Redis client monad.
class (Functor m, Applicative m, Monad m, MonadIO m, MonadCatch m) => MonadClient m where Source
Monads in which Client
actions may be embedded.
liftClient :: Client a -> m a Source
Lift a computation to the Client
monad.
MonadClient Client | |
MonadClient m => MonadClient (ReaderT r m) | |
MonadClient m => MonadClient (StateT s m) | |
MonadClient m => MonadClient (StateT s m) | |
MonadClient m => MonadClient (ExceptT e m) |
stepwise :: MonadClient m => Redis IO a -> m a Source
Execute the given redis commands stepwise. I.e. every
command is send to the server and the response fetched and parsed before
the next command. A failing command which produces a RedisError
will
interrupt the command sequence and the error will be thrown as an
exception.
pipelined :: MonadClient m => Redis IO a -> m a Source
Execute the given redis commands pipelined. I.e. commands are send in
batches to the server and the responses are fetched and parsed after
a full batch has been sent. A failing command which produces
a RedisError
will not prevent subsequent commands from being
executed by the redis server. However the first error will be thrown as
an exception.
pubSub :: MonadClient m => (ByteString -> ByteString -> PubSub IO ()) -> PubSub IO () -> m () Source
Execute the given publish/subscribe commands. The first parameter is the callback function which will be invoked with channel and message once messages arrive.
Connection pool
Client and pool settings
defSettings :: Settings Source
Default settings.
- host = localhost
- port = 6379
- idle timeout = 60s
- stripes = 2
- connections per stripe = 25
- connect timeout = 5s
- send-receive timeout = 10s
setIdleTimeout :: NominalDiffTime -> Settings -> Settings Source
setMaxConnections :: Int -> Settings -> Settings Source
Maximum connections per pool stripe.
setPoolStripes :: Int -> Settings -> Settings Source
setConnectTimeout :: NominalDiffTime -> Settings -> Settings Source
When a pool connection is opened, connect timeout is the maximum time we are willing to wait for the connection attempt to the redis server to succeed.
Exceptions
data ConnectionError Source
ConnectionsBusy | All connections are in use. |
ConnectionClosed | The connection has been closed unexpectedly. |
ConnectTimeout | Connecting to redis server took too long. |
newtype InternalError Source
General error, e.g. parsing redis responses failed.
A single send-receive cycle took too long.
Re-exports
module Data.Redis.Command