| Safe Haskell | None |
|---|
Database.Persist.Zookeeper
- data ZookeeperConf = ZookeeperConf {
- zCoord :: String
- zTimeout :: Timeout
- zNumStripes :: Int
- zIdleTime :: NominalDiffTime
- zMaxResources :: Int
- type Connection = Pool Zookeeper
- newtype ZookeeperT m a = ZookeeperT {
- runZookeeperT :: ReaderT Connection m a
- thisConnection :: Monad m => ZookeeperT m Connection
- withZookeeperConn :: (Monad m, MonadIO m) => ZookeeperConf -> (Connection -> m a) -> m a
- runZookeeperPool :: ZookeeperT m a -> Connection -> m a
- runZookeeper :: MonadBaseControl IO m => Connection -> ReaderT Zookeeper m b -> m b
- defaultZookeeperConf :: ZookeeperConf
- defaultZookeeperSettings :: MkPersistSettings
- execZookeeperT :: (Read a, Show a, Monad m, MonadIO m) => (Zookeeper -> IO (Either ZKError a)) -> ReaderT Zookeeper m a
- dummyFromFilts :: [Filter v] -> Maybe v
- data OrNull
- filterClauseHelper :: PersistEntity val => Bool -> OrNull -> val -> [Filter val] -> (Bool, Text, [PersistValue])
- filterClause :: PersistEntity val => val -> [Filter val] -> (Bool, Text, [PersistValue])
Documentation
data ZookeeperConf Source
Information required to connect to a Zookeeper server
Constructors
| ZookeeperConf | |
Fields
| |
Instances
type Connection = Pool ZookeeperSource
newtype ZookeeperT m a Source
Monad reader transformer keeping Zookeeper connection through out the work
Constructors
| ZookeeperT | |
Fields
| |
Instances
| MonadTrans ZookeeperT | |
| Monad m => Monad (ZookeeperT m) | |
| Functor m => Functor (ZookeeperT m) | |
| MonadPlus m => MonadPlus (ZookeeperT m) | |
| Applicative m => Applicative (ZookeeperT m) | |
| MonadIO m => MonadIO (ZookeeperT m) |
thisConnection :: Monad m => ZookeeperT m ConnectionSource
Extracts connection from ZookeeperT monad transformer
withZookeeperConn :: (Monad m, MonadIO m) => ZookeeperConf -> (Connection -> m a) -> m aSource
Run a connection reader function against a Zookeeper configuration
runZookeeperPool :: ZookeeperT m a -> Connection -> m aSource
runZookeeper :: MonadBaseControl IO m => Connection -> ReaderT Zookeeper m b -> m bSource
execZookeeperT :: (Read a, Show a, Monad m, MonadIO m) => (Zookeeper -> IO (Either ZKError a)) -> ReaderT Zookeeper m aSource
dummyFromFilts :: [Filter v] -> Maybe vSource
Arguments
| :: PersistEntity val | |
| => Bool | include WHERE? |
| -> OrNull | |
| -> val | |
| -> [Filter val] | |
| -> (Bool, Text, [PersistValue]) |
filterClause :: PersistEntity val => val -> [Filter val] -> (Bool, Text, [PersistValue])Source