Skip to content

Commit

Permalink
Separate nockma run commands into subcommands
Browse files Browse the repository at this point in the history
```
Usage: juvix dev nockma run COMMAND

  Subcommands used to run an Anoma program. Use with artefacts obtained from
  compilation with the anoma target

Available options:
  -h,--help                Show this help text

Available commands:
  builtin-evaluator        Run with the builtin Nockma evaluator
  ephemeral-client         Run with an ephemeral Anoma client
  with-client              Run with a running Anoma client
```
  • Loading branch information
paulcadman committed Nov 19, 2024
1 parent 11a4333 commit 1684ea5
Show file tree
Hide file tree
Showing 12 changed files with 263 additions and 82 deletions.
6 changes: 3 additions & 3 deletions app/Commands/Dev/Nockma/Options.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ data NockmaCommand
= NockmaRepl NockmaReplOptions
| NockmaEval NockmaEvalOptions
| NockmaFormat NockmaFormatOptions
| NockmaRun NockmaRunOptions
| NockmaRun NockmaRunCommand
| NockmaEncode NockmaEncodeOptions
| NockmaIde NockmaIdeCommand
deriving stock (Data)
Expand Down Expand Up @@ -53,8 +53,8 @@ parseNockmaCommand =
runInfo :: ParserInfo NockmaCommand
runInfo =
info
(NockmaRun <$> parseNockmaRunOptions)
(progDesc ("Run an Anoma program. It should be used with artefacts obtained from compilation with the anoma target. If the --" <> anomaDirOptLongStr <> " is given, then it runs the code in an anoma node"))
(NockmaRun <$> parseNockmaRunCommand)
(progDesc "Subcommands used to run an Anoma program. Use with artefacts obtained from compilation with the anoma target")

commandFromAsm :: Mod CommandFields NockmaCommand
commandFromAsm = command "eval" fromAsmInfo
Expand Down
56 changes: 9 additions & 47 deletions app/Commands/Dev/Nockma/Run.hs
Original file line number Diff line number Diff line change
@@ -1,51 +1,13 @@
module Commands.Dev.Nockma.Run where

import Anoma.Effect
import Commands.Base hiding (Atom)
import Commands.Base
import Commands.Dev.Nockma.Run.BuiltinClient as BuiltinClient
import Commands.Dev.Nockma.Run.EphemeralClient as EphemeralClient
import Commands.Dev.Nockma.Run.Options
import Juvix.Compiler.Nockma.Anoma
import Juvix.Compiler.Nockma.EvalCompiled
import Juvix.Compiler.Nockma.Evaluator
import Juvix.Compiler.Nockma.Pretty
import Juvix.Compiler.Nockma.Translation.FromSource qualified as Nockma
import Commands.Dev.Nockma.Run.WithClient as WithClient

runCommand :: forall r. (Members AppEffects r) => NockmaRunOptions -> Sem r ()
runCommand opts = do
afile <- fromAppPathFile inputFile
argsFile <- mapM fromAppPathFile (opts ^. nockmaRunArgs)
parsedArgs <- runAppError @JuvixError (mapM Nockma.cueJammedFileOrPretty argsFile)
parsedTerm <- runAppError @JuvixError (Nockma.cueJammedFileOrPretty afile)
case parsedTerm of
TermAtom {} -> exitFailMsg "Expected nockma input to be a cell"
t@(TermCell {}) -> case opts ^. nockmaRunAnomaDir of
Just path -> do
anomaDir <- AnomaPath <$> fromAppPathDir path
runInAnoma anomaDir t (maybe [] unfoldList parsedArgs)
Nothing -> do
let formula = anomaCallTuple parsedArgs
(counts, res) <-
runOpCounts
. runReader defaultEvalOptions
. runOutputSem @(Term Natural) (logInfo . mkAnsiText . ppTrace)
$ evalCompiledNock' t formula
putStrLn (ppPrint res)
let statsFile = replaceExtension' ".profile" afile
writeFileEnsureLn statsFile (prettyText counts)
where
inputFile :: AppPath File
inputFile = opts ^. nockmaRunFile

