language-ninja-0.2.0: A library for dealing with the Ninja build language.

CopyrightCopyright 2017 Awake Security
LicenseApache-2.0
Maintaineropensource@awakesecurity.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Language.Ninja.IR

Contents

Description

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

Synopsis

Language.Ninja.IR.Ninja

data Ninja Source #

A parsed and normalized Ninja file.

Since: 0.1.0

Instances

Eq Ninja Source # 

Methods

(==) :: Ninja -> Ninja -> Bool #

(/=) :: Ninja -> Ninja -> Bool #

Show Ninja Source # 

Methods

showsPrec :: Int -> Ninja -> ShowS #

show :: Ninja -> String #

showList :: [Ninja] -> ShowS #

Generic Ninja Source # 

Associated Types

type Rep Ninja :: * -> * #

Methods

from :: Ninja -> Rep Ninja x #

to :: Rep Ninja x -> Ninja #

Hashable Ninja Source #

Default Hashable instance via Generic.

Since: 0.1.0

Methods

hashWithSalt :: Int -> Ninja -> Int #

hash :: Ninja -> Int #

ToJSON Ninja Source #

Converts to {meta: …, builds: …, phonys: …, defaults: …, pools: …}.

Since: 0.1.0

FromJSON Ninja Source #

Inverse of the ToJSON instance.

Since: 0.1.0

NFData Ninja Source #

Default NFData instance via Generic.

Since: 0.1.0

Methods

rnf :: Ninja -> () #

(Monad m, NinjaConstraint (Serial m)) => Serial m Ninja Source #

Default Serial instance via Generic.

Since: 0.1.0

Methods

series :: Series m Ninja #

(Monad m, NinjaConstraint (CoSerial m)) => CoSerial m Ninja Source #

Default CoSerial instance via Generic.

Since: 0.1.0

Methods

coseries :: Series m b -> Series m (Ninja -> b) #

type Rep Ninja Source # 

makeNinja :: Ninja Source #

Construct a default Ninja value.

Since: 0.1.0

ninjaMeta :: Lens' Ninja Meta Source #

Metadata, which includes top-level variables like builddir.

Since: 0.1.0

ninjaBuilds :: Lens' Ninja (HashSet Build) Source #

Compiled build declarations.

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

ninjaPools :: Lens' Ninja (HashSet Pool) Source #

The set of pools for this Ninja file.

Since: 0.1.0

Language.Ninja.IR.Meta

data Meta Source #

Ninja top-level metadata, as documented here.

Since: 0.1.0

Instances

Eq Meta Source # 

Methods

(==) :: Meta -> Meta -> Bool #

(/=) :: Meta -> Meta -> Bool #

Ord Meta Source # 

Methods

compare :: Meta -> Meta -> Ordering #

(<) :: Meta -> Meta -> Bool #

(<=) :: Meta -> Meta -> Bool #

(>) :: Meta -> Meta -> Bool #

(>=) :: Meta -> Meta -> Bool #

max :: Meta -> Meta -> Meta #

min :: Meta -> Meta -> Meta #

Show Meta Source # 

Methods

showsPrec :: Int -> Meta -> ShowS #

show :: Meta -> String #

showList :: [Meta] -> ShowS #

Generic Meta Source # 

Associated Types

type Rep Meta :: * -> * #

Methods

from :: Meta -> Rep Meta x #

to :: Rep Meta x -> Meta #

Hashable Meta Source #

Default Hashable instance via Generic.

Since: 0.1.0

Methods

hashWithSalt :: Int -> Meta -> Int #

hash :: Meta -> Int #

ToJSON Meta Source #

Converts to {req-version: …, build-dir: …}.

Since: 0.1.0

FromJSON Meta Source #

Inverse of the ToJSON instance.

Since: 0.1.0

NFData Meta Source #

Default NFData instance via Generic.

Since: 0.1.0

Methods

rnf :: Meta -> () #

(Monad m, Serial m Version, Serial m Text) => Serial m Meta Source #

Default Serial instance via Generic.

Since: 0.1.0

Methods

series :: Series m Meta #

(Monad m, CoSerial m Version, CoSerial m Text) => CoSerial m Meta Source #

