-- SPDX-FileCopyrightText: 2021 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA -- | Morley client initialization. module Morley.Client.Init ( MorleyClientConfig (..) , mkMorleyClientEnv , mkLogAction -- * Lens , mccEndpointUrlL , mccTezosClientPathL , mccMbTezosClientDataDirL , mccVerbosityL , mccSecretKeyL ) where import Colog (cmap, fmtMessage, logTextStderr, msgSeverity) import Colog.Core (Severity(..), filterBySeverity) import Morley.Util.Lens import Servant.Client (BaseUrl(..)) import System.Environment (lookupEnv) import Morley.Client.Env import Morley.Client.Logging (ClientLogAction, logFlush) import Morley.Client.RPC.HttpClient import Morley.Client.TezosClient.Impl (getTezosClientConfig) import Morley.Client.TezosClient.Types import Morley.Tezos.Crypto.Ed25519 qualified as Ed25519 -- | Data necessary for morley client initialization. data MorleyClientConfig = MorleyClientConfig { mccEndpointUrl :: Maybe BaseUrl -- ^ URL of tezos endpoint on which operations are performed , mccTezosClientPath :: FilePath -- ^ Path to @tezos-client@ binary through which operations are -- performed , mccMbTezosClientDataDir :: Maybe FilePath -- ^ Path to @tezos-client@ data directory. , mccVerbosity :: Word -- ^ Verbosity level. @0@ means that only important messages will be -- printed. The greater this value is, the more messages will be -- printed during execution. After some small unspecified limit -- increasing this value does not change anything. , mccSecretKey :: Maybe Ed25519.SecretKey -- ^ Custom secret key to use for signing. } deriving stock Show makeLensesWith postfixLFields ''MorleyClientConfig -- | Construct 'MorleyClientEnv'. -- -- * @tezos-client@ path is taken from 'MorleyClientConfig', but can be -- overridden using @MORLEY_TEZOS_CLIENT@ environment variable. -- * Node data is taken from @tezos-client@ config and can be overridden -- by 'MorleyClientConfig'. -- * The rest is taken from 'MorleyClientConfig' as is. mkMorleyClientEnv :: MonadIO m => MorleyClientConfig -> IO (MorleyClientEnv' m) mkMorleyClientEnv MorleyClientConfig{..} = do envTezosClientPath <- lookupEnv "MORLEY_TEZOS_CLIENT" let tezosClientPath = fromMaybe mccTezosClientPath envTezosClientPath TezosClientConfig {..} <- getTezosClientConfig tezosClientPath mccMbTezosClientDataDir let endpointUrl = fromMaybe tcEndpointUrl mccEndpointUrl tezosClientEnv = TezosClientEnv { tceEndpointUrl = endpointUrl , tceTezosClientPath = tezosClientPath , tceMbTezosClientDataDir = mccMbTezosClientDataDir } clientEnv <- newClientEnv endpointUrl pure MorleyClientEnv { mceTezosClient = tezosClientEnv , mceLogAction = mkLogAction mccVerbosity , mceSecretKey = mccSecretKey , mceClientEnv = clientEnv } -- | Make appropriate 'ClientLogAction' based on verbosity specified by the user. mkLogAction :: MonadIO m => Word -> ClientLogAction m mkLogAction verbosity = filterBySeverity severity msgSeverity (fmtMessage `cmap` logTextStderrFlush) where severity = case verbosity of 0 -> Warning 1 -> Info _ -> Debug logTextStderrFlush = logTextStderr <> logFlush stderr