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

ZooKeeper.Types

Synopsis

Documentation

data ZHandle Source #

Instances

Instances details
Eq ZHandle Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

(==) :: ZHandle -> ZHandle -> Bool

(/=) :: ZHandle -> ZHandle -> Bool

Show ZHandle Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> ZHandle -> ShowS

show :: ZHandle -> String

showList :: [ZHandle] -> ShowS

data ClientID Source #

Instances

Instances details
Eq ClientID Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

(==) :: ClientID -> ClientID -> Bool

(/=) :: ClientID -> ClientID -> Bool

Show ClientID Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> ClientID -> ShowS

show :: ClientID -> String

showList :: [ClientID] -> ShowS

data ZooOp Source #

This structure holds all the arguments necessary for one op as part of a containing multi_op via zooMulti.

data ZooOpResult Source #

Instances

Instances details
Eq ZooOpResult Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

(==) :: ZooOpResult -> ZooOpResult -> Bool

(/=) :: ZooOpResult -> ZooOpResult -> Bool

Show ZooOpResult Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> ZooOpResult -> ShowS

show :: ZooOpResult -> String

showList :: [ZooOpResult] -> ShowS

data AclVector Source #

Instances

Instances details
Eq AclVector Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

(==) :: AclVector -> AclVector -> Bool

(/=) :: AclVector -> AclVector -> Bool

Show AclVector Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> AclVector -> ShowS

show :: AclVector -> String

showList :: [AclVector] -> ShowS

zooOpenAclUnsafe :: AclVector Source #

This is a completely open ACL

zooReadAclUnsafe :: AclVector Source #

This ACL gives the world the ability to read.

zooCreatorAllAcl :: AclVector Source #

This ACL gives the creators authentication id's all permissions.

data ZooAcl Source #

Constructors

ZooAcl 

Instances

Instances details
Show ZooAcl Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> ZooAcl -> ShowS

show :: ZooAcl -> String

showList :: [ZooAcl] -> ShowS

data HsWatcherCtx Source #

Instances

Instances details
Show HsWatcherCtx Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> HsWatcherCtx -> ShowS

show :: HsWatcherCtx -> String

showList :: [HsWatcherCtx] -> ShowS

data DataCompletion Source #

Instances

Instances details
Eq DataCompletion Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Show DataCompletion Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> DataCompletion -> ShowS

show :: DataCompletion -> String

showList :: [DataCompletion] -> ShowS

newtype StatCompletion Source #

Constructors

StatCompletion 

Instances

Instances details
Eq StatCompletion Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Show StatCompletion Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> StatCompletion -> ShowS

show :: StatCompletion -> String

showList :: [StatCompletion] -> ShowS

newtype StringCompletion Source #

Instances

Instances details
Show StringCompletion Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> StringCompletion -> ShowS

show :: StringCompletion -> String

showList :: [StringCompletion] -> ShowS

newtype StringsCompletion Source #

Instances

Instances details
Show StringsCompletion Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> StringsCompletion -> ShowS

show :: StringsCompletion -> String

showList :: [StringsCompletion] -> ShowS

data AclCompletion Source #

Instances

Instances details
Show AclCompletion Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> AclCompletion -> ShowS

show :: AclCompletion -> String

showList :: [AclCompletion] -> ShowS

data Stat Source #

Constructors

Stat 

Fields

Instances

Instances details
Eq Stat Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

(==) :: Stat -> Stat -> Bool

(/=) :: Stat -> Stat -> Bool

Show Stat Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> Stat -> ShowS

show :: Stat -> String

showList :: [Stat] -> ShowS

data ZooEvent Source #

Watch Types

These constants indicate the event that caused the watch event. They are possible values of the first parameter of the watcher callback.

Instances

Instances details
Eq ZooEvent Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

(==) :: ZooEvent -> ZooEvent -> Bool

(/=) :: ZooEvent -> ZooEvent -> Bool

Show ZooEvent Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> ZooEvent -> ShowS

show :: ZooEvent -> String

showList :: [ZooEvent] -> ShowS

Storable ZooEvent Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

sizeOf :: ZooEvent -> Int

alignment :: ZooEvent -> Int

peekElemOff :: Ptr ZooEvent -> Int -> IO ZooEvent

pokeElemOff :: Ptr ZooEvent -> Int -> ZooEvent -> IO ()

peekByteOff :: Ptr b -> Int -> IO ZooEvent

pokeByteOff :: Ptr b -> Int -> ZooEvent -> IO ()

peek :: Ptr ZooEvent -> IO ZooEvent

poke :: Ptr ZooEvent -> ZooEvent -> IO ()

pattern ZooCreateEvent :: ZooEvent Source #

A node has been created.

This is only generated by watches on non-existent nodes. These watches are set using zooWatchExists.

pattern ZooDeleteEvent :: ZooEvent Source #

A node has been deleted.

This is only generated by watches on nodes. These watches are set using zooWatchExists and zooWatchGet.

pattern ZooChangedEvent :: ZooEvent Source #

A node has changed.

This is only generated by watches on nodes. These watches are set using zooWatchExists and zooWatchGet.

pattern ZooSessionEvent :: ZooEvent Source #

A session has been lost.

This is generated when a client loses contact or reconnects with a server.

