{-# LANGUAGE RecordWildCards #-}
--------------------------------------------------------------------------------
-- |
-- Module : Database.EventStore.Internal.Operation.WriteEvents
-- Copyright : (C) 2015 Yorick Laupa
-- License : (see the file LICENSE)
--
-- Maintainer : Yorick Laupa <yo.eight@gmail.com>
-- Stability : provisional
-- Portability : non-portable
--
--------------------------------------------------------------------------------
module Database.EventStore.Internal.Operation.WriteEvents
    ( writeEvents ) where

--------------------------------------------------------------------------------
import Data.Maybe

--------------------------------------------------------------------------------
import Data.ProtocolBuffers

--------------------------------------------------------------------------------
import Database.EventStore.Internal.Command
import Database.EventStore.Internal.Communication (Transmit(..))
import Database.EventStore.Internal.Control (publishWith)
import Database.EventStore.Internal.Exec
import Database.EventStore.Internal.Operation (OpResult(..))
import Database.EventStore.Internal.Operation
import Database.EventStore.Internal.Operation.Write.Common
import Database.EventStore.Internal.Operation.WriteEvents.Message
import Database.EventStore.Internal.Prelude
import Database.EventStore.Internal.Settings
import Database.EventStore.Internal.Stream
import Database.EventStore.Internal.Types

-------------------------------------------------------------------------------
writeEvents
  :: Settings
  -> Exec
  -> Text
  -> ExpectedVersion
  -> Maybe Credentials
  -> [Event]
  -> IO (Async WriteResult)
writeEvents :: Settings
-> Exec
-> Text
-> ExpectedVersion
-> Maybe Credentials
-> [Event]
-> IO (Async WriteResult)
writeEvents Settings
setts Exec
exec Text
stream ExpectedVersion
version Maybe Credentials
creds [Event]
evts
  = do Mailbox
m <- IO Mailbox
forall (m :: * -> *). MonadBase IO m => m Mailbox
mailboxNew
       IO WriteResult -> IO (Async (StM IO WriteResult))
forall (m :: * -> *) a.
MonadBaseControl IO m =>
m a -> m (Async (StM m a))
async (IO WriteResult -> IO (Async (StM IO WriteResult)))
-> IO WriteResult -> IO (Async (StM IO WriteResult))
forall a b. (a -> b) -> a -> b
$
         do [NewEvent]
nevts <- (Event -> IO NewEvent) -> [Event] -> IO [NewEvent]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Event -> IO NewEvent
eventToNewEventIO [Event]
evts
            let req :: Request
req = Text -> Int64 -> [NewEvent] -> Bool -> Request
newRequest Text
stream (ExpectedVersion -> Int64
expVersionInt64 ExpectedVersion
version) [NewEvent]
nevts (Settings -> Bool
s_requireMaster Settings
setts)

            Package
pkg <- Command -> Maybe Credentials -> Request -> IO Package
forall msg (m :: * -> *).
(Encode msg, MonadIO m) =>
Command -> Maybe Credentials -> msg -> m Package
createPkg Command
writeEventsCmd Maybe Credentials
creds Request
req

            IO (Loop WriteResult) -> IO WriteResult
forall (m :: * -> *) a. Monad m => m (Loop a) -> m a
keepLooping (IO (Loop WriteResult) -> IO WriteResult)
-> IO (Loop WriteResult) -> IO WriteResult
forall a b. (a -> b) -> a -> b
$ do
              Exec -> Transmit -> IO ()
forall p a (m :: * -> *).
(Pub p, Typeable a, MonadIO m) =>
p -> a -> m ()
publishWith Exec
exec (Mailbox -> Lifetime -> Package -> Transmit
Transmit Mailbox
m Lifetime
OneTime Package
pkg)
              Either OperationError Response
outcome <- Mailbox -> IO (Either OperationError Response)
forall (m :: * -> *) resp.
(MonadBase IO m, Decode resp) =>
Mailbox -> m (Either OperationError resp)
mailboxReadDecoded Mailbox
m
              case Either OperationError Response
outcome of
                Left OperationError
e
                  -> OperationError -> IO (Loop WriteResult)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throw OperationError
e
                Right Response
resp
                  -> let r :: FieldType (Field 1 (RequiredField (Always (Enumeration OpResult))))
r = Field 1 (RequiredField (Always (Enumeration OpResult)))
-> FieldType
     (Field 1 (RequiredField (Always (Enumeration OpResult))))
forall a. HasField a => a -> FieldType a
getField (Field 1 (RequiredField (Always (Enumeration OpResult)))
 -> FieldType
      (Field 1 (RequiredField (Always (Enumeration OpResult)))))
-> Field 1 (RequiredField (Always (Enumeration OpResult)))
-> FieldType
     (Field 1 (RequiredField (Always (Enumeration OpResult))))
forall a b. (a -> b) -> a -> b
$ Response -> Required 1 (Enumeration OpResult)
_result Response
resp
                         com_pos :: FieldType (Field 6 (OptionalField (Last (Value Int64))))
com_pos = Field 6 (OptionalField (Last (Value Int64)))
-> FieldType (Field 6 (OptionalField (Last (Value Int64))))
forall a. HasField a => a -> FieldType a
getField (Field 6 (OptionalField (Last (Value Int64)))
 -> FieldType (Field 6 (OptionalField (Last (Value Int64)))))
-> Field 6 (OptionalField (Last (Value Int64)))
-> FieldType (Field 6 (OptionalField (Last (Value Int64))))
forall a b. (a -> b) -> a -> b
$ Response -> Optional 6 (Value Int64)
_commitPosition Response
resp
                         prep_pos :: FieldType (Field 5 (OptionalField (Last (Value Int64))))
prep_pos = Field 5 (OptionalField (Last (Value Int64)))
-> FieldType (Field 5 (OptionalField (Last (Value Int64))))
forall a. HasField a => a -> FieldType a
getField (Field 5 (OptionalField (Last (Value Int64)))
 -> FieldType (Field 5 (OptionalField (Last (Value Int64)))))
-> Field 5 (OptionalField (Last (Value Int64)))
-> FieldType (Field 5 (OptionalField (Last (Value Int64))))
forall a b. (a -> b) -> a -> b
$ Response -> Optional 5 (Value Int64)
_preparePosition Response
resp
                         lst_num :: FieldType (Field 4 (RequiredField (Always (Value Int64))))
lst_num = Field 4 (RequiredField (Always (Value Int64)))
-> FieldType (Field 4 (RequiredField (Always (Value Int64))))
forall a. HasField a => a -> FieldType a
getField (Field 4 (RequiredField (Always (Value Int64)))
 -> FieldType (Field 4 (RequiredField (Always (Value Int64)))))
-> Field 4 (RequiredField (Always (Value Int64)))
-> FieldType (Field 4 (RequiredField (Always (Value Int64))))
forall a b. (a -> b) -> a -> b
$ Response -> Required 4 (Value Int64)
_lastNumber Response
resp
                         com_pos_int :: Int64
com_pos_int = Int64 -> Maybe Int64 -> Int64
forall a. a -> Maybe a -> a
fromMaybe (-Int64
1) Maybe Int64
FieldType (Field 6 (OptionalField (Last (Value Int64))))
com_pos
                         prep_pos_int :: Int64
prep_pos_int = Int64 -> Maybe Int64 -> Int64
forall a. a -> Maybe a -> a
fromMaybe (-Int64
1) Maybe Int64
FieldType (Field 5 (OptionalField (Last (Value Int64))))
prep_pos
                         pos :: Position
pos = Int64 -> Int64 -> Position
Position Int64
com_pos_int Int64
prep_pos_int
                         res :: WriteResult
res = Int64 -> Position -> WriteResult
WriteResult Int64
FieldType (Field 4 (RequiredField (Always (Value Int64))))
lst_num Position
pos in
                     case FieldType (Field 1 (RequiredField (Always (Enumeration OpResult))))
r of
                         FieldType (Field 1 (RequiredField (Always (Enumeration OpResult))))
OP_SUCCESS -> Loop WriteResult -> IO (Loop WriteResult)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Loop WriteResult -> IO (Loop WriteResult))
-> Loop WriteResult -> IO (Loop WriteResult)
forall a b. (a -> b) -> a -> b
$ WriteResult -> Loop WriteResult
forall a. a -> Loop a
Break WriteResult
res
                         FieldType (Field 1 (RequiredField (Always (Enumeration OpResult))))
