Skip to content

Commit

Permalink
PS: Simplify execution by automatically including the default spec
Browse files Browse the repository at this point in the history
  • Loading branch information
ad-si committed Feb 19, 2024
1 parent c2a2d86 commit c298730
Show file tree
Hide file tree
Showing 5 changed files with 70 additions and 14 deletions.
9 changes: 9 additions & 0 deletions purescript/spago.lock
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ workspace:
- argonaut
- argonaut-generic
- console
- debug
- effect
- node-process
- prelude
Expand All @@ -31,6 +32,7 @@ workspace:
- contravariant
- control
- datetime
- debug
- distributive
- effect
- either
Expand Down Expand Up @@ -763,6 +765,13 @@ packages:
- partial
- prelude
- tuples
debug:
type: registry
version: 6.0.2
integrity: sha256-vmkYFuXYuELBzeauvgHG6E6Kf/Hp1dAnxwE9ByHfwSg=
dependencies:
- functions
- prelude
distributive:
type: registry
version: 6.0.0
Expand Down
1 change: 1 addition & 0 deletions purescript/spago.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ package:
- argonaut
- argonaut-generic
- console
- debug
- effect
- node-process
- prelude
Expand Down
38 changes: 30 additions & 8 deletions purescript/src/Oclis/Executor.purs
Original file line number Diff line number Diff line change
Expand Up @@ -4,14 +4,10 @@

module Oclis where

import Oclis.Types

import Prelude (Unit, bind, discard, pure, unit, (#), ($), (-), (<>), (>), (||))

import Ansi.Codes (Color(..))
import Ansi.Output (withGraphics, foreground)
import Oclis.Parser (tokensToCliArguments)
import Oclis.Tokenizer (tokenizeCliArguments)
import Data.Argonaut.Decode (decodeJson)
import Data.Argonaut.Decode.Error (printJsonDecodeError)
import Data.Argonaut.Parser (jsonParser)
Expand All @@ -25,6 +21,11 @@ import Effect (Effect)
import Effect.Class.Console (log, error)
import Node.Process (argv, setExitCode)

import Oclis.Parser (tokensToCliArguments)
import Oclis.SpecEmbed (fileContent)
import Oclis.Tokenizer (tokenizeCliArguments)
import Oclis.Types

-- TODO: Automatically disable colors if not supported
makeRed :: String -> String
makeRed str =
Expand Down Expand Up @@ -144,11 +145,34 @@ repeatString :: String -> Int -> String
repeatString str n =
fold $ replicate n str

callCliApp
-- | Convenience function to call the CLI app with the default spec and args.
-- | Use `callCliAppWith`` if you want to provide your own values.
callCliApp :: (ExecutorContext -> Effect (Result String Unit)) -> Effect Unit
callCliApp executor =
case parseCliSpec fileContent of
Error errMsg -> do
error $
"ERROR:\n"
<> "The auto-generated CLI specification in SpecEmbed.purs "
<> "could not be parsed.\n"
<> "This should not be possible!\n"
<> "Please make sure you didn't accidentally modify any Oclis files\n"
<> "and report following error at "
<> "https://github.com/Airsequel/Oclis/issues/new:\n"
<> "\n"
<> errMsg
setExitCode 1
Ok cliSpec -> do
arguments <- argv
_ <- callCliAppWith cliSpec executor arguments
pure unit

callCliAppWith
:: Oclis
-> (ExecutorContext -> Effect (Result String Unit))
-> Array String
-> Effect (Result String Unit)
callCliApp cliSpec@(Oclis cliSpecRaw) executor = do
callCliAppWith cliSpec@(Oclis cliSpecRaw) executor arguments = do
let
lengthLongestCmd :: Int
lengthLongestCmd =
Expand Down Expand Up @@ -184,8 +208,6 @@ callCliApp cliSpec@(Oclis cliSpecRaw) executor = do
)
)

arguments <- argv

let
argsNoInterpreter = arguments # drop 1 -- Drop "node"
cliArgsMb =
Expand Down
14 changes: 14 additions & 0 deletions purescript/src/Oclis/SpecEmbed.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
-- | This file exists only for testing purposes.
-- | The actual implementation in the user's project
-- | is generated by the `oclis build` command.

module Oclis.SpecEmbed where

fileContent :: String
fileContent =
"""
{
"name": "placeholder",
"description": "This is a placeholder command"
}
"""
22 changes: 16 additions & 6 deletions purescript/test/Executor.purs
Original file line number Diff line number Diff line change
Expand Up @@ -9,14 +9,24 @@ import Effect.Class (liftEffect)
import Test.Spec (Spec, describe, it)
import Test.Spec.Assertions (fail, shouldEqual, shouldReturn)

import Oclis (callCommand)
import Oclis (callCliApp, callCommand)
import Oclis.Parser (tokensToCliArguments)
import Oclis.Tokenizer (tokenizeCliArguments)
import Oclis.Types (CliArgPrim(..), CliArgument(..), Oclis(..), emptyCliSpecRaw)

tests :: Spec Unit
tests =
describe "Execution" do
it "executes a command with included spec" do
let
executor context = do
context.command `shouldEqual` Nothing
context.usageString `shouldEqual` "xxx"
context.arguments `shouldEqual` []
pure $ Ok unit

liftEffect (callCliApp executor) `shouldReturn` unit

describe "Help" do
let
cliSpec = Oclis emptyCliSpecRaw
Expand Down Expand Up @@ -65,12 +75,12 @@ tests =
cliSpec = Oclis emptyCliSpecRaw
usageString = "Irrelevant"
executor context = do
context.command `shouldEqual` Just "help"
context.command `shouldEqual` Just "version"
context.usageString `shouldEqual` usageString
context.arguments `shouldEqual` []
pure $ Ok unit

it "shows help output for -v" do
it "shows version output for -v" do
let
toolArgs = [ "git", "-v" ]
tokens = tokenizeCliArguments toolArgs
Expand All @@ -81,7 +91,7 @@ tests =
liftEffect (callCommand cliSpec usageString cliArgs executor)
`shouldReturn` (Ok unit)

it "shows help output for --version" do
it "shows version output for --version" do
let
toolArgs = [ "git", "--version" ]
tokens = tokenizeCliArguments toolArgs
Expand All @@ -92,9 +102,9 @@ tests =
liftEffect (callCommand cliSpec usageString cliArgs executor)
`shouldReturn` (Ok unit)

it "shows help output for `help`" do
it "shows version output for `version`" do
let
toolArgs = [ "git", "help" ]
toolArgs = [ "git", "version" ]
tokens = tokenizeCliArguments toolArgs

case tokensToCliArguments cliSpec tokens of
Expand Down

0 comments on commit c298730

Please sign in to comment.