| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Database.Persist.Zookeeper
- data ZookeeperConf = ZookeeperConf {}
- type Connection = Pool ZooStat
- newtype ZookeeperT m a = ZookeeperT {
- runZookeeperT :: ReaderT Connection m a
- runZookeeperPool :: ZookeeperT m a -> Connection -> m a
- withZookeeperConn :: (Monad m, MonadIO m) => ZookeeperConf -> (Connection -> m a) -> m a
- thisConnection :: Monad m => ZookeeperT m Connection
- module Database.Persist
- data ZookeeperBackend
- execZookeeperT :: (Read a, Show a, Monad m, MonadIO m) => (Zookeeper -> IO (Either ZKError a)) -> ZookeeperT m a
- filter2path :: PersistEntity val => [Filter val] -> String
- getMap :: PersistEntity val => val -> Map Text PersistValue
- getList :: PersistEntity val => val -> [(Text, PersistValue)]
- getFieldsName :: PersistEntity val => val -> [Text]
- getFieldName :: (PersistEntity val, PersistField typ) => EntityField val typ -> Text
- fieldval :: (PersistEntity val, PersistField typ) => EntityField val typ -> val -> PersistValue
- updateEntity :: PersistEntity val => val -> [Update val] -> Either Text val
- updateVals :: PersistEntity val => [(Text, PersistValue)] -> Update val -> [(Text, PersistValue)]
- updateVal :: PersistEntity val => PersistValue -> Update val -> PersistValue
- 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 ZooStat Source
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) | |
| (Applicative m, Functor m, MonadIO m, MonadBaseControl IO m) => PersistUnique (ZookeeperT m) | |
| (Applicative m, Functor m, MonadIO m, MonadBaseControl IO m) => PersistQuery (ZookeeperT m) | |
| (Applicative m, Functor m, MonadIO m, MonadBaseControl IO m) => PersistStore (ZookeeperT m) | |
| type PersistMonadBackend (ZookeeperT m) = ZookeeperBackend |
runZookeeperPool :: ZookeeperT m a -> Connection -> m a Source
withZookeeperConn :: (Monad m, MonadIO m) => ZookeeperConf -> (Connection -> m a) -> m a Source
Run a connection reader function against a Zookeeper configuration
thisConnection :: Monad m => ZookeeperT m Connection Source
Extracts connection from ZookeeperT monad transformer
module Database.Persist
data ZookeeperBackend Source
Instances
| PathPiece (KeyBackend ZookeeperBackend entity) | ToPathPiece is used to convert a key to/from text |
execZookeeperT :: (Read a, Show a, Monad m, MonadIO m) => (Zookeeper -> IO (Either ZKError a)) -> ZookeeperT m a Source
filter2path :: PersistEntity val => [Filter val] -> String Source
getMap :: PersistEntity val => val -> Map Text PersistValue Source
getList :: PersistEntity val => val -> [(Text, PersistValue)] Source
getFieldsName :: PersistEntity val => val -> [Text] Source
getFieldName :: (PersistEntity val, PersistField typ) => EntityField val typ -> Text Source
fieldval :: (PersistEntity val, PersistField typ) => EntityField val typ -> val -> PersistValue Source
updateEntity :: PersistEntity val => val -> [Update val] -> Either Text val Source
updateVals :: PersistEntity val => [(Text, PersistValue)] -> Update val -> [(Text, PersistValue)] Source
updateVal :: PersistEntity val => PersistValue -> Update val -> PersistValue Source
dummyFromFilts :: [Filter v] -> Maybe v Source
Arguments
| :: PersistEntity val | |
| => Bool | include WHERE? |
| -> OrNull | |
| -> val | |
| -> [Filter val] | |
| -> (Bool, Text, [PersistValue]) |
filterClause :: PersistEntity val => val -> [Filter val] -> (Bool, Text, [PersistValue]) Source