OP_PREPARE_TIMEOUT -> Loop WriteResult -> IO (Loop WriteResult)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Loop WriteResult
forall a. Loop a
Loop
                         FieldType (Field 1 (RequiredField (Always (Enumeration OpResult))))
OP_FORWARD_TIMEOUT -> Loop WriteResult -> IO (Loop WriteResult)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Loop WriteResult
forall a. Loop a
Loop
                         FieldType (Field 1 (RequiredField (Always (Enumeration OpResult))))
OP_COMMIT_TIMEOUT -> Loop WriteResult -> IO (Loop WriteResult)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Loop WriteResult
forall a. Loop a
Loop
                         FieldType (Field 1 (RequiredField (Always (Enumeration OpResult))))
OP_WRONG_EXPECTED_VERSION -> OperationError -> IO (Loop WriteResult)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throw (OperationError -> IO (Loop WriteResult))
-> OperationError -> IO (Loop WriteResult)
forall a b. (a -> b) -> a -> b
$ Text -> ExpectedVersion -> OperationError
WrongExpectedVersion Text
stream ExpectedVersion
version
                         FieldType (Field 1 (RequiredField (Always (Enumeration OpResult))))
OP_STREAM_DELETED -> OperationError -> IO (Loop WriteResult)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throw (OperationError -> IO (Loop WriteResult))
-> OperationError -> IO (Loop WriteResult)
forall a b. (a -> b) -> a -> b
$ StreamName -> OperationError
StreamDeleted (StreamName -> OperationError) -> StreamName -> OperationError
forall a b. (a -> b) -> a -> b
$ Text -> StreamName
StreamName Text
stream
                         FieldType (Field 1 (RequiredField (Always (Enumeration OpResult))))
OP_INVALID_TRANSACTION -> OperationError -> IO (Loop WriteResult)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throw OperationError
InvalidTransaction
                         FieldType (Field 1 (RequiredField (Always (Enumeration OpResult))))
OP_ACCESS_DENIED -> OperationError -> IO (Loop WriteResult)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throw (OperationError -> IO (Loop WriteResult))
-> OperationError -> IO (Loop WriteResult)
forall a b. (a -> b) -> a -> b
$ StreamName -> OperationError
forall t. StreamId t -> OperationError
AccessDenied (Text -> StreamName
StreamName Text
stream)