-- SPDX-FileCopyrightText: 2023 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA -- | Helpers used to call @octez-client@. module Morley.Client.TezosClient.Helpers ( CallMode(..) , callTezosClient , callTezosClientStrict , readProcessWithExitCode' ) where import Unsafe qualified ((!!)) import Colourista (formatWith, red) import Control.Exception (IOException, throwIO) import Data.ByteArray (ScrubbedBytes) import Data.Text qualified as T import System.Exit (ExitCode(..)) import System.Process (readProcessWithExitCode) import Morley.Client.Logging import Morley.Client.TezosClient.Types import Morley.Client.TezosClient.Types.Errors import Morley.Client.Util (scrubbedBytesToString) -- | Datatype that represents modes for calling node from @octez-client@. data CallMode = MockupMode -- ^ Mode in which @octez-client@ doesn't perform any actual RPC calls to the node -- and use mock instead. | ClientMode -- ^ Normal mode in which @octez-client@ performs all necessary RPC calls to the node. -- | Call @octez-client@ with given arguments. Arguments defined by -- config are added automatically. The second argument specifies what -- should be done in failure case. It takes stdout and stderr -- output. Possible handling: -- -- 1. Parse a specific error and throw it. -- 2. Parse an expected error that shouldn't cause a failure. -- Return @True@ in this case. -- 3. Detect an unexpected error, return @False@. -- In this case 'UnexpectedClientFailure' will be throw. callTezosClient :: forall env m. (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => (Text -> Text -> IO Bool) -> [String] -> CallMode -> Maybe ScrubbedBytes -> m Text callTezosClient errHandler args mode mbInput = retryEConnreset mode $ do TezosClientEnv {..} <- view tezosClientEnvL let extraArgs :: [String] extraArgs = mconcat [ ["-E", toCmdArg tceEndpointUrl] , maybe [] (\dir -> ["-d", dir]) tceMbTezosClientDataDir , ["--mode", case mode of MockupMode -> "mockup" ClientMode -> "client" ] ] allArgs = extraArgs ++ args logDebug $ "Running: " <> unwords (toText <$> tceTezosClientPath:allArgs) let ifNotEmpty prefix output | null output = "" | otherwise = prefix <> ":\n" <> output logOutput :: Text -> Text -> m () logOutput output errOutput = logDebug $ ifNotEmpty "stdout" output <> ifNotEmpty "stderr" errOutput liftIO (readProcessWithExitCode' tceTezosClientPath allArgs (maybe "" scrubbedBytesToString mbInput)) >>= \case (ExitSuccess, toText -> output, toText -> errOutput) -> output <$ logOutput output errOutput (ExitFailure errCode, toText -> output, toText -> errOutput) -> do checkCounterError errOutput checkEConnreset errOutput liftIO $ unlessM (errHandler output errOutput) $ throwM $ UnexpectedClientFailure errCode output errOutput output <$ logOutput output errOutput where checkCounterError :: Text -> m () checkCounterError errOutput | "Counter" `T.isPrefixOf` errOutput && "already used for contract" `T.isInfixOf` errOutput = do let splittedErrOutput = words errOutput liftIO $ throwM $ CounterIsAlreadyUsed (splittedErrOutput Unsafe.!! 1) (splittedErrOutput Unsafe.!! 5) checkCounterError _ = pass checkEConnreset :: Text -> m () checkEConnreset errOutput | "Unix.ECONNRESET" `T.isInfixOf` errOutput = throwM EConnreset checkEConnreset _ = pass -- Helper function that retries @octez-client@ call action in case of @ECONNRESET@. -- Note that this error cannot appear in case of 'MockupMode' call. retryEConnreset :: CallMode -> m a -> m a retryEConnreset MockupMode action = action retryEConnreset ClientMode action = retryEConnresetImpl 0 action retryEConnresetImpl :: Integer -> m a -> m a retryEConnresetImpl attempt action = action `catch` \err -> do case err of EConnreset -> if attempt >= maxRetryAmount then throwM err else retryEConnresetImpl (attempt + 1) action anotherErr -> throwM anotherErr maxRetryAmount = 5 -- | Call @octez-client@ and expect success. callTezosClientStrict :: (WithClientLog env m, HasTezosClientEnv env, MonadIO m, MonadCatch m) => [String] -> CallMode -> Maybe ScrubbedBytes -> m Text callTezosClientStrict = callTezosClient errHandler where errHandler _ _ = pure False -- | Variant of @readProcessWithExitCode@ that prints a better error in case of -- an exception in the inner @readProcessWithExitCode@ call. readProcessWithExitCode' :: FilePath -> [String] -> String -> IO (ExitCode, String, String) readProcessWithExitCode' fp args inp = catch (readProcessWithExitCode fp args inp) handler where handler :: IOException -> IO (ExitCode, String, String) handler e = do hPutStrLn @Text stderr $ formatWith [red] errorMsg throwIO e errorMsg = "ERROR!! There was an error in executing `" <> toText fp <> "` program. Is the \ \ executable available in PATH ?"