language-ninja-0.1.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.Target

Contents

Description

Types relating to Ninja build targets, outputs, and dependencies.

Since: 0.1.0

Synopsis

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.1.0-CTXTL0Lugm4Llo91nN4SIr" 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

Output

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.1.0-CTXTL0Lugm4Llo91nN4SIr" 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

Dependency

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.1.0-CTXTL0Lugm4Llo91nN4SIr" 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.1.0-CTXTL0Lugm4Llo91nN4SIr" 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