@@ -30,14 +30,17 @@ where
30
30
31
31
import Data.Bifoldable (Bifoldable (.. ))
32
32
import Data.Bifunctor (Bifunctor (.. ))
33
- import Data.Bitraversable (Bitraversable (.. ), bimapM , bisequenceA )
33
+ import Data.Bitraversable (Bitraversable (.. ), bimapM , bisequence )
34
34
import Data.Int (Int64 )
35
35
import Data.Text (Text )
36
36
import Data.Typeable (Typeable )
37
37
import GHC.Generics (Generic )
38
38
import Kafka.Internal.Setup (HasKafka (.. ), HasKafkaConf (.. ), Kafka (.. ), KafkaConf (.. ))
39
39
import Kafka.Types (Millis (.. ), PartitionId (.. ), TopicName (.. ))
40
40
41
+ -- | The main type for Kafka consumption, used e.g. to poll and commit messages.
42
+ --
43
+ -- Its constructor is intentionally not exposed, instead, one should used 'newConsumer' to acquire such a value.
41
44
data KafkaConsumer = KafkaConsumer
42
45
{ kcKafkaPtr :: ! Kafka
43
46
, kcKafkaConf :: ! KafkaConf
@@ -51,8 +54,17 @@ instance HasKafkaConf KafkaConsumer where
51
54
getKafkaConf = kcKafkaConf
52
55
{-# INLINE getKafkaConf #-}
53
56
57
+ -- | Consumer group ID. Different consumers with the same consumer group ID will get assigned different partitions of each subscribed topic.
58
+ --
59
+ -- See <https://kafka.apache.org/documentation/#group.id Kafka documentation on consumer group>
54
60
newtype ConsumerGroupId = ConsumerGroupId { unConsumerGroupId :: Text } deriving (Show , Ord , Eq , Generic )
61
+
62
+ -- | A message offset in a partition
55
63
newtype Offset = Offset { unOffset :: Int64 } deriving (Show , Eq , Ord , Read , Generic )
64
+
65
+ -- | Where to reset the offset when there is no initial offset in Kafka
66
+ --
67
+ -- See <https://kafka.apache.org/documentation/#auto.offset.reset Kafka documentation on offset reset>
56
68
data OffsetReset = Earliest | Latest deriving (Show , Eq , Generic )
57
69
58
70
-- | A set of events which happen during the rebalancing process
@@ -67,6 +79,7 @@ data RebalanceEvent =
67
79
| RebalanceRevoke [(TopicName , PartitionId )]
68
80
deriving (Eq , Show , Generic )
69
81
82
+ -- | The partition offset
70
83
data PartitionOffset =
71
84
PartitionOffsetBeginning
72
85
| PartitionOffsetEnd
@@ -75,11 +88,13 @@ data PartitionOffset =
75
88
| PartitionOffsetInvalid
76
89
deriving (Eq , Show , Generic )
77
90
91
+ -- | Partitions subscribed by a consumer
78
92
data SubscribedPartitions
79
- = SubscribedPartitions [PartitionId ]
80
- | SubscribedPartitionsAll
93
+ = SubscribedPartitions [PartitionId ] -- ^ Subscribe only to those partitions
94
+ | SubscribedPartitionsAll -- ^ Subscribe to all partitions
81
95
deriving (Show , Eq , Generic )
82
96
97
+ -- | Consumer record timestamp
83
98
data Timestamp =
84
99
CreateTime ! Millis
85
100
| LogAppendTime ! Millis
@@ -119,8 +134,8 @@ data ConsumerRecord k v = ConsumerRecord
119
134
, crPartition :: ! PartitionId -- ^ Kafka partition this message was received from
120
135
, crOffset :: ! Offset -- ^ Offset within the 'crPartition' Kafka partition
121
136
, crTimestamp :: ! Timestamp -- ^ Message timestamp
122
- , crKey :: ! k
123
- , crValue :: ! v
137
+ , crKey :: ! k -- ^ Message key
138
+ , crValue :: ! v -- ^ Message value
124
139
}
125
140
deriving (Eq , Show , Read , Typeable , Generic )
126
141
@@ -148,53 +163,56 @@ instance Bitraversable ConsumerRecord where
148
163
bitraverse f g r = (\ k v -> bimap (const k) (const v) r) <$> f (crKey r) <*> g (crValue r)
149
164
{-# INLINE bitraverse #-}
150
165
166
+ {-# DEPRECATED crMapKey "Isn't concern of this library. Use 'first'" #-}
151
167
crMapKey :: (k -> k' ) -> ConsumerRecord k v -> ConsumerRecord k' v
152
168
crMapKey = first
153
169
{-# INLINE crMapKey #-}
154
170
171
+ {-# DEPRECATED crMapValue "Isn't concern of this library. Use 'second'" #-}
155
172
crMapValue :: (v -> v' ) -> ConsumerRecord k v -> ConsumerRecord k v'
156
173
crMapValue = second
157
174
{-# INLINE crMapValue #-}
158
175
176
+ {-# DEPRECATED crMapKV "Isn't concern of this library. Use 'bimap'" #-}
159
177
crMapKV :: (k -> k' ) -> (v -> v' ) -> ConsumerRecord k v -> ConsumerRecord k' v'
160
178
crMapKV = bimap
161
179
{-# INLINE crMapKV #-}
162
180
163
- {-# DEPRECATED sequenceFirst "Isn't concern of this library. Use 'bitraverse id pure'" #-}
181
+ {-# DEPRECATED sequenceFirst "Isn't concern of this library. Use @ 'bitraverse' 'id' ' pure'@ " #-}
164
182
sequenceFirst :: (Bitraversable t , Applicative f ) => t (f k ) v -> f (t k v )
165
183
sequenceFirst = bitraverse id pure
166
184
{-# INLINE sequenceFirst #-}
167
185
168
- {-# DEPRECATED traverseFirst "Isn't concern of this library. Use 'bitraverse f pure'" #-}
186
+ {-# DEPRECATED traverseFirst "Isn't concern of this library. Use @ 'bitraverse' f ' pure'@ " #-}
169
187
traverseFirst :: (Bitraversable t , Applicative f )
170
188
=> (k -> f k' )
171
189
-> t k v
172
190
-> f (t k' v )
173
191
traverseFirst f = bitraverse f pure
174
192
{-# INLINE traverseFirst #-}
175
193
176
- {-# DEPRECATED traverseFirstM "Isn't concern of this library. Use 'bitraverse id pure <$> bitraverse f pure r' " #-}
194
+ {-# DEPRECATED traverseFirstM "Isn't concern of this library. Use @ 'bitraverse' 'id' ' pure' ' <$>' ' bitraverse' f ' pure' r@ " #-}
177
195
traverseFirstM :: (Bitraversable t , Applicative f , Monad m )
178
196
=> (k -> m (f k' ))
179
197
-> t k v
180
198
-> m (f (t k' v ))
181
199
traverseFirstM f r = bitraverse id pure <$> bitraverse f pure r
182
200
{-# INLINE traverseFirstM #-}
183
201
184
- {-# DEPRECATED traverseM "Isn't concern of this library. Use 'sequenceA <$> traverse f r' " #-}
202
+ {-# DEPRECATED traverseM "Isn't concern of this library. Use @ 'sequenceA' ' <$>' ' traverse' f r@ " #-}
185
203
traverseM :: (Traversable t , Applicative f , Monad m )
186
204
=> (v -> m (f v' ))
187
205
-> t v
188
206
-> m (f (t v' ))
189
207
traverseM f r = sequenceA <$> traverse f r
190
208
{-# INLINE traverseM #-}
191
209
192
- {-# DEPRECATED bitraverseM "Isn't concern of this library. Use 'bisequenceA <$> bimapM f g r' " #-}
210
+ {-# DEPRECATED bitraverseM "Isn't concern of this library. Use @ 'bisequenceA' ' <$>' ' bimapM' f g r@ " #-}
193
211
bitraverseM :: (Bitraversable t , Applicative f , Monad m )
194
212
=> (k -> m (f k' ))
195
213
-> (v -> m (f v' ))
196
214
-> t k v
197
215
-> m (f (t k' v' ))
198
- bitraverseM f g r = bisequenceA <$> bimapM f g r
216
+ bitraverseM f g r = bisequence <$> bimapM f g r
199
217
{-# INLINE bitraverseM #-}
200
218
0 commit comments