Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
Instances
Eq Request Source # | |
Show Request Source # | |
Generic Request Source # | |
Serializable Request Source # | |
type Rep Request Source # | |
Defined in Network.Kafka.Protocol type Rep Request = D1 (MetaData "Request" "Network.Kafka.Protocol" "milena-0.5.3.0-56TArgubqLBEBU4ve7tukD" True) (C1 (MetaCons "Request" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (CorrelationId, ClientId, RequestMessage)))) |
data KafkaError Source #
NoError |
|
Unknown |
|
OffsetOutOfRange |
|
InvalidMessage |
|
UnknownTopicOrPartition |
|
InvalidMessageSize |
|
LeaderNotAvailable |
|
NotLeaderForPartition |
|
RequestTimedOut |
|
BrokerNotAvailable |
|
ReplicaNotAvailable |
|
MessageSizeTooLarge |
|
StaleControllerEpochCode |
|
OffsetMetadataTooLargeCode |
|
OffsetsLoadInProgressCode |
|
ConsumerCoordinatorNotAvailableCode |
|
NotCoordinatorForConsumerCode |
|
TopicAlreadyExists |
|
UnsupportedCompressionType |
|
Instances
Instances
Eq Metadata Source # | |
Show Metadata Source # | |
IsString Metadata Source # | |
Defined in Network.Kafka.Protocol fromString :: String -> Metadata # | |
Generic Metadata Source # | |
Deserializable Metadata Source # | |
Defined in Network.Kafka.Protocol | |
Serializable Metadata Source # | |
type Rep Metadata Source # | |
Defined in Network.Kafka.Protocol type Rep Metadata = D1 (MetaData "Metadata" "Network.Kafka.Protocol" "milena-0.5.3.0-56TArgubqLBEBU4ve7tukD" True) (C1 (MetaCons "Metadata" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 KafkaString))) |
newtype ConsumerGroup Source #
Instances
newtype OffsetFetchRequest Source #
OffsetFetchReq (ConsumerGroup, [(TopicName, [Partition])]) |
Instances
newtype OffsetCommitRequest Source #
OffsetCommitReq (ConsumerGroup, [(TopicName, [(Partition, Offset, Time, Metadata)])]) |
Instances
newtype CreateTopicsRequest Source #
CreateTopicsReq ([(TopicName, Partition, ReplicationFactor, [(Partition, Replicas)], [(KafkaString, Metadata)])], Timeout) |
Instances
newtype GroupCoordinatorRequest Source #
Instances
Eq GroupCoordinatorRequest Source # | |
Defined in Network.Kafka.Protocol | |
Show GroupCoordinatorRequest Source # | |
Defined in Network.Kafka.Protocol showsPrec :: Int -> GroupCoordinatorRequest -> ShowS # show :: GroupCoordinatorRequest -> String # showList :: [GroupCoordinatorRequest] -> ShowS # | |
Generic GroupCoordinatorRequest Source # | |
Defined in Network.Kafka.Protocol type Rep GroupCoordinatorRequest :: Type -> Type # | |
Serializable GroupCoordinatorRequest Source # | |
Defined in Network.Kafka.Protocol | |
type Rep GroupCoordinatorRequest Source # | |
Defined in Network.Kafka.Protocol type Rep GroupCoordinatorRequest = D1 (MetaData "GroupCoordinatorRequest" "Network.Kafka.Protocol" "milena-0.5.3.0-56TArgubqLBEBU4ve7tukD" True) (C1 (MetaCons "GroupCoordinatorReq" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ConsumerGroup))) |
newtype ReplicationFactor Source #
Instances
data ResponseMessage Source #
Instances
Instances
Eq Value Source # | |
Show Value Source # | |
Generic Value Source # | |
Deserializable Value Source # | |
Defined in Network.Kafka.Protocol deserialize :: Get Value Source # | |
Serializable Value Source # | |
type Rep Value Source # | |
Defined in Network.Kafka.Protocol type Rep Value = D1 (MetaData "Value" "Network.Kafka.Protocol" "milena-0.5.3.0-56TArgubqLBEBU4ve7tukD" True) (C1 (MetaCons "Value" PrefixI True) (S1 (MetaSel (Just "_valueBytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe KafkaBytes)))) |
Instances
Eq Key Source # | |
Show Key Source # | |
Generic Key Source # | |
Deserializable Key Source # | |
Defined in Network.Kafka.Protocol deserialize :: Get Key Source # | |
Serializable Key Source # | |
type Rep Key Source # | |
Defined in Network.Kafka.Protocol type Rep Key = D1 (MetaData "Key" "Network.Kafka.Protocol" "milena-0.5.3.0-56TArgubqLBEBU4ve7tukD" True) (C1 (MetaCons "Key" PrefixI True) (S1 (MetaSel (Just "_keyBytes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe KafkaBytes)))) |
data Attributes Source #
Instances
Instances
Enum MagicByte Source # | |
Defined in Network.Kafka.Protocol succ :: MagicByte -> MagicByte # pred :: MagicByte -> MagicByte # fromEnum :: MagicByte -> Int # enumFrom :: MagicByte -> [MagicByte] # enumFromThen :: MagicByte -> MagicByte -> [MagicByte] # enumFromTo :: MagicByte -> MagicByte -> [MagicByte] # enumFromThenTo :: MagicByte -> MagicByte -> MagicByte -> [MagicByte] # | |
Eq MagicByte Source # | |
Integral MagicByte Source # | |
Defined in Network.Kafka.Protocol | |
Num MagicByte Source # | |
Defined in Network.Kafka.Protocol | |
Ord MagicByte Source # | |
Defined in Network.Kafka.Protocol | |
Real MagicByte Source # | |
Defined in Network.Kafka.Protocol toRational :: MagicByte -> Rational # | |
Show MagicByte Source # | |
Generic MagicByte Source # | |
Deserializable MagicByte Source # | |
Defined in Network.Kafka.Protocol | |
Serializable MagicByte Source # | |
type Rep MagicByte Source # | |
Defined in Network.Kafka.Protocol |
Instances
Enum Crc Source # | |
Eq Crc Source # | |
Integral Crc Source # | |
Num Crc Source # | |
Ord Crc Source # | |
Real Crc Source # | |
Defined in Network.Kafka.Protocol toRational :: Crc -> Rational # | |
Show Crc Source # | |
Generic Crc Source # | |
Deserializable Crc Source # | |
Defined in Network.Kafka.Protocol deserialize :: Get Crc Source # | |
Serializable Crc Source # | |
type Rep Crc Source # | |
Defined in Network.Kafka.Protocol |
data CompressionCodec Source #
Instances
Eq CompressionCodec Source # | |
Defined in Network.Kafka.Protocol (==) :: CompressionCodec -> CompressionCodec -> Bool # (/=) :: CompressionCodec -> CompressionCodec -> Bool # | |
Show CompressionCodec Source # | |
Defined in Network.Kafka.Protocol showsPrec :: Int -> CompressionCodec -> ShowS # show :: CompressionCodec -> String # showList :: [CompressionCodec] -> ShowS # | |
Generic CompressionCodec Source # | |
Defined in Network.Kafka.Protocol type Rep CompressionCodec :: Type -> Type # from :: CompressionCodec -> Rep CompressionCodec x # to :: Rep CompressionCodec x -> CompressionCodec # | |
type Rep CompressionCodec Source # | |
Message | |
|
Instances
Enum Offset Source # | |
Defined in Network.Kafka.Protocol | |
Eq Offset Source # | |
Integral Offset Source # | |
Defined in Network.Kafka.Protocol | |
Num Offset Source # | |
Ord Offset Source # | |
Real Offset Source # | |
Defined in Network.Kafka.Protocol toRational :: Offset -> Rational # | |
Show Offset Source # | |
Generic Offset Source # | |
Deserializable Offset Source # | |
Defined in Network.Kafka.Protocol deserialize :: Get Offset Source # | |
Serializable Offset Source # | |
type Rep Offset Source # | |
Defined in Network.Kafka.Protocol |
data MessageSetMember Source #
Instances
data MessageSet Source #
Instances
Instances
Enum Partition Source # | |
Defined in Network.Kafka.Protocol succ :: Partition -> Partition # pred :: Partition -> Partition # fromEnum :: Partition -> Int # enumFrom :: Partition -> [Partition] # enumFromThen :: Partition -> Partition -> [Partition] # enumFromTo :: Partition -> Partition -> [Partition] # enumFromThenTo :: Partition -> Partition -> Partition -> [Partition] # | |
Eq Partition Source # | |
Integral Partition Source # | |
Defined in Network.Kafka.Protocol | |
Num Partition Source # | |
Defined in Network.Kafka.Protocol | |
Ord Partition Source # | |
Defined in Network.Kafka.Protocol | |
Real Partition Source # | |
Defined in Network.Kafka.Protocol toRational :: Partition -> Rational # | |
Show Partition Source # | |
Generic Partition Source # | |
Deserializable Partition Source # | |
Defined in Network.Kafka.Protocol | |
Serializable Partition Source # | |
type Rep Partition Source # | |
Defined in Network.Kafka.Protocol |
Instances
Enum Timeout Source # | |
Eq Timeout Source # | |
Integral Timeout Source # | |
Defined in Network.Kafka.Protocol | |
Num Timeout Source # | |
Ord Timeout Source # | |
Real Timeout Source # | |
Defined in Network.Kafka.Protocol toRational :: Timeout -> Rational # | |
Show Timeout Source # | |
Generic Timeout Source # | |
Deserializable Timeout Source # | |
Defined in Network.Kafka.Protocol deserialize :: Get Timeout Source # | |
Serializable Timeout Source # | |
type Rep Timeout Source # | |
Defined in Network.Kafka.Protocol |
newtype RequiredAcks Source #
Instances
newtype ProduceRequest Source #
ProduceReq (RequiredAcks, Timeout, [(TopicName, [(Partition, MessageSet)])]) |
Instances
Instances
Enum MaxBytes Source # | |
Eq MaxBytes Source # | |
Integral MaxBytes Source # | |
Defined in Network.Kafka.Protocol | |
Num MaxBytes Source # | |
Ord MaxBytes Source # | |
Defined in Network.Kafka.Protocol | |
Real MaxBytes Source # | |
Defined in Network.Kafka.Protocol toRational :: MaxBytes -> Rational # | |
Show MaxBytes Source # | |
Generic MaxBytes Source # | |
Deserializable MaxBytes Source # | |
Defined in Network.Kafka.Protocol | |
Serializable MaxBytes Source # | |
type Rep MaxBytes Source # | |
Defined in Network.Kafka.Protocol |
Instances
Enum MinBytes Source # | |
Eq MinBytes Source # | |
Integral MinBytes Source # | |
Defined in Network.Kafka.Protocol | |
Num MinBytes Source # | |
Ord MinBytes Source # | |
Defined in Network.Kafka.Protocol | |
Real MinBytes Source # | |
Defined in Network.Kafka.Protocol toRational :: MinBytes -> Rational # | |
Show MinBytes Source # | |
Generic MinBytes Source # | |
Deserializable MinBytes Source # | |
Defined in Network.Kafka.Protocol | |
Serializable MinBytes Source # | |
type Rep MinBytes Source # | |
Defined in Network.Kafka.Protocol |
newtype MaxWaitTime Source #
Instances
Instances
Enum ReplicaId Source # | |
Defined in Network.Kafka.Protocol succ :: ReplicaId -> ReplicaId # pred :: ReplicaId -> ReplicaId # fromEnum :: ReplicaId -> Int # enumFrom :: ReplicaId -> [ReplicaId] # enumFromThen :: ReplicaId -> ReplicaId -> [ReplicaId] # enumFromTo :: ReplicaId -> ReplicaId -> [ReplicaId] # enumFromThenTo :: ReplicaId -> ReplicaId -> ReplicaId -> [ReplicaId] # | |
Eq ReplicaId Source # | |
Integral ReplicaId Source # | |
Defined in Network.Kafka.Protocol | |
Num ReplicaId Source # | |
Defined in Network.Kafka.Protocol | |
Ord ReplicaId Source # | |
Defined in Network.Kafka.Protocol | |
Real ReplicaId Source # | |
Defined in Network.Kafka.Protocol toRational :: ReplicaId -> Rational # | |
Show ReplicaId Source # | |
Generic ReplicaId Source # | |
Deserializable ReplicaId Source # | |
Defined in Network.Kafka.Protocol | |
Serializable ReplicaId Source # | |
type Rep ReplicaId Source # | |
Defined in Network.Kafka.Protocol |
newtype FetchRequest Source #
Instances
newtype MaxNumberOfOffsets Source #
Instances
Instances
Bounded Time Source # | |
Enum Time Source # | |
Eq Time Source # | |
Integral Time Source # | |
Num Time Source # | |
Ord Time Source # | |
Real Time Source # | |
Defined in Network.Kafka.Protocol toRational :: Time -> Rational # | |
Show Time Source # | |
Generic Time Source # | |
Serializable Time Source # | |
type Rep Time Source # | |
Defined in Network.Kafka.Protocol |
newtype OffsetRequest Source #
Instances
newtype OffsetFetchResponse Source #
OffsetFetchResp [(TopicName, [(Partition, Offset, Metadata, KafkaError)])] |
Instances
newtype OffsetCommitResponse Source #
OffsetCommitResp [(TopicName, [(Partition, KafkaError)])] |
Instances
newtype PartitionMetadata Source #
Instances
newtype TopicMetadata Source #
Instances
Eq TopicMetadata Source # | |
Defined in Network.Kafka.Protocol (==) :: TopicMetadata -> TopicMetadata -> Bool # (/=) :: TopicMetadata -> TopicMetadata -> Bool # | |
Show TopicMetadata Source # | |
Defined in Network.Kafka.Protocol showsPrec :: Int -> TopicMetadata -> ShowS # show :: TopicMetadata -> String # showList :: [TopicMetadata] -> ShowS # | |
Generic TopicMetadata Source # | |
Defined in Network.Kafka.Protocol type Rep TopicMetadata :: Type -> Type # from :: TopicMetadata -> Rep TopicMetadata x # to :: Rep TopicMetadata x -> TopicMetadata # | |
Deserializable TopicMetadata Source # | |
Defined in Network.Kafka.Protocol | |
type Rep TopicMetadata Source # | |
Defined in Network.Kafka.Protocol type Rep TopicMetadata = D1 (MetaData "TopicMetadata" "Network.Kafka.Protocol" "milena-0.5.3.0-56TArgubqLBEBU4ve7tukD" True) (C1 (MetaCons "TopicMetadata" PrefixI True) (S1 (MetaSel (Just "_topicMetadataFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (KafkaError, TopicName, [PartitionMetadata])))) |
Instances
Enum Port Source # | |
Eq Port Source # | |
Integral Port Source # | |
Num Port Source # | |
Ord Port Source # | |
Real Port Source # | |
Defined in Network.Kafka.Protocol toRational :: Port -> Rational # | |
Show Port Source # | |
Generic Port Source # | |
Deserializable Port Source # | |
Defined in Network.Kafka.Protocol deserialize :: Get Port Source # | |
type Rep Port Source # | |
Defined in Network.Kafka.Protocol |
Instances
Eq Host Source # | |
Ord Host Source # | |
Show Host Source # | |
IsString Host Source # | |
Defined in Network.Kafka.Protocol fromString :: String -> Host # | |
Generic Host Source # | |
Deserializable Host Source # | |
Defined in Network.Kafka.Protocol deserialize :: Get Host Source # | |
type Rep Host Source # | |
Defined in Network.Kafka.Protocol type Rep Host = D1 (MetaData "Host" "Network.Kafka.Protocol" "milena-0.5.3.0-56TArgubqLBEBU4ve7tukD" True) (C1 (MetaCons "Host" PrefixI True) (S1 (MetaSel (Just "_hostKString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 KafkaString))) |
Instances
Enum NodeId Source # | |
Defined in Network.Kafka.Protocol | |
Eq NodeId Source # | |
Integral NodeId Source # | |
Defined in Network.Kafka.Protocol | |
Num NodeId Source # | |
Ord NodeId Source # | |
Real NodeId Source # | |
Defined in Network.Kafka.Protocol toRational :: NodeId -> Rational # | |
Show NodeId Source # | |
Generic NodeId Source # | |
Deserializable NodeId Source # | |
Defined in Network.Kafka.Protocol deserialize :: Get NodeId Source # | |
type Rep NodeId Source # | |
Defined in Network.Kafka.Protocol |
Broker | |
|
newtype MetadataResponse Source #
Instances
newtype CreateTopicsResponse Source #
Instances
newtype FetchResponse Source #
FetchResp | |
|
Instances
newtype PartitionOffsets Source #
Instances
newtype OffsetResponse Source #
Instances
Eq OffsetResponse Source # | |
Defined in Network.Kafka.Protocol (==) :: OffsetResponse -> OffsetResponse -> Bool # (/=) :: OffsetResponse -> OffsetResponse -> Bool # | |
Show OffsetResponse Source # | |
Defined in Network.Kafka.Protocol showsPrec :: Int -> OffsetResponse -> ShowS # show :: OffsetResponse -> String # showList :: [OffsetResponse] -> ShowS # | |
Generic OffsetResponse Source # | |
Defined in Network.Kafka.Protocol type Rep OffsetResponse :: Type -> Type # from :: OffsetResponse -> Rep OffsetResponse x # to :: Rep OffsetResponse x -> OffsetResponse # | |
Deserializable OffsetResponse Source # | |
Defined in Network.Kafka.Protocol | |
type Rep OffsetResponse Source # | |
Defined in Network.Kafka.Protocol type Rep OffsetResponse = D1 (MetaData "OffsetResponse" "Network.Kafka.Protocol" "milena-0.5.3.0-56TArgubqLBEBU4ve7tukD" True) (C1 (MetaCons "OffsetResp" PrefixI True) (S1 (MetaSel (Just "_offsetResponseFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(TopicName, [PartitionOffsets])]))) |
newtype ProduceResponse Source #
ProduceResp | |
|
Instances
newtype KafkaString Source #
Instances
newtype KafkaBytes Source #
Instances
Instances
Eq TopicName Source # | |
Ord TopicName Source # | |
Defined in Network.Kafka.Protocol | |
Show TopicName Source # | |
IsString TopicName Source # | |
Defined in Network.Kafka.Protocol fromString :: String -> TopicName # | |
Generic TopicName Source # | |
Deserializable TopicName Source # | |
Defined in Network.Kafka.Protocol | |
Serializable TopicName Source # | |
type Rep TopicName Source # | |
Defined in Network.Kafka.Protocol type Rep TopicName = D1 (MetaData "TopicName" "Network.Kafka.Protocol" "milena-0.5.3.0-56TArgubqLBEBU4ve7tukD" True) (C1 (MetaCons "TName" PrefixI True) (S1 (MetaSel (Just "_tName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 KafkaString))) |
newtype MetadataRequest Source #
Instances
data RequestMessage Source #
Instances
Instances
Eq ClientId Source # | |
Show ClientId Source # | |
IsString ClientId Source # | |
Defined in Network.Kafka.Protocol fromString :: String -> ClientId # | |
Generic ClientId Source # | |
Deserializable ClientId Source # | |
Defined in Network.Kafka.Protocol | |
Serializable ClientId Source # | |
type Rep ClientId Source # | |
Defined in Network.Kafka.Protocol type Rep ClientId = D1 (MetaData "ClientId" "Network.Kafka.Protocol" "milena-0.5.3.0-56TArgubqLBEBU4ve7tukD" True) (C1 (MetaCons "ClientId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 KafkaString))) |
newtype CorrelationId Source #
Instances
newtype ApiVersion Source #
Instances
Instances
Enum ApiKey Source # | |
Defined in Network.Kafka.Protocol | |
Eq ApiKey Source # | |
Integral ApiKey Source # | |
Defined in Network.Kafka.Protocol | |
Num ApiKey Source # | |
Ord ApiKey Source # | |
Real ApiKey Source # | |
Defined in Network.Kafka.Protocol toRational :: ApiKey -> Rational # | |
Show ApiKey Source # | |
Generic ApiKey Source # | |
Deserializable ApiKey Source # | |
Defined in Network.Kafka.Protocol deserialize :: Get ApiKey Source # | |
Serializable ApiKey Source # | |
type Rep ApiKey Source # | |
Defined in Network.Kafka.Protocol |
newtype GroupCoordinatorResponse Source #
Instances
Eq GroupCoordinatorResponse Source # | |
Defined in Network.Kafka.Protocol | |
Show GroupCoordinatorResponse Source # | |
Defined in Network.Kafka.Protocol showsPrec :: Int -> GroupCoordinatorResponse -> ShowS # show :: GroupCoordinatorResponse -> String # showList :: [GroupCoordinatorResponse] -> ShowS # | |
Generic GroupCoordinatorResponse Source # | |
Defined in Network.Kafka.Protocol type Rep GroupCoordinatorResponse :: Type -> Type # | |
Deserializable GroupCoordinatorResponse Source # | |
Defined in Network.Kafka.Protocol | |
type Rep GroupCoordinatorResponse Source # | |
Defined in Network.Kafka.Protocol type Rep GroupCoordinatorResponse = D1 (MetaData "GroupCoordinatorResponse" "Network.Kafka.Protocol" "milena-0.5.3.0-56TArgubqLBEBU4ve7tukD" True) (C1 (MetaCons "GroupCoordinatorResp" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (KafkaError, Broker)))) |
class Deserializable a where Source #
deserialize :: Get a Source #
Instances
class Serializable a where Source #
Instances
MetadataRR :: MonadIO m => MetadataRequest -> ReqResp (m MetadataResponse) | |
ProduceRR :: MonadIO m => ProduceRequest -> ReqResp (m ProduceResponse) | |
FetchRR :: MonadIO m => FetchRequest -> ReqResp (m FetchResponse) | |
OffsetRR :: MonadIO m => OffsetRequest -> ReqResp (m OffsetResponse) | |
TopicsRR :: MonadIO m => CreateTopicsRequest -> ReqResp (m CreateTopicsResponse) |
doRequest' :: (Deserializable a, MonadIO m) => CorrelationId -> Handle -> Request -> m (Either String a) Source #
doRequest :: MonadIO m => ClientId -> CorrelationId -> Handle -> ReqResp (m a) -> m (Either String a) Source #
errorKafka :: KafkaError -> Int16 Source #
requestBytes :: Request -> ByteString Source #
apiKey :: RequestMessage -> ApiKey Source #
produceResponseFields :: Iso' ProduceResponse [(TopicName, [(Partition, KafkaError, Offset)])] Source #
fetchResponseFields :: Iso' FetchResponse [(TopicName, [(Partition, KafkaError, Offset, MessageSet)])] Source #
partitionMetadataFields :: Iso' PartitionMetadata (KafkaError, Partition, Leader, Replicas, Isr) Source #
messageFields :: Iso' Message (Crc, MagicByte, Attributes, Key, Value) Source #
valueBytes :: Iso' Value (Maybe KafkaBytes) Source #
fetchResponseByTopic :: TopicName -> Fold FetchResponse (Partition, KafkaError, Offset, MessageSet) Source #
messageSetByPartition :: Partition -> Fold (Partition, KafkaError, Offset, MessageSet) MessageSetMember Source #
findPartitionMetadata :: Applicative f => TopicName -> LensLike' f TopicMetadata [PartitionMetadata] Source #
portId :: IndexPreservingGetter Port PortID Source #