Default CoSerial instance via Generic.

Since: 0.1.0

Methods

coseries :: Series m b -> Series m (Meta -> b) #

type Rep Meta Source # 
type Rep Meta = D1 (MetaData "Meta" "Language.Ninja.IR.Meta" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" False) (C1 (MetaCons "MkMeta" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_metaReqVersion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Version))) (S1 (MetaSel (Just Symbol "_metaBuildDir") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Path)))))

makeMeta :: Meta Source #

Construct a default Meta value.

Since: 0.1.0

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

data Build Source #

A Ninja build declaration, as documented here.

Since: 0.1.0

Instances

Eq Build Source # 

Methods

(==) :: Build -> Build -> Bool #

(/=) :: Build -> Build -> Bool #

Show Build Source # 

Methods

showsPrec :: Int -> Build -> ShowS #

show :: Build -> String #

showList :: [Build] -> ShowS #

Generic Build Source # 

Associated Types

type Rep Build :: * -> * #

Methods

from :: Build -> Rep Build x #

to :: Rep Build x -> Build #

Hashable Build Source #

Default Hashable instance via Generic.

Since: 0.1.0

Methods

hashWithSalt :: Int -> Build -> Int #

hash :: Build -> Int #

ToJSON Build Source #

Converts to {rule: …, outputs: …, dependencies: …}.

Since: 0.1.0

FromJSON Build Source #

Inverse of the ToJSON instance.

Since: 0.1.0

NFData Build Source #

Default NFData instance via Generic.

Since: 0.1.0

Methods

rnf :: Build -> () #

(Monad m, BuildConstraint (Serial m)) => Serial m Build Source #

Default Serial instance via Generic.

Since: 0.1.0

Methods

series :: Series m Build #

(Monad m, BuildConstraint (CoSerial m)) => CoSerial m Build Source #

Default CoSerial instance via Generic.

Since: 0.1.0

Methods

coseries :: Series m b -> Series m (Build -> b) #

type Rep Build Source # 
type Rep Build = D1 (MetaData "Build" "Language.Ninja.IR.Build" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" False) (C1 (MetaCons "MkBuild" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_buildRule") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Rule)) ((:*:) (S1 (MetaSel (Just Symbol "_buildOuts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashSet Output))) (S1 (MetaSel (Just Symbol "_buildDeps") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashSet Dependency))))))

makeBuild :: Rule -> Build Source #

Construct a default Build from the given Rule

Since: 0.1.0

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

data Rule Source #

A Ninja rule declaration, as documented here.

Since: 0.1.0

Instances

Eq Rule Source # 

Methods

(==) :: Rule -> Rule -> Bool #

(/=) :: Rule -> Rule -> Bool #

Ord Rule Source # 

Methods

compare :: Rule -> Rule -> Ordering #

(<) :: Rule -> Rule -> Bool #

(<=) :: Rule -> Rule -> Bool #

(>) :: Rule -> Rule -> Bool #

(>=) :: Rule -> Rule -> Bool #

max :: Rule -> Rule -> Rule #

min :: Rule -> Rule -> Rule #

Show Rule Source # 

Methods

showsPrec :: Int -> Rule -> ShowS #

show :: Rule -> String #

showList :: [Rule] -> ShowS #

Generic Rule Source # 

Associated Types

type Rep Rule :: * -> * #

Methods

from :: Rule -> Rep Rule x #

to :: Rep Rule x -> Rule #

Hashable Rule Source #

Default Hashable instance via Generic.

Since: 0.1.0

Methods

hashWithSalt :: Int -> Rule -> Int #

hash :: Rule -> Int #

ToJSON Rule Source #

Converts to {name: …, command: …, desc: …, pool: …, depfile: …, deps: …, generator: …, restat: …, rsp: …}.

Since: 0.1.0

FromJSON Rule Source #

Inverse of the ToJSON instance.

Since: 0.1.0

NFData Rule Source #

Default NFData instance via Generic.

Since: 0.1.0

Methods

rnf :: Rule -> () #

(Monad m, Serial m Text) => Serial m Rule Source #

Default Serial instance via Generic.

Since: 0.1.0

Methods

series :: Series m Rule #

(Monad m, CoSerial m Text) => CoSerial m Rule Source #

Default CoSerial instance via Generic.

Since: 0.1.0

Methods

coseries :: Series m b -> Series m (Rule -> b) #

type Rep Rule Source # 

makeRule Source #

Arguments

:: Text

The rule name.

-> Command

The command to run.

-> Rule

A rule that runs this command.

Construct an Rule with the given name and command, with default values for all other attributes (e.g.: False, Nothing, poolDefault).

Since: 0.1.0

ruleName :: Lens' Rule Text Source #

The name of the rule.

Since: 0.1.0

ruleCommand :: Lens' Rule Command Source #

The command that this rule will run.

Since: 0.1.0

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

Instances

Eq SpecialDeps Source # 
Ord SpecialDeps Source # 
Read SpecialDeps Source # 
Show SpecialDeps Source # 
Generic SpecialDeps Source # 

Associated Types

type Rep SpecialDeps :: * -> * #

Hashable SpecialDeps Source #

Default Hashable instance via Generic.

Since: 0.1.0

ToJSON SpecialDeps Source #

Converts to {deps: "gcc"} or {deps: "msvc", prefix: …}.

Since: 0.1.0

FromJSON SpecialDeps Source #

Inverse of the ToJSON instance.

Since: 0.1.0

NFData SpecialDeps Source #

Default NFData instance via Generic.

Since: 0.1.0

Methods

rnf :: SpecialDeps -> () #

(Monad m, Serial m Text) => Serial m SpecialDeps Source #

Default Serial instance via Generic.

Since: 0.1.0

(Monad m, CoSerial m Text) => CoSerial m SpecialDeps Source #

Default CoSerial instance via Generic.

Since: 0.1.0

Methods

coseries :: Series m b -> Series m (SpecialDeps -> b) #

type Rep SpecialDeps Source # 
type Rep SpecialDeps = D1 (MetaData "SpecialDeps" "Language.Ninja.IR.Rule" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" False) ((:+:) (C1 (MetaCons "SpecialDepsGCC" PrefixI False) U1) (C1 (MetaCons "SpecialDepsMSVC" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

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

Instances

Eq ResponseFile Source # 
Ord ResponseFile Source # 
Show ResponseFile Source # 
Generic ResponseFile Source # 

Associated Types

type Rep ResponseFile :: * -> * #

Hashable ResponseFile Source #

Default Hashable instance via Generic.

Since: 0.1.0

ToJSON ResponseFile Source #

Converts to {path: …, content: …}.

Since: 0.1.0

FromJSON ResponseFile Source #

Inverse of the ToJSON instance.

Since: 0.1.0

NFData ResponseFile Source #

Default NFData instance via Generic.

Since: 0.1.0

Methods

rnf :: ResponseFile -> () #

(Monad m, Serial m Text) => Serial m ResponseFile Source #

Default Serial instance via Generic.

Since: 0.1.0

(Monad m, CoSerial m Text) => CoSerial m ResponseFile Source #

Default CoSerial instance via Generic.

Since: 0.1.0

Methods

coseries :: Series m b -> Series m (ResponseFile -> b) #

type Rep ResponseFile Source # 
type Rep ResponseFile = D1 (MetaData "ResponseFile" "Language.Ninja.IR.Rule" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" False) (C1 (MetaCons "MkResponseFile" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_responseFilePath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Path)) (S1 (MetaSel (Just Symbol "_responseFileContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

makeResponseFile Source #

Arguments

:: Path

Corresponds to rspfile.

-> Text

Corresponds to rspfile_content.

-> 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

data Target Source #

This type represents a Ninja target name.

Since: 0.1.0

Instances

Eq Target Source # 

Methods

(==) :: Target -> Target -> Bool #

(/=) :: Target -> Target -> Bool #

Ord Target Source # 
Read Target Source # 
Show Target Source # 
IsString Target Source # 

Methods

fromString :: String -> Target #

Generic Target Source # 

Associated Types

type Rep Target :: * -> * #

Methods

from :: Target -> Rep Target x #

to :: Rep Target x -> Target #

Hashable Target Source # 

Methods

hashWithSalt :: Int -> Target -> Int #

hash :: Target -> Int #

ToJSON Target Source # 
ToJSONKey Target Source # 
FromJSON Target Source # 
FromJSONKey Target Source # 
NFData Target Source # 

Methods

rnf :: Target -> () #

(Monad m, Serial m Text) => Serial m Target Source #

Uses the underlying IText instance.

Since: 0.1.0

Methods

series :: Series m Target #

(Monad m, CoSerial m Text) => CoSerial m Target Source #

Uses the underlying IText instance.

Since: 0.1.0

Methods

coseries :: Series m b -> Series m (Target -> b) #

type Rep Target Source # 
type Rep Target = D1 (MetaData "Target" "Language.Ninja.IR.Target" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" True) (C1 (MetaCons "MkTarget" PrefixI True) (S1 (MetaSel (Just Symbol "_targetIText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IText)))

makeTarget :: Text -> Target Source #

Construct a Target from some Text.

Since: 0.1.0

targetIText :: Iso' Target IText Source #

An isomorphism between a Target and its underlying IText.

Since: 0.1.0

targetText :: Iso' Target Text Source #

An isomorphism that gives access to a Text-typed view of a Target, even though the underlying data has type IText.

This is equivalent to targetIText . from itext.

Since: 0.1.0

data Output Source #

A Ninja build output.

More information is available here.

Since: 0.1.0

Instances

Eq Output Source # 

Methods

(==) :: Output -> Output -> Bool #

(/=) :: Output -> Output -> Bool #

Ord Output Source # 
Read Output Source # 
Show Output Source # 
Generic Output Source # 

Associated Types

type Rep Output :: * -> * #

Methods

from :: Output -> Rep Output x #

to :: Rep Output x -> Output #

Hashable Output Source #

Default Hashable instance via Generic.

Since: 0.1.0

Methods

hashWithSalt :: Int -> Output -> Int #

hash :: Output -> Int #

ToJSON Output Source #

Converts to {target: …, type: …}.

Since: 0.1.0

FromJSON Output Source #

Inverse of the ToJSON instance.

Since: 0.1.0

NFData Output Source #

Default NFData instance via Generic.

Since: 0.1.0

Methods

rnf :: Output -> () #

(Monad m, Serial m Text) => Serial m Output Source #

Default Serial instance via Generic.

Since: 0.1.0

Methods

series :: Series m Output #

(Monad m, CoSerial m Text) => CoSerial m Output Source #

Default CoSerial instance via Generic.

Since: 0.1.0

Methods

coseries :: Series m b -> Series m (Output -> b) #

type Rep Output Source # 
type Rep Output = D1 (MetaData "Output" "Language.Ninja.IR.Target" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" True) (C1 (MetaCons "MkOutput" PrefixI True) (S1 (MetaSel (Just Symbol "_outputTarget") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Target)))

makeOutput Source #

Arguments

:: Target

The underlying target.

-> Output 

Construct an Output.

Since: 0.1.0

outputTarget :: Lens' Output Target Source #

A lens for the Target of an Output.

Since: 0.1.0

data Dependency Source #

A build dependency.

More information is available here.

Since: 0.1.0

Instances

Eq Dependency Source # 
Ord Dependency Source # 
Read Dependency Source # 
Show Dependency Source # 
Generic Dependency Source # 

Associated Types

type Rep Dependency :: * -> * #

Hashable Dependency Source #

Default Hashable instance via Generic.

Since: 0.1.0

ToJSON Dependency Source #

Converts to {target: …, type: …}.

Since: 0.1.0

FromJSON Dependency Source #

Inverse of the ToJSON instance.

Since: 0.1.0

NFData Dependency Source #

Default NFData instance via Generic.

Since: 0.1.0

Methods

rnf :: Dependency -> () #

(Monad m, Serial m Text) => Serial m Dependency Source #

Default Serial instance via Generic.

Since: 0.1.0

(Monad m, CoSerial m Text) => CoSerial m Dependency Source #

Default CoSerial instance via Generic.

Since: 0.1.0

Methods

coseries :: Series m b -> Series m (Dependency -> b) #

type Rep Dependency Source # 
type Rep Dependency = D1 (MetaData "Dependency" "Language.Ninja.IR.Target" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" False) (C1 (MetaCons "MkDependency" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_dependencyTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Target)) (S1 (MetaSel (Just Symbol "_dependencyType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DependencyType))))

makeDependency Source #

Arguments

:: 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

data DependencyType Source #

The type of a Dependency: normal, implicit, or order-only.

Since: 0.1.0

Constructors

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

Instances

Eq DependencyType Source # 
Ord DependencyType Source # 
Read DependencyType Source # 
Show DependencyType Source # 
Generic DependencyType Source # 

Associated Types

type Rep DependencyType :: * -> * #

Hashable DependencyType Source #

Default Hashable instance via Generic.

Since: 0.1.0

ToJSON DependencyType Source #

Converts to "normal", "implicit", and "order-only" respectively.

Since: 0.1.0

FromJSON DependencyType Source #

Inverse of the ToJSON instance.

Since: 0.1.0

NFData DependencyType Source #

Default NFData instance via Generic.

Since: 0.1.0

Methods

rnf :: DependencyType -> () #

Monad m => Serial m DependencyType Source #

Default Serial instance via Generic.

Since: 0.1.0

Monad m => CoSerial m DependencyType Source #

Default CoSerial instance via Generic.

Since: 0.1.0

Methods

coseries :: Series m b -> Series m (DependencyType -> b) #

type Rep DependencyType Source # 
type Rep DependencyType = D1 (MetaData "DependencyType" "Language.Ninja.IR.Target" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" False) ((:+:) (C1 (MetaCons "NormalDependency" PrefixI False) U1) (C1 (MetaCons "OrderOnlyDependency" PrefixI False) U1))

_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

data Pool Source #

A Ninja pool declaration, as documented here.

Since: 0.1.0

Instances

Eq Pool Source # 

Methods

(==) :: Pool -> Pool -> Bool #

(/=) :: Pool -> Pool -> Bool #

Ord Pool Source # 

Methods

compare :: Pool -> Pool -> Ordering #

(<) :: Pool -> Pool -> Bool #

(<=) :: Pool -> Pool -> Bool #

(>) :: Pool -> Pool -> Bool #

(>=) :: Pool -> Pool -> Bool #

max :: Pool -> Pool -> Pool #

min :: Pool -> Pool -> Pool #

Read Pool Source # 
Show Pool Source # 

Methods

showsPrec :: Int -> Pool -> ShowS #

show :: Pool -> String #

showList :: [Pool] -> ShowS #

Generic Pool Source # 

Associated Types

type Rep Pool :: * -> * #

Methods

from :: Pool -> Rep Pool x #

to :: Rep Pool x -> Pool #

Hashable Pool Source #

Default Hashable instance via Generic.

Since: 0.1.0

Methods

hashWithSalt :: Int -> Pool -> Int #

hash :: Pool -> Int #

ToJSON Pool Source #

Converts to {name: …, depth: …}.

Since: 0.1.0

FromJSON Pool Source #

Inverse of the ToJSON instance.

Since: 0.1.0

NFData Pool Source #

Default NFData instance via Generic.

Since: 0.1.0

Methods

rnf :: Pool -> () #

(Monad m, Serial m Text) => Serial m Pool Source #

Uses the underlying instances.

Since: 0.1.0

Methods

series :: Series m Pool #

(Monad m, CoSerial m Text) => CoSerial m Pool Source #

Uses the underlying instances.

Since: 0.1.0

Methods

coseries :: Series m b -> Series m (Pool -> b) #

type Rep Pool Source # 
type Rep Pool = D1 (MetaData "Pool" "Language.Ninja.IR.Pool" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" False) (C1 (MetaCons "MkPool" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_poolName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PoolName)) (S1 (MetaSel (Just Symbol "_poolDepth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PoolDepth))))

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

