{-# LANGUAGE DeriveDataTypeable #-}
module Database.EventStore.Internal.Subscription.Types where
import Data.UUID
import Database.EventStore.Internal.Prelude
import Database.EventStore.Internal.Subscription.Message
import Database.EventStore.Internal.Types
data SubDropReason
= SubUnsubscribed
| SubAccessDenied
| SubNotFound
| SubPersistDeleted
| SubAborted
| SubNotAuthenticated (Maybe Text)
| SubServerError (Maybe Text)
| SubNotHandled !NotHandledReason !(Maybe MasterInfo)
| SubClientError !Text
| SubSubscriberMaxCountReached
deriving (Int -> SubDropReason -> ShowS
[SubDropReason] -> ShowS
SubDropReason -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubDropReason] -> ShowS
$cshowList :: [SubDropReason] -> ShowS
show :: SubDropReason -> String
$cshow :: SubDropReason -> String
showsPrec :: Int -> SubDropReason -> ShowS
$cshowsPrec :: Int -> SubDropReason -> ShowS
Show, SubDropReason -> SubDropReason -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubDropReason -> SubDropReason -> Bool
$c/= :: SubDropReason -> SubDropReason -> Bool
== :: SubDropReason -> SubDropReason -> Bool
$c== :: SubDropReason -> SubDropReason -> Bool
Eq)
toSubDropReason :: DropReason -> SubDropReason
toSubDropReason :: DropReason -> SubDropReason
toSubDropReason DropReason
D_Unsubscribed = SubDropReason
SubUnsubscribed
toSubDropReason DropReason
D_NotFound = SubDropReason
SubNotFound
toSubDropReason DropReason
D_AccessDenied = SubDropReason
SubAccessDenied
toSubDropReason DropReason
D_PersistentSubscriptionDeleted = SubDropReason
SubPersistDeleted
toSubDropReason DropReason
D_SubscriberMaxCountReached = SubDropReason
SubSubscriberMaxCountReached
data SubscriptionClosed = SubscriptionClosed (Maybe SubDropReason)
deriving (Int -> SubscriptionClosed -> ShowS
[SubscriptionClosed] -> ShowS
SubscriptionClosed -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionClosed] -> ShowS
$cshowList :: [SubscriptionClosed] -> ShowS
show :: SubscriptionClosed -> String
$cshow :: SubscriptionClosed -> String
showsPrec :: Int -> SubscriptionClosed -> ShowS
$cshowsPrec :: Int -> SubscriptionClosed -> ShowS
Show, Typeable)
instance Exception SubscriptionClosed
newtype SubscriptionId = SubscriptionId UUID deriving (SubscriptionId -> SubscriptionId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionId -> SubscriptionId -> Bool
$c/= :: SubscriptionId -> SubscriptionId -> Bool
== :: SubscriptionId -> SubscriptionId -> Bool
$c== :: SubscriptionId -> SubscriptionId -> Bool
Eq, Eq SubscriptionId
SubscriptionId -> SubscriptionId -> Bool
SubscriptionId -> SubscriptionId -> Ordering
SubscriptionId -> SubscriptionId -> SubscriptionId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SubscriptionId -> SubscriptionId -> SubscriptionId
$cmin :: SubscriptionId -> SubscriptionId -> SubscriptionId
max :: SubscriptionId -> SubscriptionId -> SubscriptionId
$cmax :: SubscriptionId -> SubscriptionId -> SubscriptionId
>= :: SubscriptionId -> SubscriptionId -> Bool
$c>= :: SubscriptionId -> SubscriptionId -> Bool
> :: SubscriptionId -> SubscriptionId -> Bool
$c> :: SubscriptionId -> SubscriptionId -> Bool
<= :: SubscriptionId -> SubscriptionId -> Bool
$c<= :: SubscriptionId -> SubscriptionId -> Bool
< :: SubscriptionId -> SubscriptionId -> Bool
$c< :: SubscriptionId -> SubscriptionId -> Bool
compare :: SubscriptionId -> SubscriptionId -> Ordering
$ccompare :: SubscriptionId -> SubscriptionId -> Ordering
Ord, Int -> SubscriptionId -> ShowS
[SubscriptionId] -> ShowS
SubscriptionId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionId] -> ShowS
$cshowList :: [SubscriptionId] -> ShowS
show :: SubscriptionId -> String
$cshow :: SubscriptionId -> String
showsPrec :: Int -> SubscriptionId -> ShowS
$cshowsPrec :: Int -> SubscriptionId -> ShowS
Show)
data SubDetails =
SubDetails { SubDetails -> UUID
subId :: !UUID
, SubDetails -> Int64
subCommitPos :: !Int64
, SubDetails -> Maybe Int64
subLastEventNum :: !(Maybe Int64)
, SubDetails -> Maybe Text
subSubId :: !(Maybe Text)
}
data PersistAction
= PersistCreate PersistentSubscriptionSettings
| PersistUpdate PersistentSubscriptionSettings
| PersistDelete
data PersistActionException
= PersistActionFail
| PersistActionAlreadyExist
| PersistActionDoesNotExist
| PersistActionAccessDenied
| PersistActionAborted
deriving (Int -> PersistActionException -> ShowS
[PersistActionException] -> ShowS
PersistActionException -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PersistActionException] -> ShowS
$cshowList :: [PersistActionException] -> ShowS
show :: PersistActionException -> String
$cshow :: PersistActionException -> String
showsPrec :: Int -> PersistActionException -> ShowS
$cshowsPrec :: Int -> PersistActionException -> ShowS
Show, Typeable)
instance Exception PersistActionException
createRException :: CreatePersistentSubscriptionResult
-> Maybe PersistActionException
createRException :: CreatePersistentSubscriptionResult -> Maybe PersistActionException
createRException CreatePersistentSubscriptionResult
CPS_Success = forall a. Maybe a
Nothing
createRException CreatePersistentSubscriptionResult
CPS_AlreadyExists = forall a. a -> Maybe a
Just PersistActionException
PersistActionAlreadyExist
createRException CreatePersistentSubscriptionResult
CPS_Fail = forall a. a -> Maybe a
Just PersistActionException
PersistActionFail
createRException CreatePersistentSubscriptionResult
CPS_AccessDenied = forall a. a -> Maybe a
Just PersistActionException
PersistActionAccessDenied
deleteRException :: DeletePersistentSubscriptionResult
-> Maybe PersistActionException
deleteRException :: DeletePersistentSubscriptionResult -> Maybe PersistActionException
deleteRException DeletePersistentSubscriptionResult
DPS_Success = forall a. Maybe a
Nothing
deleteRException DeletePersistentSubscriptionResult
DPS_DoesNotExist = forall a. a -> Maybe a
Just PersistActionException
PersistActionDoesNotExist
deleteRException DeletePersistentSubscriptionResult
DPS_Fail = forall a. a -> Maybe a
Just PersistActionException
PersistActionFail
deleteRException DeletePersistentSubscriptionResult
DPS_AccessDenied = forall a. a -> Maybe a
Just PersistActionException
PersistActionAccessDenied
updateRException :: UpdatePersistentSubscriptionResult
-> Maybe PersistActionException
updateRException :: UpdatePersistentSubscriptionResult -> Maybe PersistActionException
updateRException UpdatePersistentSubscriptionResult
UPS_Success = forall a. Maybe a
Nothing
updateRException UpdatePersistentSubscriptionResult
UPS_DoesNotExist = forall a. a -> Maybe a
Just PersistActionException
PersistActionDoesNotExist
updateRException UpdatePersistentSubscriptionResult
UPS_Fail = forall a. a -> Maybe a
Just PersistActionException
PersistActionFail
updateRException UpdatePersistentSubscriptionResult
UPS_AccessDenied = forall a. a -> Maybe a
Just PersistActionException
PersistActionAccessDenied
data SubAction
= Submit ResolvedEvent
| Dropped SubDropReason
| Confirmed SubDetails