Skip to content

Commit

Permalink
Load operator files
Browse files Browse the repository at this point in the history
  • Loading branch information
j-mueller committed Dec 20, 2024
1 parent 5a28714 commit 7105db0
Show file tree
Hide file tree
Showing 2 changed files with 26 additions and 9 deletions.
28 changes: 22 additions & 6 deletions src/lib/Wst/Cli.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,12 +2,13 @@
{-# LANGUAGE OverloadedStrings #-}
module Wst.Cli(runMain) where

import Blammo.Logging.Simple (Message ((:#)), MonadLogger, MonadLoggerIO,
WithLogger (..), logError, logInfo, logWarn,
runLoggerLoggingT)
import Blammo.Logging.Simple (MonadLogger, MonadLoggerIO, WithLogger (..),
logError, logInfo, runLoggerLoggingT)
import Control.Monad.Except (ExceptT, MonadError, runExceptT)
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.Reader (MonadReader, ReaderT, asks, runReaderT)
import Control.Monad.Reader (MonadReader, ReaderT, runReaderT)
import Convex.Wallet.Operator (OperatorConfigSigning)
import Convex.Wallet.Operator qualified as Operator
import Data.String (IsString (..))
import Options.Applicative (customExecParser, disambiguate, helper, idm, info,
prefs, showHelpOnEmpty, showHelpOnError)
Expand All @@ -26,8 +27,12 @@ runCommand :: Command -> IO ()
runCommand com = do
env <- RuntimeEnv.loadEnv
result <- runWstApp env $ case com of
Deploy -> logInfo "Deploy"
Manage txIn com -> logInfo "Manage"
Deploy config -> deploy config
Manage _txIn _com ->
-- TODO:
-- * Implement status check (call the query endpoints and print out a summary of the results)
-- * Start the server
logInfo "Manage"
case result of
Left err -> runLoggerLoggingT env $ logError (fromString $ show err)
Right a -> pure a
Expand All @@ -43,3 +48,14 @@ newtype WstApp a = WstApp { unWstApp :: ReaderT RuntimeEnv (ExceptT AppError IO)

runWstApp :: RuntimeEnv -> WstApp a -> IO (Either AppError a)
runWstApp env WstApp{unWstApp} = runExceptT (runReaderT unWstApp env)

deploy :: (MonadLogger m, MonadIO m) => OperatorConfigSigning -> m ()
deploy config = do
logInfo "Loading operator files"
_operator <- liftIO (Operator.loadOperatorFiles config)
-- TODO:
-- Use blockfrost backend to run Wst.Offchain.Endpoints.Deployment with the operator's funds
-- Then use operator key to sign
-- Then submit transaction to blockfrost
-- Convex.Blockfrost.runBLockfrostT for the monadblockchain / monadutxoquery effects
pure ()
7 changes: 4 additions & 3 deletions src/lib/Wst/Cli/Command.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,14 +8,15 @@ module Wst.Cli.Command(

import Cardano.Api (TxIn (..), TxIx (..))
import Control.Monad (when)
import Convex.Wallet.Operator (OperatorConfigSigning,
parseOperatorConfigSigning)
import Data.String (IsString (..))
import Options.Applicative (CommandFields, Mod, Parser, ReadM, argument,
command, eitherReader, fullDesc, help, info, long,
many, metavar, optional, progDesc, short, str,
strOption, subparser, (<|>))
import Text.Read (readMaybe)


parseCommand :: Parser Command
parseCommand =
subparser $
Expand All @@ -25,7 +26,7 @@ parseCommand =
]

data Command =
Deploy
Deploy OperatorConfigSigning
| Manage TxIn ManageCommand
deriving Show

Expand All @@ -38,7 +39,7 @@ data ManageCommand =
parseDeploy :: Mod CommandFields Command
parseDeploy =
command "deploy" $
info (pure Deploy) (fullDesc <> progDesc "Deploy the directory and global params")
info (Deploy <$> parseOperatorConfigSigning) (fullDesc <> progDesc "Deploy the directory and global params")

parseManage :: Mod CommandFields Command
parseManage =
Expand Down

0 comments on commit 7105db0

Please sign in to comment.