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

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

Network.Nakadi.Internal.Http

Description

Internal module containing HTTP client relevant code.

Synopsis

Documentation

setRequestCheckStatus :: Request -> Request #

Modify the request so that non-2XX status codes generate a runtime StatusCodeException, by using throwErrorStatusCodes

Since: http-client-0.5.13

setRequestIgnoreStatus :: Request -> Request #

Modify the request so that non-2XX status codes do not generate a runtime StatusCodeException.

Since: http-client-0.4.29

defaultRequest :: Request #

A default request value, a GET request of localhost/:80, with an empty request body.

Note that the default checkResponse does nothing.

Since: http-client-0.4.30

parseRequest_ :: String -> Request #

Same as parseRequest, but parse errors cause an impure exception. Mostly useful for static strings which are known to be correctly formatted.

parseRequest :: MonadThrow m => String -> m Request #

Convert a URL into a Request.

This function defaults some of the values in Request, such as setting method to GET and requestHeaders to [].

Since this function uses MonadThrow, the return monad can be anything that is an instance of MonadThrow, such as IO or Maybe.

You can place the request method at the beginning of the URL separated by a space, e.g.:

@@ parseRequest "POST http://httpbin.org/post" @@

Note that the request method must be provided as all capital letters.

A Request created by this function won't cause exceptions on non-2XX response status codes.

To create a request which throws on non-2XX status codes, see parseUrlThrow

Since: http-client-0.4.30

data HttpException #

An exception which may be generated by this library

Since: http-client-0.5.0

Constructors

HttpExceptionRequest Request HttpExceptionContent

Most exceptions are specific to a Request. Inspect the HttpExceptionContent value for details on what occurred.

Since: http-client-0.5.0

InvalidUrlException String String

A URL (first field) is invalid for a given reason (second argument).

Since: http-client-0.5.0

proxyHost :: Proxy -> ByteString #

The host name of the HTTP proxy.

proxyPort :: Proxy -> Int #

The port number of the HTTP proxy.

data Request #

All information on how to connect to a host and what should be sent in the HTTP request.

If you simply wish to download from a URL, see parseRequest.

The constructor for this data type is not exposed. Instead, you should use either the defaultRequest value, or parseRequest to construct from a URL, and then use the records below to make modifications. This approach allows http-client to add configuration options without breaking backwards compatibility.

For example, to construct a POST request, you could do something like:

initReq <- parseRequest "http://www.example.com/path"
let req = initReq
            { method = "POST"
            }

For more information, please see http://www.yesodweb.com/book/settings-types.

Since 0.1.0

Instances
Show Request 
Instance details

Defined in Network.HTTP.Client.Types

HasNakadiRequestTemplate (Config m) Request 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiHttpErrorCallback (Config m) (Maybe (HttpErrorCallback m)) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiRequestModifier (Config m) (Request -> m Request) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiHttpResponseOpen (HttpBackend b) (Config b -> Request -> Maybe Manager -> b (Response (ConduitM () ByteString b ()))) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiHttpLbs (HttpBackend b) (Config b -> Request -> Maybe Manager -> b (Response ByteString)) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

data Response body #

A simple representation of the HTTP response.

Since 0.1.0

Instances
Functor Response 
Instance details

Defined in Network.HTTP.Client.Types

Methods

fmap :: (a -> b) -> Response a -> Response b #

(<$) :: a -> Response b -> Response a #

Foldable Response 
Instance details

Defined in Network.HTTP.Client.Types

Methods

fold :: Monoid m => Response m -> m #

foldMap :: Monoid m => (a -> m) -> Response a -> m #

foldr :: (a -> b -> b) -> b -> Response a -> b #

foldr' :: (a -> b -> b) -> b -> Response a -> b #

foldl :: (b -> a -> b) -> b -> Response a -> b #

foldl' :: (b -> a -> b) -> b -> Response a -> b #

foldr1 :: (a -> a -> a) -> Response a -> a #

foldl1 :: (a -> a -> a) -> Response a -> a #

toList :: Response a -> [a] #

null :: Response a -> Bool #

length :: Response a -> Int #

elem :: Eq a => a -> Response a -> Bool #

maximum :: Ord a => Response a -> a #

minimum :: Ord a => Response a -> a #

sum :: Num a => Response a -> a #

product :: Num a => Response a -> a #

Traversable Response 
Instance details

Defined in Network.HTTP.Client.Types

Methods

traverse :: Applicative f => (a -> f b) -> Response a -> f (Response b) #

sequenceA :: Applicative f => Response (f a) -> f (Response a) #

mapM :: Monad m => (a -> m b) -> Response a -> m (Response b) #

sequence :: Monad m => Response (m a) -> m (Response a) #

Eq body => Eq (Response body) 
Instance details

Defined in Network.HTTP.Client.Types

Methods

(==) :: Response body -> Response body -> Bool #

(/=) :: Response body -> Response body -> Bool #

Show body => Show (Response body) 
Instance details

Defined in Network.HTTP.Client.Types

Methods

showsPrec :: Int -> Response body -> ShowS #

show :: Response body -> String #

showList :: [Response body] -> ShowS #

HasNakadiStreamConnectCallback (Config m) (Maybe (StreamConnectCallback m)) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiHttpResponseOpen (HttpBackend b) (Config b -> Request -> Maybe Manager -> b (Response (ConduitM () ByteString b ()))) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiHttpResponseClose (HttpBackend b) (Response () -> b ()) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

Methods

httpResponseClose :: Lens' (HttpBackend b) (Response () -> b ())

HasNakadiHttpLbs (HttpBackend b) (Config b -> Request -> Maybe Manager -> b (Response ByteString)) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

getResponseBody :: Response a -> a #

Get the response body

Since: http-conduit-2.1.10

getResponseHeaders :: Response a -> [(HeaderName, ByteString)] #

Get all response headers

Since: http-conduit-2.1.10

getResponseHeader :: HeaderName -> Response a -> [ByteString] #

Get all response header values with the given name

Since: http-conduit-2.1.10

getResponseStatusCode :: Response a -> Int #

Get the integral status code of the response

Since: http-conduit-2.1.10

getResponseStatus :: Response a -> Status #

Get the status of the response

Since: http-conduit-2.1.10

setRequestProxy :: Maybe Proxy -> Request -> Request #

Override the default proxy server settings

Since: http-conduit-2.1.10

setRequestManager :: Manager -> Request -> Request #

Instead of using the default global Manager, use the supplied Manager.

Since: http-conduit-2.1.10

setRequestBasicAuth #

Arguments

:: ByteString

username

-> ByteString

password

-> Request 
-> Request 

Set basic auth with the given username and password

Since: http-conduit-2.1.10

setRequestBodyURLEncoded :: [(ByteString, ByteString)] -> Request -> Request #

Set the request body as URL encoded data

Note: This will change the request method to POST and set the content-type to application/x-www-form-urlencoded

Since: http-conduit-2.1.10

setRequestBodyFile :: FilePath -> Request -> Request #

Set the request body as a file

Note: This will not modify the request method. For that, please use requestMethod. You likely don't want the default of GET.

Since: http-conduit-2.1.10

setRequestBodySource #

Arguments

:: Int64

length of source

-> ConduitM () ByteString IO () 
-> Request 
-> Request 

Set the request body as a Source

Note: This will not modify the request method. For that, please use requestMethod. You likely don't want the default of GET.

Since: http-conduit-2.1.10

setRequestBodyLBS :: ByteString -> Request -> Request #

Set the request body as a lazy ByteString

Note: This will not modify the request method. For that, please use requestMethod. You likely don't want the default of GET.

Since: http-conduit-2.1.10

setRequestBodyJSON :: ToJSON a => a -> Request -> Request #

Set the request body as a JSON value

Note: This will not modify the request method. For that, please use requestMethod. You likely don't want the default of GET.

This also sets the Content-Type to application/json; charset=utf-8

Since: http-conduit-2.1.10

setRequestBody :: RequestBody -> Request -> Request #

Set the request body to the given RequestBody. You may want to consider using one of the convenience functions in the modules, e.g. requestBodyJSON.

Note: This will not modify the request method. For that, please use requestMethod. You likely don't want the default of GET.

Since: http-conduit-2.1.10

setRequestQueryString :: Query -> Request -> Request #

Set the query string parameters

Since: http-conduit-2.1.10

getRequestQueryString :: Request -> Query #

Get the query string parameters

Since: http-conduit-2.1.10

setRequestHeaders :: RequestHeaders -> Request -> Request #

Set the request headers, wiping out all previously set headers. This means if you use setRequestHeaders to set some headers and also use one of the other setters that modifies the content-type header (such as setRequestBodyJSON), be sure that setRequestHeaders is evaluated first.

Since: http-conduit-2.1.10

setRequestHeader :: HeaderName -> [ByteString] -> Request -> Request #

Set the given request header to the given list of values. Removes any previously set header values with the same name.

Since: http-conduit-2.1.10

getRequestHeader :: HeaderName -> Request -> [ByteString] #

Get all request header values for the given name

Since: http-conduit-2.1.10

addRequestHeader :: HeaderName -> ByteString -> Request -> Request #

Add a request header name/value combination

Since: http-conduit-2.1.10

setRequestPath :: ByteString -> Request -> Request #

Lens for the requested path info of the request

Since: http-conduit-2.1.10

setRequestPort :: Int -> Request -> Request #

Set the destination port of the request

Since: http-conduit-2.1.10

setRequestHost :: ByteString -> Request -> Request #

Set the destination host of the request

Since: http-conduit-2.1.10

setRequestSecure :: Bool -> Request -> Request #

Set whether this is a secureHTTPS (True) or insecureHTTP (False) request

Since: http-conduit-2.1.10

setRequestMethod :: ByteString -> Request -> Request #

Set the request method

Since: http-conduit-2.1.10

httpLbs :: MonadIO m => Request -> m (Response ByteString) #

