milena-0.5.0.2: A Kafka client for Haskell.

Safe HaskellNone
LanguageHaskell2010

Network.Kafka.Protocol

Contents

Synopsis

Documentation

class Serializable a where Source #

Minimal complete definition

serialize

Methods

serialize :: a -> Put Source #

Instances

Serializable Int8 Source # 

Methods

serialize :: Int8 -> Put Source #

Serializable Int16 Source # 

Methods

serialize :: Int16 -> Put Source #

Serializable Int32 Source # 

Methods

serialize :: Int32 -> Put Source #

Serializable Int64 Source # 

Methods

serialize :: Int64 -> Put Source #

Serializable Request Source # 
Serializable KafkaError Source # 
Serializable Metadata Source # 
Serializable ConsumerGroup Source # 
Serializable OffsetFetchRequest Source # 
Serializable OffsetCommitRequest Source # 
Serializable GroupCoordinatorRequest Source # 
Serializable Value Source # 

Methods

serialize :: Value -> Put Source #

Serializable Key Source # 

Methods

serialize :: Key -> Put Source #

Serializable Attributes Source # 
Serializable MagicByte Source # 
Serializable Crc Source # 

Methods

serialize :: Crc -> Put Source #

Serializable Message Source # 
Serializable Offset Source # 

Methods

serialize :: Offset -> Put Source #

Serializable MessageSetMember Source # 
Serializable MessageSet Source # 
Serializable Partition Source # 
Serializable Timeout Source # 
Serializable RequiredAcks Source # 
Serializable ProduceRequest Source # 
Serializable MaxBytes Source # 
Serializable MinBytes Source # 
Serializable MaxWaitTime Source # 
Serializable ReplicaId Source # 
Serializable FetchRequest Source # 
Serializable MaxNumberOfOffsets Source # 
Serializable Time Source # 

Methods

serialize :: Time -> Put Source #

Serializable OffsetRequest Source # 
Serializable Replicas Source # 
Serializable FetchResponse Source # 
Serializable ProduceResponse Source # 
Serializable KafkaString Source # 
Serializable KafkaBytes Source # 
Serializable TopicName Source # 
Serializable MetadataRequest Source # 
Serializable RequestMessage Source # 
Serializable ClientId Source # 
Serializable CorrelationId Source # 
Serializable ApiVersion Source # 
Serializable ApiKey Source # 

Methods

serialize :: ApiKey -> Put Source #

Serializable a => Serializable [a] Source # 

Methods

serialize :: [a] -> Put Source #

(Serializable a, Serializable b) => Serializable (a, b) Source # 

Methods

serialize :: (a, b) -> Put Source #

(Serializable a, Serializable b, Serializable c) => Serializable (a, b, c) Source # 

Methods

serialize :: (a, b, c) -> Put Source #

(Serializable a, Serializable b, Serializable c, Serializable d) => Serializable (a, b, c, d) Source # 

Methods

serialize :: (a, b, c, d) -> Put Source #

(Serializable a, Serializable b, Serializable c, Serializable d, Serializable e) => Serializable (a, b, c, d, e) Source # 

Methods

serialize :: (a, b, c, d, e) -> Put Source #

class Deserializable a where Source #

Minimal complete definition

deserialize

Methods

deserialize :: Get a Source #

Instances