runInAnoma :: (Members AppEffects r) => AnomaPath -> Term Natural -> [Term Natural] -> Sem r ()
runInAnoma anoma t args = runAppError @SimpleError . runAnomaEphemeral anoma $ do
res <-
runNockma
RunNockmaInput
{ _runNockmaProgram = t,
_runNockmaArgs = args
}
let traces = res ^. runNockmaTraces
renderStdOutLn (annotate AnnImportant $ "Traces (" <> show (length traces) <> "):")
forM_ traces $ \tr ->
renderStdOutLn (ppPrint tr)
renderStdOutLn (annotate AnnImportant "Result:")
renderStdOutLn (ppPrint (res ^. runNockmaResult))
runCommand :: forall r. (Members AppEffects r) => NockmaRunCommand -> Sem r ()
runCommand = \case
NockmaRunBuiltinClient opts -> BuiltinClient.runCommand opts
NockmaRunEphemeralClient opts -> EphemeralClient.runCommand opts
NockmaRunWithClient opts -> WithClient.runCommand opts
38 changes: 38 additions & 0 deletions app/Commands/Dev/Nockma/Run/Anoma.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,38 @@
module Commands.Dev.Nockma.Run.Anoma where

import Anoma.Effect
import Commands.Base hiding (Atom)
import Juvix.Compiler.Nockma.Pretty
import Juvix.Compiler.Nockma.Translation.FromSource qualified as Nockma

data RunCommandArgs = RunCommandArgs
{ _runCommandArgsFile :: Maybe (AppPath File),
_runCommandProgramFile :: AppPath File
}

makeLenses ''RunCommandArgs

