{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE GADTs                      #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures             #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE Rank2Types                 #-}
{-# LANGUAGE StandaloneDeriving         #-}
module Database.EventStore.Internal.Operation
  ( OpResult(..)
  , OperationError(..)
  , Operation
  , Need(..)
  , Code
  , Execution(..)
  , Expect(..)
  , freshId
  , failure
  , retry
  , send
  , request
  , waitFor
  , waitForOr
  , wrongVersion
  , streamDeleted
  , invalidTransaction
  , accessDenied
  , protobufDecodingError
  , serverError
  , invalidServerResponse
  , module Data.Machine
  ) where
import Prelude (String)
import Data.Machine
import Data.ProtocolBuffers
import Data.Serialize
import Data.UUID
import Database.EventStore.Internal.Command
import Database.EventStore.Internal.Prelude
import Database.EventStore.Internal.Settings
import Database.EventStore.Internal.Stream
import Database.EventStore.Internal.Types
data OpResult
    = OP_SUCCESS
    | OP_PREPARE_TIMEOUT
    | OP_COMMIT_TIMEOUT
    | OP_FORWARD_TIMEOUT
    | OP_WRONG_EXPECTED_VERSION
    | OP_STREAM_DELETED
    | OP_INVALID_TRANSACTION
    | OP_ACCESS_DENIED
    deriving (Eq, Enum, Show)
data OperationError
    = WrongExpectedVersion Text ExpectedVersion 
    | StreamDeleted StreamName                        
    | InvalidTransaction
    | forall t. AccessDenied (StreamId t)                   
    | InvalidServerResponse Command Command     
    | ProtobufDecodingError String
    | ServerError (Maybe Text)                  
    | InvalidOperation Text
    | StreamNotFound StreamName
    | NotAuthenticatedOp
      
    | Aborted
      
      
    deriving Typeable
deriving instance Show OperationError
instance Exception OperationError
data Execution a
  = Proceed a
  | Retry
  | Failed !OperationError
instance Functor Execution where
  fmap f (Proceed a) = Proceed (f a)
  fmap _ Retry       = Retry
  fmap _ (Failed e)  = Failed e
instance Applicative Execution where
  pure = return
  (<*>) = ap
instance Monad Execution where
  return = Proceed
  Proceed a >>= f = f a
  Retry     >>= _ = Retry
  Failed e  >>= _ = Failed e
type Operation output = MachineT Execution Need output
data Need a where
  NeedUUID   :: Need UUID
  NeedRemote :: Command -> ByteString -> Maybe Credentials -> Need Package
  WaitRemote :: UUID -> Need (Maybe Package)
type Code o a = PlanT Need o Execution a
freshId :: Code o UUID
freshId = awaits NeedUUID
failure :: OperationError -> Code o a
failure = lift . Failed
retry :: Code o a
retry = lift Retry
send :: (Encode req, Decode resp)
     => Command
     -> Command
     -> Maybe Credentials
     -> req
     -> Code o resp
send reqCmd expCmd cred req = do
  let payload = runPut $ encodeMessage req
  pkg <- awaits $ NeedRemote reqCmd payload cred
  let gotCmd = packageCmd pkg
  when (gotCmd /= expCmd)
    (invalidServerResponse expCmd gotCmd)
  case runGet decodeMessage (packageData pkg) of
    Left e     -> protobufDecodingError e
    Right resp -> return resp
data Expect o where
  Expect :: Decode resp => Command -> (UUID -> resp -> Code o ()) -> Expect o
runFirstMatch :: Package -> [Expect o] -> Code o ()
runFirstMatch _ [] = invalidOperation "No expectation was fulfilled"
runFirstMatch pkg (Expect cmd k:rest)
  | packageCmd pkg /= cmd = runFirstMatch pkg rest
  | otherwise =
    case runGet decodeMessage (packageData pkg) of
      Left e     -> protobufDecodingError e
      Right resp -> k (packageCorrelation pkg) resp
request :: Encode req
        => Command
        -> Maybe Credentials
        -> req
        -> [Expect o]
        -> Code o ()
request reqCmd cred rq exps = do
  let payload = runPut $ encodeMessage rq
  pkg <- awaits $ NeedRemote reqCmd payload cred
  runFirstMatch pkg exps
waitFor :: UUID -> [Expect o] -> Code o ()
waitFor pid exps = waitForOr pid stop exps
waitForOr :: UUID -> (Code o ()) -> [Expect o] -> Code o ()
waitForOr pid alt exps =
  awaits (WaitRemote pid) >>= \case
    Nothing  -> alt
    Just pkg ->
      runFirstMatch pkg exps
wrongVersion :: Text -> ExpectedVersion -> Code o a
wrongVersion stream ver = failure (WrongExpectedVersion stream ver)
streamDeleted :: StreamName -> Code o a
streamDeleted stream = failure (StreamDeleted stream)
invalidTransaction :: Code o a
invalidTransaction = failure InvalidTransaction
accessDenied :: StreamId t -> Code o a
accessDenied = failure . AccessDenied
protobufDecodingError :: String -> Code o a
protobufDecodingError = failure . ProtobufDecodingError
serverError :: Maybe Text -> Code o a
serverError = failure . ServerError
invalidServerResponse :: Command -> Command -> Code o a
invalidServerResponse expe got = failure $ InvalidServerResponse expe got
invalidOperation :: Text -> Code o a
invalidOperation = failure . InvalidOperation