hw-kafka-client-5.0.0: Kafka bindings for Haskell
Safe HaskellNone
LanguageHaskell2010

Kafka.Types

Description

Module holding types shared by consumer and producer modules.

Synopsis

Documentation

newtype BrokerId Source #

Kafka broker ID

Constructors

BrokerId 

Fields

Instances

Instances details
Eq BrokerId Source # 
Instance details

Defined in Kafka.Types

Ord BrokerId Source # 
Instance details

Defined in Kafka.Types

Read BrokerId Source # 
Instance details

Defined in Kafka.Types

Show BrokerId Source # 
Instance details

Defined in Kafka.Types

Generic BrokerId Source # 
Instance details

Defined in Kafka.Types

Associated Types

type Rep BrokerId :: Type -> Type #

Methods

from :: BrokerId -> Rep BrokerId x #

to :: Rep BrokerId x -> BrokerId #

type Rep BrokerId Source # 
Instance details

Defined in Kafka.Types

type Rep BrokerId = D1 ('MetaData "BrokerId" "Kafka.Types" "hw-kafka-client-5.0.0-inplace" 'True) (C1 ('MetaCons "BrokerId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBrokerId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

newtype PartitionId Source #

Topic partition ID

Constructors

PartitionId 

Fields

Instances

Instances details
Enum PartitionId Source # 
Instance details

Defined in Kafka.Types

Eq PartitionId Source # 
Instance details

Defined in Kafka.Types

Ord PartitionId Source # 
Instance details

Defined in Kafka.Types

Read PartitionId Source # 
Instance details

Defined in Kafka.Types

Show PartitionId Source # 
Instance details

Defined in Kafka.Types

Generic PartitionId Source # 
Instance details

Defined in Kafka.Types

Associated Types

type Rep PartitionId :: Type -> Type #

type Rep PartitionId Source # 
Instance details

Defined in Kafka.Types

type Rep PartitionId = D1 ('MetaData "PartitionId" "Kafka.Types" "hw-kafka-client-5.0.0-inplace" 'True) (C1 ('MetaCons "PartitionId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPartitionId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

newtype Millis Source #

A number of milliseconds, used to represent durations and timestamps

Constructors

Millis 

Fields

Instances

Instances details
Eq Millis Source # 
Instance details

Defined in Kafka.Types

Methods

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

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

Num Millis Source # 
Instance details

Defined in Kafka.Types

Ord Millis Source # 
Instance details

Defined in Kafka.Types

Read Millis Source # 
Instance details

Defined in Kafka.Types

Show Millis Source # 
Instance details

Defined in Kafka.Types

Generic Millis Source # 
Instance details

Defined in Kafka.Types

Associated Types

type Rep Millis :: Type -> Type #

Methods

from :: Millis -> Rep Millis x #

to :: Rep Millis x -> Millis #

type Rep Millis Source # 
Instance details

Defined in Kafka.Types

type Rep Millis = D1 ('MetaData "Millis" "Kafka.Types" "hw-kafka-client-5.0.0-inplace" 'True) (C1 ('MetaCons "Millis" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMillis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))

newtype ClientId Source #

Client ID used by Kafka to better track requests

See Kafka documentation on client ID

Constructors

ClientId 

Fields

Instances

Instances details
Eq ClientId Source # 
Instance details

Defined in Kafka.Types

Ord ClientId Source # 
Instance details

Defined in Kafka.Types

Show ClientId Source # 
Instance details

Defined in Kafka.Types

IsString ClientId Source # 
Instance details

Defined in Kafka.Types

Generic ClientId Source # 
Instance details

Defined in Kafka.Types

Associated Types

type Rep ClientId :: Type -> Type #

Methods

from :: ClientId -> Rep ClientId x #

to :: Rep ClientId x -> ClientId #

type Rep ClientId Source # 
Instance details

Defined in Kafka.Types

type Rep ClientId = D1 ('MetaData "ClientId" "Kafka.Types" "hw-kafka-client-5.0.0-inplace" 'True) (C1 ('MetaCons "ClientId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unClientId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype BatchSize Source #

Batch size used for polling

Constructors

BatchSize 

Fields

Instances

Instances details
Eq BatchSize Source # 
Instance details

Defined in Kafka.Types

Num BatchSize Source # 
Instance details

Defined in Kafka.Types

Ord BatchSize Source # 
Instance details

Defined in Kafka.Types

Read BatchSize Source # 
Instance details

Defined in Kafka.Types

Show BatchSize Source # 
Instance details

Defined in Kafka.Types

Generic BatchSize Source # 
Instance details

Defined in Kafka.Types

Associated Types

type Rep BatchSize :: Type -> Type #

type Rep BatchSize Source # 
Instance details

Defined in Kafka.Types

type Rep BatchSize = D1 ('MetaData "BatchSize" "Kafka.Types" "hw-kafka-client-5.0.0-inplace" 'True) (C1 ('MetaCons "BatchSize" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBatchSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

newtype TopicName Source #

Topic name to consume/produce messages

Wildcard (regex) topics are supported by the librdkafka assignor: any topic name in the topics list that is prefixed with ^ will be regex-matched to the full list of topics in the cluster and matching topics will be added to the subscription list.

Constructors

TopicName 

Fields

Instances

Instances details
Eq TopicName Source # 
Instance details

Defined in Kafka.Types

Ord TopicName Source # 
Instance details

Defined in Kafka.Types

Read TopicName Source # 
Instance details

Defined in Kafka.Types

Show TopicName Source # 
Instance details

Defined in Kafka.Types

IsString TopicName Source # 
Instance details

Defined in Kafka.Types

Generic TopicName Source # 
Instance details

Defined in Kafka.Types

Associated Types

type Rep TopicName :: Type -> Type #

type Rep TopicName Source # 
Instance details

Defined in Kafka.Types

type Rep TopicName = D1 ('MetaData "TopicName" "Kafka.Types" "hw-kafka-client-5.0.0-inplace" 'True) (C1 ('MetaCons "TopicName" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTopicName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype BrokerAddress Source #

Kafka broker address string (e.g. broker1:9092)

Constructors

BrokerAddress 

Instances

Instances details
Eq BrokerAddress Source # 
Instance details

Defined in Kafka.Types

Show BrokerAddress Source # 
Instance details

Defined in Kafka.Types

IsString BrokerAddress Source # 
Instance details

Defined in Kafka.Types

Generic BrokerAddress Source # 
Instance details

Defined in Kafka.Types

Associated Types

type Rep BrokerAddress :: Type -> Type #

type Rep BrokerAddress Source # 
Instance details

Defined in Kafka.Types

type Rep BrokerAddress = D1 ('MetaData "BrokerAddress" "Kafka.Types" "hw-kafka-client-5.0.0-inplace" 'True) (C1 ('MetaCons "BrokerAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBrokerAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype Timeout Source #

Timeout in milliseconds

Constructors

Timeout 

Fields

Instances

Instances details
Eq Timeout Source # 
Instance details

Defined in Kafka.Types

Methods

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

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

Read Timeout Source # 
Instance details

Defined in Kafka.Types

Show Timeout Source # 
Instance details

Defined in Kafka.Types

Generic Timeout Source # 
Instance details

Defined in Kafka.Types

Associated Types

type Rep Timeout :: Type -> Type #

Methods

from :: Timeout -> Rep Timeout x #

to :: Rep Timeout x -> Timeout #

type Rep Timeout Source # 
Instance details

Defined in Kafka.Types

type Rep Timeout = D1 ('MetaData "Timeout" "Kafka.Types" "hw-kafka-client-5.0.0-inplace" 'True) (C1 ('MetaCons "Timeout" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTimeout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data KafkaError Source #

All possible Kafka errors

Instances

Instances details
Eq KafkaError Source # 
Instance details

Defined in Kafka.Types

Show KafkaError Source # 
Instance details

Defined in Kafka.Types

Generic KafkaError Source # 
Instance details

Defined in Kafka.Types

Associated Types

type Rep KafkaError :: Type -> Type #

Exception KafkaError Source # 
Instance details

Defined in Kafka.Types

type Rep KafkaError Source # 
Instance details

Defined in Kafka.Types

type Rep KafkaError = D1 ('MetaData "KafkaError" "Kafka.Types" "hw-kafka-client-5.0.0-inplace" 'False) ((C1 ('MetaCons "KafkaError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "KafkaInvalidReturnValue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KafkaBadSpecification" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) :+: ((C1 ('MetaCons "KafkaResponseError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RdKafkaRespErrT)) :+: C1 ('MetaCons "KafkaInvalidConfigurationValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "KafkaUnknownConfigurationKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "KafkaBadConfiguration" 'PrefixI 'False) (U1 :: Type -> Type))))

data KafkaDebug Source #

Available librdkafka debug contexts

Instances

Instances details
Eq KafkaDebug Source # 
Instance details

Defined in Kafka.Types

Show KafkaDebug Source # 
Instance details

Defined in Kafka.Types

Generic KafkaDebug Source # 
Instance details

Defined in Kafka.Types

Associated Types

type Rep KafkaDebug :: Type -> Type #

type Rep KafkaDebug Source # 
Instance details

Defined in Kafka.Types

type Rep KafkaDebug = D1 ('MetaData "KafkaDebug" "Kafka.Types" "hw-kafka-client-5.0.0-inplace" 'False) (((C1 ('MetaCons "DebugGeneric" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DebugBroker" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DebugTopic" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DebugMetadata" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DebugQueue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DebugMsg" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DebugProtocol" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DebugCgrp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DebugSecurity" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DebugFetch" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DebugFeature" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DebugAll" 'PrefixI 'False) (U1 :: Type -> Type)))))

data KafkaCompressionCodec Source #

Compression codec used by a topic

See Kafka documentation on compression codecs

Constructors

NoCompression 
Gzip 
Snappy 
Lz4 

Instances

Instances details
Eq KafkaCompressionCodec Source # 
Instance details

Defined in Kafka.Types

Show KafkaCompressionCodec Source # 
Instance details

Defined in Kafka.Types

Generic KafkaCompressionCodec Source # 
Instance details

Defined in Kafka.Types

Associated Types

type Rep KafkaCompressionCodec :: Type -> Type #

type Rep KafkaCompressionCodec Source # 
Instance details

Defined in Kafka.Types

type Rep KafkaCompressionCodec = D1 ('MetaData "KafkaCompressionCodec" "Kafka.Types" "hw-kafka-client-5.0.0-inplace" 'False) ((C1 ('MetaCons "NoCompression" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Gzip" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Snappy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Lz4" 'PrefixI 'False) (U1 :: Type -> Type)))

data TopicType Source #

Whether the topic is created by a user or by the system

Constructors

User

Normal topics that are created by user.

System

Topics starting with a double underscore "__" (__consumer_offsets, __confluent.support.metrics, etc.) are considered "system" topics

Instances

Instances details
Eq TopicType Source # 
Instance details

Defined in Kafka.Types

Ord TopicType Source # 
Instance details

Defined in Kafka.Types

Read TopicType Source # 
Instance details

Defined in Kafka.Types

Show TopicType Source # 
Instance details

Defined in Kafka.Types

Generic TopicType Source # 
Instance details

Defined in Kafka.Types

Associated Types

type Rep TopicType :: Type -> Type #

type Rep TopicType Source # 
Instance details

Defined in Kafka.Types

type Rep TopicType = D1 ('MetaData "TopicType" "Kafka.Types" "hw-kafka-client-5.0.0-inplace" 'False) (C1 ('MetaCons "User" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "System" 'PrefixI 'False) (U1 :: Type -> Type))

data Headers Source #

Headers that might be passed along with a record

Instances

Instances details
Eq Headers Source # 
Instance details

Defined in Kafka.Types

Methods

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

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

Read Headers Source # 
Instance details

Defined in Kafka.Types

Show Headers Source # 
Instance details

Defined in Kafka.Types

Generic Headers Source # 
Instance details

Defined in Kafka.Types

Associated Types

type Rep Headers :: Type -> Type #

Methods

from :: Headers -> Rep Headers x #

to :: Rep Headers x -> Headers #

Semigroup Headers Source # 
Instance details

Defined in Kafka.Types

Monoid Headers Source # 
Instance details

Defined in Kafka.Types

type Rep Headers Source # 
Instance details

Defined in Kafka.Types

type Rep Headers = D1 ('MetaData "Headers" "Kafka.Types" "hw-kafka-client-5.0.0-inplace" 'True) (C1 ('MetaCons "Headers" 'PrefixI 'True) (S1 ('MetaSel ('Just "unHeaders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ByteString, ByteString)])))

topicType :: TopicName -> TopicType Source #

Deduce the type of a topic from its name, by checking if it starts with a double underscore "__"

kafkaDebugToText :: KafkaDebug -> Text Source #

Convert a KafkaDebug into its librdkafka string equivalent.

This is used internally by the library but may be useful to some developers.

kafkaCompressionCodecToText :: KafkaCompressionCodec -> Text Source #

Convert a KafkaCompressionCodec into its librdkafka string equivalent.

This is used internally by the library but may be useful to some developers.