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

ZooKeeper.Exception

Synopsis

Documentation

data ZooException Source #

The root exception type of ZooKeeper.

Instances

Instances details
Show ZooException Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZooException -> ShowS

show :: ZooException -> String

showList :: [ZooException] -> ShowS

Exception ZooException Source # 
Instance details

Defined in ZooKeeper.Exception

data ZooExInfo Source #

Zookeeper error informations.

Constructors

ZooExInfo 

Fields

Instances

Instances details
Show ZooExInfo Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZooExInfo -> ShowS

show :: ZooExInfo -> String

showList :: [ZooExInfo] -> ShowS

Print ZooExInfo Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

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

System and server-side errors

This is never thrown by the server, it shouldn't be used other than to indicate a range. Specifically error codes greater than this value, but lesser than ZAPIERROR, are system errors.

newtype ZSYSTEMERROR Source #

Constructors

ZSYSTEMERROR ZooExInfo 

Instances

Instances details
Show ZSYSTEMERROR Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZSYSTEMERROR -> ShowS

show :: ZSYSTEMERROR -> String

showList :: [ZSYSTEMERROR] -> ShowS

Exception ZSYSTEMERROR Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZCONNECTIONLOSS Source #

Instances

Instances details
Show ZCONNECTIONLOSS Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZCONNECTIONLOSS -> ShowS

show :: ZCONNECTIONLOSS -> String

showList :: [ZCONNECTIONLOSS] -> ShowS

Exception ZCONNECTIONLOSS Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZMARSHALLINGERROR Source #

Instances

Instances details
Show ZMARSHALLINGERROR Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZMARSHALLINGERROR -> ShowS

show :: ZMARSHALLINGERROR -> String

showList :: [ZMARSHALLINGERROR] -> ShowS

Exception ZMARSHALLINGERROR Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZUNIMPLEMENTED Source #

Instances

Instances details
Show ZUNIMPLEMENTED Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZUNIMPLEMENTED -> ShowS

show :: ZUNIMPLEMENTED -> String

showList :: [ZUNIMPLEMENTED] -> ShowS

Exception ZUNIMPLEMENTED Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZOPERATIONTIMEOUT Source #

Instances

Instances details
Show ZOPERATIONTIMEOUT Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZOPERATIONTIMEOUT -> ShowS

show :: ZOPERATIONTIMEOUT -> String

showList :: [ZOPERATIONTIMEOUT] -> ShowS

Exception ZOPERATIONTIMEOUT Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZBADARGUMENTS Source #

Constructors

ZBADARGUMENTS ZooExInfo 

Instances

Instances details
Show ZBADARGUMENTS Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZBADARGUMENTS -> ShowS

show :: ZBADARGUMENTS -> String

showList :: [ZBADARGUMENTS] -> ShowS

Exception ZBADARGUMENTS Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZINVALIDSTATE Source #

Constructors

ZINVALIDSTATE ZooExInfo 

Instances

Instances details
Show ZINVALIDSTATE Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZINVALIDSTATE -> ShowS

show :: ZINVALIDSTATE -> String

showList :: [ZINVALIDSTATE] -> ShowS

Exception ZINVALIDSTATE Source # 
Instance details

Defined in ZooKeeper.Exception

API Errors

This is never thrown by the server, it shouldn't be used other than to indicate a range. Specifically error codes greater than this value are API errors (while values less than this indicate a ZSYSTEMERROR).

newtype ZAPIERROR Source #

Constructors

ZAPIERROR ZooExInfo 

Instances

Instances details
Show ZAPIERROR Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZAPIERROR -> ShowS

show :: ZAPIERROR -> String

showList :: [ZAPIERROR] -> ShowS

Exception ZAPIERROR Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZNONODE Source #

Constructors

ZNONODE ZooExInfo 

Instances

Instances details
Show ZNONODE Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZNONODE -> ShowS

show :: ZNONODE -> String

