hzk-2.1.0: Haskell client library for Apache Zookeeper

Copyright(C) 2013 Diego Souza
LicenseBSD-style (see the file LICENSE)
MaintainerDiego Souza <dsouza@c0d3.xxx>
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

Database.Zookeeper

Contents

Description

Zookeeper client library

Synopsis

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

addAuth Source

Arguments

:: Zookeeper

Zookeeper handle

-> Scheme

Scheme id of the authentication scheme. Natively supported:

  • ''digest'' -> password authentication;

    • ''ip'' -> client's IP address;
    • ''host'' -> client's hostname;
-> 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;

setWatcher Source

Arguments

:: Zookeeper

Zookeeper handle

-> Watcher

New watch function to register

-> IO () 

Sets [or redefines] the watcher function

withZookeeper Source

Arguments

:: 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

getState Source

Arguments

:: Zookeeper

Zookeeper handle

-> IO State

Current 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

get Source

Arguments

:: 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)

exists Source

Arguments

:: Zookeeper

Zookeeper handle

-> String

The name of the znode expressed as a file name with slashes separating ancestors of the znode

-> Maybe Watcher

This is set even if the znode does not exist. This allows users to watch znodes to appear

-> IO (Either ZKError Stat) 

getAcl Source

Arguments

:: Zookeeper

The zookeeper handle

-> String

The name of the znode expressed as a file name with slashes separating ancestors of the znode

-> IO (Either ZKError (AclList, Stat)) 

Gets the acl associated with a node (asynchronous). Unexpectedly, setAcl and getAcl are not symmetric:

setAcl zh path Nothing OpenAclUnsafe
getAcl zh path (..) -- yields AclList instead of OpenAclUnsafe

getChildren Source

Arguments

:: 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

set Source

Arguments

:: 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 Nothing is given the version check will not take place

-> IO (Either ZKError Stat) 

Sets the data associated with a znode (synchronous)

create Source

Arguments

:: 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

delete Source

Arguments

:: 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 Nothing is given the version check will not take place

-> IO (Either ZKError ()) 

| Checks the existence of a znode (synchronous)

Delete a znode in zookeeper (synchronous)

setAcl Source

Arguments

:: 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 Nothing is given the version check will not take place

-> 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

type Scheme = String Source

Authentication scheme provider

type Timeout = Int Source

Timeout in milliseconds

type Watcher Source

Arguments

 = 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.

data ClientID Source

The current clientid that may be used to reconnect

Instances

data Zookeeper Source

Zookeeper connection handler

data Acl Source

Constructors

Acl 

Fields

aclScheme :: String

The ACL scheme (e.g. "ip", "world", "digest"

aclId :: String

The schema-depent ACL identity (e.g. scheme="ip", id="127.0.0.1")

aclFlags :: [Perm]

The [non empty] list of permissions

Instances

data Perm Source

The permission bits of a ACL

Constructors

CanRead

Can read data and enumerate its children

CanAdmin

Can modify permissions bits

CanWrite

Can modify data

CanCreate

Can create children

CanDelete

Can remove

Instances

data Stat Source

The stat of a znode

Constructors

Stat 

Fields

statCzxId :: Int64

The zxid of the change that caused this node to be created

statMzxId :: Int64

The zxid of the change that last modified this znode

statPzxId :: Int64

The zxid of the change that last modified children of this znode

statCreatetime :: Int64

The time in milliseconds from epoch when this znode was created

statModifytime :: Int64

The time in milliseconds from epoch when this znode was last modified

statVersion :: Int32

The number of changes to the data of this znode

statChildrenVersion :: Int32

The number of changes to the children of this znode

statAclVersion :: Int32

The number of changes to the acl of this znode

statDataLength :: Int32

The length of the data field of this znode

statNumChildren :: Int32

The number of children of this znode

statEphemeralOwner :: Maybe Int64

The session id of the owner of this znode if the znode is an ephemeral node

Instances

data Event Source

Constructors

ChildEvent 
CreatedEvent 
DeletedEvent 
ChangedEvent 
SessionEvent 
NotWatchingEvent 
UnknownEvent Int

Used when the underlying C API has returned an unknown event type

Instances

data State Source

Constructors

ExpiredSessionState 
AuthFailedState 
ConnectingState 
AssociatingState 
ConnectedState 
UnknownState Int

Used when the underlying C API has returned an unknown status code

Instances

data AclList Source

Constructors

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

Instances

data CreateFlag Source

The optional flags you may use to create a node

Constructors

Sequence

A unique monotonically increasing sequence number is appended to the path name

Ephemeral

The znode will automatically get removed if the client session goes away

Error values