Skip to content

Commit

Permalink
CLI setup
Browse files Browse the repository at this point in the history
  • Loading branch information
j-mueller committed Dec 20, 2024
1 parent 01c808a commit 5a28714
Show file tree
Hide file tree
Showing 4 changed files with 76 additions and 5 deletions.
34 changes: 31 additions & 3 deletions src/lib/Wst/Cli.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,19 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
module Wst.Cli(runMain) where

import Blammo.Logging.Simple (Message ((:#)), MonadLogger, MonadLoggerIO,
WithLogger (..), logError, logInfo, logWarn,
runLoggerLoggingT)
import Control.Monad.Except (ExceptT, MonadError, runExceptT)
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.Reader (MonadReader, ReaderT, asks, runReaderT)
import Data.String (IsString (..))
import Options.Applicative (customExecParser, disambiguate, helper, idm, info,
prefs, showHelpOnEmpty, showHelpOnError)
import Wst.Cli.Command (Command, parseCommand)
import Wst.Cli.Command (Command (..), parseCommand)
import Wst.Cli.RuntimeEnv (RuntimeEnv)
import Wst.Cli.RuntimeEnv qualified as RuntimeEnv

runMain :: IO ()
runMain = do
Expand All @@ -13,5 +24,22 @@ runMain = do

runCommand :: Command -> IO ()
runCommand com = do
putStrLn "runCommand"
print com
env <- RuntimeEnv.loadEnv
result <- runWstApp env $ case com of
Deploy -> logInfo "Deploy"
Manage txIn com -> logInfo "Manage"
case result of
Left err -> runLoggerLoggingT env $ logError (fromString $ show err)
Right a -> pure a

data AppError = AppError
deriving stock Show

newtype WstApp a = WstApp { unWstApp :: ReaderT RuntimeEnv (ExceptT AppError IO) a }
deriving newtype (Monad, Applicative, Functor, MonadIO, MonadReader RuntimeEnv, MonadError AppError)
deriving
(MonadLogger, MonadLoggerIO)
via (WithLogger RuntimeEnv (ExceptT AppError IO))

runWstApp :: RuntimeEnv -> WstApp a -> IO (Either AppError a)
runWstApp env WstApp{unWstApp} = runExceptT (runReaderT unWstApp env)
2 changes: 1 addition & 1 deletion src/lib/Wst/Cli/Command.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ data Command =
-- | Commands that require a deployed system
data ManageCommand =
Status
| StartServer
deriving stock Show

parseDeploy :: Mod CommandFields Command
Expand Down Expand Up @@ -63,7 +64,6 @@ txInReader = eitherReader $ \str -> do
(txId, txIx) <- case break ((==) '.') str of
(txId, _:txIx) -> Right (txId, txIx)
_ -> Left "Expected <tx-id>.<index>"
-- 8c728a68fed42fe4893fb84ee2c6276a25e642d9892962af3234f952ea641993
when (length txId /= 64) $ Left "Expected tx ID with 64 characters"
ix <- case readMaybe @Word txIx of
Nothing -> Left "Expected tx index"
Expand Down
39 changes: 39 additions & 0 deletions src/lib/Wst/Cli/RuntimeEnv.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
{-# LANGUAGE TemplateHaskell #-}
{-| Data that we need when running the CLI
-}
module Wst.Cli.RuntimeEnv(
RuntimeEnv(..),
loadEnv,
) where

import Blammo.Logging (Logger)
import Blammo.Logging.Logger (HasLogger (..), newLogger)
import Blammo.Logging.LogSettings.Env qualified as LogSettingsEnv
import Blockfrost.Auth (mkProject)
import Blockfrost.Client.Auth qualified as Blockfrost
import Control.Lens (makeLensesFor)
import Data.Text qualified as Text
import System.Environment qualified

data RuntimeEnv
= RuntimeEnv
{ envLogger :: Logger
, envBlockfrost :: Blockfrost.Project

}

makeLensesFor
[ ("envLogger", "logger")
, ("envBlockfrostProject", "blockfrostProject")
]
'RuntimeEnv

instance HasLogger RuntimeEnv where
loggerL = logger

-- | Load the 'RuntimeEnv' from environment variables
loadEnv :: IO RuntimeEnv
loadEnv =
RuntimeEnv
<$> (LogSettingsEnv.parse >>= newLogger)
<*> fmap (mkProject . Text.pack) (System.Environment.getEnv "WST_BLOCKFROST_TOKEN")
6 changes: 5 additions & 1 deletion src/wst-poc.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,7 @@ library
Types.Constants
Wst.Cli
Wst.Cli.Command
Wst.Cli.RuntimeEnv
Wst.Client
Wst.Offchain
Wst.Offchain.BuildTx.Blacklist
Expand All @@ -90,8 +91,11 @@ library
hs-source-dirs: lib
build-depends:
, aeson
, base >=4.14 && <4.20
, base >=4.14 && <4.20
, base16-bytestring
, Blammo
, blockfrost-api
, blockfrost-client-core
, bytestring
, cardano-api
, cardano-ledger-api
Expand Down

0 comments on commit 5a28714

Please sign in to comment.