mirror of
https://github.com/natefaubion/purescript-tidy.git
synced 2024-11-26 00:09:27 +03:00
Use argparse-basic for bin
This commit is contained in:
parent
9fab3f7cf7
commit
8ae9cac8f2
141
bin/Main.purs
141
bin/Main.purs
@ -2,16 +2,16 @@ module Main where
|
||||
|
||||
import Prelude
|
||||
|
||||
import ArgParse.Basic (ArgParser)
|
||||
import ArgParse.Basic as Arg
|
||||
import Control.Parallel (parTraverse)
|
||||
import Data.Array as Array
|
||||
import Data.Either (Either(..))
|
||||
import Data.Foldable (elem, findMap, fold, foldMap, foldl, foldr, for_)
|
||||
import Data.Int as Int
|
||||
import Data.Foldable (fold, foldMap, foldl, foldr, for_)
|
||||
import Data.Map as Map
|
||||
import Data.Maybe (Maybe(..), fromMaybe)
|
||||
import Data.Monoid (power)
|
||||
import Data.Newtype (unwrap)
|
||||
import Data.Number as Number
|
||||
import Data.String (Pattern(..))
|
||||
import Data.String as String
|
||||
import Data.Tuple (Tuple(..), snd, uncurry)
|
||||
@ -38,32 +38,123 @@ import PureScript.CST.TokenStream (TokenStep(..), TokenStream)
|
||||
import PureScript.CST.TokenStream as TokenStream
|
||||
import PureScript.CST.Types (Declaration(..), Export(..), FixityOp(..), Module(..), ModuleBody(..), ModuleHeader(..), ModuleName, Name(..), Operator(..), Separated(..), Token(..), Wrapped(..))
|
||||
|
||||
type FormatOptions =
|
||||
{ indent :: Int
|
||||
, operators :: Maybe String
|
||||
, ribbon :: Number
|
||||
, unicode :: UnicodeOption
|
||||
, width :: Int
|
||||
}
|
||||
|
||||
data Command
|
||||
= GenerateOperators (Array String)
|
||||
| FormatInPlace FormatOptions (Array String)
|
||||
| Format FormatOptions
|
||||
|
||||
parser :: ArgParser Command
|
||||
parser =
|
||||
Arg.choose "command"
|
||||
[ Arg.command [ "generate-operators" ]
|
||||
"Generate an operator precedence table for better operator formatting.\nBest used with `spago sources`. Prints to stdout."
|
||||
do
|
||||
GenerateOperators <$> pursGlobs
|
||||
<* Arg.flagHelp
|
||||
, Arg.command [ "format-in-place" ]
|
||||
"Format source files in place."
|
||||
do
|
||||
FormatInPlace <$> formatOptions <*> pursGlobs
|
||||
<* Arg.flagHelp
|
||||
, Arg.command [ "format" ]
|
||||
"Format input over stdin."
|
||||
do
|
||||
Format <$> formatOptions
|
||||
<* Arg.flagHelp
|
||||
]
|
||||
<* Arg.flagInfo [ "--version", "-v" ] "Shows the current version." "v1.0.0"
|
||||
<* Arg.flagHelp
|
||||
where
|
||||
formatOptions =
|
||||
Arg.fromRecord
|
||||
{ indent:
|
||||
Arg.argument [ "--indent", "-i" ]
|
||||
"Number of spaces to use as indentation.\nDefaults to 2."
|
||||
# Arg.int
|
||||
# Arg.default 2
|
||||
, operators:
|
||||
Arg.argument [ "--operators", "-o" ]
|
||||
"Path to an operator table generated by `generate-operators`.\nDefault is to use a pre-generated table of core and contrib."
|
||||
# Arg.unformat "FILE_PATH" pure
|
||||
# Arg.optional
|
||||
, ribbon:
|
||||
Arg.argument [ "--ribbon", "-r" ]
|
||||
"The ratio of printable width to maximum width.\nFrom 0 to 1. Defaults to 1."
|
||||
# Arg.number
|
||||
# Arg.default 1.0
|
||||
, unicode: unicodeOption
|
||||
, width:
|
||||
Arg.argument [ "--width", "-w" ]
|
||||
"The maximum width of the document in columns.\nDefaults to no maximum."
|
||||
# Arg.int
|
||||
# Arg.default top
|
||||
}
|
||||
|
||||
unicodeOption =
|
||||
Arg.choose "unicode argument"
|
||||
[ Arg.flag [ "--unicode-source", "-us" ]
|
||||
"Unicode punctuation is rendered as it appears in the source input.\nDefault."
|
||||
$> UnicodeSource
|
||||
, Arg.flag [ "--unicode-always", "-ua" ]
|
||||
"Unicode punctuation is always preferred."
|
||||
$> UnicodeAlways
|
||||
, Arg.flag [ "--unicode-never", "-un" ]
|
||||
"Unicode punctuation is never preferred."
|
||||
$> UnicodeNever
|
||||
]
|
||||
# Arg.default UnicodeSource
|
||||
|
||||
pursGlobs =
|
||||
Arg.anyNotFlag "PURS_GLOB" "Globs for PureScript sources."
|
||||
# Arg.unfolded1
|
||||
|
||||
main :: Effect Unit
|
||||
main = launchAff_ do
|
||||
args <- Array.drop 1 <$> liftEffect Process.argv
|
||||
case Array.uncons args of
|
||||
Just { head, tail } | head == "generate-operators" ->
|
||||
operatorTableCommand tail
|
||||
_ ->
|
||||
formatCommand args
|
||||
args <- Array.drop 2 <$> liftEffect Process.argv
|
||||
let
|
||||
parsedCmd =
|
||||
Arg.parseArgs "purs-tidy" "A tidy-upper for PureScript source code." parser args
|
||||
|
||||
formatCommand :: Array String -> Aff Unit
|
||||
case parsedCmd of
|
||||
Left err -> do
|
||||
Console.log $ Arg.printArgError err
|
||||
case err of
|
||||
Arg.ArgError _ Arg.ShowHelp ->
|
||||
liftEffect $ Process.exit 0
|
||||
Arg.ArgError _ (Arg.ShowInfo _) ->
|
||||
liftEffect $ Process.exit 0
|
||||
_ ->
|
||||
liftEffect $ Process.exit 1
|
||||
Right cmd ->
|
||||
case cmd of
|
||||
GenerateOperators globs ->
|
||||
generateOperatorsCommand globs
|
||||
FormatInPlace options globs ->
|
||||
mempty
|
||||
Format options ->
|
||||
formatCommand options
|
||||
|
||||
formatCommand :: FormatOptions -> Aff Unit
|
||||
formatCommand args = do
|
||||
contents <- readStdin
|
||||
let
|
||||
unicode
|
||||
| elem "--unicode-never" args = UnicodeNever
|
||||
| elem "--unicode-always" args = UnicodeAlways
|
||||
| otherwise = UnicodeSource
|
||||
|
||||
pageWidth = fromMaybe top $ findMap (String.stripPrefix (Pattern "--width=") >=> Int.fromString) args
|
||||
ribbonRatio = fromMaybe 1.0 $ findMap (String.stripPrefix (Pattern "--ribbon=") >=> Number.fromString) args
|
||||
indentWidth = fromMaybe 2 $ findMap (String.stripPrefix (Pattern "--indent=") >=> Int.fromString) args
|
||||
indentUnit = power " " indentWidth
|
||||
print = Dodo.print Dodo.plainText { pageWidth, ribbonRatio, indentWidth, indentUnit }
|
||||
print = Dodo.print Dodo.plainText
|
||||
{ pageWidth: args.width
|
||||
, ribbonRatio: args.ribbon
|
||||
, indentWidth: args.indent
|
||||
, indentUnit: power " " args.indent
|
||||
}
|
||||
|
||||
operators <-
|
||||
case findMap (String.stripPrefix (Pattern "--operators=")) args of
|
||||
case args.operators of
|
||||
Nothing ->
|
||||
pure $ parseOperatorTable defaultOperators
|
||||
Just path -> do
|
||||
@ -72,10 +163,10 @@ formatCommand args = do
|
||||
|
||||
case parseModule contents of
|
||||
ParseSucceeded ok -> do
|
||||
let opts = defaultFormatOptions { operators = remapOperators operators ok, unicode = unicode }
|
||||
let opts = defaultFormatOptions { operators = remapOperators operators ok, unicode = args.unicode }
|
||||
Console.log $ print $ toDoc $ formatModule opts ok
|
||||
ParseSucceededWithErrors ok _ -> do
|
||||
let opts = defaultFormatOptions { operators = remapOperators operators ok, unicode = unicode }
|
||||
let opts = defaultFormatOptions { operators = remapOperators operators ok, unicode = args.unicode }
|
||||
Console.log $ print $ toDoc $ formatModule opts ok
|
||||
ParseFailed err ->
|
||||
Console.log $ printParseError err.error
|
||||
@ -90,8 +181,8 @@ readStdin = makeAff \k -> do
|
||||
k <<< Right =<< Ref.read contents
|
||||
pure mempty
|
||||
|
||||
operatorTableCommand :: Array String -> Aff Unit
|
||||
operatorTableCommand globs = do
|
||||
generateOperatorsCommand :: Array String -> Aff Unit
|
||||
generateOperatorsCommand globs = do
|
||||
sourcePaths <- expandGlobsCwd globs
|
||||
modules <- sourcePaths # Array.fromFoldable # parTraverse \path -> do
|
||||
contents <- liftEffect <<< Buffer.toString UTF8 =<< FS.readFile path
|
||||
|
@ -1,6 +1,7 @@
|
||||
{ name = "purescript-tidy-cli"
|
||||
, dependencies =
|
||||
[ "aff"
|
||||
, "argparse-basic"
|
||||
, "console"
|
||||
, "dodo-printer"
|
||||
, "effect"
|
||||
|
@ -47,6 +47,18 @@ let additions =
|
||||
, repo = "https://github.com/natefaubion/purescript-node-glob-basic.git"
|
||||
, version = "v1.1.0"
|
||||
}
|
||||
, argparse-basic =
|
||||
{ dependencies =
|
||||
[ "either"
|
||||
, "foldable-traversable"
|
||||
, "lists"
|
||||
, "maybe"
|
||||
, "record"
|
||||
, "strings"
|
||||
]
|
||||
, repo = "https://github.com/natefaubion/purescript-argparse-basic.git"
|
||||
, version = "v1.0.0"
|
||||
}
|
||||
}
|
||||
|
||||
in upstream // overrides // additions
|
||||
|
@ -5,7 +5,7 @@ import Prelude
|
||||
import Data.Array (mapWithIndex)
|
||||
import Data.Array as Array
|
||||
import Data.Maybe (Maybe(..))
|
||||
import Data.String (Pattern(..), Replacement(..))
|
||||
import Data.String (Pattern(..))
|
||||
import Data.String as String
|
||||
import Effect (Effect)
|
||||
import Node.Buffer as Buffer
|
||||
|
Loading…
Reference in New Issue
Block a user