hw-kafka-client-4.0.2: Kafka bindings for Haskell

Safe HaskellNone
LanguageHaskell2010

Kafka.Metadata

Description

Module with metadata types and functions.

Synopsis

Documentation

data KafkaMetadata Source #

Instances
Eq KafkaMetadata Source # 
Instance details

Defined in Kafka.Metadata

Show KafkaMetadata Source # 
Instance details

Defined in Kafka.Metadata

Generic KafkaMetadata Source # 
Instance details

Defined in Kafka.Metadata

Associated Types

type Rep KafkaMetadata :: Type -> Type #

type Rep KafkaMetadata Source # 
Instance details

Defined in Kafka.Metadata

type Rep KafkaMetadata = D1 (MetaData "KafkaMetadata" "Kafka.Metadata" "hw-kafka-client-4.0.2-inplace" False) (C1 (MetaCons "KafkaMetadata" PrefixI True) (S1 (MetaSel (Just "kmBrokers") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [BrokerMetadata]) :*: (S1 (MetaSel (Just "kmTopics") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TopicMetadata]) :*: S1 (MetaSel (Just "kmOrigBroker") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 BrokerId))))

data BrokerMetadata Source #

Instances
Eq BrokerMetadata Source # 
Instance details

Defined in Kafka.Metadata

Show BrokerMetadata Source # 
Instance details

Defined in Kafka.Metadata

Generic BrokerMetadata Source # 
Instance details

Defined in Kafka.Metadata

Associated Types

type Rep BrokerMetadata :: Type -> Type #

type Rep BrokerMetadata Source # 
Instance details

Defined in Kafka.Metadata

type Rep BrokerMetadata = D1 (MetaData "BrokerMetadata" "Kafka.Metadata" "hw-kafka-client-4.0.2-inplace" False) (C1 (MetaCons "BrokerMetadata" PrefixI True) (S1 (MetaSel (Just "bmBrokerId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 BrokerId) :*: (S1 (MetaSel (Just "bmBrokerHost") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "bmBrokerPort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))))

data TopicMetadata Source #

Instances
Eq TopicMetadata Source # 
Instance details

Defined in Kafka.Metadata

Show TopicMetadata Source # 
Instance details

Defined in Kafka.Metadata

Generic TopicMetadata Source # 
Instance details

Defined in Kafka.Metadata

Associated Types

type Rep TopicMetadata :: Type -> Type #

type Rep TopicMetadata Source # 
Instance details

Defined in Kafka.Metadata

data PartitionMetadata Source #

data GroupMemberInfo Source #

newtype GroupProtocolType Source #

Constructors

GroupProtocolType Text 
Instances
Eq GroupProtocolType Source # 
Instance details

Defined in Kafka.Metadata

Ord GroupProtocolType Source # 
Instance details

Defined in Kafka.Metadata

Read GroupProtocolType Source # 
Instance details

Defined in Kafka.Metadata

Show GroupProtocolType Source # 
Instance details

Defined in Kafka.Metadata

Generic GroupProtocolType Source # 
Instance details

Defined in Kafka.Metadata

Associated Types

type Rep GroupProtocolType :: Type -> Type #

type Rep GroupProtocolType Source # 
Instance details

Defined in Kafka.Metadata