makePoolCustom Source #

Arguments

:: Text

The pool name.

-> Positive

The pool depth.

-> Pool 

Create a pool with the given name and depth.

Since: 0.1.0

poolName :: Getter Pool PoolName Source #

A Getter that gives the name of a pool.

Since: 0.1.0

poolDepth :: Getter Pool PoolDepth Source #

A Getter that gives the depth of a pool.

Since: 0.1.0

data PoolName Source #

The name of a Ninja pool.

More information is available here.

Since: 0.1.0

Instances

Eq PoolName Source # 
Ord PoolName Source # 
Read PoolName Source # 
Show PoolName Source # 
IsString PoolName Source #

Converts from string via parsePoolName.

Since: 0.1.0

Generic PoolName Source # 

Associated Types

type Rep PoolName :: * -> * #

Methods

from :: PoolName -> Rep PoolName x #

to :: Rep PoolName x -> PoolName #

Hashable PoolName Source #

Default Hashable instance via Generic.

Since: 0.1.0

Methods

hashWithSalt :: Int -> PoolName -> Int #

hash :: PoolName -> Int #

ToJSON PoolName Source #

Converts to JSON string via printPoolName.

Since: 0.1.0

ToJSONKey PoolName Source #

Converts to JSON string via printPoolName.

Since: 0.1.0