runInAnoma :: forall r. (Members '[Error SimpleError, Anoma] r, Members AppEffects r) => RunCommandArgs -> Sem r ()
runInAnoma runArgs = do
afile <- fromAppPathFile (runArgs ^. runCommandProgramFile)
argsFile <- mapM fromAppPathFile (runArgs ^. runCommandArgsFile)
parsedArgs <- runAppError @JuvixError (mapM Nockma.cueJammedFileOrPretty argsFile)
parsedTerm <- runAppError @JuvixError (Nockma.cueJammedFileOrPretty afile)
case parsedTerm of
TermAtom {} -> exitFailMsg "Expected nockma input to be a cell"
t@(TermCell {}) -> go t (maybe [] unfoldList parsedArgs)
where
go :: Term Natural -> [Term Natural] -> Sem r ()
go t args = do
res <-
runNockma
RunNockmaInput
{ _runNockmaProgram = t,
_runNockmaArgs = args
}
let traces = res ^. runNockmaTraces
renderStdOutLn (annotate AnnImportant $ "Traces (" <> show (length traces) <> "):")
forM_ traces $ \tr ->
renderStdOutLn (ppPrint tr)
renderStdOutLn (annotate AnnImportant "Result:")
renderStdOutLn (ppPrint (res ^. runNockmaResult))
29 changes: 29 additions & 0 deletions app/Commands/Dev/Nockma/Run/BuiltinClient.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@
module Commands.Dev.Nockma.Run.BuiltinClient where

import Commands.Base hiding (Atom)
import Commands.Dev.Nockma.Run.BuiltinClient.Options
import Juvix.Compiler.Nockma.Anoma
import Juvix.Compiler.Nockma.EvalCompiled
import Juvix.Compiler.Nockma.Evaluator
import Juvix.Compiler.Nockma.Pretty
import Juvix.Compiler.Nockma.Translation.FromSource qualified as Nockma

runCommand :: forall r. (Members AppEffects r) => NockmaRunBuiltinClientOptions -> Sem r ()
runCommand opts = do
afile <- fromAppPathFile (opts ^. nockmaRunBuiltinFile)
argsFile <- mapM fromAppPathFile (opts ^. nockmaRunBuiltinArgs)
parsedArgs <- runAppError @JuvixError (mapM Nockma.cueJammedFileOrPretty argsFile)
parsedTerm <- runAppError @JuvixError (Nockma.cueJammedFileOrPretty afile)
case parsedTerm of
TermAtom {} -> exitFailMsg "Expected nockma input to be a cell"
t@(TermCell {}) -> do
let formula = anomaCallTuple parsedArgs
(counts, res) <-
runOpCounts
. runReader defaultEvalOptions
. runOutputSem @(Term Natural) (logInfo . mkAnsiText . ppTrace)
$ evalCompiledNock' t formula
putStrLn (ppPrint res)
when (opts ^. nockmaRunBuiltinProfile) $ do
let statsFile = replaceExtension' ".profile" afile
writeFileEnsureLn statsFile (prettyText counts)
25 changes: 25 additions & 0 deletions app/Commands/Dev/Nockma/Run/BuiltinClient/Options.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
module Commands.Dev.Nockma.Run.BuiltinClient.Options where

import CommonOptions

data NockmaRunBuiltinClientOptions = NockmaRunBuiltinClientOptions
{ _nockmaRunBuiltinFile :: AppPath File,
_nockmaRunBuiltinAnomaDir :: Maybe (AppPath Dir),
_nockmaRunBuiltinProfile :: Bool,
_nockmaRunBuiltinArgs :: Maybe (AppPath File)
}
deriving stock (Data)

makeLenses ''NockmaRunBuiltinClientOptions

parseNockmaRunBuiltinClientOptions :: Parser NockmaRunBuiltinClientOptions
parseNockmaRunBuiltinClientOptions = do
_nockmaRunBuiltinFile <- parseInputFile FileExtNockma
_nockmaRunBuiltinArgs <- optional anomaArgsOpt
_nockmaRunBuiltinAnomaDir <- optional anomaDirOpt
_nockmaRunBuiltinProfile <-
switch
( long "profile"
<> help "Report evaluator profiling statistics"
)
pure NockmaRunBuiltinClientOptions {..}
19 changes: 19 additions & 0 deletions app/Commands/Dev/Nockma/Run/EphemeralClient.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
module Commands.Dev.Nockma.Run.EphemeralClient where

import Anoma.Effect
import Commands.Base hiding (Atom)
import Commands.Dev.Nockma.Run.Anoma
import Commands.Dev.Nockma.Run.EphemeralClient.Options

runCommand :: forall r. (Members AppEffects r) => NockmaRunEphemeralClientOptions -> Sem r ()
runCommand opts = do
anomaDir <- AnomaPath <$> fromAppPathDir (opts ^. nockmaRunEphemeralAnomaDir)
runAppError @SimpleError
. runAnomaEphemeral anomaDir
$ runInAnoma runArgs
where
runArgs =
RunCommandArgs
{ _runCommandProgramFile = opts ^. nockmaRunEphemeralFile,
_runCommandArgsFile = opts ^. nockmaRunEphemeralArgs
}
19 changes: 19 additions & 0 deletions app/Commands/Dev/Nockma/Run/EphemeralClient/Options.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
module Commands.Dev.Nockma.Run.EphemeralClient.Options where

import CommonOptions

data NockmaRunEphemeralClientOptions = NockmaRunEphemeralClientOptions
{ _nockmaRunEphemeralFile :: AppPath File,
_nockmaRunEphemeralAnomaDir :: AppPath Dir,
_nockmaRunEphemeralArgs :: Maybe (AppPath File)
}
deriving stock (Data)

makeLenses ''NockmaRunEphemeralClientOptions

parseNockmaRunEphemeralClientOptions :: Parser NockmaRunEphemeralClientOptions
parseNockmaRunEphemeralClientOptions = do
_nockmaRunEphemeralFile <- parseInputFile FileExtNockma
_nockmaRunEphemeralArgs <- optional anomaArgsOpt
_nockmaRunEphemeralAnomaDir <- anomaDirOpt
pure NockmaRunEphemeralClientOptions {..}
73 changes: 45 additions & 28 deletions app/Commands/Dev/Nockma/Run/Options.hs
Original file line number Diff line number Diff line change
@@ -1,34 +1,51 @@
module Commands.Dev.Nockma.Run.Options where
module Commands.Dev.Nockma.Run.Options
( module Commands.Dev.Nockma.Run.BuiltinClient.Options,
module Commands.Dev.Nockma.Run.EphemeralClient.Options,
module Commands.Dev.Nockma.Run.WithClient.Options,
module Commands.Dev.Nockma.Run.Options,
)
where

import Commands.Dev.Nockma.Run.BuiltinClient.Options
import Commands.Dev.Nockma.Run.EphemeralClient.Options
import Commands.Dev.Nockma.Run.WithClient.Options
import CommonOptions

data NockmaRunOptions = NockmaRunOptions
{ _nockmaRunFile :: AppPath File,
_nockmaRunAnomaDir :: Maybe (AppPath Dir),
_nockmaRunProfile :: Bool,
_nockmaRunArgs :: Maybe (AppPath File)
}
data NockmaRunCommand
= NockmaRunBuiltinClient NockmaRunBuiltinClientOptions
| NockmaRunEphemeralClient NockmaRunEphemeralClientOptions
| NockmaRunWithClient NockmaRunWithClientOptions
deriving stock (Data)

makeLenses ''NockmaRunOptions
makeLenses ''NockmaRunCommand

parseNockmaRunOptions :: Parser NockmaRunOptions
parseNockmaRunOptions = do
_nockmaRunFile <- parseInputFile FileExtNockma
_nockmaRunArgs <- optional $ do
_pathPath <-
option
somePreFileOpt
( long "args"
<> metavar "ARGS_FILE"
<> help "Path to file containing args. When run on anoma, the args file should contain a list (i.e. to pass 2 and [1 4] as args, the contents should be [2 [1 4] 0])."
<> action "file"
)
pure AppPath {_pathIsInput = True, ..}
_nockmaRunAnomaDir <- optional anomaDirOpt
_nockmaRunProfile <-
switch
( long "profile"
<> help "Report evaluator profiling statistics"
)
pure NockmaRunOptions {..}
parseNockmaRunCommand :: Parser NockmaRunCommand
parseNockmaRunCommand =
hsubparser
( mconcat
[ commandRunBuiltinClient,
commandRunEphemeralClient,
commandRunWithClient
]
)

commandRunBuiltinClient :: Mod CommandFields NockmaRunCommand
commandRunBuiltinClient =
command "builtin-evaluator" $
info
(NockmaRunBuiltinClient <$> parseNockmaRunBuiltinClientOptions)
(progDesc "Run with the builtin Nockma evaluator")

commandRunEphemeralClient :: Mod CommandFields NockmaRunCommand
commandRunEphemeralClient =
command "ephemeral-client" $
info
(NockmaRunEphemeralClient <$> parseNockmaRunEphemeralClientOptions)
(progDesc "Run with an ephemeral Anoma client")

commandRunWithClient :: Mod CommandFields NockmaRunCommand
commandRunWithClient =
command "with-client" $
info
(NockmaRunWithClient <$> parseNockmaRunWithClientOptions)
(progDesc "Run with a running Anoma client")
23 changes: 23 additions & 0 deletions app/Commands/Dev/Nockma/Run/WithClient.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
module Commands.Dev.Nockma.Run.WithClient where

import Anoma.Effect
import Commands.Base hiding (Atom)
import Commands.Dev.Nockma.Run.Anoma
import Commands.Dev.Nockma.Run.WithClient.Options

runCommand :: forall r. (Members AppEffects r) => NockmaRunWithClientOptions -> Sem r ()
runCommand opts =
runAppError @SimpleError
. runAnomaWithClient grpcInfo
$ runInAnoma runArgs
where
grpcInfo =
AnomaGrpcClientInfo
{ _anomaGrpcClientInfoUrl = opts ^. nockmaRunWithClientUrl,
_anomaGrpcClientInfoPort = opts ^. nockmaRunWithClientGrpcPort
}
runArgs =
RunCommandArgs
{ _runCommandProgramFile = opts ^. nockmaRunWithClientFile,
_runCommandArgsFile = opts ^. nockmaRunWithClientArgs
}
35 changes: 35 additions & 0 deletions app/Commands/Dev/Nockma/Run/WithClient/Options.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
module Commands.Dev.Nockma.Run.WithClient.Options where

import CommonOptions

data NockmaRunWithClientOptions = NockmaRunWithClientOptions
{ _nockmaRunWithClientFile :: AppPath File,
_nockmaRunWithClientGrpcPort :: Int,
_nockmaRunWithClientUrl :: String,
_nockmaRunWithClientArgs :: Maybe (AppPath File)
}
deriving stock (Data)

makeLenses ''NockmaRunWithClientOptions

parseNockmaRunWithClientOptions :: Parser NockmaRunWithClientOptions
parseNockmaRunWithClientOptions = do
_nockmaRunWithClientFile <- parseInputFile FileExtNockma
_nockmaRunWithClientArgs <- optional anomaArgsOpt
_nockmaRunWithClientGrpcPort <-
option
(fromIntegral <$> naturalNumberOpt)
( long "grpc-port"
<> short 'p'
<> help ("The GRPC port of a running Anoma client")
<> metavar "PORT"
)
_nockmaRunWithClientUrl <- do
let defaultUrl :: String = "localhost"
strOption
( long "url"
<> help ("The URL of a running Anoma client. default: " <> defaultUrl)
<> value defaultUrl
<> metavar "URL"
)
pure NockmaRunWithClientOptions {..}
12 changes: 12 additions & 0 deletions app/CommonOptions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -95,6 +95,18 @@ anomaDirOpt = do
_pathPath = path
}

