nakadi-client-0.2.0.1: Client library for the Nakadi Event Broker

Copyright(c) Moritz Schulte 2017
LicenseBSD3
Maintainermtesseract@silverratio.net
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Network.Nakadi.Types.Service

Description

This module provides the Nakadi Service Types.

Synopsis

Documentation

newtype CursorOffset Source #

Type for cursor offsets.

Constructors

CursorOffset Text 

Instances

Eq CursorOffset Source # 
Ord CursorOffset Source # 
Show CursorOffset Source # 
IsString CursorOffset Source # 
Generic CursorOffset Source # 

Associated Types

type Rep CursorOffset :: * -> * #

Hashable CursorOffset Source # 
ToJSON CursorOffset Source # 
FromJSON CursorOffset Source # 
HasNakadiOffset Cursor CursorOffset 
HasNakadiOldestAvailableOffset Partition CursorOffset 
HasNakadiNewestAvailableOffset Partition CursorOffset 
type Rep CursorOffset Source # 
type Rep CursorOffset = D1 (MetaData "CursorOffset" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "CursorOffset" PrefixI True) (S1 (MetaSel (Just Symbol "unCursorOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype EventTypeName Source #

Type for event type names.

Constructors

EventTypeName Text 

Instances

Eq EventTypeName Source # 
Ord EventTypeName Source # 
Show EventTypeName Source # 
IsString EventTypeName Source # 
Generic EventTypeName Source # 

Associated Types

type Rep EventTypeName :: * -> * #

Hashable EventTypeName Source # 
ToJSON EventTypeName Source # 
FromJSON EventTypeName Source # 
HasNakadiName EventType EventTypeName 
HasNakadiEventTypes Subscription [EventTypeName] 
type Rep EventTypeName Source # 
type Rep EventTypeName = D1 (MetaData "EventTypeName" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "EventTypeName" PrefixI True) (S1 (MetaSel (Just Symbol "unEventTypeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype PartitionName Source #

Type for partition names.

Constructors

PartitionName Text 

Instances

Eq PartitionName Source # 
Ord PartitionName Source # 
Show PartitionName Source # 
IsString PartitionName Source # 
Generic PartitionName Source # 

Associated Types

type Rep PartitionName :: * -> * #

Hashable PartitionName Source # 
ToJSON PartitionName Source # 
FromJSON PartitionName Source # 
HasNakadiPartition Cursor PartitionName 
HasNakadiPartition Partition PartitionName 
type Rep PartitionName Source # 
type Rep PartitionName = D1 (MetaData "PartitionName" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "PartitionName" PrefixI True) (S1 (MetaSel (Just Symbol "unPartitionName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Cursor Source #

Type for cursors.

Instances

Eq Cursor Source # 

Methods

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

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

Ord Cursor Source # 
Show Cursor Source # 
Generic Cursor Source # 

Associated Types

type Rep Cursor :: * -> * #

Methods

from :: Cursor -> Rep Cursor x #

to :: Rep Cursor x -> Cursor #

Hashable Cursor Source # 

Methods

hashWithSalt :: Int -> Cursor -> Int #

hash :: Cursor -> Int #

ToJSON Cursor Source # 
FromJSON Cursor Source # 
HasNakadiPartition Cursor PartitionName 
HasNakadiOffset Cursor CursorOffset 
HasNakadiInitialCursor CursorDistanceQuery Cursor 
HasNakadiFinalCursor CursorDistanceQuery Cursor 
HasNakadiItems CursorCommit [Cursor] 
HasNakadiCursor (EventStreamBatch a0) Cursor 
type Rep Cursor Source # 
type Rep Cursor = D1 (MetaData "Cursor" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "Cursor" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_partition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartitionName)) (S1 (MetaSel (Just Symbol "_offset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CursorOffset))))

newtype ApplicationName Source #

Type for application names.

Constructors

ApplicationName Text 

Instances

Eq ApplicationName Source # 
Ord ApplicationName Source # 
Show ApplicationName Source # 
IsString ApplicationName Source # 
Generic ApplicationName Source # 
Hashable ApplicationName Source # 
ToJSON ApplicationName Source # 
FromJSON ApplicationName Source # 
HasNakadiOwningApplication Subscription ApplicationName 
HasNakadiOwningApplication EventType (Maybe ApplicationName) 
type Rep ApplicationName Source # 
type Rep ApplicationName = D1 (MetaData "ApplicationName" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "ApplicationName" PrefixI True) (S1 (MetaSel (Just Symbol "unApplicationName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data SubscriptionsListResponse Source #

SubscriptionsListResponse

Instances

Eq SubscriptionsListResponse Source # 
Ord SubscriptionsListResponse Source # 
Show SubscriptionsListResponse Source # 
Generic SubscriptionsListResponse Source # 
Hashable SubscriptionsListResponse Source # 
ToJSON SubscriptionsListResponse Source # 
FromJSON SubscriptionsListResponse Source # 
HasNakadiLinks SubscriptionsListResponse PaginationLinks 
HasNakadiItems SubscriptionsListResponse [Subscription] 
type Rep SubscriptionsListResponse Source # 
type Rep SubscriptionsListResponse = D1 (MetaData "SubscriptionsListResponse" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "SubscriptionsListResponse" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_links") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PaginationLinks)) (S1 (MetaSel (Just Symbol "_items") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Subscription]))))

data SubscriptionCursor Source #

Type fo rsubscription cursors.

Instances

Eq SubscriptionCursor Source # 
Ord SubscriptionCursor Source # 
Show SubscriptionCursor Source # 
Generic SubscriptionCursor Source # 
ToJSON SubscriptionCursor Source # 
FromJSON SubscriptionCursor Source # 
HasNakadiSubscriptionCursor SubscriptionCursor 
HasNakadiItems SubscriptionCursorCommit [SubscriptionCursor] 
HasNakadiCursor (SubscriptionEventStreamBatch a0) SubscriptionCursor 
type Rep SubscriptionCursor Source # 
type Rep SubscriptionCursor = D1 (MetaData "SubscriptionCursor" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "SubscriptionCursor" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_partition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartitionName)) (S1 (MetaSel (Just Symbol "_offset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CursorOffset))) ((:*:) (S1 (MetaSel (Just Symbol "_eventType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EventTypeName)) (S1 (MetaSel (Just Symbol "_cursorToken") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))))

newtype FlowId Source #

A Flow ID.

Constructors

FlowId Text 

Instances

Eq FlowId Source # 

Methods

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

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

Ord FlowId Source # 
Show FlowId Source # 
Generic FlowId Source # 

Associated Types

type Rep FlowId :: * -> * #

Methods

from :: FlowId -> Rep FlowId x #

to :: Rep FlowId x -> FlowId #

ToJSON FlowId Source # 
FromJSON FlowId Source # 
type Rep FlowId Source # 
type Rep FlowId = D1 (MetaData "FlowId" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "FlowId" PrefixI True) (S1 (MetaSel (Just Symbol "unFlowId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data SubscriptionCursorWithoutToken Source #

Type for subscription cursors without token.

Instances

Eq SubscriptionCursorWithoutToken Source # 
Ord SubscriptionCursorWithoutToken Source # 
Show SubscriptionCursorWithoutToken Source # 
Generic SubscriptionCursorWithoutToken Source # 
Hashable SubscriptionCursorWithoutToken Source # 
ToJSON SubscriptionCursorWithoutToken Source # 
FromJSON SubscriptionCursorWithoutToken Source # 
HasNakadiInitialCursors Subscription (Maybe [SubscriptionCursorWithoutToken]) 
type Rep SubscriptionCursorWithoutToken Source # 
type Rep SubscriptionCursorWithoutToken = D1 (MetaData "SubscriptionCursorWithoutToken" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "SubscriptionCursorWithoutToken" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_partition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartitionName)) ((:*:) (S1 (MetaSel (Just Symbol "_offset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CursorOffset)) (S1 (MetaSel (Just Symbol "_eventType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EventTypeName)))))

newtype SubscriptionCursorCommit Source #

Type for commit object for subscription cursor committing.

newtype CursorCommit Source #

Type for commit objects for cursor committing.

Constructors

CursorCommit [Cursor] 

newtype SubscriptionId Source #

Type for subscription IDs.

Constructors

SubscriptionId UUID 

Instances

Eq SubscriptionId Source # 
Ord SubscriptionId Source # 
Show SubscriptionId Source # 
Generic SubscriptionId Source # 

Associated Types

type Rep SubscriptionId :: * -> * #

Hashable SubscriptionId Source # 
ToJSON SubscriptionId Source # 
FromJSON SubscriptionId Source # 
HasNakadiSubscriptionId SubscriptionEventStream SubscriptionId 
HasNakadiSubscriptionId SubscriptionEventStreamContext SubscriptionId 
HasNakadiId SubscriptionId UUID 
HasNakadiId Subscription (Maybe SubscriptionId) 
type Rep SubscriptionId Source # 
type Rep SubscriptionId = D1 (MetaData "SubscriptionId" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "SubscriptionId" PrefixI True) (S1 (MetaSel (Just Symbol "unSubscriptionId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

newtype StreamId Source #

Type for stream IDs.

Constructors

StreamId Text 

Instances

Eq StreamId Source # 
Ord StreamId Source # 
Show StreamId Source # 
Generic StreamId Source # 

Associated Types

type Rep StreamId :: * -> * #

Methods

from :: StreamId -> Rep StreamId x #

to :: Rep StreamId x -> StreamId #

ToJSON StreamId Source # 
FromJSON StreamId Source # 
HasNakadiStreamId SubscriptionEventStream StreamId 
HasNakadiStreamId SubscriptionEventStreamContext StreamId 
HasNakadiId StreamId Text 

Methods

id :: Lens' StreamId Text

type Rep StreamId Source # 
type Rep StreamId = D1 (MetaData "StreamId" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "StreamId" PrefixI True) (S1 (MetaSel (Just Symbol "unStreamId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Timestamp Source #

Type for timestamps.

Constructors

Timestamp UTCTime 

Instances

Eq Timestamp Source # 
Ord Timestamp Source # 
Show Timestamp Source # 
Generic Timestamp Source # 

Associated Types

type Rep Timestamp :: * -> * #

Hashable Timestamp Source # 
ToJSON Timestamp Source # 
FromJSON Timestamp Source # 
HasNakadiOccurredAt Metadata Timestamp 
HasNakadiUTCTime Timestamp UTCTime 
HasNakadiCreatedAt Subscription (Maybe Timestamp) 
HasNakadiCreatedAt EventTypeSchema (Maybe Timestamp) 
type Rep Timestamp Source # 
type Rep Timestamp = D1 (MetaData "Timestamp" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "Timestamp" PrefixI True) (S1 (MetaSel (Just Symbol "unTimestamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)))

data Metadata Source #

Metadata

Constructors

Metadata Text Timestamp [Text] (Maybe Text) 

Instances

Eq Metadata Source # 
Show Metadata Source # 
Generic Metadata Source # 

Associated Types

type Rep Metadata :: * -> * #

Methods

from :: Metadata -> Rep Metadata x #

to :: Rep Metadata x -> Metadata #

ToJSON Metadata Source # 
FromJSON Metadata Source # 
HasNakadiOccurredAt Metadata Timestamp 
HasNakadiEid Metadata Text 
HasNakadiPartition Metadata (Maybe Text) 
HasNakadiParentEids Metadata [Text] 
HasNakadiMetadata (Event a0) Metadata 

Methods

metadata :: Lens' (Event a0) Metadata

type Rep Metadata Source # 
type Rep Metadata = D1 (MetaData "Metadata" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "Metadata" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_eid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_occurredAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Timestamp))) ((:*:) (S1 (MetaSel (Just Symbol "_parentEids") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text])) (S1 (MetaSel (Just Symbol "_partition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))))

data Event a Source #

Event

Constructors

Event a Metadata 

Instances

Eq a => Eq (Event a) Source # 

Methods

(==) :: Event a -> Event a -> Bool #

(/=) :: Event a -> Event a -> Bool #

Show a => Show (Event a) Source # 

Methods

showsPrec :: Int -> Event a -> ShowS #

show :: Event a -> String #

showList :: [Event a] -> ShowS #

Generic (Event a) Source # 

Associated Types

type Rep (Event a) :: * -> * #

Methods

from :: Event a -> Rep (Event a) x #

to :: Rep (Event a) x -> Event a #

ToJSON a0 => ToJSON (Event a0) Source # 
FromJSON a0 => FromJSON (Event a0) Source # 
HasNakadiPayload (Event a0) a0 

Methods

payload :: Lens' (Event a0) a0

HasNakadiMetadata (Event a0) Metadata 

Methods

metadata :: Lens' (Event a0) Metadata

HasNakadiEvents (EventStreamBatch a0) (Maybe (Vector (Event a0))) 

Methods

events :: Lens' (EventStreamBatch a0) (Maybe (Vector (Event a0)))

HasNakadiEvents (SubscriptionEventStreamBatch a0) (Maybe (Vector (Event a0))) 
type Rep (Event a) Source # 
type Rep (Event a) = D1 (MetaData "Event" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "Event" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_payload") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Just Symbol "_metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Metadata))))

data EventStreamBatch a Source #

EventStreamBatch

Constructors

EventStreamBatch Cursor (Maybe (Vector (Event a))) 

Instances

Show a => Show (EventStreamBatch a) Source # 
Generic (EventStreamBatch a) Source # 

Associated Types

type Rep (EventStreamBatch a) :: * -> * #

ToJSON a0 => ToJSON (EventStreamBatch a0) Source # 
FromJSON a0 => FromJSON (EventStreamBatch a0) Source # 
HasNakadiCursor (EventStreamBatch a0) Cursor 
HasNakadiEvents (EventStreamBatch a0) (Maybe (Vector (Event a0))) 

Methods

events :: Lens' (EventStreamBatch a0) (Maybe (Vector (Event a0)))

type Rep (EventStreamBatch a) Source # 
type Rep (EventStreamBatch a) = D1 (MetaData "EventStreamBatch" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "EventStreamBatch" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cursor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cursor)) (S1 (MetaSel (Just Symbol "_events") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Vector (Event a)))))))

data SubscriptionEventStreamBatch a Source #

SubscriptionEventStreamBatch

Instances

Show a => Show (SubscriptionEventStreamBatch a) Source # 
Generic (SubscriptionEventStreamBatch a) Source # 
ToJSON a0 => ToJSON (SubscriptionEventStreamBatch a0) Source # 
FromJSON a0 => FromJSON (SubscriptionEventStreamBatch a0) Source # 
HasNakadiSubscriptionCursor (SubscriptionEventStreamBatch a) 
HasNakadiCursor (SubscriptionEventStreamBatch a0) SubscriptionCursor 
HasNakadiEvents (SubscriptionEventStreamBatch a0) (Maybe (Vector (Event a0))) 
type Rep (SubscriptionEventStreamBatch a) Source # 
type Rep (SubscriptionEventStreamBatch a) = D1 (MetaData "SubscriptionEventStreamBatch" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "SubscriptionEventStreamBatch" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cursor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SubscriptionCursor)) (S1 (MetaSel (Just Symbol "_events") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Vector (Event a)))))))

newtype EventId Source #

ID of an Event

Constructors

EventId UUID 

Instances

Eq EventId Source # 

Methods

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

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

Ord EventId Source # 
Show EventId Source # 
Generic EventId Source # 

Associated Types

type Rep EventId :: * -> * #

Methods

from :: EventId -> Rep EventId x #

to :: Rep EventId x -> EventId #

Hashable EventId Source # 

Methods

hashWithSalt :: Int -> EventId -> Int #

hash :: EventId -> Int #

ToJSON EventId Source # 
FromJSON EventId Source # 
HasNakadiId EventId UUID 

Methods

id :: Lens' EventId UUID

type Rep EventId Source # 
type Rep EventId = D1 (MetaData "EventId" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "EventId" PrefixI True) (S1 (MetaSel (Just Symbol "unEventId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

data CursorDistanceQuery Source #

Type for cursor-distance queries. Represents the request to compute the distance between initial cursor and final cursor.

Instances

Eq CursorDistanceQuery Source # 
Ord CursorDistanceQuery Source # 
Show CursorDistanceQuery Source # 
Generic CursorDistanceQuery Source # 
Hashable CursorDistanceQuery Source # 
ToJSON CursorDistanceQuery Source # 
FromJSON CursorDistanceQuery Source # 
HasNakadiInitialCursor CursorDistanceQuery Cursor 
HasNakadiFinalCursor CursorDistanceQuery Cursor 
type Rep CursorDistanceQuery Source # 
type Rep CursorDistanceQuery = D1 (MetaData "CursorDistanceQuery" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "CursorDistanceQuery" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_initialCursor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cursor)) (S1 (MetaSel (Just Symbol "_finalCursor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cursor))))

newtype CursorDistanceResult Source #

Type for results of cursor-distance-queries.

Instances

Eq CursorDistanceResult Source # 
Ord CursorDistanceResult Source # 
Show CursorDistanceResult Source # 
Generic CursorDistanceResult Source # 
Hashable CursorDistanceResult Source # 
ToJSON CursorDistanceResult Source # 
FromJSON CursorDistanceResult Source # 
HasNakadiDistance CursorDistanceResult Int64 
type Rep CursorDistanceResult Source # 
type Rep CursorDistanceResult = D1 (MetaData "CursorDistanceResult" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "CursorDistanceResult" PrefixI True) (S1 (MetaSel (Just Symbol "_distance") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))

data SubscriptionPosition Source #

Type for subscription positions.

Instances

Eq SubscriptionPosition Source # 
Ord SubscriptionPosition Source # 
Show SubscriptionPosition Source # 
Generic SubscriptionPosition Source # 
Hashable SubscriptionPosition Source # 
ToJSON SubscriptionPosition Source # 
FromJSON SubscriptionPosition Source # 
HasNakadiReadFrom Subscription (Maybe SubscriptionPosition) 
type Rep SubscriptionPosition Source # 
type Rep SubscriptionPosition = D1 (MetaData "SubscriptionPosition" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) ((:+:) (C1 (MetaCons "SubscriptionPositionBegin" PrefixI False) U1) ((:+:) (C1 (MetaCons "SubscriptionPositionEnd" PrefixI False) U1) (C1 (MetaCons "SubscriptionPositionCursors" PrefixI False) U1)))

data Subscription Source #

Type for a Subscription.

Instances

Eq Subscription Source # 
Ord Subscription Source # 
Show Subscription Source # 
Generic Subscription Source # 

Associated Types

type Rep Subscription :: * -> * #

Hashable Subscription Source # 
ToJSON Subscription Source # 
FromJSON Subscription Source # 
HasNakadiOwningApplication Subscription ApplicationName 
HasNakadiCreatedAt Subscription (Maybe Timestamp) 
HasNakadiItems SubscriptionsListResponse [Subscription] 
HasNakadiReadFrom Subscription (Maybe SubscriptionPosition) 
HasNakadiInitialCursors Subscription (Maybe [SubscriptionCursorWithoutToken]) 
HasNakadiId Subscription (Maybe SubscriptionId) 
HasNakadiEventTypes Subscription [EventTypeName] 
HasNakadiConsumerGroup Subscription (Maybe Text) 
type Rep Subscription Source # 

data PublishingStatus Source #

Type for publishing status.

Instances

Eq PublishingStatus Source # 
Ord PublishingStatus Source # 
Show PublishingStatus Source # 
Generic PublishingStatus Source # 
Hashable PublishingStatus Source # 
ToJSON PublishingStatus Source # 
FromJSON PublishingStatus Source # 
type Rep PublishingStatus Source # 
type Rep PublishingStatus = D1 (MetaData "PublishingStatus" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) ((:+:) (C1 (MetaCons "PublishingStatusSubmitted" PrefixI False) U1) ((:+:) (C1 (MetaCons "PublishingStatusFailed" PrefixI False) U1) (C1 (MetaCons "PublishingStatusAborted" PrefixI False) U1)))

data Step Source #

Step

Instances

Eq Step Source # 

Methods

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

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

Ord Step Source # 

Methods

compare :: Step -> Step -> Ordering #

(<) :: Step -> Step -> Bool #

(<=) :: Step -> Step -> Bool #

(>) :: Step -> Step -> Bool #

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

max :: Step -> Step -> Step #

min :: Step -> Step -> Step #

Show Step Source # 

Methods

showsPrec :: Int -> Step -> ShowS #

show :: Step -> String #

showList :: [Step] -> ShowS #

Generic Step Source # 

Associated Types

type Rep Step :: * -> * #

Methods

from :: Step -> Rep Step x #

to :: Rep Step x -> Step #

Hashable Step Source # 

Methods

hashWithSalt :: Int -> Step -> Int #

hash :: Step -> Int #

ToJSON Step Source # 
FromJSON Step Source # 
type Rep Step Source # 
type Rep Step = D1 (MetaData "Step" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) ((:+:) ((:+:) (C1 (MetaCons "StepNone" PrefixI False) U1) (C1 (MetaCons "StepValidating" PrefixI False) U1)) ((:+:) (C1 (MetaCons "StepPartitioning" PrefixI False) U1) ((:+:) (C1 (MetaCons "StepEnriching" PrefixI False) U1) (C1 (MetaCons "StepPublishing" PrefixI False) U1))))

data BatchItemResponse Source #

In case of failures during batch publishing, Nakadi returns detailed information about which events failed to be published. This per-event information is a batch item response.

Instances

Eq BatchItemResponse Source # 
Ord BatchItemResponse Source # 
Show BatchItemResponse Source # 
Generic BatchItemResponse Source # 
Hashable BatchItemResponse Source # 
ToJSON BatchItemResponse Source # 
FromJSON BatchItemResponse Source # 
type Rep BatchItemResponse Source # 
type Rep BatchItemResponse = D1 (MetaData "BatchItemResponse" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "BatchItemResponse" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_eid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe EventId))) (S1 (MetaSel (Just Symbol "_publishingStatus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PublishingStatus))) ((:*:) (S1 (MetaSel (Just Symbol "_step") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Step))) (S1 (MetaSel (Just Symbol "_detail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))))

data SchemaType Source #

SchemaType

Constructors

SchemaTypeJson 

Instances

Eq SchemaType Source # 
Ord SchemaType Source # 
Show SchemaType Source # 
Generic SchemaType Source # 

Associated Types

type Rep SchemaType :: * -> * #

Hashable SchemaType Source # 
ToJSON SchemaType Source # 
FromJSON SchemaType Source # 
HasNakadiSchemaType EventTypeSchema SchemaType 
type Rep SchemaType Source # 
type Rep SchemaType = D1 (MetaData "SchemaType" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "SchemaTypeJson" PrefixI False) U1)

data EventTypeSchema Source #

Type for the schema of an event type.

Instances

Eq EventTypeSchema Source # 
Ord EventTypeSchema Source # 
Show EventTypeSchema Source # 
Generic EventTypeSchema Source # 
Hashable EventTypeSchema Source # 
ToJSON EventTypeSchema Source # 
FromJSON EventTypeSchema Source # 
HasNakadiSchemaType EventTypeSchema SchemaType 
HasNakadiSchema EventTypeSchema Text 
HasNakadiSchema EventType EventTypeSchema 
HasNakadiVersion EventTypeSchema (Maybe SchemaVersion) 
HasNakadiCreatedAt EventTypeSchema (Maybe Timestamp) 
HasNakadiItems EventTypeSchemasResponse [EventTypeSchema] 
type Rep EventTypeSchema Source # 
type Rep EventTypeSchema = D1 (MetaData "EventTypeSchema" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "EventTypeSchema" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_version") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SchemaVersion))) (S1 (MetaSel (Just Symbol "_createdAt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Timestamp)))) ((:*:) (S1 (MetaSel (Just Symbol "_schemaType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SchemaType)) (S1 (MetaSel (Just Symbol "_schema") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))))

newtype PaginationLink Source #

PaginationLink

Constructors

PaginationLink Text 

data PaginationLinks Source #

PaginationLinks

data EventTypeSchemasResponse Source #

EventTypeSchemasResponse

Instances

Eq EventTypeSchemasResponse Source # 
Ord EventTypeSchemasResponse Source # 
Show EventTypeSchemasResponse Source # 
Generic EventTypeSchemasResponse Source # 
Hashable EventTypeSchemasResponse Source # 
ToJSON EventTypeSchemasResponse Source # 
FromJSON EventTypeSchemasResponse Source # 
HasNakadiLinks EventTypeSchemasResponse PaginationLinks 
HasNakadiItems EventTypeSchemasResponse [EventTypeSchema] 
type Rep EventTypeSchemasResponse Source # 
type Rep EventTypeSchemasResponse = D1 (MetaData "EventTypeSchemasResponse" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "EventTypeSchemasResponse" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_links") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PaginationLinks)) (S1 (MetaSel (Just Symbol "_items") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [EventTypeSchema]))))

newtype SchemaVersion Source #

Type for the version of a schema.

Constructors

SchemaVersion Text 

Instances

Eq SchemaVersion Source # 
Ord SchemaVersion Source # 
Show SchemaVersion Source # 
IsString SchemaVersion Source # 
Generic SchemaVersion Source # 

Associated Types

type Rep SchemaVersion :: * -> * #

Hashable SchemaVersion Source # 
ToJSON SchemaVersion Source # 
FromJSON SchemaVersion Source # 
HasNakadiVersion EventTypeSchema (Maybe SchemaVersion) 
type Rep SchemaVersion Source # 
type Rep SchemaVersion = D1 (MetaData "SchemaVersion" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "SchemaVersion" PrefixI True) (S1 (MetaSel (Just Symbol "unSchemaVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Offset Source #

Type for offset values.

Constructors

Offset Int64 

Instances

Eq Offset Source # 

Methods

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

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

Ord Offset Source # 
Show Offset Source # 
Generic Offset Source # 

Associated Types

type Rep Offset :: * -> * #

Methods

from :: Offset -> Rep Offset x #

to :: Rep Offset x -> Offset #

Hashable Offset Source # 

Methods

hashWithSalt :: Int -> Offset -> Int #

hash :: Offset -> Int #

type Rep Offset Source # 
type Rep Offset = D1 (MetaData "Offset" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "Offset" PrefixI True) (S1 (MetaSel (Just Symbol "unOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))

newtype Limit Source #

Type for limit values.

Constructors

Limit Int64 

Instances

Eq Limit Source # 

Methods

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

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

Ord Limit Source # 

Methods

compare :: Limit -> Limit -> Ordering #

(<) :: Limit -> Limit -> Bool #

(<=) :: Limit -> Limit -> Bool #

(>) :: Limit -> Limit -> Bool #

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

max :: Limit -> Limit -> Limit #

min :: Limit -> Limit -> Limit #

Show Limit Source # 

Methods

showsPrec :: Int -> Limit -> ShowS #

show :: Limit -> String #

showList :: [Limit] -> ShowS #

Generic Limit Source # 

Associated Types

type Rep Limit :: * -> * #

Methods

from :: Limit -> Rep Limit x #

to :: Rep Limit x -> Limit #

Hashable Limit Source # 

Methods

hashWithSalt :: Int -> Limit -> Int #

hash :: Limit -> Int #

type Rep Limit Source # 
type Rep Limit = D1 (MetaData "Limit" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "Limit" PrefixI True) (S1 (MetaSel (Just Symbol "unLimit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))

data PartitionStat Source #

Type for per-partition statistics.

Instances

Eq PartitionStat Source # 
Ord PartitionStat Source # 
Show PartitionStat Source # 
Generic PartitionStat Source # 

Associated Types

type Rep PartitionStat :: * -> * #

ToJSON PartitionStat Source # 
FromJSON PartitionStat Source # 
type Rep PartitionStat Source # 
type Rep PartitionStat = D1 (MetaData "PartitionStat" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "PartitionStat" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_partition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartitionName)) (S1 (MetaSel (Just Symbol "_state") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartitionState))) ((:*:) (S1 (MetaSel (Just Symbol "_unconsumedEvents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)) (S1 (MetaSel (Just Symbol "_streamId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StreamId)))))

data SubscriptionEventTypeStats Source #

Nakadi type SubscriptionEventTypeStats.

Instances

Eq SubscriptionEventTypeStats Source # 
Ord SubscriptionEventTypeStats Source # 
Show SubscriptionEventTypeStats Source # 
Generic SubscriptionEventTypeStats Source # 
ToJSON SubscriptionEventTypeStats Source # 
FromJSON SubscriptionEventTypeStats Source # 
HasNakadiItems SubscriptionEventTypeStatsResult [SubscriptionEventTypeStats] 
type Rep SubscriptionEventTypeStats Source # 
type Rep SubscriptionEventTypeStats = D1 (MetaData "SubscriptionEventTypeStats" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "SubscriptionEventTypeStats" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_eventType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EventTypeName)) (S1 (MetaSel (Just Symbol "_partitions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PartitionStat]))))

newtype SubscriptionEventTypeStatsResult Source #

SubscriptionEventTypeStatsResult

Instances

Eq SubscriptionEventTypeStatsResult Source # 
Ord SubscriptionEventTypeStatsResult Source # 
Show SubscriptionEventTypeStatsResult Source # 
Generic SubscriptionEventTypeStatsResult Source # 
ToJSON SubscriptionEventTypeStatsResult Source # 
FromJSON SubscriptionEventTypeStatsResult Source # 
HasNakadiItems SubscriptionEventTypeStatsResult [SubscriptionEventTypeStats] 
type Rep SubscriptionEventTypeStatsResult Source # 
type Rep SubscriptionEventTypeStatsResult = D1 (MetaData "SubscriptionEventTypeStatsResult" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "SubscriptionEventTypeStatsResult" PrefixI True) (S1 (MetaSel (Just Symbol "_items") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SubscriptionEventTypeStats])))

data EventTypeCategory Source #

Type for the category of an EventType.

Instances

Eq EventTypeCategory Source # 
Ord EventTypeCategory Source # 
Show EventTypeCategory Source # 
Generic EventTypeCategory Source # 
Hashable EventTypeCategory Source # 
ToJSON EventTypeCategory Source # 
FromJSON EventTypeCategory Source # 
HasNakadiCategory EventType (Maybe EventTypeCategory) 
type Rep EventTypeCategory Source # 
type Rep EventTypeCategory = D1 (MetaData "EventTypeCategory" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) ((:+:) (C1 (MetaCons "EventTypeCategoryUndefined" PrefixI False) U1) ((:+:) (C1 (MetaCons "EventTypeCategoryData" PrefixI False) U1) (C1 (MetaCons "EventTypeCategoryBusiness" PrefixI False) U1)))

data PartitionStrategy Source #

Type for a partitioning strategy.

Instances

Eq PartitionStrategy Source # 
Ord PartitionStrategy Source # 
Show PartitionStrategy Source # 
IsString PartitionStrategy Source # 
Generic PartitionStrategy Source # 
Hashable PartitionStrategy Source # 
ToJSON PartitionStrategy Source # 
FromJSON PartitionStrategy Source # 
HasNakadiPartitionStrategy EventType (Maybe PartitionStrategy) 
type Rep PartitionStrategy Source # 
type Rep PartitionStrategy = D1 (MetaData "PartitionStrategy" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) ((:+:) ((:+:) (C1 (MetaCons "PartitionStrategyRandom" PrefixI False) U1) (C1 (MetaCons "PartitionStrategyUser" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PartitionStrategyHash" PrefixI False) U1) (C1 (MetaCons "PartitionStrategyCustom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))))

data EnrichmentStrategy Source #

Type for an enrichment stragey.

Instances

Eq EnrichmentStrategy Source # 
Ord EnrichmentStrategy Source # 
Show EnrichmentStrategy Source # 
Generic EnrichmentStrategy Source # 
Hashable EnrichmentStrategy Source # 
ToJSON EnrichmentStrategy Source # 
FromJSON EnrichmentStrategy Source # 
HasNakadiEnrichmentStrategies EventType (Maybe [EnrichmentStrategy]) 
type Rep EnrichmentStrategy Source # 
type Rep EnrichmentStrategy = D1 (MetaData "EnrichmentStrategy" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "EnrichmentStrategyMetadata" PrefixI False) U1)

data CompatibilityMode Source #

Type for an event type compatibility mode.

Instances

Eq CompatibilityMode Source # 
Ord CompatibilityMode Source # 
Show CompatibilityMode Source # 
Generic CompatibilityMode Source # 
Hashable CompatibilityMode Source # 
ToJSON CompatibilityMode Source # 
FromJSON CompatibilityMode Source # 
HasNakadiCompatibilityMode EventType (Maybe CompatibilityMode) 
type Rep CompatibilityMode Source # 
type Rep CompatibilityMode = D1 (MetaData "CompatibilityMode" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) ((:+:) (C1 (MetaCons "CompatibilityModeCompatible" PrefixI False) U1) ((:+:) (C1 (MetaCons "CompatibilityModeForward" PrefixI False) U1) (C1 (MetaCons "CompatibilityModeNone" PrefixI False) U1)))

newtype PartitionKeyField Source #

Type for a partitioning key field.

Constructors

PartitionKeyField Text 

Instances

Eq PartitionKeyField Source # 
Ord PartitionKeyField Source # 
Show PartitionKeyField Source # 
IsString PartitionKeyField Source # 
Generic PartitionKeyField Source # 
Hashable PartitionKeyField Source # 
ToJSON PartitionKeyField Source # 
FromJSON PartitionKeyField Source # 
HasNakadiPartitionKeyFields EventType (Maybe [PartitionKeyField]) 
type Rep PartitionKeyField Source # 
type Rep PartitionKeyField = D1 (MetaData "PartitionKeyField" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" True) (C1 (MetaCons "PartitionKeyField" PrefixI True) (S1 (MetaSel (Just Symbol "unPartitionKeyField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data EventType Source #

EventType

Instances

Eq EventType Source # 
Ord EventType Source # 
Show EventType Source # 
Generic EventType Source # 

Associated Types

type Rep EventType :: * -> * #

Hashable EventType Source # 
ToJSON EventType Source # 
FromJSON EventType Source # 
HasNakadiSchema EventType EventTypeSchema 
HasNakadiName EventType EventTypeName 
HasNakadiPartitionStrategy EventType (Maybe PartitionStrategy) 
HasNakadiPartitionKeyFields EventType (Maybe [PartitionKeyField]) 
HasNakadiOwningApplication EventType (Maybe ApplicationName) 
HasNakadiOptions EventType (Maybe EventTypeOptions) 
HasNakadiEnrichmentStrategies EventType (Maybe [EnrichmentStrategy]) 
HasNakadiDefaultStatistic EventType (Maybe EventTypeStatistics) 
HasNakadiCompatibilityMode EventType (Maybe CompatibilityMode) 
HasNakadiCategory EventType (Maybe EventTypeCategory) 
type Rep EventType Source # 
type Rep EventType = D1 (MetaData "EventType" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "EventType" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EventTypeName)) (S1 (MetaSel (Just Symbol "_owningApplication") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ApplicationName)))) ((:*:) (S1 (MetaSel (Just Symbol "_category") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe EventTypeCategory))) ((:*:) (S1 (MetaSel (Just Symbol "_enrichmentStrategies") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [EnrichmentStrategy]))) (S1 (MetaSel (Just Symbol "_partitionStrategy") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PartitionStrategy)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_compatibilityMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe CompatibilityMode))) (S1 (MetaSel (Just Symbol "_schema") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EventTypeSchema))) ((:*:) (S1 (MetaSel (Just Symbol "_partitionKeyFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [PartitionKeyField]))) ((:*:) (S1 (MetaSel (Just Symbol "_defaultStatistic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe EventTypeStatistics))) (S1 (MetaSel (Just Symbol "_options") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe EventTypeOptions))))))))

data DataChangeEvent a Source #

DataChangeEvent

Instances

Eq a => Eq (DataChangeEvent a) Source # 
Show a => Show (DataChangeEvent a) Source # 
Generic (DataChangeEvent a) Source # 

Associated Types

type Rep (DataChangeEvent a) :: * -> * #

ToJSON a0 => ToJSON (DataChangeEvent a0) Source # 
FromJSON a0 => FromJSON (DataChangeEvent a0) Source # 
type Rep (DataChangeEvent a) Source # 
type Rep (DataChangeEvent a) = D1 (MetaData "DataChangeEvent" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "DataChangeEvent" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_payload") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Just Symbol "_metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Metadata))) ((:*:) (S1 (MetaSel (Just Symbol "_dataType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_dataOp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DataOp)))))

data EventEnriched a Source #

Type of enriched event.

Instances

Eq a => Eq (EventEnriched a) Source # 
Show a => Show (EventEnriched a) Source # 
Generic (EventEnriched a) Source # 

Associated Types

type Rep (EventEnriched a) :: * -> * #

ToJSON a0 => ToJSON (EventEnriched a0) Source # 
FromJSON a0 => FromJSON (EventEnriched a0) Source # 
type Rep (EventEnriched a) Source # 
type Rep (EventEnriched a) = D1 (MetaData "EventEnriched" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "EventEnriched" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_payload") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) (S1 (MetaSel (Just Symbol "_metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MetadataEnriched))))

data MetadataEnriched Source #

Type of enriched metadata values.

Instances

Eq MetadataEnriched Source # 
Show MetadataEnriched Source # 
Generic MetadataEnriched Source # 
ToJSON MetadataEnriched Source # 
FromJSON MetadataEnriched Source # 
type Rep MetadataEnriched Source # 

data EventTypeStatistics Source #

Type for event type statistics.

Instances

Eq EventTypeStatistics Source # 
Ord EventTypeStatistics Source # 
Show EventTypeStatistics Source # 
Generic EventTypeStatistics Source # 
Hashable EventTypeStatistics Source # 
ToJSON EventTypeStatistics Source # 
FromJSON EventTypeStatistics Source # 
HasNakadiDefaultStatistic EventType (Maybe EventTypeStatistics) 
type Rep EventTypeStatistics Source # 
type Rep EventTypeStatistics = D1 (MetaData "EventTypeStatistics" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "EventTypeStatistics" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_messagesPerMinute") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)) (S1 (MetaSel (Just Symbol "_messageSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64))) ((:*:) (S1 (MetaSel (Just Symbol "_readParallelism") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)) (S1 (MetaSel (Just Symbol "_writeParallelism") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))))

data EventTypeOptions Source #

Type for event type options.

Constructors

EventTypeOptions Int64 

Instances

Eq EventTypeOptions Source # 
Ord EventTypeOptions Source # 
Show EventTypeOptions Source # 
Generic EventTypeOptions Source # 
Hashable EventTypeOptions Source # 
ToJSON EventTypeOptions Source # 
FromJSON EventTypeOptions Source # 
HasNakadiOptions EventType (Maybe EventTypeOptions) 
type Rep EventTypeOptions Source # 
type Rep EventTypeOptions = D1 (MetaData "EventTypeOptions" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.2.0.1-5yLFsgfwCKJDJaD007lc44" False) (C1 (MetaCons "EventTypeOptions" PrefixI True) (S1 (MetaSel (Just Symbol "_retentionTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))