zoovisitor-0.1.3.1: A haskell binding to Apache Zookeeper C library(mt) using Haskell Z project.
Safe HaskellNone
LanguageHaskell2010

ZooKeeper

Synopsis

Documentation

zooSetDebugLevel :: ZooLogLevel -> IO () Source #

Sets the debugging level for the zookeeper library

zookeeperResInit Source #

Arguments

:: HasCallStack 
=> CBytes

host, comma separated host:port pairs, each corresponding to a zk server. e.g. "127.0.0.1:3000,127.0.0.1:3001,127.0.0.1:3002"

-> CInt

timeout

-> Maybe ClientID

The id of a previously established session that this client will be reconnecting to. Pass Nothing if not reconnecting to a previous session. Clients can access the session id of an established, valid, connection by calling zooGetClientID. If the session corresponding to the specified clientid has expired, or if the clientid is invalid for any reason, the returned ZHandle will be invalid -- the ZHandle state will indicate the reason for failure (typically ZooExpiredSession).

-> CInt

flags, reserved for future use. Should be set to zero.

-> Resource ZHandle 

Create a resource of handle to used communicate with zookeeper.

withResource :: (MonadMask m, MonadIO m, HasCallStack) => Resource a -> (a -> m b) -> m b #

Create a new resource and run some computation, resource is guarantee to be closed.

Be careful, don't leak the resource through the computation return value because after the computation finishes, the resource is already closed.

data Resource a #

A Resource is an IO action which acquires some resource of type a and also returns a finalizer of type IO () that releases the resource.

The only safe way to use a Resource is withResource and withResource', You should not use the acquire field directly, unless you want to implement your own resource management. In the later case, you should mask_ acquire since some resource initializations may assume async exceptions are masked.

MonadIO instance is provided so that you can lift IO computation inside Resource, this is convenient for propagating Resource around since many IO computations carry finalizers.

A convention in Z-IO is that functions returning a Resource should be named in initXXX format, users are strongly recommended to follow this convention.

There're two additional guarantees we made in Z-IO:

Library authors providing initXXX are also encouraged to provide these guarantees.

Instances

Instances details
Monad Resource 
Instance details

Defined in Z.IO.Resource

Methods

(>>=) :: Resource a -> (a -> Resource b) -> Resource b #

(>>) :: Resource a -> Resource b -> Resource b #

return :: a -> Resource a #

Functor Resource 
Instance details

Defined in Z.IO.Resource

Methods

fmap :: (a -> b) -> Resource a -> Resource b #

(<$) :: a -> Resource b -> Resource a #

Applicative Resource 
Instance details

Defined in Z.IO.Resource

Methods

pure :: a -> Resource a #

(<*>) :: Resource (a -> b) -> Resource a -> Resource b #

liftA2 :: (a -> b -> c) -> Resource a -> Resource b -> Resource c #

(*>) :: Resource a -> Resource b -> Resource b #

(<*) :: Resource a -> Resource b -> Resource a #

MonadIO Resource 
Instance details

Defined in Z.IO.Resource

Methods

liftIO :: IO a -> Resource a #

zooCreate Source #

Arguments

:: HasCallStack 
=> ZHandle

The zookeeper handle obtained by a call to zookeeperResInit

-> CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> Maybe Bytes

The data to be stored in the node.

-> AclVector

The initial ACL of the node. The ACL must not be null or empty.

-> CreateMode

This parameter can be set to ZooPersistent for normal create or an OR of the Create Flags

-> IO StringCompletion

The result when the request completes. One of the following exceptions will be thrown if error happens:

  • ZNONODE the parent node does not exist.
  • ZNODEEXISTS the node already exists
  • ZNOAUTH the client does not have permission.
  • ZNOCHILDRENFOREPHEMERALS cannot create children of ephemeral nodes.

Create a node.

This method will create a node in ZooKeeper. A node can only be created if it does not already exist. The Create Flags affect the creation of nodes. If ZooEphemeral flag is set, the node will automatically get removed if the client session goes away. If the ZooSequence flag is set, a unique monotonically increasing sequence number is appended to the path name. The sequence number is always fixed length of 10 digits, 0 padded.

Throw one of the following exceptions on failure:

  • ZBADARGUMENTS - invalid input parameters
  • ZINVALIDSTATE - zhandle state is either ZOO_SESSION_EXPIRED_STATE or ZOO_AUTH_FAILED_STATE
  • ZMARSHALLINGERROR - failed to marshall a request; possibly, out of memory