showList :: [ZNONODE] -> ShowS

Exception ZNONODE Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZNOAUTH Source #

Constructors

ZNOAUTH ZooExInfo 

Instances

Instances details
Show ZNOAUTH Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZNOAUTH -> ShowS

show :: ZNOAUTH -> String

showList :: [ZNOAUTH] -> ShowS

Exception ZNOAUTH Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZBADVERSION Source #

Constructors

ZBADVERSION ZooExInfo 

Instances

Instances details
Show ZBADVERSION Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZBADVERSION -> ShowS

show :: ZBADVERSION -> String

showList :: [ZBADVERSION] -> ShowS

Exception ZBADVERSION Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZNODEEXISTS Source #

Constructors

ZNODEEXISTS ZooExInfo 

Instances

Instances details
Show ZNODEEXISTS Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZNODEEXISTS -> ShowS

show :: ZNODEEXISTS -> String

showList :: [ZNODEEXISTS] -> ShowS

Exception ZNODEEXISTS Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZNOTEMPTY Source #

Constructors

ZNOTEMPTY ZooExInfo 

Instances

Instances details
Show ZNOTEMPTY Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZNOTEMPTY -> ShowS

show :: ZNOTEMPTY -> String

showList :: [ZNOTEMPTY] -> ShowS

Exception ZNOTEMPTY Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZSESSIONEXPIRED Source #

Instances

Instances details
Show ZSESSIONEXPIRED Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZSESSIONEXPIRED -> ShowS

show :: ZSESSIONEXPIRED -> String

showList :: [ZSESSIONEXPIRED] -> ShowS

Exception ZSESSIONEXPIRED Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZINVALIDCALLBACK Source #

Instances

Instances details
Show ZINVALIDCALLBACK Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZINVALIDCALLBACK -> ShowS

show :: ZINVALIDCALLBACK -> String

showList :: [ZINVALIDCALLBACK] -> ShowS

Exception ZINVALIDCALLBACK Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZINVALIDACL Source #

Constructors

ZINVALIDACL ZooExInfo 

Instances

Instances details
Show ZINVALIDACL Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZINVALIDACL -> ShowS

show :: ZINVALIDACL -> String

showList :: [ZINVALIDACL] -> ShowS

Exception ZINVALIDACL Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZAUTHFAILED Source #

Constructors

ZAUTHFAILED ZooExInfo 

Instances

Instances details
Show ZAUTHFAILED Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZAUTHFAILED -> ShowS

show :: ZAUTHFAILED -> String

showList :: [ZAUTHFAILED] -> ShowS

Exception ZAUTHFAILED Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZCLOSING Source #

Constructors

ZCLOSING ZooExInfo 

Instances

Instances details
Show ZCLOSING Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZCLOSING -> ShowS

show :: ZCLOSING -> String

showList :: [ZCLOSING] -> ShowS

Exception ZCLOSING Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZNOTHING Source #

Constructors

ZNOTHING ZooExInfo 

Instances

Instances details
Show ZNOTHING Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZNOTHING -> ShowS

show :: ZNOTHING -> String

showList :: [ZNOTHING] -> ShowS

Exception ZNOTHING Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZSESSIONMOVED Source #

Constructors

ZSESSIONMOVED ZooExInfo 

Instances

Instances details
Show ZSESSIONMOVED Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZSESSIONMOVED -> ShowS

show :: ZSESSIONMOVED -> String

showList :: [ZSESSIONMOVED] -> ShowS

Exception ZSESSIONMOVED Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZNOTREADONLY Source #

Constructors

ZNOTREADONLY ZooExInfo 

Instances

Instances details
Show ZNOTREADONLY Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZNOTREADONLY -> ShowS

show :: ZNOTREADONLY -> String

showList :: [ZNOTREADONLY] -> ShowS

Exception ZNOTREADONLY Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZNOWATCHER Source #

Constructors

ZNOWATCHER ZooExInfo 

