| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Database.Persist.Zookeeper
- data ZookeeperConf = ZookeeperConf {}
- type Connection = Pool Zookeeper
- type Action = ReaderT Zookeeper
- execZookeeper :: (Read a, Show a, Monad m, MonadIO m) => (Zookeeper -> IO (Either ZKError a)) -> Action m a
- withZookeeperPool :: (Monad m, MonadIO m) => ZookeeperConf -> (Connection -> m a) -> m a
- runZookeeperPool :: MonadBaseControl IO m => Action m b -> Connection -> m b
- defaultZookeeperConf :: ZookeeperConf
- defaultZookeeperSettings :: MkPersistSettings
- deleteRecursive :: (Monad m, MonadIO m) => String -> Action m ()
- data family BackendKey backend
- 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])
- addIdx :: [[String]] -> [(String, Int)]
- delIdx :: [(String, Int)] -> [[String]]
- dropIdx :: Int -> [[String]] -> [[String]]
- takeIdx :: Int -> [[String]] -> [[String]]
- sortIdx' :: Ord a => Bool -> [(String, a)] -> [[(String, a)]]
- sortIdx :: Ord a => Bool -> [[(String, a)]] -> [[(String, a)]]
- fstIdx :: Ord a => [[(String, a)]] -> [[String]]
- selectOptParser' :: (PersistStore backend, MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => [[String]] -> [SelectOpt val] -> ReaderT backend m [[String]]
- selectOptParser :: (PersistStore backend, MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => [String] -> [SelectOpt val] -> ReaderT backend m [String]
Documentation
data ZookeeperConf Source
Information required to connect to a Zookeeper server
Constructors
| ZookeeperConf | |
Fields
| |
Instances
type Connection = Pool Zookeeper Source
execZookeeper :: (Read a, Show a, Monad m, MonadIO m) => (Zookeeper -> IO (Either ZKError a)) -> Action m a Source
withZookeeperPool :: (Monad m, MonadIO m) => ZookeeperConf -> (Connection -> m a) -> m a Source
Run a connection reader function against a Zookeeper configuration
runZookeeperPool :: MonadBaseControl IO m => Action m b -> Connection -> m b Source
data family BackendKey backend
Instances
| Bounded (BackendKey SqlBackend) | |
| Enum (BackendKey SqlBackend) | |
| Eq (BackendKey Zookeeper) | |
| Eq (BackendKey SqlBackend) | |
| Integral (BackendKey SqlBackend) | |
| Num (BackendKey SqlBackend) | |
| Ord (BackendKey Zookeeper) | |
| Ord (BackendKey SqlBackend) | |
| Read (BackendKey Zookeeper) | |
| Read (BackendKey SqlBackend) | |
| Real (BackendKey SqlBackend) | |
| Show (BackendKey Zookeeper) | |
| Show (BackendKey SqlBackend) | |
| ToJSON (BackendKey Zookeeper) | |
| ToJSON (BackendKey SqlBackend) | |
| FromJSON (BackendKey Zookeeper) | |
| FromJSON (BackendKey SqlBackend) | |
| PathPiece (BackendKey Zookeeper) | ToPathPiece is used to convert a key to/from text |
| PathPiece (BackendKey SqlBackend) | |
| PersistFieldSql (BackendKey Zookeeper) | |
| PersistFieldSql (BackendKey SqlBackend) | |
| PersistField (BackendKey Zookeeper) | |
| PersistField (BackendKey SqlBackend) | |
| data BackendKey Zookeeper = ZooKey {} | |
| data BackendKey SqlBackend = SqlBackendKey {} |
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
selectOptParser' :: (PersistStore backend, MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => [[String]] -> [SelectOpt val] -> ReaderT backend m [[String]] Source
selectOptParser :: (PersistStore backend, MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => [String] -> [SelectOpt val] -> ReaderT backend m [String] Source