Deserializable Int8 Source # 
Deserializable Int16 Source # 
Deserializable Int32 Source # 
Deserializable Int64 Source # 
Deserializable KafkaError Source # 
Deserializable Metadata Source # 
Deserializable ConsumerGroup Source # 
Deserializable Value Source # 
Deserializable Key Source # 
Deserializable Attributes Source # 
Deserializable MagicByte Source # 
Deserializable Crc Source # 
Deserializable Message Source # 
Deserializable Offset Source # 
Deserializable MessageSetMember Source # 
Deserializable MessageSet Source # 
Deserializable Partition Source # 
Deserializable Timeout Source # 
Deserializable RequiredAcks Source # 
Deserializable MaxBytes Source # 
Deserializable MinBytes Source # 
Deserializable MaxWaitTime Source # 
Deserializable ReplicaId Source # 
Deserializable FetchRequest Source # 
Deserializable OffsetFetchResponse Source # 
Deserializable OffsetCommitResponse Source # 
Deserializable Isr Source # 
Deserializable Replicas Source # 
Deserializable Leader Source # 
Deserializable PartitionMetadata Source # 
Deserializable TopicMetadata Source # 
Deserializable Port Source # 
Deserializable Host Source # 
Deserializable NodeId Source # 
Deserializable Broker Source # 
Deserializable MetadataResponse Source # 
Deserializable FetchResponse Source # 
Deserializable PartitionOffsets Source # 
Deserializable OffsetResponse Source # 
Deserializable ProduceResponse Source # 
Deserializable KafkaString Source # 
Deserializable KafkaBytes Source # 
Deserializable TopicName Source # 
Deserializable MetadataRequest Source # 
Deserializable ClientId Source # 
Deserializable CorrelationId Source # 
Deserializable ApiVersion Source # 
Deserializable ApiKey Source # 
Deserializable GroupCoordinatorResponse Source # 
Deserializable a => Deserializable [a] Source # 

Methods

deserialize :: Get [a] Source #

(Deserializable a, Deserializable b) => Deserializable (a, b) Source # 

Methods

deserialize :: Get (a, b) Source #

(Deserializable a, Deserializable b, Deserializable c) => Deserializable (a, b, c) Source # 

Methods

deserialize :: Get (a, b, c) Source #

(Deserializable a, Deserializable b, Deserializable c, Deserializable d) => Deserializable (a, b, c, d) Source # 

Methods

deserialize :: Get (a, b, c, d) Source #

(Deserializable a, Deserializable b, Deserializable c, Deserializable d, Deserializable e) => Deserializable (a, b, c, d, e) Source # 

Methods

deserialize :: Get (a, b, c, d, e) Source #

newtype ApiKey Source #

Constructors

ApiKey Int16 

Instances

Enum ApiKey Source # 
Eq ApiKey Source # 

Methods

(==) :: ApiKey -> ApiKey -> Bool #

(/=) :: ApiKey -> ApiKey -> Bool #

Integral ApiKey Source # 
Num ApiKey Source # 
Ord ApiKey Source # 
Real ApiKey Source # 
Show ApiKey Source # 
Deserializable ApiKey Source # 
Serializable ApiKey Source # 

Methods

serialize :: ApiKey -> Put Source #

newtype ApiVersion Source #

Constructors

ApiVersion Int16 

Instances

Enum ApiVersion Source # 
Eq ApiVersion Source # 
Integral ApiVersion Source # 
Num ApiVersion Source # 
Ord ApiVersion Source # 
Real ApiVersion Source # 
Show ApiVersion Source # 
Deserializable ApiVersion Source # 
Serializable ApiVersion Source # 

newtype CorrelationId Source #

Constructors

CorrelationId Int32 

Instances

Enum CorrelationId Source # 
Eq CorrelationId Source # 
Integral CorrelationId Source # 
Num CorrelationId Source # 
Ord CorrelationId Source # 
Real CorrelationId Source # 
Show CorrelationId Source # 
Deserializable CorrelationId Source # 
Serializable CorrelationId Source # 

newtype NodeId Source #

Constructors

NodeId 

Fields

Instances

newtype Host Source #

Constructors

Host 

Instances

Eq Host Source # 

Methods

(==) :: Host -> Host -> Bool #

(/=) :: Host -> Host -> Bool #

Ord Host Source # 

Methods

compare :: Host -> Host -> Ordering #

(<) :: Host -> Host -> Bool #

(<=) :: Host -> Host -> Bool #

(>) :: Host -> Host -> Bool #

(>=) :: Host -> Host -> Bool #

max :: Host -> Host -> Host #

min :: Host -> Host -> Host #

Show Host Source # 

Methods

showsPrec :: Int -> Host -> ShowS #

show :: Host -> String #

showList :: [Host] -> ShowS #

IsString Host Source # 

Methods

fromString :: String -> Host #

Deserializable Host Source # 

newtype Port Source #

Constructors

Port 

Fields

Instances

Enum Port Source # 

Methods

succ :: Port -> Port #

