Copyright | Copyright 2017 Awake Security |
---|---|
License | Apache-2.0 |
Maintainer | opensource@awakesecurity.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
The Ninja build language intermediate representation after compilation.
This module re-exports all of the modules under the Language.Ninja.IR namespace for convenience.
It is recommended that you import it with the following style:
import qualified Language.Ninja.IR as IR
Since: 0.1.0
- data Ninja
- makeNinja :: Ninja
- ninjaMeta :: Lens' Ninja Meta
- ninjaBuilds :: Lens' Ninja (HashSet Build)
- ninjaPhonys :: Lens' Ninja (HashMap Target (HashSet Target))
- ninjaDefaults :: Lens' Ninja (HashSet Target)
- ninjaPools :: Lens' Ninja (HashSet Pool)
- data Meta
- makeMeta :: Meta
- metaReqVersion :: Lens' Meta (Maybe Version)
- metaBuildDir :: Lens' Meta (Maybe Path)
- data Build
- makeBuild :: Rule -> Build
- buildRule :: Lens' Build Rule
- buildOuts :: Lens' Build (HashSet Output)
- buildDeps :: Lens' Build (HashSet Dependency)
- data Rule
- makeRule :: Text -> Command -> Rule
- ruleName :: Lens' Rule Text
- ruleCommand :: Lens' Rule Command
- ruleDescription :: Lens' Rule (Maybe Text)
- rulePool :: Lens' Rule PoolName
- ruleDepfile :: Lens' Rule (Maybe Path)
- ruleSpecialDeps :: Lens' Rule (Maybe SpecialDeps)
- ruleGenerator :: Lens' Rule Bool
- ruleRestat :: Lens' Rule Bool
- ruleResponseFile :: Lens' Rule (Maybe ResponseFile)
- data SpecialDeps
- makeSpecialDepsGCC :: SpecialDeps
- makeSpecialDepsMSVC :: Text -> SpecialDeps
- _SpecialDepsGCC :: Prism' SpecialDeps ()
- _SpecialDepsMSVC :: Prism' SpecialDeps Text
- data ResponseFile
- makeResponseFile :: Path -> Text -> ResponseFile
- responseFilePath :: Lens' ResponseFile Path
- responseFileContent :: Lens' ResponseFile Text
- data Target
- makeTarget :: Text -> Target
- targetIText :: Iso' Target IText
- targetText :: Iso' Target Text
- data Output
- makeOutput :: Target -> Output
- outputTarget :: Lens' Output Target
- data Dependency
- makeDependency :: Target -> DependencyType -> Dependency
- dependencyTarget :: Lens' Dependency Target
- dependencyType :: Lens' Dependency DependencyType
- data DependencyType
- _NormalDependency :: Prism' DependencyType ()
- _OrderOnlyDependency :: Prism' DependencyType ()
- data Pool
- makePool :: PoolName -> PoolDepth -> Maybe Pool
- makePoolDefault :: Pool
- makePoolConsole :: Pool
- makePoolCustom :: Text -> Positive -> Pool
- poolName :: Getter Pool PoolName
- poolDepth :: Getter Pool PoolDepth
- data PoolName
- makePoolNameDefault :: PoolName
- makePoolNameConsole :: PoolName
- makePoolNameCustom :: Text -> PoolName
- _PoolNameDefault :: Getter PoolName (Maybe ())
- _PoolNameConsole :: Getter PoolName (Maybe ())
- _PoolNameCustom :: Getter PoolName (Maybe Text)
- poolNameText :: Iso' PoolName Text
- printPoolName :: PoolName -> Text
- parsePoolName :: Text -> PoolName
- data PoolDepth
- makePoolDepth :: Positive -> PoolDepth
- makePoolInfinite :: PoolDepth
- poolDepthPositive :: Iso' PoolDepth (Maybe Positive)
Language.Ninja.IR.Ninja
A parsed and normalized Ninja file.
Since: 0.1.0
Eq Ninja Source # | |
Show Ninja Source # | |
Generic Ninja Source # | |
Hashable Ninja Source # | Default Since: 0.1.0 |
ToJSON Ninja Source # | Converts to Since: 0.1.0 |
FromJSON Ninja Source # | Inverse of the Since: 0.1.0 |
NFData Ninja Source # | Default Since: 0.1.0 |
(Monad m, NinjaConstraint (Serial m)) => Serial m Ninja Source # | Default Since: 0.1.0 |
(Monad m, NinjaConstraint (CoSerial m)) => CoSerial m Ninja Source # | Default Since: 0.1.0 |
type Rep Ninja Source # | |
ninjaMeta :: Lens' Ninja Meta Source #
Metadata, which includes top-level variables like builddir
.
Since: 0.1.0
ninjaPhonys :: Lens' Ninja (HashMap Target (HashSet Target)) Source #
Phony targets, as documented here.
Since: 0.1.0
ninjaDefaults :: Lens' Ninja (HashSet Target) Source #
The set of default targets, as documented here.
Since: 0.1.0
Language.Ninja.IR.Meta
Ninja top-level metadata, as documented here.
Since: 0.1.0
Eq Meta Source # | |
Ord Meta Source # | |
Show Meta Source # | |
Generic Meta Source # | |
Hashable Meta Source # | Default Since: 0.1.0 |
ToJSON Meta Source # | Converts to Since: 0.1.0 |
FromJSON Meta Source # | Inverse of the Since: 0.1.0 |
NFData Meta Source # | Default Since: 0.1.0 |
(Monad m, Serial m Version, Serial m Text) => Serial m Meta Source # | Default Since: 0.1.0 |
(Monad m, CoSerial m Version, CoSerial m Text) => CoSerial m Meta Source # | Default Since: 0.1.0 |
type Rep Meta Source # | |
metaReqVersion :: Lens' Meta (Maybe Version) Source #
Corresponds to the ninja_required_version
top-level variable.
Since: 0.1.0
metaBuildDir :: Lens' Meta (Maybe Path) Source #
Corresponds to the builddir
top-level variable.
Since: 0.1.0
Language.Ninja.IR.Build
A Ninja build
declaration, as documented
here.
Since: 0.1.0
Eq Build Source # | |
Show Build Source # | |
Generic Build Source # | |
Hashable Build Source # | Default Since: 0.1.0 |
ToJSON Build Source # | Converts to Since: 0.1.0 |
FromJSON Build Source # | Inverse of the Since: 0.1.0 |
NFData Build Source # | Default Since: 0.1.0 |
(Monad m, BuildConstraint (Serial m)) => Serial m Build Source # | Default Since: 0.1.0 |
(Monad m, BuildConstraint (CoSerial m)) => CoSerial m Build Source # | Default Since: 0.1.0 |
type Rep Build Source # | |
buildRule :: Lens' Build Rule Source #
The rule to execute when building any of the outputs.
Since: 0.1.0
buildOuts :: Lens' Build (HashSet Output) Source #
The outputs that are built as a result of rule execution.
Since: 0.1.0
buildDeps :: Lens' Build (HashSet Dependency) Source #
The dependencies that must be satisfied before this can be built.
Since: 0.1.0
Language.Ninja.IR.Rule
A Ninja rule
declaration, as documented
here.
Since: 0.1.0
Eq Rule Source # | |
Ord Rule Source # | |
Show Rule Source # | |
Generic Rule Source # | |
Hashable Rule Source # | Default Since: 0.1.0 |
ToJSON Rule Source # | Converts to
Since: 0.1.0 |
FromJSON Rule Source # | Inverse of the Since: 0.1.0 |
NFData Rule Source # | Default Since: 0.1.0 |
(Monad m, Serial m Text) => Serial m Rule Source # | Default Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m Rule Source # | Default Since: 0.1.0 |
type Rep Rule Source # | |
ruleDescription :: Lens' Rule (Maybe Text) Source #
A short description of the command, used to pretty-print the command
as it's running. The ninja -v
flag controls whether to print the
full command or its description; if a command fails, the full command
line will always be printed before the command's output.
Since: 0.1.0
rulePool :: Lens' Rule PoolName Source #
The process pool in which this rule will be executed.
Since: 0.1.0
ruleDepfile :: Lens' Rule (Maybe Path) Source #
If set, this should be a path to an optional Makefile that contains extra implicit dependencies. This is used to support C/C++ header dependencies. For more information, read the Ninja documentation here.
Since: 0.1.0
ruleSpecialDeps :: Lens' Rule (Maybe SpecialDeps) Source #
If set, enables special dependency processing used in C/C++ header dependencies. For more information, read the Ninja documentation here.
Since: 0.1.0
ruleGenerator :: Lens' Rule Bool Source #
If this is true, specifies that this rule is used to re-invoke the generator program. Files built using generator rules are treated specially in two ways: firstly, they will not be rebuilt if the command line changes; and secondly, they are not cleaned by default.
Since: 0.1.0
ruleRestat :: Lens' Rule Bool Source #
If true, causes Ninja to re-stat the command's outputs after execution of the command. Each output whose modification time the command did not change will be treated as though it had never needed to be built. This may cause the output's reverse dependencies to be removed from the list of pending build actions.
Since: 0.1.0
ruleResponseFile :: Lens' Rule (Maybe ResponseFile) Source #
If present, Ninja will use a response file for the given command, i.e. write the selected string to the given file before calling the command and delete the file after the command is done.
This is particularly useful on Windows OS, where the maximal length of a command line is limited and response files must be used instead.
Since: 0.1.0
data SpecialDeps Source #
Special dependency information, as described here.
Since: 0.1.0
Eq SpecialDeps Source # | |
Ord SpecialDeps Source # | |
Read SpecialDeps Source # | |
Show SpecialDeps Source # | |
Generic SpecialDeps Source # | |
Hashable SpecialDeps Source # | Default Since: 0.1.0 |
ToJSON SpecialDeps Source # | Converts to Since: 0.1.0 |
FromJSON SpecialDeps Source # | Inverse of the Since: 0.1.0 |
NFData SpecialDeps Source # | Default Since: 0.1.0 |
(Monad m, Serial m Text) => Serial m SpecialDeps Source # | Default Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m SpecialDeps Source # | Default Since: 0.1.0 |
type Rep SpecialDeps Source # | |
makeSpecialDepsGCC :: SpecialDeps Source #
Construct a SpecialDeps
corresponding to the case in which deps = gcc
is set in a Ninja build rule.
Since: 0.1.0
makeSpecialDepsMSVC :: Text -> SpecialDeps Source #
Construct a SpecialDeps
corresponding to the case in which deps = msvc
is set and msvc_deps_prefix = …
.
The msvc_deps_prefix
field defines the string which should be stripped
from msvc
's /showIncludes
output. It is only needed if the version of
Visual Studio being used is not English. The value of msvc_deps_prefix
is "Note: including file: "
by default.
Since: 0.1.0
_SpecialDepsGCC :: Prism' SpecialDeps () Source #
A prism for the deps = gcc
case.
Since: 0.1.0
_SpecialDepsMSVC :: Prism' SpecialDeps Text Source #
A prism for the deps = msvc
/ msvc_deps_prefix = …
case.
Since: 0.1.0
data ResponseFile Source #
A response file to use during rule execution, as documented here.
Since: 0.1.0
Eq ResponseFile Source # | |
Ord ResponseFile Source # | |
Show ResponseFile Source # | |
Generic ResponseFile Source # | |
Hashable ResponseFile Source # | Default Since: 0.1.0 |
ToJSON ResponseFile Source # | Converts to Since: 0.1.0 |
FromJSON ResponseFile Source # | Inverse of the Since: 0.1.0 |
NFData ResponseFile Source # | Default Since: 0.1.0 |
(Monad m, Serial m Text) => Serial m ResponseFile Source # | Default Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m ResponseFile Source # | Default Since: 0.1.0 |
type Rep ResponseFile Source # | |
:: Path | Corresponds to |
-> Text | Corresponds to |
-> ResponseFile |
Construct a ResponseFile
with the given Path
and content Text
.
Since: 0.1.0
responseFilePath :: Lens' ResponseFile Path Source #
A lens for the rspfile
field.
Since: 0.1.0
responseFileContent :: Lens' ResponseFile Text Source #
A lens for the rspfile_content
field.
Since: 0.1.0
Language.Ninja.IR.Target
This type represents a Ninja target name.
Since: 0.1.0
Eq Target Source # | |
Ord Target Source # | |
Read Target Source # | |
Show Target Source # | |
IsString Target Source # | |
Generic Target Source # | |
Hashable Target Source # | |
ToJSON Target Source # | |
ToJSONKey Target Source # | |
FromJSON Target Source # | |
FromJSONKey Target Source # | |
NFData Target Source # | |
(Monad m, Serial m Text) => Serial m Target Source # | Uses the underlying Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m Target Source # | Uses the underlying Since: 0.1.0 |
type Rep Target Source # | |
targetIText :: Iso' Target IText Source #
An isomorphism between a Target
and its underlying IText
.
Since: 0.1.0
Eq Output Source # | |
Ord Output Source # | |
Read Output Source # | |
Show Output Source # | |
Generic Output Source # | |
Hashable Output Source # | Default Since: 0.1.0 |
ToJSON Output Source # | Converts to Since: 0.1.0 |
FromJSON Output Source # | Inverse of the Since: 0.1.0 |
NFData Output Source # | Default Since: 0.1.0 |
(Monad m, Serial m Text) => Serial m Output Source # | Default Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m Output Source # | Default Since: 0.1.0 |
type Rep Output Source # | |
data Dependency Source #
Eq Dependency Source # | |
Ord Dependency Source # | |
Read Dependency Source # | |
Show Dependency Source # | |
Generic Dependency Source # | |
Hashable Dependency Source # | Default Since: 0.1.0 |
ToJSON Dependency Source # | Converts to Since: 0.1.0 |
FromJSON Dependency Source # | Inverse of the Since: 0.1.0 |
NFData Dependency Source # | Default Since: 0.1.0 |
(Monad m, Serial m Text) => Serial m Dependency Source # | Default Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m Dependency Source # | Default Since: 0.1.0 |
type Rep Dependency Source # | |
:: Target | The underlying target. |
-> DependencyType | The dependency type (normal, implicit, or order-only). |
-> Dependency |
Construct a Dependency
.
Since: 0.1.0
dependencyTarget :: Lens' Dependency Target Source #
A lens for the Target
of a Dependency
.
Since: 0.1.0
dependencyType :: Lens' Dependency DependencyType Source #
A lens for the DependencyType
of a Dependency
.
Since: 0.1.0
data DependencyType Source #
The type of a Dependency
: normal, implicit, or order-only.
Since: 0.1.0
NormalDependency | A normal dependency. Since: 0.1.0 |
OrderOnlyDependency | An order-only dependency. These are only rebuilt if there is at least one non-order-only dependency that is out of date. Section 4.3 "Types of Prerequisites" in the GNU Make manual has a good explanation of this concept. Since: 0.1.0 |
Eq DependencyType Source # | |
Ord DependencyType Source # | |
Read DependencyType Source # | |
Show DependencyType Source # | |
Generic DependencyType Source # | |
Hashable DependencyType Source # | Default Since: 0.1.0 |
ToJSON DependencyType Source # | Converts to Since: 0.1.0 |
FromJSON DependencyType Source # | Inverse of the Since: 0.1.0 |
NFData DependencyType Source # | Default Since: 0.1.0 |
Monad m => Serial m DependencyType Source # | Default Since: 0.1.0 |
Monad m => CoSerial m DependencyType Source # | Default Since: 0.1.0 |
type Rep DependencyType Source # | |
_NormalDependency :: Prism' DependencyType () Source #
A prism for the NormalDependency
constructor.
Since: 0.1.0
_OrderOnlyDependency :: Prism' DependencyType () Source #
A prism for the OrderOnlyDependency
constructor.
Since: 0.1.0
Language.Ninja.IR.Pool
A Ninja pool
declaration, as documented
here.
Since: 0.1.0
Eq Pool Source # | |
Ord Pool Source # | |
Read Pool Source # | |
Show Pool Source # | |
Generic Pool Source # | |
Hashable Pool Source # | Default Since: 0.1.0 |
ToJSON Pool Source # | Converts to Since: 0.1.0 |
FromJSON Pool Source # | Inverse of the Since: 0.1.0 |
NFData Pool Source # | Default Since: 0.1.0 |
(Monad m, Serial m Text) => Serial m Pool Source # | Uses the underlying instances. Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m Pool Source # | Uses the underlying instances. Since: 0.1.0 |
type Rep Pool Source # | |
makePool :: PoolName -> PoolDepth -> Maybe Pool Source #
Construct a Pool
, given its name and depth.
Since: 0.1.0
makePoolDefault :: Pool Source #
The default pool, i.e.: the one whose name is the empty string.
Since: 0.1.0
makePoolConsole :: Pool Source #
The console
pool.
Since: 0.1.0
Create a pool with the given name and depth.
Since: 0.1.0
Eq PoolName Source # | |
Ord PoolName Source # | |
Read PoolName Source # | |
Show PoolName Source # | |
IsString PoolName Source # | Converts from string via Since: 0.1.0 |
Generic PoolName Source # | |
Hashable PoolName Source # | Default Since: 0.1.0 |
ToJSON PoolName Source # | Converts to JSON string via Since: 0.1.0 |
ToJSONKey PoolName Source # | Converts to JSON string via Since: 0.1.0 |
FromJSON PoolName Source # | Inverse of the Since: 0.1.0 |
FromJSONKey PoolName Source # | Inverse of the Since: 0.1.0 |
NFData PoolName Source # | Default Since: 0.1.0 |
(Monad m, Serial m Text) => Serial m PoolName Source # | Uses the underlying Since: 0.1.0 |
(Monad m, CoSerial m Text) => CoSerial m PoolName Source # | Uses the underlying Since: 0.1.0 |
type Rep PoolName Source # | |
makePoolNameDefault :: PoolName Source #
Create a PoolName
corresponding to the built-in default pool, i.e.: the
pool that is selected if the pool
attribute is set to the empty string.
Since: 0.1.0
makePoolNameConsole :: PoolName Source #
Create a PoolName
corresponding to the built-in console
pool.
Since: 0.1.0
makePoolNameCustom :: Text -> PoolName Source #
Create a PoolName
corresponding to a custom pool.
Note: this can fail at runtime if given the empty string or "console"
,
so you should consider parsePoolName
as a safer alternative.
Since: 0.1.0
_PoolNameDefault :: Getter PoolName (Maybe ()) Source #
A one-way prism corresponding to the poolNameDefault
constructor.
Since: 0.1.0
_PoolNameConsole :: Getter PoolName (Maybe ()) Source #
A one-way prism corresponding to the poolNameConsole
constructor.
Since: 0.1.0
_PoolNameCustom :: Getter PoolName (Maybe Text) Source #
A one-way prism corresponding to the poolNameConsole
constructor.
Since: 0.1.0
poolNameText :: Iso' PoolName Text Source #
An isomorphism between a PoolName
and the corresponding Text
.
Equivalent to
.iso
printPoolName
parsePoolName
Since: 0.1.0
printPoolName :: PoolName -> Text Source #
parsePoolName :: Text -> PoolName Source #
Inverse of printPoolName
.
>>>
parsePoolName ""
PoolNameDefault
>>>
parsePoolName "console"
PoolNameConsole
>>>
parsePoolName "foobar"
PoolNameCustom "foobar"
Since: 0.1.0
Eq PoolDepth Source # | |
Ord PoolDepth Source # | |
Read PoolDepth Source # | |
Show PoolDepth Source # | |
Generic PoolDepth Source # | |
Hashable PoolDepth Source # | Default Since: 0.1.0 |
ToJSON PoolDepth Source # | Converts Since: 0.1.0 |
FromJSON PoolDepth Source # | Inverse of the Since: 0.1.0 |
NFData PoolDepth Source # | Default Since: 0.1.0 |
Monad m => Serial m PoolDepth Source # | Default Since: 0.1.0 |
Monad m => CoSerial m PoolDepth Source # | Default Since: 0.1.0 |
type Rep PoolDepth Source # | |
makePoolDepth :: Positive -> PoolDepth Source #
Construct a finite PoolDepth
from an integer, which should be a number
greater than or equal to 1.
Since: 0.1.0
makePoolInfinite :: PoolDepth Source #
Construct an infinite PoolDepth
. This constructor is needed for the
default pool (pool = ""
), which has an infinite depth.
Since: 0.1.0
poolDepthPositive :: Iso' PoolDepth (Maybe Positive) Source #
An isomorphism between a PoolDepth
and a
;
the Maybe
Positive
Nothing
case maps to makePoolInfinite
and the Just
case
maps to makePoolDepth
.
Since: 0.1.0