Instances

Instances details
Show ZNOWATCHER Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZNOWATCHER -> ShowS

show :: ZNOWATCHER -> String

showList :: [ZNOWATCHER] -> ShowS

Exception ZNOWATCHER Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZRECONFIGDISABLED Source #

Instances

Instances details
Show ZRECONFIGDISABLED Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZRECONFIGDISABLED -> ShowS

show :: ZRECONFIGDISABLED -> String

showList :: [ZRECONFIGDISABLED] -> ShowS

Exception ZRECONFIGDISABLED Source # 
Instance details

Defined in ZooKeeper.Exception

newtype ZTHROTTLEDOP Source #

Constructors

ZTHROTTLEDOP ZooExInfo 

Instances

Instances details
Show ZTHROTTLEDOP Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> ZTHROTTLEDOP -> ShowS

show :: ZTHROTTLEDOP -> String

showList :: [ZTHROTTLEDOP] -> ShowS

Exception ZTHROTTLEDOP Source # 
Instance details

Defined in ZooKeeper.Exception

Other Errors

data SYSERRNO Source #

Instances

Instances details
Show SYSERRNO Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> SYSERRNO -> ShowS

show :: SYSERRNO -> String

showList :: [SYSERRNO] -> ShowS

Exception SYSERRNO Source # 
Instance details

Defined in ZooKeeper.Exception

data UNKNOWN_ERR Source #

Instances

Instances details
Show UNKNOWN_ERR Source # 
Instance details

Defined in ZooKeeper.Exception

Methods

showsPrec :: Int -> UNKNOWN_ERR -> ShowS

show :: UNKNOWN_ERR -> String

showList :: [UNKNOWN_ERR] -> ShowS

Exception UNKNOWN_ERR Source # 
Instance details

Defined in ZooKeeper.Exception

throwZooError :: CInt -> CallStack -> IO a Source #

throwZooErrorIfLeft :: HasCallStack => Either CInt a -> IO a Source #

throwZooErrorIfLeft' :: HasCallStack => (CInt -> Bool) -> Either CInt a -> IO (Maybe a) Source #

Error number patterns

pattern CZOK :: CInt Source #

pattern CZSYSTEMERROR :: CInt Source #

pattern CZDATAINCONSISTENCY :: CInt Source #

pattern CZCONNECTIONLOSS :: CInt Source #

pattern CZMARSHALLINGERROR :: CInt Source #

pattern CZUNIMPLEMENTED :: CInt Source #

pattern CZOPERATIONTIMEOUT :: CInt Source #

pattern CZBADARGUMENTS :: CInt Source #

pattern CZINVALIDSTATE :: CInt Source #

pattern CZNEWCONFIGNOQUORUM :: CInt Source #

pattern CZRECONFIGINPROGRESS :: CInt Source #

pattern CZSSLCONNECTIONERROR :: CInt Source #

pattern CZAPIERROR :: CInt Source #

pattern CZNONODE :: CInt Source #

pattern CZNOAUTH :: CInt Source #

pattern CZBADVERSION :: CInt Source #

pattern CZNODEEXISTS :: CInt Source #

pattern CZNOTEMPTY :: CInt Source #

pattern CZSESSIONEXPIRED :: CInt Source #

pattern CZINVALIDCALLBACK :: CInt Source #

pattern CZINVALIDACL :: CInt Source #

pattern CZAUTHFAILED :: CInt Source #

pattern CZCLOSING :: CInt Source #

pattern CZNOTHING :: CInt Source #

pattern CZSESSIONMOVED :: CInt Source #

pattern CZNOTREADONLY :: CInt Source #

pattern CZNOWATCHER :: CInt Source #

pattern CZRECONFIGDISABLED :: CInt Source #

pattern CZTHROTTLEDOP :: CInt Source #

Helpers

throwIO :: Exception e => e -> IO a #

getCErrNum :: IO CInt Source #