pred :: Port -> Port #

toEnum :: Int -> Port #

fromEnum :: Port -> Int #

enumFrom :: Port -> [Port] #

enumFromThen :: Port -> Port -> [Port] #

enumFromTo :: Port -> Port -> [Port] #

enumFromThenTo :: Port -> Port -> Port -> [Port] #

Eq Port Source # 

Methods

(==) :: Port -> Port -> Bool #

(/=) :: Port -> Port -> Bool #

Integral Port Source # 

Methods

quot :: Port -> Port -> Port #

rem :: Port -> Port -> Port #

div :: Port -> Port -> Port #

mod :: Port -> Port -> Port #

quotRem :: Port -> Port -> (Port, Port) #

divMod :: Port -> Port -> (Port, Port) #

toInteger :: Port -> Integer #

Num Port Source # 

Methods

(+) :: Port -> Port -> Port #

(-) :: Port -> Port -> Port #

(*) :: Port -> Port -> Port #

negate :: Port -> Port #

abs :: Port -> Port #

signum :: Port -> Port #

fromInteger :: Integer -> Port #

Ord Port Source # 

Methods

compare :: Port -> Port -> Ordering #

(<) :: Port -> Port -> Bool #

(<=) :: Port -> Port -> Bool #

(>) :: Port -> Port -> Bool #

(>=) :: Port -> Port -> Bool #

max :: Port -> Port -> Port #

min :: Port -> Port -> Port #

Real Port Source # 

Methods

toRational :: Port -> Rational #

Show Port Source # 

Methods

showsPrec :: Int -> Port -> ShowS #

show :: Port -> String #

showList :: [Port] -> ShowS #

Deserializable Port Source # 

newtype Isr Source #

Constructors

Isr [Int32] 

Instances

Eq Isr Source # 

Methods

(==) :: Isr -> Isr -> Bool #

(/=) :: Isr -> Isr -> Bool #

Show Isr Source # 

Methods

showsPrec :: Int -> Isr -> ShowS #

show :: Isr -> String #

showList :: [Isr] -> ShowS #

Deserializable Isr Source # 

newtype Time Source #

Constructors

Time 

Fields

Instances

Bounded Time Source # 
Enum Time Source # 

Methods

succ :: Time -> Time #

pred :: Time -> Time #

toEnum :: Int -> Time #

fromEnum :: Time -> Int #

enumFrom :: Time -> [Time] #

enumFromThen :: Time -> Time -> [Time] #

enumFromTo :: Time -> Time -> [Time] #

enumFromThenTo :: Time -> Time -> Time -> [Time] #

Eq Time Source # 

Methods

(==) :: Time -> Time -> Bool #

(/=) :: Time -> Time -> Bool #

Integral Time Source # 

Methods

quot :: Time -> Time -> Time #

rem :: Time -> Time -> Time #

div :: Time -> Time -> Time #

mod :: Time -> Time -> Time #

quotRem :: Time -> Time -> (Time, Time) #

divMod :: Time -> Time -> (Time, Time) #

toInteger :: Time -> Integer #

Num Time Source # 

Methods

(+) :: Time -> Time -> Time #

(-) :: Time -> Time -> Time #

(*) :: Time -> Time -> Time #

negate :: Time -> Time #

abs :: Time -> Time #

signum :: Time -> Time #

fromInteger :: Integer -> Time #

Ord Time Source # 

Methods

compare :: Time -> Time -> Ordering #

(<) :: Time -> Time -> Bool #

(<=) :: Time -> Time -> Bool #

(>) :: Time -> Time -> Bool #

(>=) :: Time -> Time -> Bool #

max :: Time -> Time -> Time #

min :: Time -> Time -> Time #

Real Time Source # 

Methods

toRational :: Time -> Rational #

Show Time Source # 

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Serializable Time Source # 

Methods

serialize :: Time -> Put Source #

newtype MaxNumberOfOffsets Source #

Instances

Enum MaxNumberOfOffsets Source # 
Eq MaxNumberOfOffsets Source # 
Integral MaxNumberOfOffsets Source # 
Num MaxNumberOfOffsets Source # 
Ord MaxNumberOfOffsets Source # 
Real MaxNumberOfOffsets Source # 
Show MaxNumberOfOffsets Source # 
Serializable MaxNumberOfOffsets Source # 

