Copyright | (C) 2013 Diego Souza |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Diego Souza <dsouza@c0d3.xxx> |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
Zookeeper client library
- addAuth :: Zookeeper -> Scheme -> ByteString -> (Either ZKError () -> IO ()) -> IO ()
- setWatcher :: Zookeeper -> Watcher -> IO ()
- withZookeeper :: String -> Timeout -> Maybe Watcher -> Maybe ClientID -> (Zookeeper -> IO a) -> IO a
- getState :: Zookeeper -> IO State
- getClientId :: Zookeeper -> IO ClientID
- setDebugLevel :: ZLogLevel -> IO ()
- getRecvTimeout :: Zookeeper -> IO Int
- get :: Zookeeper -> String -> Maybe Watcher -> IO (Either ZKError (Maybe ByteString, Stat))
- exists :: Zookeeper -> String -> Maybe Watcher -> IO (Either ZKError Stat)
- getAcl :: Zookeeper -> String -> IO (Either ZKError (AclList, Stat))
- getChildren :: Zookeeper -> String -> Maybe Watcher -> IO (Either ZKError [String])
- ownsEphemeral :: ClientID -> Stat -> IO Bool
- set :: Zookeeper -> String -> Maybe ByteString -> Maybe Version -> IO (Either ZKError Stat)
- create :: Zookeeper -> String -> Maybe ByteString -> AclList -> [CreateFlag] -> IO (Either ZKError String)
- delete :: Zookeeper -> String -> Maybe Version -> IO (Either ZKError ())
- setAcl :: Zookeeper -> String -> Maybe Version -> AclList -> IO (Either ZKError ())
- type Scheme = String
- type Timeout = Int
- type Watcher = Zookeeper -> Event -> State -> Maybe String -> IO ()
- data ClientID
- data Zookeeper
- data Acl = Acl {}
- data Perm
- data Stat = Stat {}
- data Event
- data State
- data AclList
- = List [Acl]
- | CreatorAll
- | OpenAclUnsafe
- | ReadAclUnsafe
- type Version = Int32
- data ZLogLevel
- data CreateFlag
- data ZKError
- = ApiError
- | NoAuthError
- | NoNodeError
- | SystemError
- | ClosingError
- | NothingError
- | NotEmptyError
- | AuthFailedError
- | BadVersionError
- | InvalidACLError
- | NodeExistsError
- | MarshallingError
- | BadArgumentsError
- | InvalidStateError
- | SessionMovedError
- | UnimplmenetedError
- | ConnectionLossError
- | SessionExpiredError
- | InvalidCallbackError
- | OperationTimeoutError
- | DataInconsistencyError
- | RuntimeInconsistencyError
- | NoChildrenForEphemeralsError
- | UnknownError Int
Description
This library provides haskell bindings for zookeeper c-library (mt).
Example
The following snippet creates a ''/foobar'' znode, then it lists and prints all children of the root znode:
module Main where import Database.Zookeeper import Control.Concurrent main :: IO () main = do mvar <- newEmptyMVar withZookeeper "localhost:2181" 1000 (Just $ watcher mvar) Nothing $ \_ -> do takeMVar mvar >>= print where watcher mvar zh _ ConnectedState _ = void $ create zh "/foobar" Nothing OpenAclUnsafe [] getChildren zh "/" Nothing >>= putMVar mvar
Notes
- Watcher callbacks must never block;
- Make sure you link against zookeeper_mt;
- Make sure you are using the
threaded
(GHC) runtime; - The connection is closed right before the
withZookeeper
terminates; - There is no yet support for multi operations (executing a series of operations atomically);
Connection
:: Zookeeper | Zookeeper handle |
-> Scheme | Scheme id of the authentication scheme. Natively supported:
|
-> ByteString | Applicaton credentials. The actual value depends on the scheme |
-> (Either ZKError () -> IO ()) | The callback function |
-> IO () |
Specify application credentials (asynchronous)
The application calls this function to specify its credentials for purposes of authentication. The server will use the security provider specified by the scheme parameter to authenticate the client connection. If the authentication request has failed:
- the server connection is dropped;
- the watcher is called witht AuthFailedState value as the state parameter;
Sets [or redefines] the watcher function
:: String | The zookeeper endpoint to connect to. This is given as-is to the underlying C API. Briefly, host:port separated by comma. At the end, you may define an optional chroot, like the following: localhost:2181,localhost:2182/foobar |
-> Timeout | The session timeout (milliseconds) |
-> Maybe Watcher | The global watcher function. When notifications are triggered this function will be invoked |
-> Maybe ClientID | The id of a previously established session that this client will be reconnecting to |
-> (Zookeeper -> IO a) | The main loop. The session is terminated when this function exists (successfully or not) |
-> IO a |
Connects to the zookeeper cluster. This function may throw an exception if a valid zookeeper handle could not be created.
The connection is terminated right before this function returns.
Configuration/State
The current state of this session
getClientId :: Zookeeper -> IO ClientID Source
The client session id, only valid if the session currently connected [ConnectedState]
setDebugLevel :: ZLogLevel -> IO () Source
Sets the debugging level for the c-library
getRecvTimeout :: Zookeeper -> IO Int Source
The timeout for this session, only valid if the session is currently connected [ConnectedState]
Reading
:: Zookeeper | The Zookeeper handle |
-> String | The name of the znode expressed as a file name with slashes separating ancestors of the znode |
-> Maybe Watcher | When provided, a watch will be set at the server to notify the client if the node changes |
-> IO (Either ZKError (Maybe ByteString, Stat)) |
Gets the data associated with a znode (asynchronous)
:: Zookeeper | Zookeeper handle |
-> String | The name of the znode expressed as a file name with slashes separating ancestors of the znode |
-> Maybe Watcher | The watch to be set at the server to notify the user if the node changes |
-> IO (Either ZKError [String]) |
Lists the children of a znode
ownsEphemeral :: ClientID -> Stat -> IO Bool Source
Test if the ephemeral node has been created by this clientid. This function shall return False if the node is not ephemeral or is not owned by this clientid.
Writing
:: Zookeeper | Zookeeper handle |
-> String | The name of the znode expressed as a file name with slashes separating ancestors of the znode |
-> Maybe ByteString | The data to set on this znode |
-> Maybe Version | The expected version of the znode. The function will fail
if the actual version of the znode does not match the
expected version. If |
-> IO (Either ZKError Stat) |
Sets the data associated with a znode (synchronous)
:: Zookeeper | Zookeeper handle |
-> String | The name of the znode expressed as a file name with slashes separating ancestors of the znode |
-> Maybe ByteString | The data to be stored in the znode |
-> AclList | The initial ACL of the node. The ACL must not be empty |
-> [CreateFlag] | Optional, may be empty |
-> IO (Either ZKError String) |
Creates a znode
:: Zookeeper | Zookeeper handle |
-> String | The name of the znode expressed as a file name with slashes separating ancestors of the znode |
-> Maybe Version | The expected version of the znode. The function will fail
if the actual version of the znode does not match the
expected version. If |
-> IO (Either ZKError ()) |
| Checks the existence of a znode (synchronous)
Delete a znode in zookeeper (synchronous)
:: Zookeeper | Zookeeper handle |
-> String | The name of the znode expressed as a file name with slashes separating ancestors of the znode |
-> Maybe Version | The expected version of the znode. The function will fail
if the actual version of the znode does not match the
expected version. If |
-> AclList | The ACL list to be set on the znode. The ACL must not be empty |
-> IO (Either ZKError ()) |
Sets the acl associated with a node. This operation is not
recursive on the children. See getAcl
for more information (synchronous)
Types
= Zookeeper | |
-> Event | The event that has triggered the watche |
-> State | The connection state |
-> Maybe String | The znode for which the watched is triggered |
-> IO () |
The watcher function, which allows you to get notified about zookeeper events.
The permission bits of a ACL
The stat of a znode
Stat | |
|
ChildEvent | |
CreatedEvent | |
DeletedEvent | |
ChangedEvent | |
SessionEvent | |
NotWatchingEvent | |
UnknownEvent Int | Used when the underlying C API has returned an unknown event type |
ExpiredSessionState | |
AuthFailedState | |
ConnectingState | |
AssociatingState | |
ConnectedState | |
UnknownState Int | Used when the underlying C API has returned an unknown status code |
List [Acl] | A [non empty] list of ACLs |
CreatorAll | This gives the creators authentication id's all permissions |
OpenAclUnsafe | This is a completely open ACL |
ReadAclUnsafe | This ACL gives the world the ability to read |
data CreateFlag Source
The optional flags you may use to create a node
Error values
Zookeeper error codes