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.Pool0.1.0

Contents

Description

Types relating to Ninja pools.

Synopsis

Pool

data Pool Source 0.1.0#

A Ninja pool declaration, as documented here.

Instances

Eq Pool  

Methods

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

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

Ord Pool  

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

Methods

showsPrec :: Int -> Pool -> ShowS #

show :: Pool -> String #

showList :: [Pool] -> ShowS #

Generic Pool  

Associated Types

type Rep Pool :: * -> * #

Methods

from :: Pool -> Rep Pool x #

to :: Rep Pool x -> Pool #

Hashable Pool

Default Hashable instance via Generic.0.1.0

Methods

hashWithSalt :: Int -> Pool -> Int #

hash :: Pool -> Int #

ToJSON Pool

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

FromJSON Pool

Inverse of the ToJSON instance.0.1.0

NFData Pool

Default NFData instance via Generic.0.1.0

Methods

rnf :: Pool -> () #

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

Uses the underlying instances.0.1.0

Methods

series :: Series m Pool #

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

Uses the underlying instances.0.1.0

Methods

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

type Rep Pool  
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 0.1.0#

Construct a Pool, given its name and depth.

makePoolDefault :: Pool Source 0.1.0#

The default pool, i.e.: the one whose name is the empty string.

makePoolConsole :: Pool Source 0.1.0#

The console pool.

makePoolCustom Source 0.1.0#

Arguments

:: Text

The pool name.

-> Positive

The pool depth.

-> Pool 

Create a pool with the given name and depth.

poolName :: Getter Pool PoolName Source 0.1.0#

A Getter that gives the name of a pool.

poolDepth :: Getter Pool PoolDepth Source 0.1.0#

A Getter that gives the depth of a pool.

PoolName

data PoolName Source 0.1.0#

The name of a Ninja pool.

More information is available here.

Instances

Eq PoolName  
Ord PoolName  
Read PoolName  
Show PoolName  
IsString PoolName

Converts from string via parsePoolName.0.1.0

Generic PoolName  

Associated Types

type Rep PoolName :: * -> * #

Methods

from :: PoolName -> Rep PoolName x #

to :: Rep PoolName x -> PoolName #

Hashable PoolName

Default Hashable instance via Generic.0.1.0

Methods

hashWithSalt :: Int -> PoolName -> Int #

hash :: PoolName -> Int #

ToJSON PoolName

Converts to JSON string via printPoolName.0.1.0

ToJSONKey PoolName

Converts to JSON string via printPoolName.0.1.0

FromJSON PoolName

Inverse of the ToJSON instance.0.1.0

FromJSONKey PoolName

Inverse of the ToJSONKey instance.0.1.0

NFData PoolName

Default NFData instance via Generic.0.1.0

Methods

rnf :: PoolName -> () #

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

Uses the underlying Text instance.0.1.0

Methods

series :: Series m PoolName #

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

Uses the underlying Text instance.0.1.0

Methods

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

type Rep PoolName  
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 0.1.0#

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.

makePoolNameConsole :: PoolName Source 0.1.0#

Create a PoolName corresponding to the built-in console pool.

makePoolNameCustom :: Text -> PoolName Source 0.1.0#

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.

_PoolNameDefault :: Getter PoolName (Maybe ()) Source 0.1.0#

A one-way prism corresponding to the poolNameDefault constructor.

_PoolNameConsole :: Getter PoolName (Maybe ()) Source 0.1.0#

A one-way prism corresponding to the poolNameConsole constructor.

_PoolNameCustom :: Getter PoolName (Maybe Text) Source 0.1.0#

A one-way prism corresponding to the poolNameConsole constructor.

poolNameText :: Iso' PoolName Text Source 0.1.0#

An isomorphism between a PoolName and the corresponding Text. Equivalent to iso printPoolName parsePoolName.

printPoolName :: PoolName -> Text Source 0.1.0#

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"

parsePoolName :: Text -> PoolName Source 0.1.0#

Inverse of printPoolName.

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

PoolDepth

data PoolDepth Source 0.1.0#

The depth of a Ninja pool.

More information is available here.

Instances

Eq PoolDepth  
Ord PoolDepth  
Read PoolDepth  
Show PoolDepth  
Generic PoolDepth  

Associated Types

type Rep PoolDepth :: * -> * #

Hashable PoolDepth

Default Hashable instance via Generic.0.1.0

ToJSON PoolDepth

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

FromJSON PoolDepth

Inverse of the ToJSON instance.0.1.0

NFData PoolDepth

Default NFData instance via Generic.0.1.0

Methods

rnf :: PoolDepth -> () #

Monad m => Serial m PoolDepth

Default Serial instance via Generic.0.1.0

Methods

series :: Series m PoolDepth #

Monad m => CoSerial m PoolDepth

Default CoSerial instance via Generic.0.1.0

Methods

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

type Rep PoolDepth  
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 0.1.0#

Construct a finite PoolDepth from an integer, which should be a number greater than or equal to 1.

makePoolInfinite :: PoolDepth Source 0.1.0#

Construct an infinite PoolDepth. This constructor is needed for the default pool (pool = ""), which has an infinite depth.

poolDepthPositive :: Iso' PoolDepth (Maybe Positive) Source 0.1.0#

An isomorphism between a PoolDepth and a Maybe Positive; the Nothing case maps to makePoolInfinite and the Just case maps to makePoolDepth.