Skip to content

Commit

Permalink
PureScript: Rename all instances of CliSpec to Oclis
Browse files Browse the repository at this point in the history
  • Loading branch information
ad-si committed Feb 17, 2024
1 parent 259d222 commit 422ea67
Show file tree
Hide file tree
Showing 10 changed files with 623 additions and 600 deletions.
8 changes: 6 additions & 2 deletions flake.nix
Original file line number Diff line number Diff line change
Expand Up @@ -25,12 +25,16 @@
defaultPackage = naersk-lib.buildPackage ./.;
devShell = with pkgs; mkShell {
buildInputs = [
graphviz # For generating the processing-pipeline infographic
# For Oclis itself
cargo
graphviz # For generating the processing-pipeline infographic
pre-commit
rustc
rustfmt
pre-commit
rustPackages.clippy

# For target languages PureScript and JavaScript
nodejs_20
] ++ systemSpecificPkgs;
RUST_SRC_PATH = rustPlatform.rustLibSrc;
};
Expand Down
8 changes: 8 additions & 0 deletions purescript/makefile
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
.PHONY: help
help: makefile
@tail -n +4 makefile | grep ".PHONY"


.PHONY: test
test:
npx spago test
2 changes: 0 additions & 2 deletions purescript/src/CliSpec/readme.md

This file was deleted.

28 changes: 15 additions & 13 deletions purescript/src/CliSpec.purs → purescript/src/Oclis/Executor.purs
Original file line number Diff line number Diff line change
@@ -1,13 +1,15 @@
module CliSpec where
-- | CAUTION: THIS FILE IS GENERATED. DO NOT EDIT MANUALLY!

import CliSpec.Types
module Oclis where

import Oclis.Types

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

import Ansi.Codes (Color(..))
import Ansi.Output (withGraphics, foreground)
import CliSpec.Parser (tokensToCliArguments)
import CliSpec.Tokenizer (tokenizeCliArguments)
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 Down Expand Up @@ -36,7 +38,7 @@ errorAndExit message = do
setExitCode 1
pure $ Error message

parseCliSpec :: String -> Result String CliSpec
parseCliSpec :: String -> Result String Oclis
parseCliSpec cliSpecJsonStr = do
let cliSpecRes = fromEither $ jsonParser cliSpecJsonStr

Expand All @@ -49,12 +51,12 @@ parseCliSpec cliSpecJsonStr = do
# fromEither

callCommand
:: CliSpec
:: Oclis
-> String
-> Array CliArgument
-> (String -> String -> Array CliArgument -> Effect (Result String Unit))
-> Effect (Result String Unit)
callCommand (CliSpec cliSpec) usageString args executor = do
callCommand (Oclis cliSpec) usageString args executor = do
case args # head of
Nothing -> do
log "No arguments provided"
Expand Down Expand Up @@ -97,7 +99,7 @@ callCommand (CliSpec cliSpec) usageString args executor = do
let
commandMb = cliSpec.commands
# fromMaybe []
# find (\(CliSpec cmd) -> cmd.name == cmdName)
# find (\(Oclis cmd) -> cmd.name == cmdName)
providedArgs = args # drop 2

case commandMb of
Expand All @@ -111,7 +113,7 @@ callCommand (CliSpec cliSpec) usageString args executor = do
setExitCode 1
pure (Error errStr)

Just (CliSpec _command) -> do
Just (Oclis _command) -> do
executor cmdName usageString providedArgs

Just arg -> do
Expand All @@ -135,17 +137,17 @@ repeatString str n =
fold $ replicate n str

