Coder Social home page Coder Social logo

eventstore's Introduction

REPO HAS MOVED!

This client is now officiallly supported by EventStore Ltd. The code is now hosted here: https://github.com/EventStore/EventStoreDB-Client-Haskell

EventStore Haskell TCP client

Talk and exchange ideas in our dedicated Discord Server

That driver supports 100% of EventStore features ! More information about the GetEventStore database can be found there: https://eventstore.com/

Requirements

  • 64bits system
  • GHC >= 8.0.3
  • Cabal >= 1.18
  • EventStore >= 4 (Doesn't support EventStore 2020 Preview yet, previously named version 6).

Note: If you use this client version >= to 1.1, it will only supports EventStore >= 4.0.0.

Install

$ cabal update
$ cabal install eventstore
  • From source
$ git clone https://github.com/YoEight/eventstore.git
$ cd eventstore
$ cabal install

How to test

Tests are available. Those assume a server is running on 127.0.0.1 and 1113 port.

$ cabal test

How to use

{-# LANGUAGE OverloadedStrings #-} -- That library uses `Text` pervasively. This pragma permits to use
                                   -- String literal when a Text is needed.
module Main where

import Control.Concurrent.Async (wait)
import Data.Aeson
-- It requires to have `aeson` package installed. Note that EventStore doesn't constraint you to JSON
-- format but putting common use aside, by doing so you'll be able to use some interesting EventStore
-- features like its Complex Event Processing (CEP) capabality.

import Database.EventStore
-- Note that imports 'NonEmpty' data constructor and 'nonEmpty' function from
-- 'Data.List.NonEmpty'.

main :: IO ()
main = do
    -- A common pattern with an EventStore connection is to create a single instance only and pass it
    -- wherever you need it (it's threadsafe). It's very important to not consider an EventStore connection like
    -- its regular SQL counterpart. An EventStore connection will try its best to reconnect
    -- automatically to the server if the connection dropped. Of course that behavior can be tuned
    -- through some settings.
    conn <- connect defaultSettings (Static "127.0.0.1" 1113)
    let js  = object ["isHaskellTheBest" .= True] -- (.=) comes from Data.Aeson module.
        evt = createEvent "programming" Nothing (withJson js)

    -- Appends an event to a stream named `languages`.
    as <- sendEvent conn (StreamName "languages") anyVersion evt Nothing

    -- EventStore interactions are fundamentally asynchronous. Nothing requires you to wait
    -- for the completion of an operation, but it's good to know if something went wrong.
    _ <- wait as

    -- Again, if you decide to `shutdown` an EventStore connection, it means your application is
    -- about to terminate.
    shutdown conn

    -- Make sure the EventStore connection completes every ongoing operation. For instance, if
    -- at the moment we call `shutdown` and some operations (or subscriptions) were still pending,
    -- the connection aborted all of them.
    waitTillClosed conn

Notes

That library was tested on Linux and OSX.

Contributions and bug reports are welcome!

BSD3 License

-Yorick Laupa

eventstore's People

Contributors

gitter-badger avatar nrolland avatar paullucas avatar puffnfresh avatar yoeight avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

eventstore's Issues

waitTillClosed: thread blocked indefinitely in an STM transaction

Hey, not sure if this is a bug or I'm doing it wrong.

main = do
  es <- connect defaultSettings (Static "localhost" 1113)
  shutdown es
  waitTillClosed es

This will result in *** Exception: thread blocked indefinitely in an STM transaction if the connect fails (for instance if the server is not up).

I kinda feel like this should not fail since the connection is technically shut down.
From what I can see there is also no way of checking (or waiting) until the connection has been successful.

Having Protobuf decoding issues sporadically on EventStore server 3.9.*

This might be caused by a protobuf bug. Interestingly, this behavior doesn't happen with server version prior to 3.9.

Exception: ProtobufDecodingError "Failed reading: empty\nEmpty call stack\n"

When occurring that error might not be fatal for maintaining a connection with the server. However, in some situation (like initiating a connection for the first time), it could result to not being able to connect.

Env: Linux and OSX
GHC: 8.0.1

More investigation is needed.

ps: Tried with a 3rd party Java 8 driver, didn't experience any issue.

eventstore-0.8.0.0 does not compile

Citing from http://hydra.nixos.org/build/25135256/log/raw:

Database/EventStore/Internal/Types.hs:445:56:
    Couldn't match type ‘Int64’ with ‘Int32’
    Expected type: Int64 -> CTime
      Actual type: Int32 -> CTime
    In the second argument of ‘(.)’, namely ‘CTime’
    In the second argument of ‘(.)’, namely ‘realToFrac . CTime’

That code seems to assume it's running on a 64 bit machine?

Example app

Hello,
is there a working example for the library ?
So it could serve as demo purpose.

Thanks for this driver anyway ! 👍

Driver re-sends already processed events in catchup subscriptions

In #61 the last 2 events are resent after killing the store. I thought that was pretty odd and thought it's an off-by-2 problem.

Turns out if you start a catchup-subscription with an event number higher than the max event number of the stream all events are resent after reconnecting to the store.

Given a stream that contains 18 events, called "strim":

sub <- subscribeFrom es "strim" True (Just 14) (Just 500)

Running the subscription with following program:

  forever $ do
    next <- resolvedEventOriginal <$> nextEvent sub
    print $ recordedEventNumber next

Will result in the output:

14
15
16
17

as expected. After eventstore reconnection the output will look like this:

14
15
16
17
16
17

I would expect the output to not change.

Starting the subscription at the current event:

sub <- subscribeFrom es "strim" True (Just 18) (Just 500)

will produce following output:

as expected (no events processed). But will result in

0
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17

after a eventstore reconnection occurs.
Expected behaviour here would be unchanged output.

Implement stopwatch using Clock monotonic coarse.

Current stopwatch implementation is using time package to get elapsed time, which is slow and too precise for our need. Using clock package with MonotonicCoarse clock type should yield some performance gain.

Feedback : Making calls safe or document errors that could occur

Hi I'm using your client in my application, and I'm now dealing with handling Errors...
It could be cool if you provide what kind of exceptions that could raise from the different calls (but this documentation could be not up to date...) or even provide a safe version of your API with something like Either CallErros a

I'm trying to figure out for example what kind of errors you are triggering for readEventsForward by example...

P.S : thank you for the lib otherwise... I can use the eventstore thanks to you...

readEvent fails on Slave nodes

When using readEvent to fetch event 0 from a stream, we receive an error if connecting to a slave node.

*Main Lib Process> connect defaultSettings "10.128.204.191" 1113 >>= \conn -> readEvent conn "batches" 0 False >>= wait

*** Exception: InvalidServerResponse 177 241
*Main Lib Process> connect defaultSettings "10.128.236.46" 1113 >>= \conn -> readEvent conn "batches" 0 False >>= wait

ReadSuccess ReadEvent {readEventStream = "batches", readEventNumber = 0, readEventResolved = ResolvedEvent {resolvedEventRecord = Just (RecordedEvent {recordedEventStreamId = "batches", recordedEventId = 2ad56c57-b601-1143-8c50-ce46d51880df, recordedEventNumber = 0, recordedEventType = "batch_quantity_changed", recordedEventData = "{\n  \"batch_id\": \"689434f3-c772-49e9-9229-5ca891172f02\",\n  \"product_sku\": \"CHARTC024GRY-UK\",\n  \"unallocated_quantity\": 1\n}", recordedEventMetadata = Just "", recordedEventIsJson = True, recordedEventCreated = Just 2015-06-17 20:08:08.12 UTC}), resolvedEventLink = Nothing, resolvedEventPosition = Nothing}}
*Main Lib Process> connect defaultSettings "10.128.212.175" 1113 >>= \conn -> readEvent conn "batches" 0 False >>= wait
*** Exception: InvalidServerResponse 177 241

thread blocked indefinitely in an STM transaction during reconnection

Using this program:

{-# LANGUAGE OverloadedStrings #-}

module Test4 where

import Database.EventStore
import Control.Monad (forever)

main :: IO ()
main = do
  es <- connect defaultSettings { s_retry = keepRetrying } (Static "localhost" 1113)
  sub <- subscribeFrom es "strim" True (Just 15) (Just 500)

  forever $ do
    next <- resolvedEventOriginal <$> nextEvent sub
    print $ recordedEventNumber next

The driver will recover from killing the eventstore once. On the second kill, the exception is thrown.

15
16
17
16 -- after the first kill
17
*** Exception: thread blocked indefinitely in an STM transaction -- after the second kill

It's also weird that the driver sends the last 2 events. This is described in more detail in an upcoming issue.

Expected behaviour: The driver should just continue to reconnect in the background and no exception should be thrown.

eventstore-0.12.0.0 (LTS-6.x) does not compile on 32 bit Linux

Citing from https://build.opensuse.org/package/live_build_log/devel:languages:haskell:lts:6/ghc-eventstore/openSUSE_Tumbleweed/i586:

[  161s] Database/EventStore/Internal/Types.hs:343:56:
[  161s]     Couldn't match type ‘Int64’ with ‘Int32’
[  161s]     Expected type: Int64 -> CTime
[  161s]       Actual type: Int32 -> CTime
[  161s]     In the second argument of ‘(.)’, namely ‘CTime’
[  161s]     In the second argument of ‘(.)’, namely ‘realToFrac . CTime’

fails to buid with aeson-2.0

eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:788:11: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the first argument of ‘(.=)’, namely ‘p_readRoles’
eventstore                >       In the expression: p_readRoles .= streamACLReadRoles
eventstore                >       In the first argument of ‘cleanPairs’, namely
eventstore                >         ‘[p_readRoles .= streamACLReadRoles,
eventstore                >           p_writeRoles .= streamACLWriteRoles,
eventstore                >           p_deleteRoles .= streamACLDeleteRoles,
eventstore                >           p_metaReadRoles .= streamACLMetaReadRoles, ....]’
eventstore                >     |
eventstore                > 788 |         [ p_readRoles      .= streamACLReadRoles
eventstore                >     |           ^^^^^^^^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:789:11: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the first argument of ‘(.=)’, namely ‘p_writeRoles’
eventstore                >       In the expression: p_writeRoles .= streamACLWriteRoles
eventstore                >       In the first argument of ‘cleanPairs’, namely
eventstore                >         ‘[p_readRoles .= streamACLReadRoles,
eventstore                >           p_writeRoles .= streamACLWriteRoles,
eventstore                >           p_deleteRoles .= streamACLDeleteRoles,
eventstore                >           p_metaReadRoles .= streamACLMetaReadRoles, ....]’
eventstore                >     |
eventstore                > 789 |         , p_writeRoles     .= streamACLWriteRoles
eventstore                >     |           ^^^^^^^^^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:790:11: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the first argument of ‘(.=)’, namely ‘p_deleteRoles’
eventstore                >       In the expression: p_deleteRoles .= streamACLDeleteRoles
eventstore                >       In the first argument of ‘cleanPairs’, namely
eventstore                >         ‘[p_readRoles .= streamACLReadRoles,
eventstore                >           p_writeRoles .= streamACLWriteRoles,
eventstore                >           p_deleteRoles .= streamACLDeleteRoles,
eventstore                >           p_metaReadRoles .= streamACLMetaReadRoles, ....]’
eventstore                >     |
eventstore                > 790 |         , p_deleteRoles    .= streamACLDeleteRoles
eventstore                >     |           ^^^^^^^^^^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:791:11: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the first argument of ‘(.=)’, namely ‘p_metaReadRoles’
eventstore                >       In the expression: p_metaReadRoles .= streamACLMetaReadRoles
eventstore                >       In the first argument of ‘cleanPairs’, namely
eventstore                >         ‘[p_readRoles .= streamACLReadRoles,
eventstore                >           p_writeRoles .= streamACLWriteRoles,
eventstore                >           p_deleteRoles .= streamACLDeleteRoles,
eventstore                >           p_metaReadRoles .= streamACLMetaReadRoles, ....]’
eventstore                >     |
eventstore                > 791 |         , p_metaReadRoles  .= streamACLMetaReadRoles
eventstore                >     |           ^^^^^^^^^^^^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:792:11: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the first argument of ‘(.=)’, namely ‘p_metaWriteRoles’
eventstore                >       In the expression: p_metaWriteRoles .= streamACLMetaWriteRoles
eventstore                >       In the first argument of ‘cleanPairs’, namely
eventstore                >         ‘[p_readRoles .= streamACLReadRoles,
eventstore                >           p_writeRoles .= streamACLWriteRoles,
eventstore                >           p_deleteRoles .= streamACLDeleteRoles,
eventstore                >           p_metaReadRoles .= streamACLMetaReadRoles, ....]’
eventstore                >     |
eventstore                > 792 |         , p_metaWriteRoles .= streamACLMetaWriteRoles
eventstore                >     |           ^^^^^^^^^^^^^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:801:11: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the first argument of ‘(.=)’, namely ‘p_maxAge’
eventstore                >       In the expression: p_maxAge .= fmap toInt64 streamMetadataMaxAge
eventstore                >       In the first argument of ‘cleanPairs’, namely
eventstore                >         ‘[p_maxAge .= fmap toInt64 streamMetadataMaxAge,
eventstore                >           p_maxCount .= streamMetadataMaxCount,
eventstore                >           p_truncateBefore .= streamMetadataTruncateBefore,
eventstore                >           p_cacheControl .= fmap toInt64 streamMetadataCacheControl, ....]’
eventstore                >     |
eventstore                > 801 |         [ p_maxAge         .= fmap toInt64 streamMetadataMaxAge
eventstore                >     |           ^^^^^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:802:11: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the first argument of ‘(.=)’, namely ‘p_maxCount’
eventstore                >       In the expression: p_maxCount .= streamMetadataMaxCount
eventstore                >       In the first argument of ‘cleanPairs’, namely
eventstore                >         ‘[p_maxAge .= fmap toInt64 streamMetadataMaxAge,
eventstore                >           p_maxCount .= streamMetadataMaxCount,
eventstore                >           p_truncateBefore .= streamMetadataTruncateBefore,
eventstore                >           p_cacheControl .= fmap toInt64 streamMetadataCacheControl, ....]’
eventstore                >     |
eventstore                > 802 |         , p_maxCount       .= streamMetadataMaxCount
eventstore                >     |           ^^^^^^^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:803:11: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the first argument of ‘(.=)’, namely ‘p_truncateBefore’
eventstore                >       In the expression: p_truncateBefore .= streamMetadataTruncateBefore
eventstore                >       In the first argument of ‘cleanPairs’, namely
eventstore                >         ‘[p_maxAge .= fmap toInt64 streamMetadataMaxAge,
eventstore                >           p_maxCount .= streamMetadataMaxCount,
eventstore                >           p_truncateBefore .= streamMetadataTruncateBefore,
eventstore                >           p_cacheControl .= fmap toInt64 streamMetadataCacheControl, ....]’
eventstore                >     |
eventstore                > 803 |         , p_truncateBefore .= streamMetadataTruncateBefore
eventstore                >     |           ^^^^^^^^^^^^^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:804:11: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the first argument of ‘(.=)’, namely ‘p_cacheControl’
eventstore                >       In the expression:
eventstore                >         p_cacheControl .= fmap toInt64 streamMetadataCacheControl
eventstore                >       In the first argument of ‘cleanPairs’, namely
eventstore                >         ‘[p_maxAge .= fmap toInt64 streamMetadataMaxAge,
eventstore                >           p_maxCount .= streamMetadataMaxCount,
eventstore                >           p_truncateBefore .= streamMetadataTruncateBefore,
eventstore                >           p_cacheControl .= fmap toInt64 streamMetadataCacheControl, ....]’
eventstore                >     |
eventstore                > 804 |         , p_cacheControl   .= fmap toInt64 streamMetadataCacheControl
eventstore                >     |           ^^^^^^^^^^^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:805:11: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the first argument of ‘(.=)’, namely ‘p_acl’
eventstore                >       In the expression: p_acl .= fmap streamACLJSON streamMetadataACL
eventstore                >       In the first argument of ‘cleanPairs’, namely
eventstore                >         ‘[p_maxAge .= fmap toInt64 streamMetadataMaxAge,
eventstore                >           p_maxCount .= streamMetadataMaxCount,
eventstore                >           p_truncateBefore .= streamMetadataTruncateBefore,
eventstore                >           p_cacheControl .= fmap toInt64 streamMetadataCacheControl, ....]’
eventstore                >     |
eventstore                > 805 |         , p_acl            .= fmap streamACLJSON streamMetadataACL
eventstore                >     |           ^^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:882:22: error:
eventstore                >     • Couldn't match type: HashMap Text v0
eventstore                >                      with: Data.Aeson.KeyMap.KeyMap A.Value
eventstore                >       Expected: Object -> Object
eventstore                >         Actual: HashMap Text v0 -> HashMap Text v0
eventstore                >     • In the expression: filterWithKey go
eventstore                >       In an equation for ‘keepUserProperties’:
eventstore                >           keepUserProperties
eventstore                >             = filterWithKey go
eventstore                >             where
eventstore                >                 go k _ = notMember k internalMetaProperties
eventstore                >     |
eventstore                > 882 | keepUserProperties = filterWithKey go
eventstore                >     |                      ^^^^^^^^^^^^^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:889:51: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the second argument of ‘(A..:)’, namely ‘k’
eventstore                >       In the second argument of ‘fmap’, namely ‘(m A..: k)’
eventstore                >       In the expression: fmap (fmap go) (m A..: k)
eventstore                >     |
eventstore                > 889 | parseNominalDiffTime k m = fmap (fmap go) (m A..: k)
eventstore                >     |                                                   ^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:910:24: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the second argument of ‘(A..:)’, namely ‘name’
eventstore                >       In the first argument of ‘(<|>)’, namely ‘obj A..: name’
eventstore                >       In a stmt of a 'do' block: mV <- obj A..: name <|> pure Nothing
eventstore                >     |
eventstore                > 910 |         mV <- obj A..: name <|> pure Nothing
eventstore                >     |                        ^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:913:25: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the second argument of ‘(A..:)’, namely ‘name’
eventstore                >       In the expression: obj A..: name
eventstore                >       In an equation for ‘multiple’: multiple = obj A..: name
eventstore                >     |
eventstore                > 913 |     multiple = obj A..: name
eventstore                >     |                         ^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:920:21: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the second argument of ‘(A..:)’, namely ‘p_maxCount’
eventstore                >       In the first argument of ‘(<|>)’, namely ‘m A..: p_maxCount’
eventstore                >       In the second argument of ‘(<$>)’, namely
eventstore                >         ‘(m A..: p_maxCount <|> pure Nothing)’
eventstore                >     |
eventstore                > 920 |         <$> (m A..: p_maxCount <|> pure Nothing)
eventstore                >     |                     ^^^^^^^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:922:21: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the second argument of ‘(A..:)’, namely ‘p_truncateBefore’
eventstore                >       In the first argument of ‘(<|>)’, namely ‘m A..: p_truncateBefore’
eventstore                >       In the second argument of ‘(<*>)’, namely
eventstore                >         ‘(m A..: p_truncateBefore <|> pure Nothing)’
eventstore                >     |
eventstore                > 922 |         <*> (m A..: p_truncateBefore <|> pure Nothing)
eventstore                >     |                     ^^^^^^^^^^^^^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:924:22: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the second argument of ‘(A..:)’, namely ‘p_acl’
eventstore                >       In the first argument of ‘(>>=)’, namely ‘m A..: p_acl’
eventstore                >       In the first argument of ‘(<|>)’, namely
eventstore                >         ‘(m A..: p_acl >>= traverse parseStreamACL)’
eventstore                >     |
eventstore                > 924 |         <*> ((m A..: p_acl >>= traverse parseStreamACL) <|> pure Nothing)
eventstore                >     |                      ^^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:929:41: error:
eventstore                >     • Couldn't match expected type ‘A.Key’ with actual type ‘Text’
eventstore                >     • In the second argument of ‘(A..:)’, namely ‘prop’
eventstore                >       In a stmt of a 'do' block: (secs :: Maybe Int64) <- m A..: prop
eventstore                >       In the expression:
eventstore                >         do (secs :: Maybe Int64) <- m A..: prop
eventstore                >            return $ fmap (fromSeconds . realToFrac) secs
eventstore                >     |
eventstore                > 929 |         (secs :: Maybe Int64) <- m A..: prop
eventstore                >     |                                         ^^^^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:1050:24: error:
eventstore                >     • Couldn't match expected type ‘ContainerKey Object’
eventstore                >                   with actual type ‘Text’
eventstore                >     • In the first argument of ‘insertMap’, namely ‘k’
eventstore                >       In the expression: insertMap k (toJSON v) m
eventstore                >       In an equation for ‘m'’: m' = insertMap k (toJSON v) m
eventstore                >      |
eventstore                > 1050 |         m' = insertMap k (toJSON v) m in
eventstore                >      |                        ^
eventstore                >    
eventstore                > /tmp/stack-a4cdb9ff0cebe249/eventstore-1.4.1/Database/EventStore/Internal/Types.hs:1050:27: error:
eventstore                >     • Couldn't match expected type ‘MapValue Object’
eventstore                >                   with actual type ‘A.Value’
eventstore                >     • In the second argument of ‘insertMap’, namely ‘(toJSON v)’
eventstore                >       In the expression: insertMap k (toJSON v) m
eventstore                >       In an equation for ‘m'’: m' = insertMap k (toJSON v) m
eventstore                >      |
eventstore                > 1050 |         m' = insertMap k (toJSON v) m in
eventstore                >      |                           ^^^^^^^^

Add API for stream metadata

I would like to set the max count of a stream so that I can make something like a checkpoint stream.

Being able to manipulate a stream's max age and ACL would also be useful.

[Internal] Dispose lock implementation is wrong

Not a big deal at all but at:

https://github.com/YoEight/eventstore/blob/master/Database/EventStore/Internal/Execution/Production.hs#L585

We test the first connection ever made by the client to know if the connection is closed. We should read the lastest connection available through _connRef.

Really not a big issue at all because 99% of time we keep the same connection with the server (Unless you use cluster connection). Also it can be observed only if a code relies on waitTillClosed.

Database.EventStore.connect: documentation typo

The documentation reads "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."

I believe either the first or the second occurrence of "SQL connection" should be "Event Store connection", but it is not clear which it should be.

Implement subscription confirmation timeout and custom retry settings

  • Being able to detect when a subscription request never received a confirmation from the server in given time window.

  • Currently, we only support one kind of subscription retry: when the server is too busy or not ready. We should also be able to retry when the confirmation take too long. Besides, at the moment, the driver keeps retrying. We should be able to limit how many times we retry.

Recovering subscriptions from a connection loss fails

The basic use-case I have is that I provide a WebSocket where I send events to the browser. For this I use a volatile subscription (although I've also confirmed this for catchup-subs).

My recovery strategy is to simply re-sub to a stream after the exception SubscriptionClosed is thrown. With #61 fixed this should be possible.

To reproduce this bug the following setup is needed:

  • running store at localhost:1113
  • existing stream named "strim"
  • a way to send an event to that stream

Code for testing:

{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}

module Test where

import ClassyPrelude
import Database.EventStore
import Control.Concurrent (forkIO)

main :: IO ()
main = do
  con <- connect defaultSettings { s_retry = keepRetrying } (Static "localhost" 1113)

  _ <- void . forkIO . forever $ handle (\(_ :: SubscriptionClosed) -> threadDelay 5000000) (mkSub con >>= process)

  -- this will make it so we can run our tests
  _ <- getLine :: IO String

  shutdown con >> waitTillClosed con

  where
    mkSub c = do
      putStrLn "making a subscription"
      sub <- subscribe c "strim" True

      waitConfirmation sub
      putStrLn "sub confirmed"

      return sub

    process sub = do
      putStrLn "processing..."

      forever $ do
        n <- nextEvent sub
        print (recordedEventNumber $ resolvedEventOriginal n)

To execute the test, do the following:

  • start up the store
  • run the script and send an event to that stream to confirm it's working
making a subscription
sub confirmed
processing...
81729
81730
  • next, kill the store. The driver will abort the subscription and the test script will try creating a new subscription. Output is:
making a subscription
sub confirmed
processing...
81729
81730
making a subscription
  • bring the store back up. Nothing else will happen.

Expected output would be a confirmed subscription and a continuation of processing:

making a subscription
sub confirmed
processing...
81729
81730
making a subscription
sub confirmed
processing...
81731

By inserting a threadDelay 5000000 in the exception handling function the driver seems to be able to recover, however this is unreliable at best.

InvalidOperation "No expection was fulfilled" raised randomly when subscribing to a stream.

Version: 1.1.0

[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Publishing message type SystemInit.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Message type SystemInit propagated.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Publishing message type Initialized.
[31/Jan/2018:19:48:08 +0100] eventstore [Info] Service TimerService initialized
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Message type Initialized propagated.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Publishing message type NewTimer.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Message type NewTimer propagated.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Publishing message type EstablishConnection.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Establish tcp connection on [127.0.0.1:1113]
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Message type EstablishConnection propagated.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Publishing message type Initialized.
[31/Jan/2018:19:48:08 +0100] eventstore [Info] Service ConnectionManager initialized
[31/Jan/2018:19:48:08 +0100] eventstore [Info] Entire system initialized properly
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Message type Initialized propagated.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Publishing message type SubmitOperation.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Package enqueued: Package [da08fc69-baec-48fb-8c9a-a6ed231c26a6], command: (0xc0)[subscribe-to-stream]
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Message type SubmitOperation propagated.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Publishing message type SubmitOperation.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Package enqueued: Package [678fe4cd-7053-4fab-9e06-902c7eed23cc], command: (0x82)[write-events]
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Message type SubmitOperation propagated.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Publishing message type ConnectionEstablished.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] TCP connection established: Connection [a2e89441-5ebe-4f4c-8138-2f0898a02ee1] on 127.0.0.1:1113.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Package enqueued: Package [b0efdfbc-25d5-47ff-8808-34227eecc13f], command: (0xf5)[identify-client]
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Message type ConnectionEstablished propagated.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Publishing message type PackageArrived.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Package IGNORED: Package [da08fc69-baec-48fb-8c9a-a6ed231c26a6], command: (0xc1)[subscription-confirmation].
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Message type PackageArrived propagated.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Publishing message type PackageArrived.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] TCP connection identified: Connection [a2e89441-5ebe-4f4c-8138-2f0898a02ee1] on 127.0.0.1:1113.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Message type PackageArrived propagated.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Publishing message type PackageArrived.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Package received:  Package [da08fc69-baec-48fb-8c9a-a6ed231c26a6], command: (0xc2)[stream-event-appeared].
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Message type PackageArrived propagated.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Publishing message type PackageArrived.
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Package received:  Package [678fe4cd-7053-4fab-9e06-902c7eed23cc], command: (0x83)[write-events-completed].
[31/Jan/2018:19:48:08 +0100] eventstore [Debug] Message type PackageArrived propagated.

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.