| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Kafka.Consumer.Types
Contents
Description
Module holding consumer types.
Synopsis
- data KafkaConsumer = KafkaConsumer {
- kcKafkaPtr :: !Kafka
- kcKafkaConf :: !KafkaConf
- newtype ConsumerGroupId = ConsumerGroupId {}
- newtype Offset = Offset {}
- data OffsetReset
- data RebalanceEvent
- data PartitionOffset
- data SubscribedPartitions
- data Timestamp
- data OffsetCommit
- data OffsetStoreSync
- data OffsetStoreMethod
- data TopicPartition = TopicPartition {}
- data ConsumerRecord k v = ConsumerRecord {
- crTopic :: !TopicName
- crPartition :: !PartitionId
- crOffset :: !Offset
- crTimestamp :: !Timestamp
- crHeaders :: !Headers
- crKey :: !k
- crValue :: !v
- crMapKey :: (k -> k') -> ConsumerRecord k v -> ConsumerRecord k' v
- crMapValue :: (v -> v') -> ConsumerRecord k v -> ConsumerRecord k v'
- crMapKV :: (k -> k') -> (v -> v') -> ConsumerRecord k v -> ConsumerRecord k' v'
- sequenceFirst :: (Bitraversable t, Applicative f) => t (f k) v -> f (t k v)
- traverseFirst :: (Bitraversable t, Applicative f) => (k -> f k') -> t k v -> f (t k' v)
- traverseFirstM :: (Bitraversable t, Applicative f, Monad m) => (k -> m (f k')) -> t k v -> m (f (t k' v))
- traverseM :: (Traversable t, Applicative f, Monad m) => (v -> m (f v')) -> t v -> m (f (t v'))
- bitraverseM :: (Bitraversable t, Applicative f, Monad m) => (k -> m (f k')) -> (v -> m (f v')) -> t k v -> m (f (t k' v'))
Documentation
data KafkaConsumer Source #
The main type for Kafka consumption, used e.g. to poll and commit messages.
Its constructor is intentionally not exposed, instead, one should use newConsumer to acquire such a value.
Constructors
| KafkaConsumer | |
Fields
| |
newtype ConsumerGroupId Source #
Consumer group ID. Different consumers with the same consumer group ID will get assigned different partitions of each subscribed topic.
Constructors
| ConsumerGroupId | |
Fields | |
Instances
A message offset in a partition
data OffsetReset Source #
Where to reset the offset when there is no initial offset in Kafka
Instances
| Eq OffsetReset Source # | |
Defined in Kafka.Consumer.Types | |
| Show OffsetReset Source # | |
Defined in Kafka.Consumer.Types Methods showsPrec :: Int -> OffsetReset -> ShowS # show :: OffsetReset -> String # showList :: [OffsetReset] -> ShowS # | |
| Generic OffsetReset Source # | |
Defined in Kafka.Consumer.Types Associated Types type Rep OffsetReset :: Type -> Type # | |
| type Rep OffsetReset Source # | |
data RebalanceEvent Source #
A set of events which happen during the rebalancing process
Constructors
| RebalanceBeforeAssign [(TopicName, PartitionId)] | Happens before Kafka Client confirms new assignment |
| RebalanceAssign [(TopicName, PartitionId)] | Happens after the new assignment is confirmed |
| RebalanceBeforeRevoke [(TopicName, PartitionId)] | Happens before Kafka Client confirms partitions rejection |
| RebalanceRevoke [(TopicName, PartitionId)] | Happens after the rejection is confirmed |
Instances
data PartitionOffset Source #
The partition offset
Constructors
| PartitionOffsetBeginning | |
| PartitionOffsetEnd | |
| PartitionOffset Int64 | |
| PartitionOffsetStored | |
| PartitionOffsetInvalid |
Instances
data SubscribedPartitions Source #
Partitions subscribed by a consumer
Constructors
| SubscribedPartitions [PartitionId] | Subscribe only to those partitions |
| SubscribedPartitionsAll | Subscribe to all partitions |
Instances
Consumer record timestamp
Constructors
| CreateTime !Millis | |
| LogAppendTime !Millis | |
| NoTimestamp |
Instances
| Eq Timestamp Source # | |
| Read Timestamp Source # | |
| Show Timestamp Source # | |
| Generic Timestamp Source # | |
| type Rep Timestamp Source # | |
Defined in Kafka.Consumer.Types type Rep Timestamp = D1 ('MetaData "Timestamp" "Kafka.Consumer.Types" "hw-kafka-client-5.0.0-inplace" 'False) (C1 ('MetaCons "CreateTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Millis)) :+: (C1 ('MetaCons "LogAppendTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Millis)) :+: C1 ('MetaCons "NoTimestamp" 'PrefixI 'False) (U1 :: Type -> Type))) | |
data OffsetCommit Source #
Offsets commit mode
Constructors
| OffsetCommit | Forces consumer to block until the broker offsets commit is done |
| OffsetCommitAsync | Offsets will be committed in a non-blocking way |
Instances
| Eq OffsetCommit Source # | |
Defined in Kafka.Consumer.Types | |
| Show OffsetCommit Source # | |
Defined in Kafka.Consumer.Types Methods showsPrec :: Int -> OffsetCommit -> ShowS # show :: OffsetCommit -> String # showList :: [OffsetCommit] -> ShowS # | |
| Generic OffsetCommit Source # | |
Defined in Kafka.Consumer.Types Associated Types type Rep OffsetCommit :: Type -> Type # | |
| type Rep OffsetCommit Source # | |
data OffsetStoreSync Source #
Indicates how offsets are to be synced to disk
Constructors
| OffsetSyncDisable | Do not sync offsets (in Kafka: -1) |
| OffsetSyncImmediate | Sync immediately after each offset commit (in Kafka: 0) |
| OffsetSyncInterval Int | Sync after specified interval in millis |
Instances
data OffsetStoreMethod Source #
Indicates the method of storing the offsets
Constructors
| OffsetStoreBroker | Offsets are stored in Kafka broker (preferred) |
| OffsetStoreFile FilePath OffsetStoreSync | Offsets are stored in a file (and synced to disk according to the sync policy) |
Instances
data TopicPartition Source #
Kafka topic partition structure
Constructors
| TopicPartition | |
Fields | |
Instances
data ConsumerRecord k v Source #
Represents a received message from Kafka (i.e. used in a consumer)
Constructors
| ConsumerRecord | |
Fields
| |
Instances
crMapKey :: (k -> k') -> ConsumerRecord k v -> ConsumerRecord k' v Source #
Deprecated: Isn't concern of this library. Use first
crMapValue :: (v -> v') -> ConsumerRecord k v -> ConsumerRecord k v' Source #
Deprecated: Isn't concern of this library. Use second
crMapKV :: (k -> k') -> (v -> v') -> ConsumerRecord k v -> ConsumerRecord k' v' Source #
Deprecated: Isn't concern of this library. Use bimap
Deprecated
sequenceFirst :: (Bitraversable t, Applicative f) => t (f k) v -> f (t k v) Source #
Deprecated: Isn't concern of this library. Use bitraverse id pure
traverseFirst :: (Bitraversable t, Applicative f) => (k -> f k') -> t k v -> f (t k' v) Source #
Deprecated: Isn't concern of this library. Use bitraverse f pure
traverseFirstM :: (Bitraversable t, Applicative f, Monad m) => (k -> m (f k')) -> t k v -> m (f (t k' v)) Source #
Deprecated: Isn't concern of this library. Use bitraverse id pure <$> bitraverse f pure r
traverseM :: (Traversable t, Applicative f, Monad m) => (v -> m (f v')) -> t v -> m (f (t v')) Source #
bitraverseM :: (Bitraversable t, Applicative f, Monad m) => (k -> m (f k')) -> (v -> m (f v')) -> t k v -> m (f (t k' v')) Source #
Deprecated: Isn't concern of this library. Use bisequenceA <$> bimapM f g r