Copyright | Copyright 2017 Awake Security |
---|---|
License | Apache-2.0 |
Maintainer | opensource@awakesecurity.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Introduction
This library contains most of the utilities you would ever want for working with the Ninja build language.
In general, when using language-ninja
, you'll want the following imports:
import qualified Language.Ninja.AST as AST import qualified Language.Ninja.IR as IR import qualified Language.Ninja.Errors as Errors import qualified Language.Ninja.Misc as Misc import qualified Language.Ninja.Mock as Mock import qualified Language.Ninja.Lexer as Lexer import qualified Language.Ninja.Parser as Parser import qualified Language.Ninja.Pretty as Pretty import qualified Language.Ninja.Compile as Compile
For this tutorial, we will also use some other imports:
import Control.Lens (Iso'
,Lens'
,Prism'
) import qualified Control.Lens as Lens import Control.Monad.Error.Class (MonadError
) import Data.Either (either
) import Data.Text (Text
) import qualified Data.Text as Text import Data.HashSet (HashSet
) import qualified Data.HashSet as HS import Data.HashMap.Strict (HashMap
) import qualified Data.HashMap.Strict as HM import Data.Versions (Version
)
Lexing
To lex a Ninja file, we use the Language.Ninja.Lexer module. This results in a list of _annotated_ lexemes:
lexFileIO "./build.ninja" :: IO (Lexer.Lexeme
Lexer.Ann
)
For more specialized use cases, consult the module documentation.
Parsing
To parse a Ninja file, we use the Language.Ninja.Parse module. In the simplest case, this amounts to parsing a file:
ast <- (Parser.parseFileIO
"./build.ninja") :: IO AST.Ninja
For more specialized use cases, consult the module documentation.
Abstract Syntax Tree
Now that we have parsed the Ninja file, we can take a look at the AST:
let look lens = Lens.view
lens ast look AST.ninjaRules
::HashMap
Text
AST.Rule
look AST.ninjaSingles
::HashMap
Text
AST.Build
look AST.ninjaMultiples
::HashMap
(HashSet
Text
) AST.Build
look AST.ninjaPhonys
::HashMap
Text
(HashSet
Text
) look AST.ninjaDefaults
::HashSet
Text
look AST.ninjaPools
::HashMap
Text
Int
look AST.ninjaSpecials
::HashMap
Text
Text
AST.
ninjaRules
- This field corresponds to the
rule
declarations in the parsed Ninja file. Specifically, it is a map from rule names (asText
) toAST.
s.Rule
AST.
ninjaSingles
- This field contains the set of all non-phony
build
declarations with exactly one output. Specifically, it is a map from the build output name to anAST.
.Build
AST.
ninjaMultiples
- This field contains the set of all non-phony
build
declarations with two or more outputs. Specifically, it is a map from the set of outputs to the correspondingAST.
.Build
AST.
ninjaPhonys
- This field contains the set of all phony
build
declarations, as a map from the output name to the set of dependencies. If a phonybuild
has multiple outputs, it will naturally be expanded to multiple entries in this hash map. AST.
ninjaDefaults
- This field contains the set of all targets referenced in
default
declarations. AST.
ninjaPools
- This field contains the set of all pools defined in the Ninja file, represented as a mapping from the pool name to the pool depth.
AST.
ninjaSpecials
- This field contains the set of all "special" top-level variables defined
in the Ninja file, as a mapping from the variable name to the variable
value. As it stands, this map will only ever have at most two keys:
ninja_required_version
andbuilddir
. For more on these variables, look at the manual here.
AST.Rule
Rule
A value of type AST.
is essentially the set of variables that
are bound in a Rule
rule
body, represented as a map from the variable (Text
)
to its unevaluated definition (AST.
). The underlying Expr
HashMap
can be extracted with AST.
.ruleBind
AST.Build
Build
A value of type AST.
contains four pieces of information:Build
AST.
buildRule
::Lens'
AST.Build
Text
- The name of the
rule
associated with thisbuild
declaration. AST.
buildDeps
::Lens'
AST.Build
AST.Deps
- The set of dependencies for this
build
declaration. AST.
buildEnv
::Lens'
AST.Build
(AST.Env
Text
Text
)- The set of file-level variables in scope when the
build
declaration was parsed. AST.
buildBind
::Lens'
AST.Build
(HashMap
Text
Text
)- The set of bindings (indented
key = value
pairs) for thisbuild
declaration.
AST.Deps
Deps
A value of type AST.
contains three pieces of information:Deps
AST.
depsNormal
::Lens'
AST.Deps
(HashSet
Text
)- The set of "normal" (explicit) dependencies for a
build
declaration. AST.
depsImplicit
::Lens'
AST.Deps
(HashSet
Text
)- The set of "implicit" dependencies for a
build
declaration. AST.
depsOrderOnly
::Lens'
AST.Deps
(HashSet
Text
)- The set of "order-only" dependencies for a
build
declaration.
This section of the Ninja manual describes in detail the differences between explicit, implicit, and order-only dependencies.
Compiling
To compile a Ninja AST (AST.
) to the Ninja intermediate
representation, we use Ninja
compile
from the Language.Ninja.Compile module.
In the simplest case, this looks like:
let handleError :: Either Errors.CompileError
a -> IO a handleError =either
(fail
.show
)pure
ir <- handleError (Compile.compile
ast)
Since Compile.
returns in any monad with an instance
of compile
, it is quite flexible.MonadError
Errors.CompileError
For simplicity in this case, however, we use
Either Errors.
and convert to CompileError
AST.Ninja
IO
by calling fail
when it fails.
Intermediate Representation
The language-ninja
intermediate representation, as defined in the
Language.Ninja.IR module, is a reduced form of the Ninja AST that handles
as much of the static semantics of Ninja as possible.
The Ninja IR does not have any notion of variables/scoping, does not contain
unrestricted hash maps or environments, and has the rule
declarations
inlined into the build
nodes, thus eliminating the "polymorphism"
associated with the $in
and $out
Ninja variables.
Since we have now compiled the Ninja AST, we can take a look at the IR:
let look lens = Lens.view
lens ir look IR.ninjaMeta
:: IR.Meta
look IR.ninjaBuilds
::HashSet
IR.Build
look IR.ninjaPhonys
::HashMap
IR.Target
(HashSet
IR.Target
) look IR.ninjaDefaults
::HashSet
IR.Target
look IR.ninjaPools
::HashSet
IR.Pool
These fields correspond to more well-typed versions of their counterparts in the AST. The main differences to note are:
AST.
is used to computeninjaSpecials
IR.
.ninjaMeta
Text
has mostly been replaced withIR.
where relevant.Target
AST.
andninjaSingles
AST.
have been merged into a single field:ninjaMultiples
IR.
.ninjaBuilds
AST.
is gone; theninjaRules
rule
s are now inlined into thebuild
s that use them.
IR.Meta
Meta
A value of type IR.
contains two pieces of information:Meta
IR.
metaReqVersion
::Lens'
IR.Meta
(MaybeVersion
)- The parsed Ninja version required to build this file.
This corresponds to the
ninja_required_version
top-level variable. IR.
metaBuildDir
::Lens'
IR.Meta
(Maybe Misc.Path
)- This corresponds to the
builddir
top-level variable.
IR.Build
Build
A value of type IR.
contains three pieces of information:Build
IR.
buildRule
::Lens'
IR.Build
IR.Rule
- The
rule
associated with thisbuild
declaration. IR.
buildOuts
::Lens'
IR.Build
(HashSet
IR.Output
)- The set of outputs for this
build
declaration. IR.
buildDeps
::Lens'
IR.Build
(HashSet
IR.Dependency
)- The set of dependencies for this
build
declaration.
IR.Rule
Rule
A value of type IR.
contains a lot of information. For brevity,
we will simply list the lens names and types; refer to the module
documentation (Language.Ninja.IR.Rule) for more information.Rule
IR.ruleName
::Lens'
IR.Rule
Text
IR.ruleCommand
::Lens'
IR.Rule
Misc.Command
IR.ruleDescription
::Lens'
IR.Rule
(MaybeText
) IR.rulePool
::Lens'
IR.Rule
IR.PoolName
IR.ruleDepfile
::Lens'
IR.Rule
(Maybe Misc.Path
) IR.ruleSpecialDeps
::Lens'
IR.Rule
(Maybe IR.SpecialDeps
) IR.ruleGenerator
::Lens'
IR.Rule
Bool IR.ruleRestat
::Lens'
IR.Rule
Bool IR.ruleResponseFile
::Lens'
IR.Rule
(Maybe IR.ResponseFile
)
IR.Pool
Pool
A value of type IR.
has a name (Pool
IR.
) and a
depth (poolName
IR.
). This type is correct-by-construction; it should
not be possible to construct a poolDepth
that does not correspond to a
valid pool definition or reference.Pool
Printing
Currently there is a rudimentary pretty-printer for the lexemes and the AST
in the Language.Ninja.Pretty module. It simply returns Text
such that if
let pretty =pure
. Pretty.prettyNinja
let parse = Parser.parseTextIO
then pretty >=> parse >=> pretty >=> parse
should be the same as pure
,
modulo read-only side effects and annotations.
There are plans to write a pretty-printer for the IR. This would be very useful for generating Ninja.
Executables
In addition to the library described above, this package also ships with
three executables: ninja-lex
, ninja-parse
, and ninja-compile
.
These expose the corresponding module by using the Aeson instances to render
the lexed/parsed/compiled source.
ninja-lex
The command-line interface for ninja-lex
looks like this:
$ ninja-lex --help ninja-lex version 0.1.0 Usage: ninja-lex (process | pretty) Available options: -h,--help Show this help text Available commands: process pretty
$ ninja-lex process --help Usage: ninja-lex process [--input FILEPATH] [--output FILEPATH] [--machine-readable] Available options: -h,--help Show this help text --input FILEPATH Read the given FILEPATH as a Ninja file. --output FILEPATH Output to the given FILEPATH instead of /dev/stdout. --machine-readable Should the output be fully machine-readable?
$ ninja-lex pretty --help Usage: ninja-lex pretty [--input FILEPATH] [--output FILEPATH] [--color] Available options: -h,--help Show this help text --input FILEPATH Read the given FILEPATH as a Ninja file. --output FILEPATH Output to the given FILEPATH instead of /dev/stdout. --color Should the output use ANSI color?
ninja-parse
The command-line interface for ninja-parse
looks like this:
$ ninja-parse --help ninja-parse version 0.1.0 Usage: ninja-parse (process | pretty) Available options: -h,--help Show this help text Available commands: process pretty
$ ninja-parse process --help Usage: ninja-parse process [--input FILEPATH] [--output FILEPATH] [--machine-readable] Available options: -h,--help Show this help text --input FILEPATH Read the given FILEPATH as a Ninja file. --output FILEPATH Output to the given FILEPATH instead of /dev/stdout. --machine-readable Should the output be fully machine-readable?
$ ninja-parse pretty --help Usage: ninja-parse pretty [--input FILEPATH] [--output FILEPATH] [--color] Available options: -h,--help Show this help text --input FILEPATH Read the given FILEPATH as a Ninja file. --output FILEPATH Output to the given FILEPATH instead of /dev/stdout. --color Should the output use ANSI color?
ninja-compile
The command-line interface for ninja-compile
looks like this:
$ ninja-compile --help ninja-compile version 0.1.0 Usage: ninja-compile [--input FILEPATH] [--output FILEPATH] [--machine-readable] Available options: -h,--help Show this help text --input FILEPATH Read the given FILEPATH as a Ninja file. --output FILEPATH Output to the given FILEPATH instead of /dev/stdout. --machine-readable Should the output be fully machine-readable?
Conclusion
I hope these tools will be useful to you for whatever task you want to do with the Ninja language. Happy hacking!