Copyright | (C) 2014 Yorick Laupa |
---|---|
License | (see the file LICENSE) |
Maintainer | Yorick Laupa <yo.eight@gmail.com> |
Stability | provisional |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
- data Event
- data EventData
- createEvent :: Text -> EventData -> Event
- withJson :: Value -> EventData
- withJsonAndMetadata :: Value -> Value -> EventData
- data Connection
- data Credentials
- data Settings = Settings {}
- data Retry
- atMost :: Int -> Retry
- keepRetrying :: Retry
- credentials :: ByteString -> ByteString -> Credentials
- defaultSettings :: Settings
- connect :: Settings -> String -> Int -> IO Connection
- shutdown :: Connection -> IO ()
- readEvent :: Connection -> Text -> Int32 -> Bool -> IO (Async ReadResult)
- readAllEventsBackward :: Connection -> Position -> Int32 -> Bool -> IO (Async AllEventsSlice)
- readAllEventsForward :: Connection -> Position -> Int32 -> Bool -> IO (Async AllEventsSlice)
- readStreamEventsBackward :: Connection -> Text -> Int32 -> Int32 -> Bool -> IO (Async StreamEventsSlice)
- readStreamEventsForward :: Connection -> Text -> Int32 -> Int32 -> Bool -> IO (Async StreamEventsSlice)
- deleteStream :: Connection -> Text -> ExpectedVersion -> Maybe Bool -> IO (Async DeleteResult)
- sendEvent :: Connection -> Text -> ExpectedVersion -> Event -> IO (Async WriteResult)
- sendEvents :: Connection -> Text -> ExpectedVersion -> [Event] -> IO (Async WriteResult)
- data Transaction
- transactionStart :: Connection -> Text -> ExpectedVersion -> IO (Async Transaction)
- transactionCommit :: Transaction -> IO (Async WriteResult)
- transactionRollback :: Transaction -> IO ()
- transactionSendEvents :: Transaction -> [Event] -> IO (Async ())
- data DropReason
- data Subscription
- subscribe :: Connection -> Text -> Bool -> IO (Async Subscription)
- subscribeToAll :: Connection -> Bool -> IO (Async Subscription)
- subAwait :: Subscription -> IO (Either DropReason ResolvedEvent)
- subId :: Subscription -> UUID
- subStream :: Subscription -> Text
- subResolveLinkTos :: Subscription -> Bool
- subLastCommitPos :: Subscription -> Int64
- subLastEventNumber :: Subscription -> Maybe Int32
- subUnsubscribe :: Subscription -> IO ()
- data Catchup
- data CatchupError
- subscribeFrom :: Connection -> Text -> Bool -> Maybe Int32 -> Maybe Int32 -> IO Catchup
- subscribeToAllFrom :: Connection -> Bool -> Maybe Position -> Maybe Int32 -> IO Catchup
- catchupAwait :: Catchup -> IO (Either CatchupError ResolvedEvent)
- catchupStream :: Catchup -> Text
- catchupUnsubscribe :: Catchup -> IO ()
- waitTillCatchup :: Catchup -> IO ()
- hasCaughtUp :: Catchup -> IO Bool
- data AllEventsSlice = AllEventsSlice {}
- newtype DeleteResult = DeleteResult {}
- data WriteResult = WriteResult {}
- data ReadResult = ReadResult {}
- data RecordedEvent = RecordedEvent {}
- data StreamEventsSlice = StreamEventsSlice {}
- data Position = Position {
- positionCommit :: !Int64
- positionPrepare :: !Int64
- data ReadDirection
- data ReadAllResult
- data ReadEventResult
- data ResolvedEvent = ResolvedEvent {}
- data ReadStreamResult
- data OperationException
- eventResolved :: ResolvedEvent -> Bool
- resolvedEventOriginal :: ResolvedEvent -> Maybe RecordedEvent
- resolvedEventOriginalStreamId :: ResolvedEvent -> Maybe Text
- positionStart :: Position
- positionEnd :: Position
- data ExpectedVersion
- anyStream :: ExpectedVersion
- noStream :: ExpectedVersion
- emptyStream :: ExpectedVersion
- exactStream :: Int32 -> ExpectedVersion
- module Control.Concurrent.Async
Event
withJsonAndMetadata :: Value -> Value -> EventData Source
Create a event with metadata using JSON format
Connection
data Connection Source
Represents a connection to a single EventStore node.
Global Connection
settings
Settings | |
|
Indicates how many times we should try to reconnect to the server. A value less than or equal to 0 means no retry.
Indicates we should try to reconnect to the server until the end of the Universe.
:: ByteString | Login |
-> ByteString | Password |
-> Credentials |
defaultSettings :: Settings Source
Default global settings.
:: Settings | |
-> String | HostName |
-> Int | Port |
-> IO Connection |
Creates a new Connection
to a single node. It maintains a full duplex
connection to the EventStore. An EventStore Connection
operates quite
differently than say a SQL connection. Normally when you use a SQL
connection you want to keep the connection open for a much longer of time
than when you use a SQL connection.
Another difference is that with the EventStore Connection
all operation
are handled in a full async manner (even if you call the synchronous
behaviors). Many threads can use an EvenStore Connection
at the same time
or a single thread can make many asynchronous requests. To get the most
performance out of the connection it is generally recommend to use it in
this way.
shutdown :: Connection -> IO () Source
Asynchronously closes the Connection
.
Read Operations
:: Connection | |
-> Text | Stream name |
-> Int32 | Event number |
-> Bool | Resolve Link Tos |
-> IO (Async ReadResult) |
Reads a single event from given stream.
:: Connection | |
-> Position | |
-> Int32 | Batch size |
-> Bool | Resolve Link Tos |
-> IO (Async AllEventsSlice) |
Reads events from the $all stream backward
:: Connection | |
-> Position | |
-> Int32 | Batch size |
-> Bool | Resolve Link Tos |
-> IO (Async AllEventsSlice) |
Reads events from the $all stream forward.
readStreamEventsBackward Source
:: Connection | |
-> Text | Stream name |
-> Int32 | From event number |
-> Int32 | Batch size |
-> Bool | Resolve Link Tos |
-> IO (Async StreamEventsSlice) |
Reads events from a given stream backward.
readStreamEventsForward Source
:: Connection | |
-> Text | Stream name |
-> Int32 | From event number |
-> Int32 | Batch size |
-> Bool | Resolve Link Tos |
-> IO (Async StreamEventsSlice) |
Reads events from a given stream forward.
Write Operations
:: Connection | |
-> Text | Stream name |
-> ExpectedVersion | |
-> Maybe Bool | Hard delete |
-> IO (Async DeleteResult) |
Deletes given stream.
:: Connection | |
-> Text | Stream name |
-> ExpectedVersion | |
-> Event | |
-> IO (Async WriteResult) |
Sends a single Event
to given stream.
:: Connection | |
-> Text | Stream name |
-> ExpectedVersion | |
-> [Event] | |
-> IO (Async WriteResult) |
Sends a list of Event
to given stream.
Transaction
data Transaction Source
Represents a multi-request transaction with the EventStore.
:: Connection | |
-> Text | Stream name |
-> ExpectedVersion | |
-> IO (Async Transaction) |
Starts a transaction on given stream.
transactionCommit :: Transaction -> IO (Async WriteResult) Source
Asynchronously commits this transaction.
transactionRollback :: Transaction -> IO () Source
Rollback this transaction.
transactionSendEvents :: Transaction -> [Event] -> IO (Async ()) Source
Asynchronously writes to a transaction in the EventStore.
Volatile Subscription
data DropReason Source
Represents the reason subscription drop happened.
data Subscription Source
Represents a subscription to a single stream or $all stream in the EventStore.
:: Connection | |
-> Text | Stream name |
-> Bool | Resolve Link Tos |
-> IO (Async Subscription) |
Subcribes to given stream.
:: Connection | |
-> Bool | Resolve Link Tos |
-> IO (Async Subscription) |
Subcribes to $all stream.
subAwait :: Subscription -> IO (Either DropReason ResolvedEvent) Source
Awaits for the next ResolvedEvent
.
subId :: Subscription -> UUID Source
ID of the subscription.
subStream :: Subscription -> Text Source
The name of the stream to which the subscription is subscribed.
subResolveLinkTos :: Subscription -> Bool Source
Determines whether or not any link events encontered in the stream will be resolved.
subLastCommitPos :: Subscription -> Int64 Source
The last commit position seen on the subscription (if this a subscription to $all stream).
subLastEventNumber :: Subscription -> Maybe Int32 Source
The last event number seen on the subscription (if this is a subscription to a single stream).
subUnsubscribe :: Subscription -> IO () Source
Asynchronously unsubscribe from the the stream.
Catch-up Subscription
data CatchupError Source
Errors that could arise during a catch-up subscription. Text
value
represents the stream name.
:: Connection | |
-> Text | Stream name |
-> Bool | Resolve Link Tos |
-> Maybe Int32 | Last checkpoint |
-> Maybe Int32 | Batch size |
-> IO Catchup |
Subscribes to given stream. If last checkpoint is defined, this will
readStreamEventsForward
from that event number, otherwise from the
beginning. Once last stream event reached up, a subscription request will
be sent using subscribe
.
:: Connection | |
-> Bool | Resolve Link Tos |
-> Maybe Position | Last checkpoint |
-> Maybe Int32 | Batch size |
-> IO Catchup |
Same as subscribeFrom
but applied to $all stream.
catchupAwait :: Catchup -> IO (Either CatchupError ResolvedEvent) Source
Awaits for the next ResolvedEvent
.
catchupStream :: Catchup -> Text Source
The name of the stream to which the subscription is subscribed.
catchupUnsubscribe :: Catchup -> IO () Source
Asynchronously unsubscribes from the stream.
waitTillCatchup :: Catchup -> IO () Source
Waits until Catchup
subscription catch-up its stream.
hasCaughtUp :: Catchup -> IO Bool Source
Non blocking version of waitTillCatchup
.
Results
data AllEventsSlice Source
The result of a read operation from the $all stream.
AllEventsSlice | |
|
newtype DeleteResult Source
Returned after deleting a stream. Position
of the write.
data WriteResult Source
Returned after writing to a stream.
WriteResult | |
|
data ReadResult Source
Result of a single event read operation to the EventStore.
ReadResult | |
|
data RecordedEvent Source
Represents a previously written event.
RecordedEvent | |
|
data StreamEventsSlice Source
Represents the result of a single read operation to the EventStore.
StreamEventsSlice | |
|
A structure referring to a potential logical record position in the EventStore transaction file.
Position | |
|
data ReadDirection Source
Represents the direction of read operation (both from $all an usual streams).
data ReadAllResult Source
Enumeration detailing the possible outcomes of reading a slice of $all stream.
data ReadEventResult Source
Enumeration representing the status of a single event read operation.
data ResolvedEvent Source
A structure representing a single event or an resolved link event.
ResolvedEvent | |
|
data ReadStreamResult Source
Enumeration detailing the possible outcomes of reading a slice of a stream
data OperationException Source
WrongExpectedVersion Text ExpectedVersion | Stream and Expected Version |
StreamDeleted Text | Stream |
InvalidTransaction | |
AccessDenied Text | Stream |
InvalidServerResponse Word8 Word8 | Expected, Found |
ProtobufDecodingError String | |
ServerError (Maybe Text) | Reason |
eventResolved :: ResolvedEvent -> Bool Source
Indicates whether this ResolvedEvent
is a resolved link event.
resolvedEventOriginal :: ResolvedEvent -> Maybe RecordedEvent Source
Returns the event that was read or which triggered the subscription.
If this ResolvedEvent
represents a link event, the link will be the
original event, otherwise it will be the event.
resolvedEventOriginalStreamId :: ResolvedEvent -> Maybe Text Source
The stream name of the original event.
positionStart :: Position Source
Representing the start of the transaction file.
positionEnd :: Position Source
Representing the end of the transaction file.
Misc
data ExpectedVersion Source
Constants used for expected version control.
The use of expected version can be a bit tricky especially when discussing idempotency assurances given by the EventStore.
The EventStore will assure idempotency for all operations using any value
in ExpectedVersion
except for anyStream
. When using anyStream
the EventStore will
do its best to assure idempotency but will not guarantee idempotency.
anyStream :: ExpectedVersion Source
This write should not conflict with anything and should always succeed.
noStream :: ExpectedVersion Source
The stream being written to should not yet exist. If it does exist treat that as a concurrency problem.
emptyStream :: ExpectedVersion Source
The stream should exist and should be empty. If it does not exist or is not empty, treat that as a concurrency problem.
exactStream :: Int32 -> ExpectedVersion Source
States that the last event written to the stream should have a sequence number matching your expected value.
Re-export
module Control.Concurrent.Async