-- SPDX-FileCopyrightText: 2023 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA -- | @octez-client@ config. module Morley.Client.TezosClient.Config ( TezosClientConfig (..) -- * @octez-client@ api , getTezosClientConfig ) where import Data.Aeson (FromJSON(..), eitherDecodeStrict, withObject, (.:)) import Servant.Client (BaseUrl(..)) import System.Exit (ExitCode(..)) import Morley.Client.TezosClient.Helpers import Morley.Client.TezosClient.Types.Errors -- | Configuration maintained by @octez-client@, see its @config@ subcommands -- (e. g. @octez-client config show@). -- Only the field we are interested in is present here. newtype TezosClientConfig = TezosClientConfig { tcEndpointUrl :: BaseUrl } deriving stock Show -- | For reading @octez-client@ config. instance FromJSON TezosClientConfig where parseJSON = withObject "node info" $ \o -> TezosClientConfig <$> o .: "endpoint" -- | Read @octez-client@ configuration. getTezosClientConfig :: FilePath -> Maybe FilePath -> IO TezosClientConfig getTezosClientConfig client mbDataDir = do t <- readProcessWithExitCode' client (maybe [] (\dir -> ["-d", dir]) mbDataDir ++ ["config", "show"]) "" case t of (ExitSuccess, toText -> output, _) -> case eitherDecodeStrict . encodeUtf8 . toText $ output of Right config -> pure config Left err -> throwM $ ConfigParseError err (ExitFailure errCode, toText -> output, toText -> errOutput) -> throwM $ UnexpectedClientFailure errCode output errOutput