1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-15 18:13:56 +03:00
juvix/app/Commands/Termination.hs
Jonathan Cubides 3b0cde27bb
Add CLI improvements and shell testing (#131)
* Remove input file fields from command opts

* [cli] Make version and help commands

* Fix on reviews

* Fixes for dealing with global options inside subcmds

* Fix minijuvix emacs mode and add some instance to GlobalOpts

* Remove unrelated code

* Propagate globals opts in each cmd parser

* Add initial shell tests

* Add test-shell to makefile and CI

* Fix CI: adding .local/bin to PATH

* Fixing CI

* Installing shelltest just before running it

* Install app for shell testing

* Hide global flags after cmd. Fix shell tests accordingly.

* Fixing CI

* Shell test only run on ubuntu for now
2022-06-09 16:36:07 +02:00

100 lines
2.8 KiB
Haskell

module Commands.Termination where
import Control.Monad.Extra
import Data.Text qualified as Text
import GlobalOptions
import MiniJuvix.Prelude hiding (Doc)
import MiniJuvix.Syntax.Abstract.Pretty.Base qualified as A
import Options.Applicative
data TerminationCommand
= Calls CallsOptions
| CallGraph CallGraphOptions
data CallsOptions = CallsOptions
{ _callsFunctionNameFilter :: Maybe (NonEmpty Text),
_callsShowDecreasingArgs :: A.ShowDecrArgs
}
newtype CallGraphOptions = CallGraphOptions
{ _graphFunctionNameFilter :: Maybe (NonEmpty Text)
}
makeLenses ''CallsOptions
makeLenses ''CallGraphOptions
parseCalls :: Parser CallsOptions
parseCalls = do
_callsFunctionNameFilter <-
fmap msum . optional $
nonEmpty . Text.words
<$> option
str
( long "function"
<> short 'f'
<> metavar "fun1 fun2 ..."
<> help "Only shows the specified functions"
)
_callsShowDecreasingArgs <-
option
decrArgsParser
( long "show-decreasing-args"
<> short 'd'
<> value A.ArgRel
<> help "possible values: argument, relation, both"
)
pure CallsOptions {..}
where
decrArgsParser :: ReadM A.ShowDecrArgs
decrArgsParser = eitherReader $ \s ->
case map toLower s of
"argument" -> return A.OnlyArg
"relation" -> return A.OnlyRel
"both" -> return A.ArgRel
_ -> Left "bad argument"
parseCallGraph :: Parser CallGraphOptions
parseCallGraph = do
_graphFunctionNameFilter <-
fmap msum . optional $
nonEmpty . Text.words
<$> option
str
( long "function"
<> short 'f'
<> help "Only shows the specified function"
)
pure CallGraphOptions {..}
parseTerminationCommand :: Parser TerminationCommand
parseTerminationCommand =
hsubparser $
mconcat
[ commandCalls,
commandGraph
]
where
commandCalls :: Mod CommandFields TerminationCommand
commandCalls = command "calls" minfo
where
minfo :: ParserInfo TerminationCommand
minfo =
info
(Calls <$> parseCalls)
(progDesc "Compute the calls table of a .mjuvix file")
commandGraph :: Mod CommandFields TerminationCommand
commandGraph = command "graph" minfo
where
minfo :: ParserInfo TerminationCommand
minfo =
info
(CallGraph <$> parseCallGraph)
(progDesc "Compute the complete call graph of a .mjuvix file")
callsPrettyOptions :: GlobalOptions -> CallsOptions -> A.Options
callsPrettyOptions GlobalOptions {..} CallsOptions {..} =
A.defaultOptions
{ A._optShowNameIds = _globalShowNameIds,
A._optShowDecreasingArgs = _callsShowDecreasingArgs
}