anomaArgsOpt :: Parser (AppPath File)
anomaArgsOpt = do
_pathPath <-
option
somePreFileOpt
( long "args"
<> metavar "ARGS_FILE"
<> help "Path to file containing args. The args file should contain a list (i.e. to pass 2 and [1 4] as args, the contents should be [2 [1 4] 0])."
<> action "file"
)
pure AppPath {_pathIsInput = True, ..}

parseNumThreads :: Parser NumThreads
parseNumThreads = do
option
Expand Down
10 changes: 6 additions & 4 deletions src/Anoma/Effect/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -119,10 +119,12 @@ runAnomaEphemeral anomapath body = runReader anomapath . runProcess $ do
AnomaRpc method i -> anomaRpc' method i

runAnomaWithClient :: forall r a. (Members '[Logger, EmbedIO, Error SimpleError] r) => AnomaGrpcClientInfo -> Sem (Anoma ': r) a -> Sem r a
runAnomaWithClient grpcInfo body = runProcess $ do
runReader grpcInfo $ do
(`interpret` inject body) $ \case
AnomaRpc method i -> anomaRpc' method i
runAnomaWithClient grpcInfo body =
runProcess
. runReader grpcInfo
$ do
(`interpret` inject body) $ \case
AnomaRpc method i -> anomaRpc' method i

launchAnoma :: (Members '[Logger, EmbedIO, Error SimpleError] r) => AnomaPath -> Sem r ProcessHandle
launchAnoma anomapath = runReader anomapath . runProcess $ do
Expand Down

0 comments on commit 1684ea5

Please sign in to comment.