zooSet Source #

Arguments

:: HasCallStack 
=> ZHandle

The zookeeper handle obtained by a call to zookeeperResInit

-> CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> Maybe Bytes

Data to be written to the node.

-> Maybe CInt

The expected version of the node. The function will fail if the actual version of the node does not match the expected version. If Nothing is used the version check will not take place.

-> IO StatCompletion

The result when the request completes. One of the following exceptions will be thrown if error happens:

  • ZOK operation completed successfully
  • ZNONODE the node does not exist.
  • ZNOAUTH the client does not have permission.
  • ZBADVERSION expected version does not match actual version.

Sets the data associated with a node.

Throw one of the following exceptions on failure:

  • ZBADARGUMENTS - invalid input parameters
  • ZINVALIDSTATE - zhandle state is either ZOO_SESSION_EXPIRED_STATE or ZOO_AUTH_FAILED_STATE
  • ZMARSHALLINGERROR - failed to marshall a request; possibly, out of memory

zooGet Source #

Arguments

:: HasCallStack 
=> ZHandle

The zookeeper handle obtained by a call to zookeeperResInit

-> CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> IO DataCompletion

The result when the request completes. One of the following exceptions will be thrown if:

  • ZNONODE the node does not exist.
  • ZNOAUTH the client does not have permission.

Gets the data associated with a node.

Throw one of the following exceptions on failure:

  • ZBADARGUMENTS - invalid input parameters
  • ZINVALIDSTATE - zhandle state is either in ZOO_SESSION_EXPIRED_STATE or ZOO_AUTH_FAILED_STATE
  • ZMARSHALLINGERROR - failed to marshall a request; possibly, out of memory

zooWatchGet Source #

Arguments

:: HasCallStack 
=> ZHandle 
-> CBytes 
-> (HsWatcherCtx -> IO ())

The watcher callback.

A watch will be set at the server to notify the client if the node changes.

-> (DataCompletion -> IO ())

The result callback when the request completes.

One of the following exceptions will be thrown if:

  • ZNONODE the node does not exist.
  • ZNOAUTH the client does not have permission.
-> IO () 

Gets the data associated with a node.

Throw one of the following exceptions on failure:

  • ZBADARGUMENTS - invalid input parameters
  • ZINVALIDSTATE - zhandle state is either in ZOO_SESSION_EXPIRED_STATE or ZOO_AUTH_FAILED_STATE
  • ZMARSHALLINGERROR - failed to marshall a request; possibly, out of memory

zooGetChildren Source #

Arguments

:: HasCallStack 
=> ZHandle

The zookeeper handle obtained by a call to zookeeperResInit

-> CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> IO StringsCompletion

The result when the request completes.

Throw one of the following exceptions if the request completes failed:

  • ZNONODE the node does not exist.
  • ZNOAUTH the client does not have permission.

Lists the children of a node.

Throw one of the following exceptions on failure:

  • ZBADARGUMENTS - invalid input parameters
  • ZINVALIDSTATE - zhandle state is either ZOO_SESSION_EXPIRED_STATE or ZOO_AUTH_FAILED_STATE
  • ZMARSHALLINGERROR - failed to marshall a request; possibly, out of memory

zooWatchGetChildren Source #

Arguments

:: HasCallStack 
=> ZHandle

The zookeeper handle obtained by a call to zookeeperResInit

-> CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> (HsWatcherCtx -> IO ())

The watcher callback. A watch will be set at the server to notify the client if the node changes.

-> (StringsCompletion -> IO ())

The result callback when the request completes.

One of the following exceptions will be thrown if error happens:

  • ZNONODE the node does not exist.
  • ZNOAUTH the client does not have permission.
-> IO () 

Lists the children of a node.

This function is similar to zooGetChildren except it allows one specify a watcher object.

Note that there is only one thread for triggering callbacks. Which means this function will first block on the completion, and then wating on the watcher.

Throw one of the following exceptions on failure:

ZBADARGUMENTS - invalid input parameters ZINVALIDSTATE - zhandle state is either ZOO_SESSION_EXPIRED_STATE or ZOO_AUTH_FAILED_STATE ZMARSHALLINGERROR - failed to marshall a request; possibly, out of memory

zooGetChildren2 Source #