callCliApp
:: CliSpec
:: Oclis
-> (String -> String -> Array CliArgument -> Effect (Result String Unit))
-> Effect (Result String Unit)
callCliApp cliSpec@(CliSpec cliSpecRaw) executor = do
callCliApp cliSpec@(Oclis cliSpecRaw) executor = do
let
lengthLongestCmd :: Int
lengthLongestCmd =
cliSpecRaw.commands
# fromMaybe []
# foldl
( \acc (CliSpec cmd) ->
( \acc (Oclis cmd) ->
if acc > Str.length cmd.name then acc
else Str.length cmd.name
)
Expand All @@ -162,7 +164,7 @@ callCliApp cliSpec@(CliSpec cliSpecRaw) executor = do
( cliSpecRaw.commands
# fromMaybe []
# foldMap
( \(CliSpec cmd) ->
( \(Oclis cmd) ->
cmd.name
<>
( repeatString " "
Expand Down
Original file line number Diff line number Diff line change
@@ -1,13 +1,15 @@
module CliSpec.Parser
-- | CAUTION: THIS FILE IS GENERATED. DO NOT EDIT MANUALLY!

module Oclis.Parser
( findFlagLong
, findSubCmd
, tokensToCliArguments
) where

import Data.Result

import CliSpec.Tokenizer (CliArgToken(..))
import CliSpec.Types (CliArgPrim(..), CliArgument(..), CliSpec(..), Option)
import Oclis.Tokenizer (CliArgToken(..))
import Oclis.Types (CliArgPrim(..), CliArgument(..), Oclis(..), Option)
import Data.Array (drop, find, foldl, head, last, zip)
import Data.Maybe (Maybe(..), fromMaybe)
import Data.String.CodeUnits (singleton)
Expand Down Expand Up @@ -39,20 +41,20 @@ findOptionLong cliSpecOptionsMb flagName = do
# fromMaybe []
# find (\opt -> opt.name == Just flagName)

findSubCmd :: Maybe (Array CliSpec) -> String -> Maybe CliSpec
findSubCmd :: Maybe (Array Oclis) -> String -> Maybe Oclis
findSubCmd cliSpecCommands value = do
cliSpecCommands
# fromMaybe []
# find (\(CliSpec cmd) -> cmd.name == value)
# find (\(Oclis cmd) -> cmd.name == value)

-- | Verify that the remaining tokens are allowed
-- | for the given command specification and return
-- | the corresponding `CliArgument`s.
verifyTokensAreAllowed
:: CliSpec
:: Oclis
-> Array CliArgToken
-> Result String (Array CliArgument)
verifyTokensAreAllowed (CliSpec cliSpecRaw) tokens = do
verifyTokensAreAllowed (Oclis cliSpecRaw) tokens = do
let
argsAndTokens = zip
(cliSpecRaw.arguments # fromMaybe [])
Expand Down Expand Up @@ -104,12 +106,12 @@ verifyTokensAreAllowed (CliSpec cliSpecRaw) tokens = do
-- | by matching them against the spec.
-- | Especially for the differentiation between `Option`s and `Flag`s.
tokensToCliArguments
:: CliSpec
:: Oclis
-> Array CliArgToken
-> Result String (Array CliArgument)
tokensToCliArguments cliSpec@(CliSpec cliSpecRaw) tokens = do
tokensToCliArguments cliSpec@(Oclis cliSpecRaw) tokens = do
let
mainCmdRes :: Result String CliSpec
mainCmdRes :: Result String Oclis
mainCmdRes = case tokens # head of
Just (TextToken cmdName) ->
if
Expand Down Expand Up @@ -237,5 +239,5 @@ tokensToCliArguments cliSpec@(CliSpec cliSpecRaw) tokens = do
[]

sequence
$ [ mainCmdRes <#> (\(CliSpec cmdSpec) -> CmdArg cmdSpec.name) ]
$ [ mainCmdRes <#> (\(Oclis cmdSpec) -> CmdArg cmdSpec.name) ]
<> options
Original file line number Diff line number Diff line change
@@ -1,10 +1,12 @@
module CliSpec.Tokenizer
-- | CAUTION: THIS FILE IS GENERATED. DO NOT EDIT MANUALLY!

module Oclis.Tokenizer
( CliArgToken(..)
, tokenizeCliArgument
, tokenizeCliArguments
) where

import CliSpec.Types (CliArgPrim(..))
import Oclis.Types (CliArgPrim(..))
import Data.Array (concat, drop, groupBy, null, take, (:))
import Data.Array.NonEmpty (toArray)
import Data.Foldable (elem)
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
module CliSpec.Types where
-- | CAUTION: THIS FILE IS GENERATED. DO NOT EDIT MANUALLY!

module Oclis.Types where

import Data.Argonaut.Decode (decodeJson)
import Data.Argonaut.Decode.Class (class DecodeJson)
Expand Down Expand Up @@ -96,22 +98,22 @@ type CliSpecRaw =
, funcName :: Maybe String
, options :: Maybe (Array Option)
, arguments :: Maybe (Array Argument)
, commands :: Maybe (Array CliSpec)
, commands :: Maybe (Array Oclis)
}

-- | Must be a newtype to avoid circular references
newtype CliSpec = CliSpec CliSpecRaw
newtype Oclis = Oclis CliSpecRaw

derive instance genericCliSpec :: Generic CliSpec _
derive instance eqCliSpec :: Eq CliSpec
derive instance newtypeCliSpec :: Newtype CliSpec _
instance showCliSpec :: Show CliSpec where
show = \(CliSpec specRaw) -> show specRaw
derive instance genericCliSpec :: Generic Oclis _
derive instance eqCliSpec :: Eq Oclis
derive instance newtypeCliSpec :: Newtype Oclis _
instance showCliSpec :: Show Oclis where
show = \(Oclis specRaw) -> show specRaw

instance decodeJsonCliSpec :: DecodeJson CliSpec where
instance decodeJsonCliSpec :: DecodeJson Oclis where
decodeJson = \json -> do
raw <- decodeJson json
pure (CliSpec raw)
pure (Oclis raw)

emptyCliSpecRaw :: CliSpecRaw
emptyCliSpecRaw =
Expand All @@ -125,6 +127,6 @@ emptyCliSpecRaw =
, commands: Nothing
}

emptyCliSpec :: CliSpec
emptyCliSpec :: Oclis
emptyCliSpec =
CliSpec emptyCliSpecRaw
Oclis emptyCliSpecRaw
11 changes: 11 additions & 0 deletions purescript/src/Oclis/readme.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
> [!CAUTION]
> THIS FILE IS GENERATED. DO NOT EDIT MANUALLY.
# Oclis

CLI (Command Line Interface) app builder
based on a simple, obvious specification file.

Check out the documentation at
[github.com/Airsequel/Oclis](https://github.com/Airsequel/Oclis)
for more information.
Loading

0 comments on commit 422ea67

Please sign in to comment.