newtype ReplicaId Source #

Constructors

ReplicaId Int32 

Instances

Enum ReplicaId Source # 
Eq ReplicaId Source # 
Integral ReplicaId Source # 
Num ReplicaId Source # 
Ord ReplicaId Source # 
Real ReplicaId Source # 
Show ReplicaId Source # 
Deserializable ReplicaId Source # 
Serializable ReplicaId Source # 

newtype MaxWaitTime Source #

Constructors

MaxWaitTime Int32 

Instances

Enum MaxWaitTime Source # 
Eq MaxWaitTime Source # 
Integral MaxWaitTime Source # 
Num MaxWaitTime Source # 
Ord MaxWaitTime Source # 
Real MaxWaitTime Source # 
Show MaxWaitTime Source # 
Deserializable MaxWaitTime Source # 
Serializable MaxWaitTime Source # 

newtype MinBytes Source #

Constructors

MinBytes Int32 

Instances

Enum MinBytes Source # 
Eq MinBytes Source # 
Integral MinBytes Source # 
Num MinBytes Source # 
Ord MinBytes Source # 
Real MinBytes Source # 
Show MinBytes Source # 
Deserializable MinBytes Source # 
Serializable MinBytes Source # 

newtype MaxBytes Source #

Constructors

MaxBytes Int32 

Instances

Enum MaxBytes Source # 
Eq MaxBytes Source # 
Integral MaxBytes Source # 
Num MaxBytes Source # 
Ord MaxBytes Source # 
Real MaxBytes Source # 
Show MaxBytes Source # 
Deserializable MaxBytes Source # 
Serializable MaxBytes Source # 

newtype RequiredAcks Source #

Constructors

RequiredAcks Int16 

Instances

Enum RequiredAcks Source # 
Eq RequiredAcks Source # 
Integral RequiredAcks Source # 
Num RequiredAcks Source # 
Ord RequiredAcks Source # 
Real RequiredAcks Source # 
Show RequiredAcks Source # 
Deserializable RequiredAcks Source # 
Serializable RequiredAcks Source # 

newtype Timeout Source #

Constructors

Timeout Int32 

Instances

Enum Timeout Source # 
Eq Timeout Source # 

Methods

(==) :: Timeout -> Timeout -> Bool #

(/=) :: Timeout -> Timeout -> Bool #

Integral Timeout Source # 
Num Timeout Source # 
Ord Timeout Source # 
Real Timeout Source # 
Show Timeout Source # 
Deserializable Timeout Source # 
Serializable Timeout Source # 

newtype Partition Source #

Constructors

Partition Int32 

Instances

Enum Partition Source # 
Eq Partition Source # 
Integral Partition Source # 
Num Partition Source # 
Ord Partition Source # 
Real Partition Source # 
Show Partition Source # 
Deserializable Partition Source # 
Serializable Partition Source # 

newtype Offset Source #

Constructors

Offset Int64 

Instances

Enum Offset Source # 
Eq Offset Source # 

Methods

(==) :: Offset -> Offset -> Bool #

(/=) :: Offset -> Offset -> Bool #

Integral Offset Source # 
Num Offset Source # 
Ord Offset Source # 
Real Offset Source # 
Show Offset Source # 
Deserializable Offset Source # 
Serializable Offset Source # 

Methods

serialize :: Offset -> Put Source #

newtype Crc Source #

Constructors

Crc Int32 

Instances

Enum Crc Source # 

Methods

succ :: Crc -> Crc #

pred :: Crc -> Crc #

toEnum :: Int -> Crc #

fromEnum :: Crc -> Int #

enumFrom :: Crc -> [Crc] #

enumFromThen :: Crc -> Crc -> [Crc] #

enumFromTo :: Crc -> Crc -> [Crc] #

enumFromThenTo :: Crc -> Crc -> Crc -> [Crc] #

Eq Crc Source # 

Methods

(==) :: Crc -> Crc -> Bool #

(/=) :: Crc -> Crc -> Bool #

Integral Crc Source # 

