{-# LANGUAGE DeriveDataTypeable #-}
--------------------------------------------------------------------------------
-- |
-- Module : Database.EventStore.Internal.Subscription.Types
-- Copyright : (C) 2016 Yorick Laupa
-- License : (see the file LICENSE)
--
-- Maintainer : Yorick Laupa <yo.eight@gmail.com>
-- Stability : provisional
-- Portability : non-portable
--
--------------------------------------------------------------------------------
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

--------------------------------------------------------------------------------
-- | Indicates why a subscription has been dropped.
data SubDropReason
    = SubUnsubscribed
      -- ^ Subscription connection has been closed by the user.
    | SubAccessDenied
      -- ^ The current user is not allowed to operate on the supplied stream.
    | SubNotFound
      -- ^ Given stream name doesn't exist.
    | SubPersistDeleted
      -- ^ Given stream is deleted.
    | SubAborted
      -- ^ Occurs when the user shutdown the connection from the server or if
      -- the connection to the server is no longer possible.
    | SubNotAuthenticated (Maybe Text)
    | SubServerError (Maybe Text)
      -- ^ Unexpected error from the server.
    | SubNotHandled !NotHandledReason !(Maybe MasterInfo)
    | SubClientError !Text
    | SubSubscriberMaxCountReached
    deriving (Int -> SubDropReason -> ShowS
[SubDropReason] -> ShowS
SubDropReason -> String
(Int -> SubDropReason -> ShowS)
-> (SubDropReason -> String)
-> ([SubDropReason] -> ShowS)
-> Show SubDropReason
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
(SubDropReason -> SubDropReason -> Bool)
-> (SubDropReason -> SubDropReason -> Bool) -> Eq SubDropReason
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
(Int -> SubscriptionClosed -> ShowS)
-> (SubscriptionClosed -> String)
-> ([SubscriptionClosed] -> ShowS)
-> Show SubscriptionClosed
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

--------------------------------------------------------------------------------
-- | Represents a subscription id.
newtype SubscriptionId = SubscriptionId UUID deriving (SubscriptionId -> SubscriptionId -> Bool
(SubscriptionId -> SubscriptionId -> Bool)
-> (SubscriptionId -> SubscriptionId -> Bool) -> Eq SubscriptionId
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
Eq SubscriptionId
-> (SubscriptionId -> SubscriptionId -> Ordering)
-> (SubscriptionId -> SubscriptionId -> Bool)
-> (SubscriptionId -> SubscriptionId -> Bool)
-> (SubscriptionId -> SubscriptionId -> Bool)
-> (SubscriptionId -> SubscriptionId -> Bool)
-> (SubscriptionId -> SubscriptionId -> SubscriptionId)
-> (SubscriptionId -> SubscriptionId -> SubscriptionId)
-> Ord 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
$cp1Ord :: Eq SubscriptionId
Ord, Int -> SubscriptionId -> ShowS
[SubscriptionId] -> ShowS
SubscriptionId -> String
(Int -> SubscriptionId -> ShowS)
-> (SubscriptionId -> String)
-> ([SubscriptionId] -> ShowS)
-> Show SubscriptionId
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)

--------------------------------------------------------------------------------
-- | Subscription runtime details. Not useful for the user but at least it makes
--   Haddock documentation generation less ugly.
data SubDetails =
  SubDetails { SubDetails -> UUID
subId           :: !UUID
             , SubDetails -> Int64
subCommitPos    :: !Int64
             , SubDetails -> Maybe Int64
subLastEventNum :: !(Maybe Int64)
             , SubDetails -> Maybe Text
subSubId        :: !(Maybe Text)
             }

--------------------------------------------------------------------------------
-- | Type of persistent action.
data PersistAction
    = PersistCreate PersistentSubscriptionSettings
    | PersistUpdate PersistentSubscriptionSettings
    | PersistDelete

--------------------------------------------------------------------------------
-- | Enumerates all persistent action exceptions.
data PersistActionException
    = PersistActionFail
      -- ^ The action failed.
    | PersistActionAlreadyExist
      -- ^ Happens when creating a persistent subscription on a stream with a
      --   group name already taken.
    | PersistActionDoesNotExist
      -- ^ An operation tried to do something on a persistent subscription or a
      --   stream that don't exist.
    | PersistActionAccessDenied
      -- ^ The current user is not allowed to operate on the supplied stream or
      --   persistent subscription.
    | PersistActionAborted
      -- ^ That action has been aborted because the user shutdown the connection
      --   to the server or the connection to the server is no longer possible.
    deriving (Int -> PersistActionException -> ShowS
[PersistActionException] -> ShowS
PersistActionException -> String
(Int -> PersistActionException -> ShowS)
-> (PersistActionException -> String)
-> ([PersistActionException] -> ShowS)
-> Show PersistActionException
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

--------------------------------------------------------------------------------
-- EventStore result mappers:
-- =========================
-- EventStore protocol has several values that means the exact same thing. Those
-- functions convert a specific EventStore to uniform result type common to all
-- persistent actions.
--------------------------------------------------------------------------------
createRException :: CreatePersistentSubscriptionResult
                 -> Maybe PersistActionException
createRException :: CreatePersistentSubscriptionResult -> Maybe PersistActionException
createRException CreatePersistentSubscriptionResult
CPS_Success       = Maybe PersistActionException
forall a. Maybe a
Nothing
createRException CreatePersistentSubscriptionResult
CPS_AlreadyExists = PersistActionException -> Maybe PersistActionException
forall a. a -> Maybe a
Just PersistActionException
PersistActionAlreadyExist
createRException CreatePersistentSubscriptionResult
CPS_Fail          = PersistActionException -> Maybe PersistActionException
forall a. a -> Maybe a
Just PersistActionException
PersistActionFail
createRException CreatePersistentSubscriptionResult
CPS_AccessDenied  = PersistActionException -> Maybe PersistActionException
forall a. a -> Maybe a
Just PersistActionException
PersistActionAccessDenied

--------------------------------------------------------------------------------
deleteRException :: DeletePersistentSubscriptionResult
                 -> Maybe PersistActionException
deleteRException :: DeletePersistentSubscriptionResult -> Maybe PersistActionException
deleteRException DeletePersistentSubscriptionResult
DPS_Success      = Maybe PersistActionException
forall a. Maybe a
Nothing
deleteRException DeletePersistentSubscriptionResult
DPS_DoesNotExist = PersistActionException -> Maybe PersistActionException
forall a. a -> Maybe a
Just PersistActionException
PersistActionDoesNotExist
deleteRException DeletePersistentSubscriptionResult
DPS_Fail         = PersistActionException -> Maybe PersistActionException
forall a. a -> Maybe a
Just PersistActionException
PersistActionFail
deleteRException DeletePersistentSubscriptionResult
DPS_AccessDenied = PersistActionException -> Maybe PersistActionException
forall a. a -> Maybe a
Just PersistActionException
PersistActionAccessDenied

--------------------------------------------------------------------------------
updateRException :: UpdatePersistentSubscriptionResult
                 -> Maybe PersistActionException
updateRException :: UpdatePersistentSubscriptionResult -> Maybe PersistActionException
updateRException UpdatePersistentSubscriptionResult
UPS_Success      = Maybe PersistActionException
forall a. Maybe a
Nothing
updateRException UpdatePersistentSubscriptionResult
UPS_DoesNotExist = PersistActionException -> Maybe PersistActionException
forall a. a -> Maybe a
Just PersistActionException
PersistActionDoesNotExist
updateRException UpdatePersistentSubscriptionResult
UPS_Fail         = PersistActionException -> Maybe PersistActionException
forall a. a -> Maybe a
Just PersistActionException
PersistActionFail
updateRException UpdatePersistentSubscriptionResult
UPS_AccessDenied = PersistActionException -> Maybe PersistActionException
forall a. a -> Maybe a
Just PersistActionException
PersistActionAccessDenied

--------------------------------------------------------------------------------
data SubAction
  = Submit ResolvedEvent
  | Dropped SubDropReason
  | Confirmed SubDetails