module Database.EventStore.Internal.Operation.PersistOperations
( createPersist
, updatePersist
, deletePersist
) where
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 (Exec)
import Database.EventStore.Internal.Operation
import Database.EventStore.Internal.Prelude
import Database.EventStore.Internal.Subscription.Message
import Database.EventStore.Internal.Subscription.Types
import Database.EventStore.Internal.Settings
import Database.EventStore.Internal.Types
persistOperation
:: Exec
-> Text
-> Text
-> Maybe Credentials
-> PersistAction
-> IO (Async (Maybe PersistActionException))
persistOperation :: Exec
-> Text
-> Text
-> Maybe Credentials
-> PersistAction
-> IO (Async (Maybe PersistActionException))
persistOperation Exec
exec Text
grp Text
stream Maybe Credentials
cred PersistAction
tpe
= do Mailbox
m <- forall (m :: * -> *). MonadBase IO m => m Mailbox
mailboxNew
forall (m :: * -> *) a.
MonadBaseControl IO m =>
m a -> m (Async (StM m a))
async forall a b. (a -> b) -> a -> b
$
case PersistAction
tpe of
PersistCreate PersistentSubscriptionSettings
ss
-> do let req :: CreatePersistentSubscription
req = Text
-> Text
-> PersistentSubscriptionSettings
-> CreatePersistentSubscription
_createPersistentSubscription Text
grp Text
stream PersistentSubscriptionSettings
ss
Package
pkg <- forall msg (m :: * -> *).
(Encode msg, MonadIO m) =>
Command -> Maybe Credentials -> msg -> m Package
createPkg Command
createPersistentSubscriptionCmd Maybe Credentials
cred CreatePersistentSubscription
req
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 CreatePersistentSubscriptionCompleted
outcome <- forall (m :: * -> *) resp.
(MonadBase IO m, Decode resp) =>
Mailbox -> m (Either OperationError resp)
mailboxReadDecoded Mailbox
m
case Either OperationError CreatePersistentSubscriptionCompleted
outcome of
Left OperationError
e
-> forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throw OperationError
e
Right CreatePersistentSubscriptionCompleted
resp
-> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ CreatePersistentSubscriptionResult -> Maybe PersistActionException
createRException forall a b. (a -> b) -> a -> b
$ forall a. HasField a => a -> FieldType a
getField forall a b. (a -> b) -> a -> b
$ CreatePersistentSubscriptionCompleted
-> Required 1 (Enumeration CreatePersistentSubscriptionResult)
cpscResult CreatePersistentSubscriptionCompleted
resp
PersistUpdate PersistentSubscriptionSettings
ss
-> do let req :: UpdatePersistentSubscription
req = Text
-> Text
-> PersistentSubscriptionSettings
-> UpdatePersistentSubscription
_updatePersistentSubscription Text
grp Text
stream PersistentSubscriptionSettings
ss
Package
pkg <- forall msg (m :: * -> *).
(Encode msg, MonadIO m) =>
Command -> Maybe Credentials -> msg -> m Package
createPkg Command
updatePersistentSubscriptionCmd Maybe Credentials
cred UpdatePersistentSubscription
req
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 UpdatePersistentSubscriptionCompleted
outcome <- forall (m :: * -> *) resp.
(MonadBase IO m, Decode resp) =>
Mailbox -> m (Either OperationError resp)
mailboxReadDecoded Mailbox
m
case Either OperationError UpdatePersistentSubscriptionCompleted
outcome of
Left OperationError
e
-> forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throw OperationError
e
Right UpdatePersistentSubscriptionCompleted
resp
-> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ UpdatePersistentSubscriptionResult -> Maybe PersistActionException
updateRException forall a b. (a -> b) -> a -> b
$ forall a. HasField a => a -> FieldType a
getField forall a b. (a -> b) -> a -> b
$ UpdatePersistentSubscriptionCompleted
-> Required 1 (Enumeration UpdatePersistentSubscriptionResult)
upscResult UpdatePersistentSubscriptionCompleted
resp
PersistAction
PersistDelete
-> do let req :: DeletePersistentSubscription
req = Text -> Text -> DeletePersistentSubscription
_deletePersistentSubscription Text
grp Text
stream
Package
pkg <- forall msg (m :: * -> *).
(Encode msg, MonadIO m) =>
Command -> Maybe Credentials -> msg -> m Package
createPkg Command
deletePersistentSubscriptionCmd Maybe Credentials
cred DeletePersistentSubscription
req
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 DeletePersistentSubscriptionCompleted
outcome <- forall (m :: * -> *) resp.
(MonadBase IO m, Decode resp) =>
Mailbox -> m (Either OperationError resp)
mailboxReadDecoded Mailbox
m
case Either OperationError DeletePersistentSubscriptionCompleted
outcome of
Left OperationError
e
-> forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throw OperationError
e
Right DeletePersistentSubscriptionCompleted
resp
-> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DeletePersistentSubscriptionResult -> Maybe PersistActionException
deleteRException forall a b. (a -> b) -> a -> b
$ forall a. HasField a => a -> FieldType a
getField forall a b. (a -> b) -> a -> b
$ DeletePersistentSubscriptionCompleted
-> Required 1 (Enumeration DeletePersistentSubscriptionResult)
dpscResult DeletePersistentSubscriptionCompleted
resp
createPersist
:: Exec
-> Text
-> Text
-> PersistentSubscriptionSettings
-> Maybe Credentials
-> IO (Async (Maybe PersistActionException))
createPersist :: Exec
-> Text
-> Text
-> PersistentSubscriptionSettings
-> Maybe Credentials
-> IO (Async (Maybe PersistActionException))
createPersist Exec
exec Text
grp Text
stream PersistentSubscriptionSettings
ss Maybe Credentials
cred
= Exec
-> Text
-> Text
-> Maybe Credentials
-> PersistAction
-> IO (Async (Maybe PersistActionException))
persistOperation Exec
exec Text
grp Text
stream Maybe Credentials
cred (PersistentSubscriptionSettings -> PersistAction
PersistCreate PersistentSubscriptionSettings
ss)
updatePersist
:: Exec
-> Text
-> Text
-> PersistentSubscriptionSettings
-> Maybe Credentials
-> IO (Async (Maybe PersistActionException))
updatePersist :: Exec
-> Text
-> Text
-> PersistentSubscriptionSettings
-> Maybe Credentials
-> IO (Async (Maybe PersistActionException))
updatePersist Exec
exec Text
grp Text
stream PersistentSubscriptionSettings
ss Maybe Credentials
cred
= Exec
-> Text
-> Text
-> Maybe Credentials
-> PersistAction
-> IO (Async (Maybe PersistActionException))
persistOperation Exec
exec Text
grp Text
stream Maybe Credentials
cred (PersistentSubscriptionSettings -> PersistAction
PersistUpdate PersistentSubscriptionSettings
ss)
deletePersist
:: Exec
-> Text
-> Text
-> Maybe Credentials
-> IO (Async (Maybe PersistActionException))
deletePersist :: Exec
-> Text
-> Text
-> Maybe Credentials
-> IO (Async (Maybe PersistActionException))
deletePersist Exec
exec Text
grp Text
stream Maybe Credentials
cred
= Exec
-> Text
-> Text
-> Maybe Credentials
-> PersistAction
-> IO (Async (Maybe PersistActionException))
persistOperation Exec
exec Text
grp Text
stream Maybe Credentials
cred PersistAction
PersistDelete