{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Temporal.Replay (
readHistoryProtobufFile,
writeHistoryProtobufFile,
) where
import Control.Exception
import Control.Monad.IO.Class
import Data.Aeson
import qualified Data.ByteString as BS
import Data.Char
import Data.List (intersperse)
import Data.ProtoLens
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Data.Vector (Vector)
import Lens.Family2
import Proto.Temporal.Api.History.V1.Message
import Proto.Temporal.Api.History.V1.Message_Fields
import Temporal.Common (WorkflowId (..))
import Temporal.Core.Worker (HistoryPusher, closeHistory, newReplayWorker, pushHistory)
data InvalidHistoryException = InvalidHistoryProtobufException String
deriving stock (Int -> InvalidHistoryException -> ShowS
[InvalidHistoryException] -> ShowS
InvalidHistoryException -> String
(Int -> InvalidHistoryException -> ShowS)
-> (InvalidHistoryException -> String)
-> ([InvalidHistoryException] -> ShowS)
-> Show InvalidHistoryException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InvalidHistoryException -> ShowS
showsPrec :: Int -> InvalidHistoryException -> ShowS
$cshow :: InvalidHistoryException -> String
show :: InvalidHistoryException -> String
$cshowList :: [InvalidHistoryException] -> ShowS
showList :: [InvalidHistoryException] -> ShowS
Show, InvalidHistoryException -> InvalidHistoryException -> Bool
(InvalidHistoryException -> InvalidHistoryException -> Bool)
-> (InvalidHistoryException -> InvalidHistoryException -> Bool)
-> Eq InvalidHistoryException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InvalidHistoryException -> InvalidHistoryException -> Bool
== :: InvalidHistoryException -> InvalidHistoryException -> Bool
$c/= :: InvalidHistoryException -> InvalidHistoryException -> Bool
/= :: InvalidHistoryException -> InvalidHistoryException -> Bool
Eq)
deriving anyclass (Show InvalidHistoryException
Typeable InvalidHistoryException
(Typeable InvalidHistoryException, Show InvalidHistoryException) =>
(InvalidHistoryException -> SomeException)
-> (SomeException -> Maybe InvalidHistoryException)
-> (InvalidHistoryException -> String)
-> (InvalidHistoryException -> Bool)
-> Exception InvalidHistoryException
SomeException -> Maybe InvalidHistoryException
InvalidHistoryException -> Bool
InvalidHistoryException -> String
InvalidHistoryException -> SomeException
forall e.
(Typeable e, Show e) =>
(e -> SomeException)
-> (SomeException -> Maybe e)
-> (e -> String)
-> (e -> Bool)
-> Exception e
$ctoException :: InvalidHistoryException -> SomeException
toException :: InvalidHistoryException -> SomeException
$cfromException :: SomeException -> Maybe InvalidHistoryException
fromException :: SomeException -> Maybe InvalidHistoryException
$cdisplayException :: InvalidHistoryException -> String
displayException :: InvalidHistoryException -> String
$cbacktraceDesired :: InvalidHistoryException -> Bool
backtraceDesired :: InvalidHistoryException -> Bool
Exception)
readHistoryProtobufFile :: MonadIO m => FilePath -> m History
readHistoryProtobufFile :: forall (m :: * -> *). MonadIO m => String -> m History
readHistoryProtobufFile String
fp = IO History -> m History
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO History -> m History) -> IO History -> m History
forall a b. (a -> b) -> a -> b
$ do
res <- ByteString -> Either String History
forall msg. Message msg => ByteString -> Either String msg
decodeMessage (ByteString -> Either String History)
-> IO ByteString -> IO (Either String History)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO ByteString
BS.readFile String
fp
case res of
Left String
err -> InvalidHistoryException -> IO History
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO (InvalidHistoryException -> IO History)
-> InvalidHistoryException -> IO History
forall a b. (a -> b) -> a -> b
$ String -> InvalidHistoryException
InvalidHistoryProtobufException String
err
Right History
ok -> History -> IO History
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure History
ok
writeHistoryProtobufFile :: FilePath -> History -> IO ()
writeHistoryProtobufFile :: String -> History -> IO ()
writeHistoryProtobufFile String
fp History
hist = String -> ByteString -> IO ()
BS.writeFile String
fp (History -> ByteString
forall msg. Message msg => msg -> ByteString
encodeMessage History
hist)