Alternate spelling of httpLBS

Since: http-conduit-2.1.10

parseRequestThrow_ :: String -> Request #

Same as parseRequestThrow, but parse errors cause an impure exception. Mostly useful for static strings which are known to be correctly formatted.

Since: http-conduit-2.3.2

parseRequestThrow :: MonadThrow m => String -> m Request #

Same as parseRequest, except will throw an HttpException in the event of a non-2XX response. This uses throwErrorStatusCodes to implement checkResponse.

Exactly the same as parseUrlThrow, but has a name that is more consistent with the other parseRequest functions.

Since: http-conduit-2.3.2

withResponse :: (MonadUnliftIO m, MonadIO n) => Request -> (Response (ConduitM i ByteString n ()) -> m a) -> m a #

Perform an action with the given request. This employes the bracket pattern.

This is similar to httpSource, but does not require MonadResource and allows the result to not contain a ConduitM value.

Since: http-conduit-2.2.3

httpSource :: (MonadResource m, MonadIO n) => Request -> (Response (ConduitM i ByteString n ()) -> ConduitM i o m r) -> ConduitM i o m r #

Perform an HTTP request, and get the response body as a Source.

The second argument to this function tells us how to make the Source from the Response itself. This allows you to perform actions with the status or headers, for example, in addition to the raw bytes themselves. If you just care about the response body, you can use getResponseBody as the second argument here.