pattern ZooNoWatchingEvent :: ZooEvent Source #

A watch has been removed.

This is generated when the server for some reason, probably a resource constraint, will no longer watch a node for a client.

data ZooState Source #

State Consts

These constants represent the states of a zookeeper connection. They are possible parameters of the watcher callback.

Instances

Instances details
Eq ZooState Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

(==) :: ZooState -> ZooState -> Bool

(/=) :: ZooState -> ZooState -> Bool

Show ZooState Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> ZooState -> ShowS

show :: ZooState -> String

showList :: [ZooState] -> ShowS

Print ZooState Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

toUTF8BuilderP :: Int -> ZooState -> Builder () #

Storable ZooState Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

sizeOf :: ZooState -> Int

alignment :: ZooState -> Int

peekElemOff :: Ptr ZooState -> Int -> IO ZooState

pokeElemOff :: Ptr ZooState -> Int -> ZooState -> IO ()

peekByteOff :: Ptr b -> Int -> IO ZooState

pokeByteOff :: Ptr b -> Int -> ZooState -> IO ()

peek :: Ptr ZooState -> IO ZooState

poke :: Ptr ZooState -> ZooState -> IO ()

data CreateMode Source #

These modes are used by zoo_create to affect node create.

Instances

Instances details
Eq CreateMode Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

(==) :: CreateMode -> CreateMode -> Bool

(/=) :: CreateMode -> CreateMode -> Bool

Show CreateMode Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> CreateMode -> ShowS

show :: CreateMode -> String

showList :: [CreateMode] -> ShowS

Storable CreateMode Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

sizeOf :: CreateMode -> Int

alignment :: CreateMode -> Int

peekElemOff :: Ptr CreateMode -> Int -> IO CreateMode

pokeElemOff :: Ptr CreateMode -> Int -> CreateMode -> IO ()

peekByteOff :: Ptr b -> Int -> IO CreateMode

pokeByteOff :: Ptr b -> Int -> CreateMode -> IO ()

peek :: Ptr CreateMode -> IO CreateMode

poke :: Ptr CreateMode -> CreateMode -> IO ()

pattern ZooEphemeral :: CreateMode Source #

The znode will be deleted upon the client's disconnect.

data ZooLogLevel Source #

Instances

Instances details
Eq ZooLogLevel Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

(==) :: ZooLogLevel -> ZooLogLevel -> Bool

(/=) :: ZooLogLevel -> ZooLogLevel -> Bool

Show ZooLogLevel Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> ZooLogLevel -> ShowS

show :: ZooLogLevel -> String

showList :: [ZooLogLevel] -> ShowS

Storable ZooLogLevel Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

sizeOf :: ZooLogLevel -> Int

alignment :: ZooLogLevel -> Int

peekElemOff :: Ptr ZooLogLevel -> Int -> IO ZooLogLevel

pokeElemOff :: Ptr ZooLogLevel -> Int -> ZooLogLevel -> IO ()

peekByteOff :: Ptr b -> Int -> IO ZooLogLevel

pokeByteOff :: Ptr b -> Int -> ZooLogLevel -> IO ()

peek :: Ptr ZooLogLevel -> IO ZooLogLevel

poke :: Ptr ZooLogLevel -> ZooLogLevel -> IO ()

data ZooPerm Source #

ACL permissions.

Instances

Instances details
Eq ZooPerm Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

(==) :: ZooPerm -> ZooPerm -> Bool

(/=) :: ZooPerm -> ZooPerm -> Bool

Show ZooPerm Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> ZooPerm -> ShowS

show :: ZooPerm -> String

showList :: [ZooPerm] -> ShowS

Bits ZooPerm Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

(.&.) :: ZooPerm -> ZooPerm -> ZooPerm

(.|.) :: ZooPerm -> ZooPerm -> ZooPerm

xor :: ZooPerm -> ZooPerm -> ZooPerm

complement :: ZooPerm -> ZooPerm

shift :: ZooPerm -> Int -> ZooPerm

rotate :: ZooPerm -> Int -> ZooPerm

zeroBits :: ZooPerm

bit :: Int -> ZooPerm

setBit :: ZooPerm -> Int -> ZooPerm

clearBit :: ZooPerm -> Int -> ZooPerm

complementBit :: ZooPerm -> Int -> ZooPerm

testBit :: ZooPerm -> Int -> Bool

bitSizeMaybe :: ZooPerm -> Maybe Int

bitSize :: ZooPerm -> Int

isSigned :: ZooPerm -> Bool

shiftL :: ZooPerm -> Int -> ZooPerm

unsafeShiftL :: ZooPerm -> Int -> ZooPerm

shiftR :: ZooPerm -> Int -> ZooPerm

unsafeShiftR :: ZooPerm -> Int -> ZooPerm

rotateL :: ZooPerm -> Int -> ZooPerm

rotateR :: ZooPerm -> Int -> ZooPerm

popCount :: ZooPerm -> Int

newtype StringVector Source #

Constructors

StringVector 

Fields

Instances

Instances details
Show StringVector Source # 
Instance details

Defined in ZooKeeper.Internal.Types

Methods

showsPrec :: Int -> StringVector -> ShowS

show :: StringVector -> String

showList :: [StringVector] -> ShowS