Methods

quot :: Crc -> Crc -> Crc #

rem :: Crc -> Crc -> Crc #

div :: Crc -> Crc -> Crc #

mod :: Crc -> Crc -> Crc #

quotRem :: Crc -> Crc -> (Crc, Crc) #

divMod :: Crc -> Crc -> (Crc, Crc) #

toInteger :: Crc -> Integer #

Num Crc Source # 

Methods

(+) :: Crc -> Crc -> Crc #

(-) :: Crc -> Crc -> Crc #

(*) :: Crc -> Crc -> Crc #

negate :: Crc -> Crc #

abs :: Crc -> Crc #

signum :: Crc -> Crc #

fromInteger :: Integer -> Crc #

Ord Crc Source # 

Methods

compare :: Crc -> Crc -> Ordering #

(<) :: Crc -> Crc -> Bool #

(<=) :: Crc -> Crc -> Bool #

(>) :: Crc -> Crc -> Bool #

(>=) :: Crc -> Crc -> Bool #

max :: Crc -> Crc -> Crc #

min :: Crc -> Crc -> Crc #

Real Crc Source # 

Methods

toRational :: Crc -> Rational #

Show Crc Source # 

Methods

showsPrec :: Int -> Crc -> ShowS #

show :: Crc -> String #

showList :: [Crc] -> ShowS #

Deserializable Crc Source # 
Serializable Crc Source # 

Methods

serialize :: Crc -> Put Source #

newtype MagicByte Source #

Constructors

MagicByte Int8 

Instances

Enum MagicByte Source # 
Eq MagicByte Source # 
Integral MagicByte Source # 
Num MagicByte Source # 
Ord MagicByte Source # 
Real MagicByte Source # 
Show MagicByte Source # 
Deserializable MagicByte Source # 
Serializable MagicByte Source # 

newtype Attributes Source #

Constructors

Attributes Int8 

Instances

Enum Attributes Source # 
Eq Attributes Source # 
Integral Attributes Source # 
Num Attributes Source # 
Ord Attributes Source # 
Real Attributes Source # 
Show Attributes Source # 
Deserializable Attributes Source # 
Serializable Attributes Source # 

newtype Key Source #

Constructors

Key 

Instances

data KafkaError Source #

Constructors

NoError

0 No error--it worked!

Unknown

-1 An unexpected server error

OffsetOutOfRange

1 The requested offset is outside the range of offsets maintained by the server for the given topic/partition.

InvalidMessage

2 This indicates that a message contents does not match its CRC

UnknownTopicOrPartition

3 This request is for a topic or partition that does not exist on this broker.

InvalidMessageSize

4 The message has a negative size

LeaderNotAvailable

5 This error is thrown if we are in the middle of a leadership election and there is currently no leader for this partition and hence it is unavailable for writes.

NotLeaderForPartition

6 This error is thrown if the client attempts to send messages to a replica that is not the leader for some partition. It indicates that the clients metadata is out of date.

RequestTimedOut

7 This error is thrown if the request exceeds the user-specified time limit in the request.

BrokerNotAvailable

8 This is not a client facing error and is used mostly by tools when a broker is not alive.

ReplicaNotAvailable

9 If replica is expected on a broker, but is not.

MessageSizeTooLarge

10 The server has a configurable maximum message size to avoid unbounded memory allocation. This error is thrown if the client attempt to produce a message larger than this maximum.

StaleControllerEpochCode

11 Internal error code for broker-to-broker communication.

OffsetMetadataTooLargeCode

12 If you specify a string larger than configured maximum for offset metadata

OffsetsLoadInProgressCode

14 The broker returns this error code for an offset fetch request if it is still loading offsets (after a leader change for that offsets topic partition).

ConsumerCoordinatorNotAvailableCode

15 The broker returns this error code for consumer metadata requests or offset commit requests if the offsets topic has not yet been created.

NotCoordinatorForConsumerCode

16 The broker returns this error code if it receives an offset fetch or commit request for a consumer group that it is not a coordinator for.

Generated lenses

Composed lenses

keyed :: (Field1 a a b b, Choice p, Applicative f, Eq b) => b -> Optic' p f a a Source #