type Rep GroupProtocolType = D1 (MetaData "GroupProtocolType" "Kafka.Metadata" "hw-kafka-client-4.0.2-inplace" True) (C1 (MetaCons "GroupProtocolType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype GroupProtocol Source #

Constructors

GroupProtocol Text 
Instances
Eq GroupProtocol Source # 
Instance details

Defined in Kafka.Metadata

Ord GroupProtocol Source # 
Instance details

Defined in Kafka.Metadata

Read GroupProtocol Source # 
Instance details

Defined in Kafka.Metadata

Show GroupProtocol Source # 
Instance details

Defined in Kafka.Metadata

Generic GroupProtocol Source # 
Instance details

Defined in Kafka.Metadata

Associated Types

type Rep GroupProtocol :: Type -> Type #

type Rep GroupProtocol Source # 
Instance details

Defined in Kafka.Metadata

type Rep GroupProtocol = D1 (MetaData "GroupProtocol" "Kafka.Metadata" "hw-kafka-client-4.0.2-inplace" True) (C1 (MetaCons "GroupProtocol" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data GroupState Source #

Constructors

GroupPreparingRebalance

Group is preparing to rebalance

GroupEmpty

Group has no more members, but lingers until all offsets have expired

GroupAwaitingSync

Group is awaiting state assignment from the leader

GroupStable

Group is stable

GroupDead

Group has no more members and its metadata is being removed

Instances
Eq GroupState Source # 
Instance details

Defined in Kafka.Metadata

Ord GroupState Source # 
Instance details

Defined in Kafka.Metadata

Read GroupState Source # 
Instance details

Defined in Kafka.Metadata

Show GroupState Source # 
Instance details

Defined in Kafka.Metadata

Generic GroupState Source # 
Instance details

Defined in Kafka.Metadata

Associated Types

type Rep GroupState :: Type -> Type #

type Rep GroupState Source # 
Instance details

Defined in Kafka.Metadata

type Rep GroupState = D1 (MetaData "GroupState" "Kafka.Metadata" "hw-kafka-client-4.0.2-inplace" False) ((C1 (MetaCons "GroupPreparingRebalance" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GroupEmpty" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "GroupAwaitingSync" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "GroupStable" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GroupDead" PrefixI False) (U1 :: Type -> Type))))

data GroupInfo Source #

allTopicsMetadata :: (MonadIO m, HasKafka k) => k -> Timeout -> m (Either KafkaError KafkaMetadata) Source #

Returns metadata for all topics in the cluster

topicMetadata :: (MonadIO m, HasKafka k) => k -> Timeout -> TopicName -> m (Either KafkaError KafkaMetadata) Source #

Returns metadata only for specified topic

watermarkOffsets :: (MonadIO m, HasKafka k) => k -> Timeout -> TopicName -> m [Either KafkaError WatermarkOffsets] Source #

Query broker for low (oldestbeginning) and high (newestend) offsets for a given topic.

watermarkOffsets' :: (MonadIO m, HasKafka k) => k -> Timeout -> TopicMetadata -> m [Either KafkaError WatermarkOffsets] Source #

Query broker for low (oldestbeginning) and high (newestend) offsets for a given topic.

partitionWatermarkOffsets :: (MonadIO m, HasKafka k) => k -> Timeout -> TopicName -> PartitionId -> m (Either KafkaError WatermarkOffsets) Source #

Query broker for low (oldestbeginning) and high (newestend) offsets for a specific partition

offsetsForTime :: (MonadIO m, HasKafka k) => k -> Timeout -> Millis -> [(TopicName, PartitionId)] -> m (Either KafkaError [TopicPartition]) Source #

Look up the offsets for the given partitions by timestamp.

The returned offset for each partition is the earliest offset whose timestamp is greater than or equal to the given timestamp in the corresponding partition.

offsetsForTime' :: (MonadIO m, HasKafka k) => k -> Timeout -> Millis -> TopicMetadata -> m (Either KafkaError [TopicPartition]) Source #

Look up the offsets for the given metadata by timestamp.

The returned offset for each partition is the earliest offset whose timestamp is greater than or equal to the given timestamp in the corresponding partition.

topicOffsetsForTime :: (MonadIO m, HasKafka k) => k -> Timeout -> Millis -> TopicName -> m (Either KafkaError [TopicPartition]) Source #

Look up the offsets for the given topic by timestamp.

The returned offset for each partition is the earliest offset whose timestamp is greater than or equal to the given timestamp in the corresponding partition.

allConsumerGroupsInfo :: (MonadIO m, HasKafka k) => k -> Timeout -> m (Either KafkaError [GroupInfo]) Source #

List and describe all consumer groups in cluster.

consumerGroupInfo :: (MonadIO m, HasKafka k) => k -> Timeout -> ConsumerGroupId -> m (Either KafkaError [GroupInfo]) Source #

Describe a given consumer group.