{-# LANGUAGE ApplicativeDo #-}
module Slab.Command
( Command (..)
, CommandWithPath (..)
, RenderMode (..)
, ParseMode (..)
, parserInfo
) where
import Data.Text (Text)
import Options.Applicative ((<**>))
import Options.Applicative qualified as A
data Command
= Build FilePath RenderMode FilePath
| Watch FilePath RenderMode FilePath
| Serve FilePath FilePath
| Report FilePath
|
Generate FilePath
| CommandWithPath FilePath ParseMode CommandWithPath
data CommandWithPath
= Render RenderMode
| Execute
|
Evaluate Bool
| Parse
|
Classes
|
Fragments (Maybe Text)
data RenderMode = RenderNormal | RenderPretty
data ParseMode
=
ParseShallow
|
ParseDeep
parserInfo :: A.ParserInfo Command
parserInfo :: ParserInfo Command
parserInfo =
Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
A.info (Parser Command
parser Parser Command -> Parser (Command -> Command) -> Parser Command
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Command -> Command)
forall a. Parser (a -> a)
A.helper) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$
InfoMod Command
forall a. InfoMod a
A.fullDesc
InfoMod Command -> InfoMod Command -> InfoMod Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
A.header FilePath
"slab - A programmable markup language to generate HTML"
InfoMod Command -> InfoMod Command -> InfoMod Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
A.progDesc
FilePath
"Slab is a programmable markup language to generate HTML."
parser :: A.Parser Command
parser :: Parser Command
parser =
Mod CommandFields Command -> Parser Command
forall a. Mod CommandFields a -> Parser a
A.subparser
( FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
A.command
FilePath
"build"
( Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
A.info (Parser Command
parserBuild Parser Command -> Parser (Command -> Command) -> Parser Command
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Command -> Command)
forall a. Parser (a -> a)
A.helper) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$
FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
A.progDesc
FilePath
"Build a library of Slab templates to HTML"
)
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
A.command
FilePath
"watch"
( Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
A.info (Parser Command
parserWatch Parser Command -> Parser (Command -> Command) -> Parser Command
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Command -> Command)
forall a. Parser (a -> a)
A.helper) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$
FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
A.progDesc
FilePath
"Watch and build a library of Slab templates to HTML"
)
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
A.command
FilePath
"serve"
( Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
A.info (Parser Command
parserServe Parser Command -> Parser (Command -> Command) -> Parser Command
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Command -> Command)
forall a. Parser (a -> a)
A.helper) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$
FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
A.progDesc
FilePath
"Watch and serve a library of Slab templates to HTML"
)
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
A.command
FilePath
"report"
( Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
A.info (Parser Command
parserReport Parser Command -> Parser (Command -> Command) -> Parser Command
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Command -> Command)
forall a. Parser (a -> a)
A.helper) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$
FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
A.progDesc
FilePath
"Analyse a library of Slab templates"
)
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
A.command
FilePath
"render"
( Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
A.info (Parser Command
parserRender Parser Command -> Parser (Command -> Command) -> Parser Command
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Command -> Command)
forall a. Parser (a -> a)
A.helper) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$
FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
A.progDesc
FilePath
"Render a Slab template to HTML"
)
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
A.command
FilePath
"run"
( Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
A.info (Parser Command
parserExectue Parser Command -> Parser (Command -> Command) -> Parser Command
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Command -> Command)
forall a. Parser (a -> a)
A.helper) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$
FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
A.progDesc
FilePath
"Execute a Slab template"
)
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
A.command
FilePath
"evaluate"
( Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
A.info (Parser Command
parserEvaluate Parser Command -> Parser (Command -> Command) -> Parser Command
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Command -> Command)
forall a. Parser (a -> a)
A.helper) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$
FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
A.progDesc
FilePath
"Evaluate a Slab template"
)
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
A.command
FilePath
"parse"
( Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
A.info (Parser Command
parserParse Parser Command -> Parser (Command -> Command) -> Parser Command
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Command -> Command)
forall a. Parser (a -> a)
A.helper) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$
FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
A.progDesc
FilePath
"Parse a Slab template to AST"
)
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
A.command
FilePath
"generate"
( Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
A.info (Parser Command
parserGenerate Parser Command -> Parser (Command -> Command) -> Parser Command
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Command -> Command)
forall a. Parser (a -> a)
A.helper) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$
FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
A.progDesc
FilePath
"Generate code corresponding to a Slab template"
)
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
A.command
FilePath
"classes"
( Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
A.info (Parser Command
parserClasses Parser Command -> Parser (Command -> Command) -> Parser Command
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Command -> Command)
forall a. Parser (a -> a)
A.helper) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$
FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
A.progDesc
FilePath
"Parse a Slab template and report its CSS classes"
)
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
A.command
FilePath
"fragments"
( Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
A.info (Parser Command
parserFragments Parser Command -> Parser (Command -> Command) -> Parser Command
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Command -> Command)
forall a. Parser (a -> a)
A.helper) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$
FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
A.progDesc
FilePath
"Parse a Slab template and report its fragments"
)
)
parserBuild :: A.Parser Command
parserBuild :: Parser Command
parserBuild = do
FilePath
srcDir <-
ReadM FilePath -> Mod ArgumentFields FilePath -> Parser FilePath
forall a. ReadM a -> Mod ArgumentFields a -> Parser a
A.argument
ReadM FilePath
forall s. IsString s => ReadM s
A.str
(FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
A.metavar FilePath
"DIR" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasCompleter f => FilePath -> Mod f a
A.action FilePath
"file" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
A.help FilePath
"Directory of Slab templates to build.")
RenderMode
mode <-
RenderMode
-> RenderMode -> Mod FlagFields RenderMode -> Parser RenderMode
forall a. a -> a -> Mod FlagFields a -> Parser a
A.flag
RenderMode
RenderNormal
RenderMode
RenderPretty
( FilePath -> Mod FlagFields RenderMode
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
A.long FilePath
"pretty" Mod FlagFields RenderMode
-> Mod FlagFields RenderMode -> Mod FlagFields RenderMode
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields RenderMode
forall (f :: * -> *) a. FilePath -> Mod f a
A.help FilePath
"Use pretty-printing"
)
FilePath
distDir <-
Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
A.strOption
( FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
A.long FilePath
"dist"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasValue f => a -> Mod f a
A.value FilePath
"./_site"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
A.metavar FilePath
"DIR"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
A.help
FilePath
"A destination directory for the generated HTML files."
)
pure $ FilePath -> RenderMode -> FilePath -> Command
Build FilePath
srcDir RenderMode
mode FilePath
distDir
parserServe :: A.Parser Command
parserServe :: Parser Command
parserServe = do
FilePath
srcDir <-
ReadM FilePath -> Mod ArgumentFields FilePath -> Parser FilePath
forall a. ReadM a -> Mod ArgumentFields a -> Parser a
A.argument
ReadM FilePath
forall s. IsString s => ReadM s
A.str
(FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
A.metavar FilePath
"DIR" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasCompleter f => FilePath -> Mod f a
A.action FilePath
"file" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
A.help FilePath
"Directory of Slab templates to build.")
FilePath
distDir <-
Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
A.strOption
( FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
A.long FilePath
"dist"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasValue f => a -> Mod f a
A.value FilePath
"./_site"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
A.metavar FilePath
"DIR"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
A.help
FilePath
"A directory with existing static files."
)
pure $ FilePath -> FilePath -> Command
Serve FilePath
srcDir FilePath
distDir
parserReport :: A.Parser Command
parserReport :: Parser Command
parserReport = do
FilePath
srcDir <-
ReadM FilePath -> Mod ArgumentFields FilePath -> Parser FilePath
forall a. ReadM a -> Mod ArgumentFields a -> Parser a
A.argument
ReadM FilePath
forall s. IsString s => ReadM s
A.str
(FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
A.metavar FilePath
"DIR" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasCompleter f => FilePath -> Mod f a
A.action FilePath
"file" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
A.help FilePath
"Directory of Slab templates to analyse.")
pure $ FilePath -> Command
Report FilePath
srcDir
parserWatch :: A.Parser Command
parserWatch :: Parser Command
parserWatch = do
FilePath
srcDir <-
ReadM FilePath -> Mod ArgumentFields FilePath -> Parser FilePath
forall a. ReadM a -> Mod ArgumentFields a -> Parser a
A.argument
ReadM FilePath
forall s. IsString s => ReadM s
A.str
(FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
A.metavar FilePath
"DIR" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasCompleter f => FilePath -> Mod f a
A.action FilePath
"file" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
A.help FilePath
"Directory of Slab templates to watch.")
RenderMode
mode <-
RenderMode
-> RenderMode -> Mod FlagFields RenderMode -> Parser RenderMode
forall a. a -> a -> Mod FlagFields a -> Parser a
A.flag
RenderMode
RenderNormal
RenderMode
RenderPretty
( FilePath -> Mod FlagFields RenderMode
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
A.long FilePath
"pretty" Mod FlagFields RenderMode
-> Mod FlagFields RenderMode -> Mod FlagFields RenderMode
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields RenderMode
forall (f :: * -> *) a. FilePath -> Mod f a
A.help FilePath
"Use pretty-printing"
)
FilePath
distDir <-
Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
A.strOption
( FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
A.long FilePath
"dist"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasValue f => a -> Mod f a
A.value FilePath
"./_site"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
A.metavar FilePath
"DIR"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
A.help
FilePath
"A destination directory for the generated HTML files."
)
pure $ FilePath -> RenderMode -> FilePath -> Command
Watch FilePath
srcDir RenderMode
mode FilePath
distDir
parserExectue :: A.Parser Command
parserExectue :: Parser Command
parserExectue = do
(FilePath, ParseMode)
pathAndmode <- Parser (FilePath, ParseMode)
parserWithPath
pure $ (FilePath -> ParseMode -> CommandWithPath -> Command)
-> (FilePath, ParseMode) -> CommandWithPath -> Command
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry FilePath -> ParseMode -> CommandWithPath -> Command
CommandWithPath (FilePath, ParseMode)
pathAndmode (CommandWithPath -> Command) -> CommandWithPath -> Command
forall a b. (a -> b) -> a -> b
$ CommandWithPath
Execute
parserRender :: A.Parser Command
parserRender :: Parser Command
parserRender = do
RenderMode
mode <-
RenderMode
-> RenderMode -> Mod FlagFields RenderMode -> Parser RenderMode
forall a. a -> a -> Mod FlagFields a -> Parser a
A.flag
RenderMode
RenderNormal
RenderMode
RenderPretty
( FilePath -> Mod FlagFields RenderMode
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
A.long FilePath
"pretty" Mod FlagFields RenderMode
-> Mod FlagFields RenderMode -> Mod FlagFields RenderMode
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields RenderMode
forall (f :: * -> *) a. FilePath -> Mod f a
A.help FilePath
"Use pretty-printing"
)
(FilePath, ParseMode)
pathAndmode <- Parser (FilePath, ParseMode)
parserWithPath
pure $ (FilePath -> ParseMode -> CommandWithPath -> Command)
-> (FilePath, ParseMode) -> CommandWithPath -> Command
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry FilePath -> ParseMode -> CommandWithPath -> Command
CommandWithPath (FilePath, ParseMode)
pathAndmode (CommandWithPath -> Command) -> CommandWithPath -> Command
forall a b. (a -> b) -> a -> b
$ RenderMode -> CommandWithPath
Render RenderMode
mode
parserEvaluate :: A.Parser Command
parserEvaluate :: Parser Command
parserEvaluate = do
(FilePath, ParseMode)
pathAndmode <- Parser (FilePath, ParseMode)
parserWithPath
Bool
simpl <-
Mod FlagFields Bool -> Parser Bool
A.switch
( FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
A.long FilePath
"simplify" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
A.help FilePath
"Simplify the AST"
)
pure $ (FilePath -> ParseMode -> CommandWithPath -> Command)
-> (FilePath, ParseMode) -> CommandWithPath -> Command
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry FilePath -> ParseMode -> CommandWithPath -> Command
CommandWithPath (FilePath, ParseMode)
pathAndmode (CommandWithPath -> Command) -> CommandWithPath -> Command
forall a b. (a -> b) -> a -> b
$ Bool -> CommandWithPath
Evaluate Bool
simpl
parserParse :: A.Parser Command
parserParse :: Parser Command
parserParse = do
(FilePath, ParseMode)
pathAndmode <- Parser (FilePath, ParseMode)
parserWithPath
pure $ (FilePath -> ParseMode -> CommandWithPath -> Command)
-> (FilePath, ParseMode) -> CommandWithPath -> Command
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry FilePath -> ParseMode -> CommandWithPath -> Command
CommandWithPath (FilePath, ParseMode)
pathAndmode CommandWithPath
Parse
parserGenerate :: A.Parser Command
parserGenerate :: Parser Command
parserGenerate = do
FilePath
path <- Parser FilePath
parserTemplatePath
pure $ FilePath -> Command
Generate FilePath
path
parserClasses :: A.Parser Command
parserClasses :: Parser Command
parserClasses = do
(FilePath, ParseMode)
pathAndmode <- Parser (FilePath, ParseMode)
parserWithPath
pure $ (FilePath -> ParseMode -> CommandWithPath -> Command)
-> (FilePath, ParseMode) -> CommandWithPath -> Command
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry FilePath -> ParseMode -> CommandWithPath -> Command
CommandWithPath (FilePath, ParseMode)
pathAndmode CommandWithPath
Classes
parserFragments :: A.Parser Command
parserFragments :: Parser Command
parserFragments = do
(FilePath, ParseMode)
pathAndmode <- Parser (FilePath, ParseMode)
parserWithPath
Maybe Text
mname <-
Parser Text -> Parser (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
A.optional (Parser Text -> Parser (Maybe Text))
-> Parser Text -> Parser (Maybe Text)
forall a b. (a -> b) -> a -> b
$
ReadM Text -> Mod ArgumentFields Text -> Parser Text
forall a. ReadM a -> Mod ArgumentFields a -> Parser a
A.argument
ReadM Text
forall s. IsString s => ReadM s
A.str
(FilePath -> Mod ArgumentFields Text
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
A.metavar FilePath
"NAME" Mod ArgumentFields Text
-> Mod ArgumentFields Text -> Mod ArgumentFields Text
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields Text
forall (f :: * -> *) a. FilePath -> Mod f a
A.help FilePath
"Fragment name to extract.")
pure $ (FilePath -> ParseMode -> CommandWithPath -> Command)
-> (FilePath, ParseMode) -> CommandWithPath -> Command
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry FilePath -> ParseMode -> CommandWithPath -> Command
CommandWithPath (FilePath, ParseMode)
pathAndmode (CommandWithPath -> Command) -> CommandWithPath -> Command
forall a b. (a -> b) -> a -> b
$ Maybe Text -> CommandWithPath
Fragments Maybe Text
mname
parserWithPath :: A.Parser (FilePath, ParseMode)
parserWithPath :: Parser (FilePath, ParseMode)
parserWithPath = (,) (FilePath -> ParseMode -> (FilePath, ParseMode))
-> Parser FilePath -> Parser (ParseMode -> (FilePath, ParseMode))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser FilePath
parserTemplatePath Parser (ParseMode -> (FilePath, ParseMode))
-> Parser ParseMode -> Parser (FilePath, ParseMode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser ParseMode
parserShallowFlag
parserTemplatePath :: A.Parser FilePath
parserTemplatePath :: Parser FilePath
parserTemplatePath =
ReadM FilePath -> Mod ArgumentFields FilePath -> Parser FilePath
forall a. ReadM a -> Mod ArgumentFields a -> Parser a
A.argument
ReadM FilePath
forall s. IsString s => ReadM s
A.str
(FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
A.metavar FilePath
"FILE" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasCompleter f => FilePath -> Mod f a
A.action FilePath
"file" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
A.help FilePath
"Slab template to parse.")
parserShallowFlag :: A.Parser ParseMode
parserShallowFlag :: Parser ParseMode
parserShallowFlag =
ParseMode
-> ParseMode -> Mod FlagFields ParseMode -> Parser ParseMode
forall a. a -> a -> Mod FlagFields a -> Parser a
A.flag
ParseMode
ParseDeep
ParseMode
ParseShallow
( FilePath -> Mod FlagFields ParseMode
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
A.long FilePath
"shallow" Mod FlagFields ParseMode
-> Mod FlagFields ParseMode -> Mod FlagFields ParseMode
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields ParseMode
forall (f :: * -> *) a. FilePath -> Mod f a
A.help FilePath
"Don't parse recursively the included Slab files"
)