{-# LANGUAGE OverloadedStrings #-}
import           Control.Monad.IO.Class       (liftIO)
import           Control.Monad.Trans.Resource (runResourceT)
import           Data.Conduit                 (($$))
import qualified Data.Conduit.Binary          as CB
import qualified Data.Conduit.List            as CL
import           Network.HTTP.Simple
import           System.IO                    (stdout)

main :: IO ()
main =
    runResourceT
        $ httpSource "http://httpbin.org/robots.txt" getSrc
       $$ CB.sinkHandle stdout
  where
    getSrc res = do
        liftIO $ print (getResponseStatus res, getResponseHeaders res)
        getResponseBody res

Since: http-conduit-2.2.1

httpSink :: MonadUnliftIO m => Request -> (Response () -> ConduitM ByteString Void m a) -> m a #

Perform an HTTP request and consume the body with the given Sink

Since: http-conduit-2.1.10

httpJSONEither :: (MonadIO m, FromJSON a) => Request -> m (Response (Either JSONException a)) #

Perform an HTTP request and parse the body as JSON. In the event of an JSON parse errors, a Left value will be returned.

Since: http-conduit-2.1.10

httpJSON :: (MonadIO m, FromJSON a) => Request -> m (Response a) #

Perform an HTTP request and parse the body as JSON. In the event of an JSON parse errors, a JSONException runtime exception will be thrown.

Since: http-conduit-2.1.10

httpNoBody :: MonadIO m => Request -> m (Response ()) #

Perform an HTTP request and ignore the response body.

Since: http-conduit-2.2.2

httpLBS :: MonadIO m => Request -> m (Response ByteString) #

Perform an HTTP request and return the body as a lazy ByteString. Note that the entire value will be read into memory at once (no lazy I/O will be performed). The advantage of a lazy ByteString here (versus using httpBS) is--if needed--a better in-memory representation.

Since: http-conduit-2.1.10

httpBS :: MonadIO m => Request -> m (Response ByteString) #

Perform an HTTP request and return the body as a ByteString.

Since: http-conduit-2.2.4

type ResponseHeaders = [Header] #

Response Headers

type RequestHeaders = [Header] #

Request Headers

type Header = (HeaderName, ByteString) #

Header

type Query = [QueryItem] #

Query.

General form: a=b&c=d, but if the value is Nothing, it becomes a&c=d.

type QueryItem = (ByteString, Maybe ByteString) #

Query item

type StreamConnectCallback m = Response () -> m () Source #

Config

type HttpErrorCallback m = Request -> HttpException -> RetryStatus -> Bool -> m () Source #

Type synonym for user-provided callbacks which are used for HTTP Errror propagation.

data Config m Source #

Instances
HasNakadiWorker (Config m) WorkerConfig 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiRequestTemplate (Config m) Request 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiCommitStrategy (Config m) CommitStrategy 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiSubscriptionStats (Config m) (Maybe SubscriptionStatsConf) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiStreamTimeout (Config m) (Maybe Int32) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiStreamLimit (Config m) (Maybe Int32) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiStreamKeepAliveLimit (Config m) (Maybe Int32) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiStreamConnectCallback (Config m) (Maybe (StreamConnectCallback m)) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiRetryPolicy (Config m) (RetryPolicyM IO) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiMaxUncommittedEvents (Config m) (Maybe Int32) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiManager (Config m) (Maybe Manager) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

Methods

manager :: Lens' (Config m) (Maybe Manager)

HasNakadiLogFunc (Config m) (Maybe (LogFunc m)) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

Methods

logFunc :: Lens' (Config m) (Maybe (LogFunc m))

HasNakadiHttpErrorCallback (Config m) (Maybe (HttpErrorCallback m)) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiHttp (Config m) (HttpBackend m) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

Methods

http :: Lens' (Config m) (HttpBackend m)

HasNakadiFlowId (Config m) (Maybe FlowId) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

Methods

flowId :: Lens' (Config m) (Maybe FlowId)

HasNakadiDeserializationFailureCallback (Config m) (Maybe (ByteString -> Text -> m ())) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiCommitTimeout (Config m) (Maybe CommitTimeout) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiBatchLimit (Config m) (Maybe Int32) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiBatchFlushTimeout (Config m) (Maybe Int32) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiRequestModifier (Config m) (Request -> m Request) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiHttpResponseOpen (HttpBackend b) (Config b -> Request -> Maybe Manager -> b (Response (ConduitM () ByteString b ()))) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiHttpLbs (HttpBackend b) (Config b -> Request -> Maybe Manager -> b (Response ByteString)) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

data HttpBackend b Source #

Instances
HasNakadiHttp (Config m) (HttpBackend m) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

Methods

http :: Lens' (Config m) (HttpBackend m)

HasNakadiHttpResponseOpen (HttpBackend b) (Config b -> Request -> Maybe Manager -> b (Response (ConduitM () ByteString b ()))) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiHttpResponseClose (HttpBackend b) (Response () -> b ()) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

Methods

httpResponseClose :: Lens' (HttpBackend b) (Response () -> b ())

HasNakadiHttpLbs (HttpBackend b) (Config b -> Request -> Maybe Manager -> b (Response ByteString)) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

data WorkerConfig Source #

Constructors

WorkerConfig 

Fields

Instances
HasNakadiNThreads WorkerConfig Int 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiWorker (Config m) WorkerConfig 
Instance details

Defined in Network.Nakadi.Internal.Lenses

data SubscriptionStatsConf Source #

Constructors

SubscriptionStatsConf 

Fields

Instances
HasNakadiShowTimeLag SubscriptionStatsConf Bool 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiSubscriptionStats (Config m) (Maybe SubscriptionStatsConf) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type LogFunc m = LogSource -> LogLevel -> LogStr -> m () Source #

Type of a logger callback provided to nakadi-client for logging purposes.

type LogFuncIO = LogFunc IO Source #

LogFunc specialized to IO.

data Problem Source #

Type for RFC7807 Problem objects.

Constructors

Problem 

Fields

  • problemType :: Maybe URI

    (string) - A URI reference [RFC3986] that identifies the problem type. This specification encourages that, when dereferenced, it provide human-readable documentation for the problem type (e.g., using HTML [W3C.REC-html5-20141028]). When this member is not present, its value is assumed to be "about:blank".

  • problemTitle :: Text

    (string) - A short, human-readable summary of the problem type. It SHOULD NOT change from occurrence to occurrence of the problem, except for purposes of localization (e.g., using proactive content negotiation; see [RFC7231], Section 3.4).

  • problemStatus :: Maybe Status

    "status" (number) - The HTTP status code ([RFC7231], Section 6) generated by the origin server for this occurrence of the problem.

  • problemDetail :: Maybe Text

    (string) - A human-readable explanation specific to this occurrence of the problem.

  • problemInstance :: Maybe URI

    (string) - A URI reference that identifies the specific occurrence of the problem. It may or may not yield further information if dereferenced.

  • problemCustom :: HashMap Text Value
     
Instances
Eq Problem Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Problem

Methods

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

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

Show Problem Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Problem

Generic Problem Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Problem

Associated Types

type Rep Problem :: Type -> Type #

Methods

from :: Problem -> Rep Problem x #

to :: Rep Problem x -> Problem #

ToJSON Problem Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Problem

FromJSON Problem Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Problem

type Rep Problem Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Problem

newtype CursorOffset Source #

Type for cursor offsets.

Constructors

CursorOffset 

Fields

Instances
Eq CursorOffset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord CursorOffset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show CursorOffset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

IsString CursorOffset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic CursorOffset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep CursorOffset :: Type -> Type #

Hashable CursorOffset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON CursorOffset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON CursorOffset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiOffset Cursor CursorOffset 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiOffset SubscriptionCursor CursorOffset 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiOldestAvailableOffset Partition CursorOffset 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiNewestAvailableOffset Partition CursorOffset 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep CursorOffset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep CursorOffset = D1 (MetaData "CursorOffset" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "CursorOffset" PrefixI True) (S1 (MetaSel (Just "unCursorOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype EventTypeName Source #

Type for event type names.

Constructors

EventTypeName 

Fields

Instances
Eq EventTypeName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord EventTypeName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show EventTypeName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

IsString EventTypeName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic EventTypeName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep EventTypeName :: Type -> Type #

Hashable EventTypeName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON EventTypeName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON EventTypeName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiEventType SubscriptionCursor EventTypeName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiEventType EventMetadataEnriched EventTypeName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiName EventType EventTypeName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiEventTypes SubscriptionRequest [EventTypeName] 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiEventTypes Subscription [EventTypeName] 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartitionIndexMap (WorkerRegistry a) PartitionIndexMap 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep EventTypeName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep EventTypeName = D1 (MetaData "EventTypeName" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "EventTypeName" PrefixI True) (S1 (MetaSel (Just "unEventTypeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype PartitionName Source #

Type for partition names.

Constructors

PartitionName 

Fields

Instances
Eq PartitionName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord PartitionName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show PartitionName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

IsString PartitionName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic PartitionName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep PartitionName :: Type -> Type #

Hashable PartitionName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON PartitionName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON PartitionName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiPartition Cursor PartitionName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartition SubscriptionCursor PartitionName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartition Partition PartitionName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartition PartitionStat PartitionName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartition EventMetadata (Maybe PartitionName) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartition EventMetadataEnriched (Maybe PartitionName) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartitionIndexMap (WorkerRegistry a) PartitionIndexMap 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep PartitionName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep PartitionName = D1 (MetaData "PartitionName" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "PartitionName" PrefixI True) (S1 (MetaSel (Just "unPartitionName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype PartitionCompactionKey Source #

Type for partition compaction keys.

Constructors

PartitionCompactionKey 

Fields

Instances
Eq PartitionCompactionKey Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord PartitionCompactionKey Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show PartitionCompactionKey Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

IsString PartitionCompactionKey Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic PartitionCompactionKey Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep PartitionCompactionKey :: Type -> Type #

Hashable PartitionCompactionKey Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON PartitionCompactionKey Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON PartitionCompactionKey Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiPartitionCompactionKey EventMetadata (Maybe PartitionCompactionKey) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartitionCompactionKey EventMetadataEnriched (Maybe PartitionCompactionKey) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep PartitionCompactionKey Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep PartitionCompactionKey = D1 (MetaData "PartitionCompactionKey" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "PartitionCompactionKey" PrefixI True) (S1 (MetaSel (Just "unPartitionCompactionKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Cursor Source #

Type for cursors.

Constructors

Cursor 
Instances
Eq Cursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Methods

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

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

Ord Cursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show Cursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic Cursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep Cursor :: Type -> Type #

Methods

from :: Cursor -> Rep Cursor x #

to :: Rep Cursor x -> Cursor #

Hashable Cursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Methods

hashWithSalt :: Int -> Cursor -> Int #

hash :: Cursor -> Int #

ToJSON Cursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON Cursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiPartition Cursor PartitionName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiOffset Cursor CursorOffset 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiInitialCursor CursorDistanceQuery Cursor 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiFinalCursor CursorDistanceQuery Cursor 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiItems CursorCommit [Cursor] 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep Cursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep Cursor = D1 (MetaData "Cursor" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "Cursor" PrefixI True) (S1 (MetaSel (Just "_partition") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 PartitionName) :*: S1 (MetaSel (Just "_offset") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 CursorOffset)))

newtype ApplicationName Source #

Type for application names.

Constructors

ApplicationName 
Instances
Eq ApplicationName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord ApplicationName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show ApplicationName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

IsString ApplicationName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic ApplicationName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep ApplicationName :: Type -> Type #

Hashable ApplicationName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON ApplicationName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON ApplicationName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiOwningApplication SubscriptionRequest ApplicationName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiOwningApplication Subscription ApplicationName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiOwningApplication EventType (Maybe ApplicationName) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep ApplicationName Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep ApplicationName = D1 (MetaData "ApplicationName" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "ApplicationName" PrefixI True) (S1 (MetaSel (Just "unApplicationName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data SubscriptionCursor Source #

Type fo rsubscription cursors.

Constructors

SubscriptionCursor 

Fields

Instances
Eq SubscriptionCursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord SubscriptionCursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show SubscriptionCursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic SubscriptionCursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep SubscriptionCursor :: Type -> Type #

ToJSON SubscriptionCursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON SubscriptionCursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiSubscriptionCursor SubscriptionCursor 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartition SubscriptionCursor PartitionName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiOffset SubscriptionCursor CursorOffset 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiCursor SubscriptionCursorWithCounter SubscriptionCursor 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiEventType SubscriptionCursor EventTypeName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiCursorToken SubscriptionCursor Text 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiItems SubscriptionCursorCommit [SubscriptionCursor] 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiCursor (SubscriptionEventStreamBatch a) SubscriptionCursor 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep SubscriptionCursor Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep SubscriptionCursor = D1 (MetaData "SubscriptionCursor" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "SubscriptionCursor" PrefixI True) ((S1 (MetaSel (Just "_partition") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 PartitionName) :*: S1 (MetaSel (Just "_offset") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 CursorOffset)) :*: (S1 (MetaSel (Just "_eventType") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 EventTypeName) :*: S1 (MetaSel (Just "_cursorToken") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))))

data SubscriptionCursorWithoutToken Source #

Type for subscription cursors without token.

Constructors

SubscriptionCursorWithoutToken 

Fields

Instances
Eq SubscriptionCursorWithoutToken Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord SubscriptionCursorWithoutToken Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show SubscriptionCursorWithoutToken Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic SubscriptionCursorWithoutToken Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep SubscriptionCursorWithoutToken :: Type -> Type #

Hashable SubscriptionCursorWithoutToken Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON SubscriptionCursorWithoutToken Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON SubscriptionCursorWithoutToken Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep SubscriptionCursorWithoutToken Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep SubscriptionCursorWithoutToken = D1 (MetaData "SubscriptionCursorWithoutToken" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "SubscriptionCursorWithoutToken" PrefixI True) (S1 (MetaSel (Just "_partition") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 PartitionName) :*: (S1 (MetaSel (Just "_offset") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 CursorOffset) :*: S1 (MetaSel (Just "_eventType") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 EventTypeName))))

newtype SubscriptionCursorCommit Source #

Type for commit object for subscription cursor committing.

Constructors

SubscriptionCursorCommit 

Fields

Instances
Show SubscriptionCursorCommit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic SubscriptionCursorCommit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep SubscriptionCursorCommit :: Type -> Type #

ToJSON SubscriptionCursorCommit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON SubscriptionCursorCommit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiItems SubscriptionCursorCommit [SubscriptionCursor] 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep SubscriptionCursorCommit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep SubscriptionCursorCommit = D1 (MetaData "SubscriptionCursorCommit" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "SubscriptionCursorCommit" PrefixI True) (S1 (MetaSel (Just "_items") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SubscriptionCursor])))

newtype CursorCommit Source #

Type for commit objects for cursor committing.

Constructors

CursorCommit 

Fields

Instances
Show CursorCommit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic CursorCommit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep CursorCommit :: Type -> Type #

ToJSON CursorCommit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON CursorCommit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiItems CursorCommit [Cursor] 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep CursorCommit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep CursorCommit = D1 (MetaData "CursorCommit" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "CursorCommit" PrefixI True) (S1 (MetaSel (Just "_items") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Cursor])))

newtype SubscriptionId Source #

Type for subscription IDs.

Constructors

SubscriptionId 

Fields

Instances
Eq SubscriptionId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord SubscriptionId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show SubscriptionId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic SubscriptionId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep SubscriptionId :: Type -> Type #

Hashable SubscriptionId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON SubscriptionId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON SubscriptionId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiSubscriptionId SubscriptionEventStream SubscriptionId 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiId SubscriptionId UUID 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiId Subscription SubscriptionId 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep SubscriptionId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep SubscriptionId = D1 (MetaData "SubscriptionId" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "SubscriptionId" PrefixI True) (S1 (MetaSel (Just "unSubscriptionId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

newtype StreamId Source #

Type for stream IDs.

Constructors

StreamId 

Fields

Instances
Eq StreamId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord StreamId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show StreamId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic StreamId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep StreamId :: Type -> Type #

Methods

from :: StreamId -> Rep StreamId x #

to :: Rep StreamId x -> StreamId #

ToJSON StreamId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON StreamId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiStreamId SubscriptionEventStream StreamId 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiId StreamId Text 
Instance details

Defined in Network.Nakadi.Internal.Lenses

Methods

id :: Lens' StreamId Text

HasNakadiStreamId PartitionStat (Maybe StreamId) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep StreamId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep StreamId = D1 (MetaData "StreamId" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "StreamId" PrefixI True) (S1 (MetaSel (Just "unStreamId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype Timestamp Source #

Type for timestamps.

Constructors

Timestamp 

Fields

Instances
Eq Timestamp Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord Timestamp Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show Timestamp Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic Timestamp Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep Timestamp :: Type -> Type #

Hashable Timestamp Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON Timestamp Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON Timestamp Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiOccurredAt EventMetadata Timestamp 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiOccurredAt EventMetadataEnriched Timestamp 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiReceivedAt EventMetadataEnriched Timestamp 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiCreatedAt Subscription Timestamp 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiUTCTime Timestamp UTCTime 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiCreatedAt EventTypeSchema (Maybe Timestamp) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep Timestamp Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep Timestamp = D1 (MetaData "Timestamp" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "Timestamp" PrefixI True) (S1 (MetaSel (Just "unTimestamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)))

newtype FlowId Source #

A Flow ID.

Constructors

FlowId 

Fields

Instances
Eq FlowId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Methods

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

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

Ord FlowId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show FlowId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

IsString FlowId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Methods

fromString :: String -> FlowId #

Generic FlowId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep FlowId :: Type -> Type #

Methods

from :: FlowId -> Rep FlowId x #

to :: Rep FlowId x -> FlowId #

ToJSON FlowId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON FlowId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiFlowId EventMetadataEnriched (Maybe FlowId) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiFlowId (Config m) (Maybe FlowId) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

Methods

flowId :: Lens' (Config m) (Maybe FlowId)

type Rep FlowId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep FlowId = D1 (MetaData "FlowId" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "FlowId" PrefixI True) (S1 (MetaSel (Just "unFlowId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype EventId Source #

ID of an Event

Constructors

EventId 

Fields

Instances
Eq EventId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Methods

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

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

Ord EventId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show EventId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic EventId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep EventId :: Type -> Type #

Methods

from :: EventId -> Rep EventId x #

to :: Rep EventId x -> EventId #

Hashable EventId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Methods

hashWithSalt :: Int -> EventId -> Int #

hash :: EventId -> Int #

ToJSON EventId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON EventId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiEid EventMetadata EventId 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiEid EventMetadataEnriched EventId 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiId EventId UUID 
Instance details

Defined in Network.Nakadi.Internal.Lenses

Methods

id :: Lens' EventId UUID

HasNakadiParentEids EventMetadata (Maybe [EventId]) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiParentEids EventMetadataEnriched (Maybe [EventId]) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep EventId Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep EventId = D1 (MetaData "EventId" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "EventId" PrefixI True) (S1 (MetaSel (Just "unEventId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UUID)))

data Partition Source #

Partition Data

Constructors

Partition 

Fields

data ShiftedCursor Source #

Type for shift-cursor queries.

Constructors

ShiftedCursor 

Fields

data CursorDistanceQuery Source #

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

Constructors

CursorDistanceQuery 

Fields

Instances
Eq CursorDistanceQuery Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord CursorDistanceQuery Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show CursorDistanceQuery Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic CursorDistanceQuery Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep CursorDistanceQuery :: Type -> Type #

Hashable CursorDistanceQuery Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON CursorDistanceQuery Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON CursorDistanceQuery Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiInitialCursor CursorDistanceQuery Cursor 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiFinalCursor CursorDistanceQuery Cursor 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep CursorDistanceQuery Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep CursorDistanceQuery = D1 (MetaData "CursorDistanceQuery" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "CursorDistanceQuery" PrefixI True) (S1 (MetaSel (Just "_initialCursor") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Cursor) :*: S1 (MetaSel (Just "_finalCursor") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Cursor)))

newtype CursorDistanceResult Source #

Type for results of cursor-distance-queries.

Constructors

CursorDistanceResult 

Fields

Instances
Eq CursorDistanceResult Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord CursorDistanceResult Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show CursorDistanceResult Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic CursorDistanceResult Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep CursorDistanceResult :: Type -> Type #

Hashable CursorDistanceResult Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON CursorDistanceResult Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON CursorDistanceResult Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiDistance CursorDistanceResult Int64 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep CursorDistanceResult Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep CursorDistanceResult = D1 (MetaData "CursorDistanceResult" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "CursorDistanceResult" PrefixI True) (S1 (MetaSel (Just "_distance") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))

data SubscriptionReadFrom Source #

This type models the "read_from" field contained in subscription objects.

Instances
Eq SubscriptionReadFrom Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord SubscriptionReadFrom Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show SubscriptionReadFrom Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic SubscriptionReadFrom Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep SubscriptionReadFrom :: Type -> Type #

Hashable SubscriptionReadFrom Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON SubscriptionReadFrom Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON SubscriptionReadFrom Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep SubscriptionReadFrom Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep SubscriptionReadFrom = D1 (MetaData "SubscriptionReadFrom" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "SubscriptionReadFromBegin" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SubscriptionReadFromEnd" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SubscriptionReadFromCursors" PrefixI False) (U1 :: Type -> Type)))

data SubscriptionPosition Source #

Type modelling a subscription position.

Instances
Eq SubscriptionPosition Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord SubscriptionPosition Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show SubscriptionPosition Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic SubscriptionPosition Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep SubscriptionPosition :: Type -> Type #

Hashable SubscriptionPosition Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON SubscriptionPosition Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON SubscriptionPosition Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiSubscriptionPosition Subscription SubscriptionPosition 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiSubscriptionPosition SubscriptionRequest (Maybe SubscriptionPosition) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep SubscriptionPosition Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep SubscriptionPosition = D1 (MetaData "SubscriptionPosition" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "SubscriptionPositionBegin" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "SubscriptionPositionEnd" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SubscriptionPositionCursors" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [SubscriptionCursorWithoutToken]))))

subscriptionPositionToObject :: SubscriptionPosition -> Object Source #

Internal helper function for converting a SubscriptionPosition into a JSON Object (not a JSON Value). Removes the need for partial pattern matching later.

newtype ConsumerGroup Source #

This type models the value describing the use case of a subscription. In general this is an additional identifier used to differ subscriptions having the same owning application and event types.

Constructors

ConsumerGroup 
Instances
Eq ConsumerGroup Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord ConsumerGroup Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show ConsumerGroup Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

IsString ConsumerGroup Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic ConsumerGroup Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep ConsumerGroup :: Type -> Type #

Hashable ConsumerGroup Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON ConsumerGroup Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON ConsumerGroup Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiConsumerGroup Subscription ConsumerGroup 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiConsumerGroup SubscriptionRequest (Maybe ConsumerGroup) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep ConsumerGroup Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep ConsumerGroup = D1 (MetaData "ConsumerGroup" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "ConsumerGroup" PrefixI True) (S1 (MetaSel (Just "unConsumerGroup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Subscription Source #

Type for a Subscription which has already been created.

When a subscription object is retrieved from Nakadi the following fields are regarded as mandatory:

  • id
  • owning_application
  • event_types
  • consumer_group
  • created_at
  • read_from
  • depending on read_from also cursors.
Instances
Eq Subscription Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord Subscription Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show Subscription Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic Subscription Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep Subscription :: Type -> Type #

Hashable Subscription Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON Subscription Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON Subscription Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiCreatedAt Subscription Timestamp 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiOwningApplication Subscription ApplicationName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiSubscriptionPosition Subscription SubscriptionPosition 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiId Subscription SubscriptionId 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiConsumerGroup Subscription ConsumerGroup 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiItems SubscriptionsListResponse [Subscription] 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiEventTypes Subscription [EventTypeName] 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep Subscription Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

data SubscriptionRequest Source #

Type for a Subscription which is to be created.

When a subscription is to be created the following fields are regarded as mandatory in the subscription object:

  • owning_application
  • event_types

The remaining fields are regarded as optional:

  • consumer_group
  • read_from
  • depending on read_from the field cursors might have to be present as well.
Instances
Eq SubscriptionRequest Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord SubscriptionRequest Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show SubscriptionRequest Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic SubscriptionRequest Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep SubscriptionRequest :: Type -> Type #

Hashable SubscriptionRequest Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON SubscriptionRequest Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON SubscriptionRequest Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiOwningApplication SubscriptionRequest ApplicationName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiSubscriptionPosition SubscriptionRequest (Maybe SubscriptionPosition) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiEventTypes SubscriptionRequest [EventTypeName] 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiConsumerGroup SubscriptionRequest (Maybe ConsumerGroup) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep SubscriptionRequest Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep SubscriptionRequest = D1 (MetaData "SubscriptionRequest" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "SubscriptionRequest" PrefixI True) ((S1 (MetaSel (Just "_owningApplication") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ApplicationName) :*: S1 (MetaSel (Just "_eventTypes") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [EventTypeName])) :*: (S1 (MetaSel (Just "_consumerGroup") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe ConsumerGroup)) :*: S1 (MetaSel (Just "_subscriptionPosition") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe SubscriptionPosition)))))

data PublishingStatus Source #

Type for publishing status.

Instances
Eq PublishingStatus Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord PublishingStatus Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show PublishingStatus Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic PublishingStatus Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep PublishingStatus :: Type -> Type #

Hashable PublishingStatus Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON PublishingStatus Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON PublishingStatus Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep PublishingStatus Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep PublishingStatus = D1 (MetaData "PublishingStatus" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "PublishingStatusSubmitted" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "PublishingStatusFailed" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PublishingStatusAborted" PrefixI False) (U1 :: Type -> Type)))

data Step Source #

Step

Instances
Eq Step Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Methods

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

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

Ord Step Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

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 # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Methods

showsPrec :: Int -> Step -> ShowS #

show :: Step -> String #

showList :: [Step] -> ShowS #

Generic Step Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep Step :: Type -> Type #

Methods

from :: Step -> Rep Step x #

to :: Rep Step x -> Step #

Hashable Step Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Methods

hashWithSalt :: Int -> Step -> Int #

hash :: Step -> Int #

ToJSON Step Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON Step Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep Step Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep Step = D1 (MetaData "Step" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) ((C1 (MetaCons "StepNone" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StepValidating" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "StepPartitioning" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "StepEnriching" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StepPublishing" PrefixI False) (U1 :: Type -> Type))))

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 # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord BatchItemResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show BatchItemResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic BatchItemResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep BatchItemResponse :: Type -> Type #

Hashable BatchItemResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON BatchItemResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON BatchItemResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep BatchItemResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep BatchItemResponse = D1 (MetaData "BatchItemResponse" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "BatchItemResponse" PrefixI True) ((S1 (MetaSel (Just "_eid") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe EventId)) :*: S1 (MetaSel (Just "_publishingStatus") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 PublishingStatus)) :*: (S1 (MetaSel (Just "_step") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Step)) :*: S1 (MetaSel (Just "_detail") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text)))))

newtype StreamKeepAliveLimit Source #

StreamKeepAliveLimit

Instances
Eq StreamKeepAliveLimit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord StreamKeepAliveLimit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show StreamKeepAliveLimit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON StreamKeepAliveLimit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON StreamKeepAliveLimit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

newtype BatchFlushTimeout Source #

BatchFlushTimeout

data CursorCommitResultType Source #

CursorCommitResultType

Instances
Eq CursorCommitResultType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord CursorCommitResultType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show CursorCommitResultType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON CursorCommitResultType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON CursorCommitResultType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

data CursorCommitResult Source #

CursorCommitResult

Instances
Eq CursorCommitResult Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord CursorCommitResult Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show CursorCommitResult Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON CursorCommitResult Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON CursorCommitResult Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

newtype CursorCommitResults Source #

Instances
Eq CursorCommitResults Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord CursorCommitResults Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show CursorCommitResults Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON CursorCommitResults Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON CursorCommitResults Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

data SchemaType Source #

SchemaType

Constructors

SchemaTypeJson 
Instances
Eq SchemaType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord SchemaType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show SchemaType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic SchemaType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep SchemaType :: Type -> Type #

Hashable SchemaType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON SchemaType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON SchemaType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiSchemaType EventTypeSchema SchemaType 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep SchemaType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep SchemaType = D1 (MetaData "SchemaType" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "SchemaTypeJson" PrefixI False) (U1 :: Type -> Type))

newtype SchemaVersion Source #

Type for the version of a schema.

Constructors

SchemaVersion 
Instances
Eq SchemaVersion Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord SchemaVersion Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show SchemaVersion Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

IsString SchemaVersion Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic SchemaVersion Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep SchemaVersion :: Type -> Type #

Hashable SchemaVersion Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON SchemaVersion Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON SchemaVersion Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiVersion EventMetadataEnriched SchemaVersion 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiVersion EventTypeSchema (Maybe SchemaVersion) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep SchemaVersion Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep SchemaVersion = D1 (MetaData "SchemaVersion" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "SchemaVersion" PrefixI True) (S1 (MetaSel (Just "unSchemaVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data EventTypeSchema Source #

Type for the schema of an event type.

Instances
Eq EventTypeSchema Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord EventTypeSchema Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show EventTypeSchema Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic EventTypeSchema Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep EventTypeSchema :: Type -> Type #

Hashable EventTypeSchema Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON EventTypeSchema Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON EventTypeSchema Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiSchemaType EventTypeSchema SchemaType 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiSchema EventTypeSchema Text 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiSchema EventType EventTypeSchema 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiVersion EventTypeSchema (Maybe SchemaVersion) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiCreatedAt EventTypeSchema (Maybe Timestamp) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiItems EventTypeSchemasResponse [EventTypeSchema] 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep EventTypeSchema Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep EventTypeSchema = D1 (MetaData "EventTypeSchema" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "EventTypeSchema" PrefixI True) ((S1 (MetaSel (Just "_version") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe SchemaVersion)) :*: S1 (MetaSel (Just "_createdAt") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Timestamp))) :*: (S1 (MetaSel (Just "_schemaType") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 SchemaType) :*: S1 (MetaSel (Just "_schema") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))))

newtype PaginationLink Source #

PaginationLink

Constructors

PaginationLink 

Fields

data PaginationLinks Source #

PaginationLinks

data EventTypeSchemasResponse Source #

EventTypeSchemasResponse

Instances
Eq EventTypeSchemasResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord EventTypeSchemasResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show EventTypeSchemasResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic EventTypeSchemasResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep EventTypeSchemasResponse :: Type -> Type #

Hashable EventTypeSchemasResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON EventTypeSchemasResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON EventTypeSchemasResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiLinks EventTypeSchemasResponse PaginationLinks 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiItems EventTypeSchemasResponse [EventTypeSchema] 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep EventTypeSchemasResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep EventTypeSchemasResponse = D1 (MetaData "EventTypeSchemasResponse" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "EventTypeSchemasResponse" PrefixI True) (S1 (MetaSel (Just "_links") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 PaginationLinks) :*: S1 (MetaSel (Just "_items") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [EventTypeSchema])))

data SubscriptionsListResponse Source #

SubscriptionsListResponse

Instances
Eq SubscriptionsListResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord SubscriptionsListResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show SubscriptionsListResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic SubscriptionsListResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep SubscriptionsListResponse :: Type -> Type #

Hashable SubscriptionsListResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON SubscriptionsListResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON SubscriptionsListResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiLinks SubscriptionsListResponse PaginationLinks 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiItems SubscriptionsListResponse [Subscription] 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep SubscriptionsListResponse Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep SubscriptionsListResponse = D1 (MetaData "SubscriptionsListResponse" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "SubscriptionsListResponse" PrefixI True) (S1 (MetaSel (Just "_links") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 PaginationLinks) :*: S1 (MetaSel (Just "_items") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Subscription])))

newtype Offset Source #

Type for offset values.

Constructors

Offset 

Fields

Instances
Eq Offset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Methods

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

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

Ord Offset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show Offset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic Offset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep Offset :: Type -> Type #

Methods

from :: Offset -> Rep Offset x #

to :: Rep Offset x -> Offset #

Hashable Offset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Methods

hashWithSalt :: Int -> Offset -> Int #

hash :: Offset -> Int #

type Rep Offset Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep Offset = D1 (MetaData "Offset" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "Offset" PrefixI True) (S1 (MetaSel (Just "unOffset") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))

newtype Limit Source #

Type for limit values.

Constructors

Limit 

Fields

Instances
Eq Limit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Methods

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

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

Ord Limit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

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 # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Methods

showsPrec :: Int -> Limit -> ShowS #

show :: Limit -> String #

showList :: [Limit] -> ShowS #

Generic Limit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep Limit :: Type -> Type #

Methods

from :: Limit -> Rep Limit x #

to :: Rep Limit x -> Limit #

Hashable Limit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Methods

hashWithSalt :: Int -> Limit -> Int #

hash :: Limit -> Int #

type Rep Limit Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep Limit = D1 (MetaData "Limit" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "Limit" PrefixI True) (S1 (MetaSel (Just "unLimit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)))

data PartitionState Source #

Type for partition states.

Instances
Eq PartitionState Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord PartitionState Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show PartitionState Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON PartitionState Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON PartitionState Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiState PartitionStat PartitionState 
Instance details

Defined in Network.Nakadi.Internal.Lenses

data PartitionStat Source #

Type for per-partition statistics.

Instances
Eq PartitionStat Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord PartitionStat Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show PartitionStat Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic PartitionStat Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep PartitionStat :: Type -> Type #

ToJSON PartitionStat Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON PartitionStat Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiPartition PartitionStat PartitionName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiState PartitionStat PartitionState 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiUnconsumedEvents PartitionStat (Maybe Int64) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiStreamId PartitionStat (Maybe StreamId) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiConsumerLagSeconds PartitionStat (Maybe Int64) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep PartitionStat Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

data SubscriptionEventTypeStats Source #

Nakadi type SubscriptionEventTypeStats.

Instances
Eq SubscriptionEventTypeStats Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord SubscriptionEventTypeStats Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show SubscriptionEventTypeStats Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic SubscriptionEventTypeStats Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep SubscriptionEventTypeStats :: Type -> Type #

ToJSON SubscriptionEventTypeStats Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON SubscriptionEventTypeStats Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiItems SubscriptionStats [SubscriptionEventTypeStats] 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep SubscriptionEventTypeStats Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep SubscriptionEventTypeStats = D1 (MetaData "SubscriptionEventTypeStats" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "SubscriptionEventTypeStats" PrefixI True) (S1 (MetaSel (Just "_eventType") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 EventTypeName) :*: S1 (MetaSel (Just "_partitions") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [PartitionStat])))

newtype SubscriptionStats Source #

Type modelling per-subscription statistics. Objects of this type are returned by requests to subscriptionsSUBSCRIPTION-ID/stats.

Instances
Eq SubscriptionStats Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord SubscriptionStats Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show SubscriptionStats Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic SubscriptionStats Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep SubscriptionStats :: Type -> Type #

ToJSON SubscriptionStats Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON SubscriptionStats Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiItems SubscriptionStats [SubscriptionEventTypeStats] 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep SubscriptionStats Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep SubscriptionStats = D1 (MetaData "SubscriptionStats" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "SubscriptionStats" PrefixI True) (S1 (MetaSel (Just "_items") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SubscriptionEventTypeStats])))

data EventTypeCategory Source #

Instances
Eq EventTypeCategory Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord EventTypeCategory Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show EventTypeCategory Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic EventTypeCategory Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep EventTypeCategory :: Type -> Type #

Hashable EventTypeCategory Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON EventTypeCategory Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON EventTypeCategory Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiCategory EventType (Maybe EventTypeCategory) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep EventTypeCategory Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep EventTypeCategory = D1 (MetaData "EventTypeCategory" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "EventTypeCategoryUndefined" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "EventTypeCategoryData" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EventTypeCategoryBusiness" PrefixI False) (U1 :: Type -> Type)))

data PartitionStrategy Source #

Type for a partitioning strategy.

Instances
Eq PartitionStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord PartitionStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show PartitionStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

IsString PartitionStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic PartitionStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep PartitionStrategy :: Type -> Type #

Hashable PartitionStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON PartitionStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON PartitionStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiPartitionStrategy EventType (Maybe PartitionStrategy) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep PartitionStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep PartitionStrategy = D1 (MetaData "PartitionStrategy" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) ((C1 (MetaCons "PartitionStrategyRandom" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PartitionStrategyUser" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "PartitionStrategyHash" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PartitionStrategyCustom" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))))

data EnrichmentStrategy Source #

Type for an enrichment stragey.

Instances
Eq EnrichmentStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord EnrichmentStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show EnrichmentStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic EnrichmentStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep EnrichmentStrategy :: Type -> Type #

Hashable EnrichmentStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON EnrichmentStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON EnrichmentStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiEnrichmentStrategies EventType (Maybe [EnrichmentStrategy]) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep EnrichmentStrategy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep EnrichmentStrategy = D1 (MetaData "EnrichmentStrategy" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "EnrichmentStrategyMetadata" PrefixI False) (U1 :: Type -> Type))

data CompatibilityMode Source #

Type for an event type compatibility mode.

Instances
Eq CompatibilityMode Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord CompatibilityMode Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show CompatibilityMode Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic CompatibilityMode Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep CompatibilityMode :: Type -> Type #

Hashable CompatibilityMode Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON CompatibilityMode Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON CompatibilityMode Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiCompatibilityMode EventType (Maybe CompatibilityMode) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep CompatibilityMode Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep CompatibilityMode = D1 (MetaData "CompatibilityMode" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "CompatibilityModeCompatible" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CompatibilityModeForward" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CompatibilityModeNone" PrefixI False) (U1 :: Type -> Type)))

data CleanupPolicy Source #

Type for cleanup policy.

Instances
Eq CleanupPolicy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord CleanupPolicy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show CleanupPolicy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic CleanupPolicy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep CleanupPolicy :: Type -> Type #

Hashable CleanupPolicy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON CleanupPolicy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON CleanupPolicy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiCleanupPolicy EventType (Maybe CleanupPolicy) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep CleanupPolicy Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep CleanupPolicy = D1 (MetaData "CleanupPolicy" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "CleanupPolicyDelete" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CleanupPolicyCompact" PrefixI False) (U1 :: Type -> Type))

newtype PartitionKeyField Source #

Type for a partitioning key field.

Instances
Eq PartitionKeyField Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord PartitionKeyField Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show PartitionKeyField Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

IsString PartitionKeyField Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic PartitionKeyField Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep PartitionKeyField :: Type -> Type #

Hashable PartitionKeyField Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON PartitionKeyField Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON PartitionKeyField Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiPartitionKeyFields EventType (Maybe [PartitionKeyField]) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep PartitionKeyField Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep PartitionKeyField = D1 (MetaData "PartitionKeyField" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" True) (C1 (MetaCons "PartitionKeyField" PrefixI True) (S1 (MetaSel (Just "unPartitionKeyField") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data EventTypeStatistics Source #

Type for event type statistics.

Instances
Eq EventTypeStatistics Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord EventTypeStatistics Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show EventTypeStatistics Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic EventTypeStatistics Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep EventTypeStatistics :: Type -> Type #

Hashable EventTypeStatistics Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON EventTypeStatistics Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON EventTypeStatistics Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiDefaultStatistic EventType (Maybe EventTypeStatistics) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep EventTypeStatistics Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep EventTypeStatistics = D1 (MetaData "EventTypeStatistics" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "EventTypeStatistics" PrefixI True) ((S1 (MetaSel (Just "_messagesPerMinute") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int64) :*: S1 (MetaSel (Just "_messageSize") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int64)) :*: (S1 (MetaSel (Just "_readParallelism") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int64) :*: S1 (MetaSel (Just "_writeParallelism") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int64))))

data EventTypeOptions Source #

Type for event type options.

Constructors

EventTypeOptions 
Instances
Eq EventTypeOptions Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord EventTypeOptions Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show EventTypeOptions Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic EventTypeOptions Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep EventTypeOptions :: Type -> Type #

Hashable EventTypeOptions Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON EventTypeOptions Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON EventTypeOptions Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiOptions EventType (Maybe EventTypeOptions) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep EventTypeOptions Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep EventTypeOptions = D1 (MetaData "EventTypeOptions" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "EventTypeOptions" PrefixI True) (S1 (MetaSel (Just "_retentionTime") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int64)))

data EventType Source #

EventType

Instances
Eq EventType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Ord EventType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show EventType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic EventType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep EventType :: Type -> Type #

Hashable EventType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

ToJSON EventType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON EventType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiSchema EventType EventTypeSchema 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiName EventType EventTypeName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartitionStrategy EventType (Maybe PartitionStrategy) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartitionKeyFields EventType (Maybe [PartitionKeyField]) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiOwningApplication EventType (Maybe ApplicationName) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiOptions EventType (Maybe EventTypeOptions) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiEnrichmentStrategies EventType (Maybe [EnrichmentStrategy]) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiDefaultStatistic EventType (Maybe EventTypeStatistics) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiCompatibilityMode EventType (Maybe CompatibilityMode) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiCleanupPolicy EventType (Maybe CleanupPolicy) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiCategory EventType (Maybe EventTypeCategory) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep EventType Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep EventType = D1 (MetaData "EventType" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "EventType" PrefixI True) (((S1 (MetaSel (Just "_name") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 EventTypeName) :*: S1 (MetaSel (Just "_owningApplication") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe ApplicationName))) :*: (S1 (MetaSel (Just "_category") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe EventTypeCategory)) :*: (S1 (MetaSel (Just "_enrichmentStrategies") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe [EnrichmentStrategy])) :*: S1 (MetaSel (Just "_partitionStrategy") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe PartitionStrategy))))) :*: ((S1 (MetaSel (Just "_compatibilityMode") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe CompatibilityMode)) :*: (S1 (MetaSel (Just "_schema") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 EventTypeSchema) :*: S1 (MetaSel (Just "_partitionKeyFields") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe [PartitionKeyField])))) :*: (S1 (MetaSel (Just "_cleanupPolicy") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe CleanupPolicy)) :*: (S1 (MetaSel (Just "_defaultStatistic") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe EventTypeStatistics)) :*: S1 (MetaSel (Just "_options") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe EventTypeOptions)))))))

data EventMetadata Source #

Type of published event metadata values.

Instances
Eq EventMetadata Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show EventMetadata Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic EventMetadata Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep EventMetadata :: Type -> Type #

ToJSON EventMetadata Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON EventMetadata Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiOccurredAt EventMetadata Timestamp 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiEid EventMetadata EventId 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartition EventMetadata (Maybe PartitionName) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartitionCompactionKey EventMetadata (Maybe PartitionCompactionKey) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiParentEids EventMetadata (Maybe [EventId]) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiMetadata (DataChangeEvent a) EventMetadata 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiMetadata (BusinessEvent a) EventMetadata 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep EventMetadata Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

data EventMetadataEnriched Source #

Type of event metadata enriched by Nakadi

Instances
Eq EventMetadataEnriched Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show EventMetadataEnriched Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic EventMetadataEnriched Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep EventMetadataEnriched :: Type -> Type #

ToJSON EventMetadataEnriched Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON EventMetadataEnriched Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiOccurredAt EventMetadataEnriched Timestamp 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiEid EventMetadataEnriched EventId 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiVersion EventMetadataEnriched SchemaVersion 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiReceivedAt EventMetadataEnriched Timestamp 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiEventType EventMetadataEnriched EventTypeName 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiFlowId EventMetadataEnriched (Maybe FlowId) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartition EventMetadataEnriched (Maybe PartitionName) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiPartitionCompactionKey EventMetadataEnriched (Maybe PartitionCompactionKey) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiParentEids EventMetadataEnriched (Maybe [EventId]) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiMetadata (DataChangeEventEnriched a) EventMetadataEnriched 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiMetadata (BusinessEventEnriched a) EventMetadataEnriched 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep EventMetadataEnriched Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

data SubscriptionEventStreamBatch a Source #

SubscriptionEventStreamBatch

Constructors

SubscriptionEventStreamBatch 

Fields

Instances
Show a => Show (SubscriptionEventStreamBatch a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic (SubscriptionEventStreamBatch a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep (SubscriptionEventStreamBatch a) :: Type -> Type #

ToJSON a => ToJSON (SubscriptionEventStreamBatch a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON a => FromJSON (SubscriptionEventStreamBatch a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiSubscriptionCursor (SubscriptionEventStreamBatch a) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiCursor (SubscriptionEventStreamBatch a) SubscriptionCursor 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiEvents (SubscriptionEventStreamBatch a) (Maybe (Vector a)) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiQueue (Worker a) (TBQueue (SubscriptionEventStreamBatch a)) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep (SubscriptionEventStreamBatch a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep (SubscriptionEventStreamBatch a) = D1 (MetaData "SubscriptionEventStreamBatch" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "SubscriptionEventStreamBatch" PrefixI True) (S1 (MetaSel (Just "_cursor") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 SubscriptionCursor) :*: S1 (MetaSel (Just "_events") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Vector a)))))

data DataOp Source #

Type for "data_op" as contained in the DataChangeEvent.

data DataChangeEvent a Source #

DataChangeEvent

Instances
Eq a => Eq (DataChangeEvent a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show a => Show (DataChangeEvent a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic (DataChangeEvent a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

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

ToJSON a => ToJSON (DataChangeEvent a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON a => FromJSON (DataChangeEvent a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiPayload (DataChangeEvent a) a 
Instance details

Defined in Network.Nakadi.Internal.Lenses

Methods

payload :: Lens' (DataChangeEvent a) a

HasNakadiMetadata (DataChangeEvent a) EventMetadata 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiDataType (DataChangeEvent a) Text 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiDataOp (DataChangeEvent a) DataOp 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep (DataChangeEvent a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep (DataChangeEvent a) = D1 (MetaData "DataChangeEvent" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "DataChangeEvent" PrefixI True) ((S1 (MetaSel (Just "_payload") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Just "_metadata") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 EventMetadata)) :*: (S1 (MetaSel (Just "_dataType") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_dataOp") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 DataOp))))

data DataChangeEventEnriched a Source #

A DataChangeEvent enriched by Nakadi

Instances
Eq a => Eq (DataChangeEventEnriched a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show a => Show (DataChangeEventEnriched a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic (DataChangeEventEnriched a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep (DataChangeEventEnriched a) :: Type -> Type #

ToJSON a => ToJSON (DataChangeEventEnriched a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON a => FromJSON (DataChangeEventEnriched a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiPayload (DataChangeEventEnriched a) a 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiMetadata (DataChangeEventEnriched a) EventMetadataEnriched 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiDataType (DataChangeEventEnriched a) Text 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiDataOp (DataChangeEventEnriched a) DataOp 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep (DataChangeEventEnriched a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep (DataChangeEventEnriched a) = D1 (MetaData "DataChangeEventEnriched" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "DataChangeEventEnriched" PrefixI True) ((S1 (MetaSel (Just "_payload") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Just "_metadata") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 EventMetadataEnriched)) :*: (S1 (MetaSel (Just "_dataType") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_dataOp") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 DataOp))))

data BusinessEvent a Source #

Type modelling a "Business Event". Their JSON encodings are special since the payload object is directly enriched with a metadata field. "Data Change Events" on the other side are JSON-encoded such that the complete event payload is contained in a seperate object field.

On the Haskell API side we split payload from meta data, which requires us to write custom ToJSON and FromJSON implementations.

Constructors

BusinessEvent 

Fields

Instances
Eq a => Eq (BusinessEvent a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show a => Show (BusinessEvent a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic (BusinessEvent a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep (BusinessEvent a) :: Type -> Type #

ToJSON a => ToJSON (BusinessEvent a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON a => FromJSON (BusinessEvent a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiPayload (BusinessEvent a) a 
Instance details

Defined in Network.Nakadi.Internal.Lenses

Methods

payload :: Lens' (BusinessEvent a) a

HasNakadiMetadata (BusinessEvent a) EventMetadata 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep (BusinessEvent a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep (BusinessEvent a) = D1 (MetaData "BusinessEvent" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "BusinessEvent" PrefixI True) (S1 (MetaSel (Just "_payload") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Just "_metadata") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 EventMetadata)))

data BusinessEventEnriched a Source #

Type modelling a Nakadi-enriched "Business Event". JSON encoding is basically the same as for the non-enriched Business Events.

Instances
Eq a => Eq (BusinessEventEnriched a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Show a => Show (BusinessEventEnriched a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Generic (BusinessEventEnriched a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

Associated Types

type Rep (BusinessEventEnriched a) :: Type -> Type #

ToJSON a => ToJSON (BusinessEventEnriched a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

FromJSON a => FromJSON (BusinessEventEnriched a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

HasNakadiPayload (BusinessEventEnriched a) a 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiMetadata (BusinessEventEnriched a) EventMetadataEnriched 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type Rep (BusinessEventEnriched a) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Service

type Rep (BusinessEventEnriched a) = D1 (MetaData "BusinessEventEnriched" "Network.Nakadi.Internal.Types.Service" "nakadi-client-0.7.0.0-KOzkX3CyJmv3p5G5yolcIB" False) (C1 (MetaCons "BusinessEventEnriched" PrefixI True) (S1 (MetaSel (Just "_payload") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Just "_metadata") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 EventMetadataEnriched)))

makeFieldRenamer :: [(String, String)] -> String -> String Source #

Construct a field renamer function from a field renamer map.

parseUUID :: String -> (UUID -> a) -> Value -> Parser a Source #

parseInteger :: (Integral i, Bounded i) => String -> (i -> a) -> Value -> Parser a Source #

parseString :: String -> (Text -> a) -> Value -> Parser a Source #

class (Monad b, Monad m) => MonadNakadiBase b m where Source #

Minimal complete definition

Nothing

Methods

nakadiLiftBase :: b a -> m a Source #

nakadiLiftBase :: (MonadNakadiBase b n, MonadTrans t, m ~ t n) => b a -> m a Source #

Instances
MonadNakadiBase IO IO Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

nakadiLiftBase :: IO a -> IO a Source #

MonadNakadiBase b m => MonadNakadiBase b (ResourceT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

nakadiLiftBase :: b a -> ResourceT m a Source #

MonadNakadiBase b m => MonadNakadiBase b (NoLoggingT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

nakadiLiftBase :: b a -> NoLoggingT m a Source #

MonadNakadiBase b m => MonadNakadiBase b (LoggingT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

nakadiLiftBase :: b a -> LoggingT m a Source #

MonadNakadiBase b m => MonadNakadiBase b (StateT s m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

nakadiLiftBase :: b a -> StateT s m a Source #

MonadNakadiBase b m => MonadNakadiBase b (StateT s m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

nakadiLiftBase :: b a -> StateT s m a Source #

(MonadNakadiBase b m, Monoid w) => MonadNakadiBase b (WriterT w m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

nakadiLiftBase :: b a -> WriterT w m a Source #

(MonadNakadiBase b m, Monoid w) => MonadNakadiBase b (WriterT w m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

nakadiLiftBase :: b a -> WriterT w m a Source #

MonadNakadiBase b m => MonadNakadiBase b (NakadiT b m) Source #

MonadNakadiBase

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

nakadiLiftBase :: b a -> NakadiT b m a Source #

MonadNakadiBase b m => MonadNakadiBase b (ReaderT r m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

nakadiLiftBase :: b a -> ReaderT r m a Source #

Monad m => MonadNakadiBase (LoggingT (ReaderT r m)) (LoggingT (ReaderT r m)) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

nakadiLiftBase :: LoggingT (ReaderT r m) a -> LoggingT (ReaderT r m) a Source #

Monad m => MonadNakadiBase (NakadiBaseT m) (NakadiBaseT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Monad m => MonadNakadiBase (ReaderT r m) (ReaderT r m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

nakadiLiftBase :: ReaderT r m a -> ReaderT r m a Source #

newtype NakadiBaseT m a Source #

Constructors

NakadiBaseT 

Fields

Instances
MonadTrans NakadiBaseT Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

lift :: Monad m => m a -> NakadiBaseT m a #

MonadReader r m => MonadReader r (NakadiBaseT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

ask :: NakadiBaseT m r #

local :: (r -> r) -> NakadiBaseT m a -> NakadiBaseT m a #

reader :: (r -> a) -> NakadiBaseT m a #

MonadState s m => MonadState s (NakadiBaseT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

get :: NakadiBaseT m s #

put :: s -> NakadiBaseT m () #

state :: (s -> (a, s)) -> NakadiBaseT m a #

MonadWriter w m => MonadWriter w (NakadiBaseT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

writer :: (a, w) -> NakadiBaseT m a #

tell :: w -> NakadiBaseT m () #

listen :: NakadiBaseT m a -> NakadiBaseT m (a, w) #

pass :: NakadiBaseT m (a, w -> w) -> NakadiBaseT m a #

MonadBase b m => MonadBase b (NakadiBaseT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

liftBase :: b α -> NakadiBaseT m α #

Monad m => Monad (NakadiBaseT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

(>>=) :: NakadiBaseT m a -> (a -> NakadiBaseT m b) -> NakadiBaseT m b #

(>>) :: NakadiBaseT m a -> NakadiBaseT m b -> NakadiBaseT m b #

return :: a -> NakadiBaseT m a #

fail :: String -> NakadiBaseT m a #

Functor m => Functor (NakadiBaseT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

fmap :: (a -> b) -> NakadiBaseT m a -> NakadiBaseT m b #

(<$) :: a -> NakadiBaseT m b -> NakadiBaseT m a #

Applicative m => Applicative (NakadiBaseT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

pure :: a -> NakadiBaseT m a #

(<*>) :: NakadiBaseT m (a -> b) -> NakadiBaseT m a -> NakadiBaseT m b #

liftA2 :: (a -> b -> c) -> NakadiBaseT m a -> NakadiBaseT m b -> NakadiBaseT m c #

(*>) :: NakadiBaseT m a -> NakadiBaseT m b -> NakadiBaseT m b #

(<*) :: NakadiBaseT m a -> NakadiBaseT m b -> NakadiBaseT m a #

MonadIO m => MonadIO (NakadiBaseT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

liftIO :: IO a -> NakadiBaseT m a #

MonadThrow m => MonadThrow (NakadiBaseT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

throwM :: Exception e => e -> NakadiBaseT m a #

MonadCatch m => MonadCatch (NakadiBaseT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

catch :: Exception e => NakadiBaseT m a -> (e -> NakadiBaseT m a) -> NakadiBaseT m a #

MonadMask m => MonadMask (NakadiBaseT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

mask :: ((forall a. NakadiBaseT m a -> NakadiBaseT m a) -> NakadiBaseT m b) -> NakadiBaseT m b #

uninterruptibleMask :: ((forall a. NakadiBaseT m a -> NakadiBaseT m a) -> NakadiBaseT m b) -> NakadiBaseT m b #

generalBracket :: NakadiBaseT m a -> (a -> ExitCase b -> NakadiBaseT m c) -> (a -> NakadiBaseT m b) -> NakadiBaseT m (b, c) #

MonadLogger m => MonadLogger (NakadiBaseT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> NakadiBaseT m () #

Monad m => MonadNakadiBase (NakadiBaseT m) (NakadiBaseT m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types.Base

data CommitStrategy Source #

This type encodes the supported strategies for subscription cursor committing.

Constructors

CommitSync

This strategy synchronously commits every cursor.

CommitAsync CommitBufferingStrategy

This strategy sends cursors to be committed to a dedicated thread responsible for committing them. Cursors are commited one by one, without special buffering logic.

Instances
HasNakadiCommitStrategy (Config m) CommitStrategy 
Instance details

Defined in Network.Nakadi.Internal.Lenses

data CommitBufferingStrategy Source #

This type encodes the supported buffering strategies for asynchronous subscription cursor committing.

Constructors

CommitNoBuffer

No buffering at all.

CommitTimeBuffer Int32

Buffer for the specified duration, given in milliseconds.

CommitSmartBuffer

Buffer for a fixed duration, but committing cursors immediately if the number of events processed since the last commit crosses a threshold derived from maxUncommittedEvents.

data Worker a Source #

Data type denoting an asynchronous worker.

Constructors

Worker 
Instances
HasNakadiQueue (Worker a) (TBQueue (SubscriptionEventStreamBatch a)) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiAsync (Worker a) (Async ()) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

Methods

async :: Lens' (Worker a) (Async ())

HasNakadiWorkers (WorkerRegistry a) (NonEmpty (Worker a)) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

data WorkerRegistry a Source #

Data type containing a non-empty list of worker references.

Instances
HasNakadiPartitionIndexMap (WorkerRegistry a) PartitionIndexMap 
Instance details

Defined in Network.Nakadi.Internal.Lenses

HasNakadiWorkers (WorkerRegistry a) (NonEmpty (Worker a)) 
Instance details

Defined in Network.Nakadi.Internal.Lenses

type PartitionIndexMap = HashMap (PartitionName, EventTypeName) Int Source #

Map used for mapping subscription batch cursors to worked indices.

class HasNakadiConfig b r | r -> b where Source #

Methods

nakadiConfig :: r -> Config b Source #

class (MonadNakadiBase b m, MonadThrow b, MonadMask b, MonadThrow m, MonadCatch m) => MonadNakadi b m | m -> b where Source #

The MonadNakadi typeclass is implemented by monads in which Nakadi can be called. The first parameter (b) denotes the `base monad`. This is the monad in which the core actions are run. This includes executing (non-streaming) HTTP requests and running user-provided callbacks. The typeclass provides methods for * retrieving the Nakadi configuration * locally changing the Nakadi configuration * extracting specific Nakadi configuration values * lifting actions from the The MonadNakadi typeclass is modelled closely after MonadReader.

Minimal complete definition

Nothing

Methods

nakadiAsk :: m (Config b) Source #

nakadiAsk :: (MonadNakadi b n, MonadTrans t, m ~ t n) => m (Config b) Source #

Instances
MonadNakadi IO IO Source # 
Instance details

Defined in Network.Nakadi.Internal.Types

MonadNakadi b m => MonadNakadi b (ResourceT m) Source #

ResourceT.

Instance details

Defined in Network.Nakadi.Internal.Types

MonadNakadi b m => MonadNakadi b (NoLoggingT m) Source #

NoLoggingT

Instance details

Defined in Network.Nakadi.Internal.Types

MonadNakadi b m => MonadNakadi b (LoggingT m) Source #

LoggingT

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

nakadiAsk :: LoggingT m (Config b) Source #

MonadNakadi b m => MonadNakadi b (StateT s m) Source #

StateT (lazy)

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

nakadiAsk :: StateT s m (Config b) Source #

MonadNakadi b m => MonadNakadi b (StateT s m) Source #

StateT (strict)

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

nakadiAsk :: StateT s m (Config b) Source #

(MonadNakadi b m, Monoid w) => MonadNakadi b (WriterT w m) Source #

WriterT (strict)

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

nakadiAsk :: WriterT w m (Config b) Source #

(MonadNakadi b m, Monoid w) => MonadNakadi b (WriterT w m) Source #

WriterT (lazy)

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

nakadiAsk :: WriterT w m (Config b) Source #

(MonadCatch m, MonadMask b, MonadNakadiBase b (NakadiT b m)) => MonadNakadi b (NakadiT b m) Source #

NakadiT

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

nakadiAsk :: NakadiT b m (Config b) Source #

(MonadMask b, MonadCatch m, MonadNakadiBase b (ReaderT r m), HasNakadiConfig b r) => MonadNakadi b (ReaderT r m) Source #

ReaderT

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

nakadiAsk :: ReaderT r m (Config b) Source #

newtype NakadiT b m a Source #

The NakadiT type is just a specialized ReaderT monad.

Constructors

NakadiT 

Fields

Instances
(Monad b, MonadReader r m) => MonadReader r (NakadiT b m) Source #

MonadReader

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

ask :: NakadiT b m r #

local :: (r -> r) -> NakadiT b m a -> NakadiT b m a #

reader :: (r -> a) -> NakadiT b m a #

(Monad b, MonadState s m) => MonadState s (NakadiT b m) Source #

MonadState

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

get :: NakadiT b m s #

put :: s -> NakadiT b m () #

state :: (s -> (a, s)) -> NakadiT b m a #

(Monad m, MonadBase b' m) => MonadBase b' (NakadiT b m) Source #

MonadBase

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

liftBase :: b' α -> NakadiT b m α #

MonadBaseControl b' m => MonadBaseControl b' (NakadiT b m) Source #

MonadBaseControl

Instance details

Defined in Network.Nakadi.Internal.Types

Associated Types

type StM (NakadiT b m) a :: Type #

Methods

liftBaseWith :: (RunInBase (NakadiT b m) b' -> b' a) -> NakadiT b m a #

restoreM :: StM (NakadiT b m) a -> NakadiT b m a #

MonadNakadiBase b m => MonadNakadiBase b (NakadiT b m) Source #

MonadNakadiBase

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

nakadiLiftBase :: b a -> NakadiT b m a Source #

(MonadCatch m, MonadMask b, MonadNakadiBase b (NakadiT b m)) => MonadNakadi b (NakadiT b m) Source #

NakadiT

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

nakadiAsk :: NakadiT b m (Config b) Source #

MonadTrans (NakadiT b) Source #

MonadTrans

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

lift :: Monad m => m a -> NakadiT b m a #

MonadTransControl (NakadiT b) Source #

MonadTransControl

Instance details

Defined in Network.Nakadi.Internal.Types

Associated Types

type StT (NakadiT b) a :: Type #

Methods

liftWith :: Monad m => (Run (NakadiT b) -> m a) -> NakadiT b m a #

restoreT :: Monad m => m (StT (NakadiT b) a) -> NakadiT b m a #

Monad m => Monad (NakadiT b m) Source #

Monad

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

(>>=) :: NakadiT b m a -> (a -> NakadiT b m b0) -> NakadiT b m b0 #

(>>) :: NakadiT b m a -> NakadiT b m b0 -> NakadiT b m b0 #

return :: a -> NakadiT b m a #

fail :: String -> NakadiT b m a #

Functor m => Functor (NakadiT b m) Source #

Functor for NakadiT.

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

fmap :: (a -> b0) -> NakadiT b m a -> NakadiT b m b0 #

(<$) :: a -> NakadiT b m b0 -> NakadiT b m a #

Applicative m => Applicative (NakadiT b m) Source #

Applicative for NakadiT.

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

pure :: a -> NakadiT b m a #

(<*>) :: NakadiT b m (a -> b0) -> NakadiT b m a -> NakadiT b m b0 #

liftA2 :: (a -> b0 -> c) -> NakadiT b m a -> NakadiT b m b0 -> NakadiT b m c #

(*>) :: NakadiT b m a -> NakadiT b m b0 -> NakadiT b m b0 #

(<*) :: NakadiT b m a -> NakadiT b m b0 -> NakadiT b m a #

(Monad b, MonadIO m) => MonadIO (NakadiT b m) Source #

MonadIO

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

liftIO :: IO a -> NakadiT b m a #

(Monad b, MonadUnliftIO m) => MonadUnliftIO (NakadiT b m) Source #

MonadUnliftIO

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

askUnliftIO :: NakadiT b m (UnliftIO (NakadiT b m)) #

withRunInIO :: ((forall a. NakadiT b m a -> IO a) -> IO b0) -> NakadiT b m b0 #

(Monad b, MonadResource m) => MonadResource (NakadiT b m) Source # 
Instance details

Defined in Network.Nakadi.Internal.Types

Methods

liftResourceT :: ResourceT IO a -> NakadiT b m a #

(Monad b, MonadThrow m) => MonadThrow (NakadiT b m) Source #

MonadThrow

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

throwM :: Exception e => e -> NakadiT b m a #

(Monad b, MonadCatch m) => MonadCatch (NakadiT b m) Source #

MonadCatch

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

catch :: Exception e => NakadiT b m a -> (e -> NakadiT b m a) -> NakadiT b m a #

(Monad b, MonadMask m) => MonadMask (NakadiT b m) Source #

MonadMask

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

mask :: ((forall a. NakadiT b m a -> NakadiT b m a) -> NakadiT b m b0) -> NakadiT b m b0 #

uninterruptibleMask :: ((forall a. NakadiT b m a -> NakadiT b m a) -> NakadiT b m b0) -> NakadiT b m b0 #

generalBracket :: NakadiT b m a -> (a -> ExitCase b0 -> NakadiT b m c) -> (a -> NakadiT b m b0) -> NakadiT b m (b0, c) #

MonadLogger m => MonadLogger (NakadiT b m) Source #

MonadLogger

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> NakadiT b m () #

(Monad b, MonadLoggerIO m) => MonadLoggerIO (NakadiT b m) Source #

MonadLoggerIO

Instance details

Defined in Network.Nakadi.Internal.Types

Methods

askLoggerIO :: NakadiT b m (Loc -> LogSource -> LogLevel -> LogStr -> IO ()) #

type StT (NakadiT b) a Source # 
Instance details

Defined in Network.Nakadi.Internal.Types

type StT (NakadiT b) a = a
type StM (NakadiT b m) a Source # 
Instance details

Defined in Network.Nakadi.Internal.Types

type StM (NakadiT b m) a = ComposeSt (NakadiT b) m a

runNakadiT :: Config b -> NakadiT b m a -> m a Source #

httpJsonBodyStream :: forall b m r. (MonadNakadi b m, MonadMask m) => Status -> [(Status, ByteString -> m NakadiException)] -> (Request -> Request) -> (Response (ConduitM () ByteString m ()) -> m r) -> m r Source #

httpBuildRequest Source #

Arguments

:: MonadNakadi b m 
=> (Request -> Request)

Pure request modifier

-> m Request

Resulting request to execute

conduitDecode Source #

Arguments

:: (FromJSON a, MonadNakadi b m) 
=> ConduitM ByteString a m ()

Conduit deserializing bytestrings into custom values

If no deserializationFailureCallback is set in the provided configuration (which is the default), a DeserializationFailureCallback exception will be thrown. Otherwise, simply run the callback.