FromJSON PoolName Source #

Inverse of the ToJSON instance.

Since: 0.1.0

FromJSONKey PoolName Source #

Inverse of the ToJSONKey instance.

Since: 0.1.0

NFData PoolName Source #

Default NFData instance via Generic.

Since: 0.1.0

Methods

rnf :: PoolName -> () #

(Monad m, Serial m Text) => Serial m PoolName Source #

Uses the underlying Text instance.

Since: 0.1.0

Methods

series :: Series m PoolName #

(Monad m, CoSerial m Text) => CoSerial m PoolName Source #

Uses the underlying Text instance.

Since: 0.1.0

Methods

coseries :: Series m b -> Series m (PoolName -> b) #

type Rep PoolName Source # 
type Rep PoolName = D1 (MetaData "PoolName" "Language.Ninja.IR.Pool" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" False) ((:+:) (C1 (MetaCons "PoolNameDefault" PrefixI False) U1) ((:+:) (C1 (MetaCons "PoolNameConsole" PrefixI False) U1) (C1 (MetaCons "PoolNameCustom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

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 #

Convert a PoolName to the string that, if the pool attribute is set to it, will cause the given PoolName to be parsed.

>>> printPoolName makePoolNameDefault
""
>>> printPoolName makePoolNameConsole
"console"
>>> printPoolName (makePoolNameCustom "foobar")
"foobar"

Since: 0.1.0

parsePoolName :: Text -> PoolName Source #

Inverse of printPoolName.

>>> parsePoolName ""
PoolNameDefault
>>> parsePoolName "console"
PoolNameConsole
>>> parsePoolName "foobar"
PoolNameCustom "foobar"

Since: 0.1.0

data PoolDepth Source #

The depth of a Ninja pool.

More information is available here.

Since: 0.1.0

Instances

Eq PoolDepth Source # 
Ord PoolDepth Source # 
Read PoolDepth Source # 
Show PoolDepth Source # 
Generic PoolDepth Source # 

Associated Types

type Rep PoolDepth :: * -> * #

Hashable PoolDepth Source #

Default Hashable instance via Generic.

Since: 0.1.0

ToJSON PoolDepth Source #

Converts makePoolInfinite to "infinite" and makePoolDepth to the corresponding JSON number.

Since: 0.1.0

FromJSON PoolDepth Source #

Inverse of the ToJSON instance.

Since: 0.1.0

NFData PoolDepth Source #

Default NFData instance via Generic.

Since: 0.1.0

Methods

rnf :: PoolDepth -> () #

Monad m => Serial m PoolDepth Source #

Default Serial instance via Generic.

Since: 0.1.0

Methods

series :: Series m PoolDepth #

Monad m => CoSerial m PoolDepth Source #

Default CoSerial instance via Generic.

Since: 0.1.0

Methods

coseries :: Series m b -> Series m (PoolDepth -> b) #

type Rep PoolDepth Source # 
type Rep PoolDepth = D1 (MetaData "PoolDepth" "Language.Ninja.IR.Pool" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" False) ((:+:) (C1 (MetaCons "PoolDepth" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Positive))) (C1 (MetaCons "PoolInfinite" PrefixI False) U1))

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 Maybe Positive; the Nothing case maps to makePoolInfinite and the Just case maps to makePoolDepth.

Since: 0.1.0