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

Contents

Description

Types relating to Ninja pools.

Since: 0.1.0

Synopsis

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

PoolName

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

PoolDepth

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