Arguments

:: HasCallStack 
=> ZHandle

The zookeeper handle obtained by a call to zookeeperResInit

-> CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> IO StringsStatCompletion

The result when the request completes.

Throw one of the following exceptions if the request completes failed:

  • ZNONODE the node does not exist.
  • ZNOAUTH the client does not have permission.

Lists the children of a node, and get the parent stat.

This function is new in version 3.3.0

Throw one of the following exceptions on failure:

zooWatchGetChildren2 Source #

Arguments

:: HasCallStack 
=> ZHandle

The zookeeper handle obtained by a call to zookeeperResInit

-> CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> (HsWatcherCtx -> IO ())

The watcher callback. A watch will be set at the server to notify the client if the node changes.

-> (StringsStatCompletion -> IO ())

The result callback when the request completes.

One of the following exceptions will be thrown if error happens:

  • ZNONODE the node does not exist.
  • ZNOAUTH the client does not have permission.
-> IO () 

Lists the children of a node, and get the parent stat.

This function is new in version 3.3.0

Note that there is only one thread for triggering callbacks. Which means this function will first block on the completion, and then wating on the watcher.

Throw one of the following exceptions on failure:

zooDelete Source #

Arguments

:: HasCallStack 
=> ZHandle

The zookeeper handle obtained by a call to zookeeperResInit

-> CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> Maybe CInt

The expected version of the node. The function will fail if the actual version of the node does not match the expected version. If Nothing is used the version check will not take place.

-> IO () 

Delete a node in zookeeper.

Throw one of the following exceptions on failure:

Throw one of the following exceptions if the request completes failed:

  • ZNONODE the node does not exist.
  • ZNOAUTH the client does not have permission.
  • ZBADVERSION expected version does not match actual version.
  • ZNOTEMPTY children are present; node cannot be deleted.

zooDeleteAll :: HasCallStack => ZHandle -> CBytes -> IO () Source #

Delete a node and all its children in zookeeper.

If fail will throw exceptions, check zooDeleteAll and zooGetChildren for more details

zooExists Source #

Arguments

:: HasCallStack 
=> ZHandle

The zookeeper handle obtained by a call to zookeeperResInit

-> CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> IO (Maybe StatCompletion)

The result when the request completes. Nothing means the node does not exist.

One of the following exceptions will be thrown if error happens:

  • ZNOAUTH the client does not have permission.

Checks the existence of a node in zookeeper.

Throw one of the following exceptions on failure:

  • ZBADARGUMENTS - invalid input parameters
  • ZINVALIDSTATE - zhandle state is either ZOO_SESSION_EXPIRED_STATE or ZOO_AUTH_FAILED_STATE
  • ZMARSHALLINGERROR - failed to marshall a request; possibly, out of memory

zooWatchExists Source #

Arguments

:: HasCallStack 
=> ZHandle

The zookeeper handle obtained by a call to zookeeperResInit

-> CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> (HsWatcherCtx -> IO ())

The watcher callback.

A watch will set on the specified znode on the server. The watch will be set even if the node does not exist. This allows clients to watch for nodes to appear.

-> (Maybe StatCompletion -> IO ())

The result callback when the request completes. Nothing means the node does not exist.

One of the following exceptions will be thrown if error happens:

  • ZNOAUTH the client does not have permission.
-> IO () 

Checks the existence of a node in zookeeper.

This function is similar to zooExists except it allows one specify a watcher object. The function will be called once the watch has fired.

Note that the watch will fire both when the node is created and its associated data is set.

Note that there is only one thread for triggering callbacks. Which means this function will first block on the completion, and then wating on the watcher.

Throw one of the following exceptions on failure:

  • ZBADARGUMENTS - invalid input parameters
  • ZINVALIDSTATE - zhandle state is either ZOO_SESSION_EXPIRED_STATE or ZOO_AUTH_FAILED_STATE
  • ZMARSHALLINGERROR - failed to marshall a request; possibly, out of memory

zooGetAcl Source #

Arguments

:: HasCallStack 
=> ZHandle

The zookeeper handle obtained by a call to zookeeperResInit

-> CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> IO AclCompletion

The result when the request completes.

Throw one of the following exceptions if the request completes failed:

  • ZNONODE the node does not exist.
  • ZNOAUTH the client does not have permission.

Gets the acl associated with a node.

Throw one of the following exceptions on failure:

ZBADARGUMENTS - invalid input parameters ZINVALIDSTATE - zhandle state is either ZOO_SESSION_EXPIRED_STATE or ZOO_AUTH_FAILED_STATE ZMARSHALLINGERROR - failed to marshall a request; possibly, out of memory

zooMulti Source #

Arguments

:: HasCallStack 
=> ZHandle

The zookeeper handle obtained by a call to zookeeperResInit

-> [ZooOp]

An list of operations to commit

-> IO [ZooOpResult] 

Atomically commits multiple zookeeper operations.

Throw exceptions if error happened, the exception will be any of the operations supported by a multi op, see zooCreate, zooDelete and zooSet.

zooCreateOpInit Source #

Arguments

:: CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> Maybe Bytes

The data to be stored in the node.

-> CInt

The max buffer size of the created new node path (this might be different than the supplied path because of the ZooSequence flag). If this size is 0,

Note: we do NOT check if the size is non-negative.

If the path of the new node exceeds the buffer size, the path string will be truncated to fit. The actual path of the new node in the server will not be affected by the truncation.

-> AclVector

The initial ACL of the node. The ACL must not be null or empty.

-> CreateMode

This parameter can be set to ZooPersistent for normal create or an OR of the Create Flags

-> ZooOp 

Init create op.

This function initializes a ZooOp with the arguments for a ZOO_CREATE_OP.

zooDeleteOpInit Source #

Arguments

:: CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> Maybe CInt

The expected version of the node. The function will fail if the actual version of the node does not match the expected version. If Nothing is used the version check will not take place.

-> ZooOp 

Init delete op.

This function initializes a ZooOp with the arguments for a ZOO_DELETE_OP.

zooSetOpInit Source #

Arguments

:: CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> Maybe Bytes

Data to be written to the node.

To set NULL as data use this parameter as Nothing.

-> Maybe CInt

The expected version of the node. The function will fail if the actual version of the node does not match the expected version. If Nothing is used the version check will not take place.

-> ZooOp 

Init set op.

This function initializes an ZooOp with the arguments for a ZOO_SETDATA_OP.

zooCheckOpInit Source #

Arguments

:: CBytes

The name of the node. Expressed as a file name with slashes separating ancestors of the node.

-> CInt

The expected version of the node. The function will fail if the actual version of the node does not match the expected version.

-> ZooOp 

Init check op.

This function initializes an ZooOp with the arguments for a ZOO_CHECK_OP.

zooClientID :: ZHandle -> IO ClientID Source #

Return the client session id, only valid if the connections is currently connected (ie. last watcher state is ZooConnectedState)

zooState :: ZHandle -> IO ZooState Source #

Get the state of the zookeeper connection

The return valud will be one of the State Consts

zooRecvTimeout :: ZHandle -> IO CInt Source #

Return the timeout for this session, only valid if the connections is currently connected (ie. last watcher state is ZOO_CONNECTED_STATE). This value may change after a server re-connect.

isUnrecoverable Source #

Arguments

:: ZHandle

The zookeeper handle obtained by a call to zookeeperResInit

-> IO Bool

Return True if connection is unrecoverable

Checks if the current zookeeper connection state can't be recovered.

If True, the application must close the zhandle and then try to reconnect.

zookeeperInit Source #

Arguments

:: HasCallStack 
=> CBytes

host, comma separated host:port pairs, each corresponding to a zk server. e.g. "127.0.0.1:3000,127.0.0.1:3001,127.0.0.1:3002"

-> CInt

timeout

-> Maybe ClientID

The id of a previously established session that this client will be reconnecting to. Pass Nothing if not reconnecting to a previous session. Clients can access the session id of an established, valid, connection by calling zooGetClientID. If the session corresponding to the specified clientid has expired, or if the clientid is invalid for any reason, the returned ZHandle will be invalid -- the ZHandle state will indicate the reason for failure (typically ZooExpiredSession).

-> CInt

flags, reserved for future use. Should be set to zero.

-> IO ZHandle 

Create a handle to used communicate with zookeeper.

This function creates a new handle and a zookeeper session that corresponds to that handle. At the underlying c side, session establishment is asynchronous, meaning that the session should not be considered established until (and unless) an event of state ZOO_CONNECTED_STATE is received. In haskell, this will block until state received.

If it fails to create a new zhandle or not connected, an exception will be throwed.