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

Contents

Description

This module re-exports all of the modules under the Language.Ninja.Errors namespace for convenience.

It is recommended that you import it with the following style:

import qualified Language.Ninja.Errors as Errors

Since: 0.1.0

Synopsis

Language.Ninja.Errors

data NinjaError Source #

This type subsumes any error that can be thrown during execution of a function defined in language-ninja.

Since: 0.1.0

Constructors

GenericNinjaError !Text

Generic catch-all error constructor. Avoid using this.

Since: 0.1.0

NinjaParseError !ParseError

Errors encountered during parsing.

Since: 0.1.0

NinjaCompileError !CompileError

Errors encountered during compilation.

Since: 0.1.0

throwGenericNinjaError :: MonadError NinjaError m => Text -> m a Source #

Throw a generic catch-all NinjaError.

Since: 0.1.0

Language.Ninja.Errors.Compile

data CompileError Source #

The type of errors encountered during compilation.

Since: 0.1.0

Constructors

GenericCompileError !Text

Generic catch-all error constructor. Avoid using this.

Since: 0.1.0

CompileMetaError !CompileMetaError

Errors encountered while compiling a Meta.

Since: 0.1.0

CompileBuildError !CompileBuildError

Errors encountered while compiling a Build.

Since: 0.1.0

CompileRuleError !CompileRuleError

Errors encountered while compiling a Rule.

Since: 0.1.0

CompilePhonyError !CompilePhonyError

Errors encountered while compiling the phony HashMap.

Since: 0.1.0

CompileDefaultError !CompileDefaultError

Errors encountered while compiling the default target HashSet.

Since: 0.1.0

CompilePoolError !CompilePoolError

Errors encountered while compiling a Pool.

Since: 0.1.0

Instances

Eq CompileError Source # 
Show CompileError Source # 
Generic CompileError Source # 

Associated Types

type Rep CompileError :: * -> * #

ToJSON CompileError Source #

Converts to {tag: …, value: …}.

Since: 0.1.0

Exception CompileError Source #

Default instance.

Since: 0.1.0

type Rep CompileError Source # 

throwGenericCompileError :: MonadError CompileError m => Text -> m a Source #

Throw a generic catch-all CompileError.

Since: 0.1.0

data CompileMetaError Source #

The type of errors encountered while compiling Ninja metadata.

Since: 0.1.0

Constructors

GenericCompileMetaError !Text

Generic catch-all error constructor. Avoid using this.

Since: 0.1.0

VersionParseFailure !ParsingError
Failed to parse ninja_required_version: …

Since: 0.1.0

throwGenericCompileMetaError :: MonadError CompileError m => Text -> m a Source #

Throw a generic catch-all CompileMetaError.

Since: 0.1.0

data CompilePhonyError Source #

The type of errors encountered while compiling a Ninja phony build.

Since: 0.1.0

Constructors

GenericCompilePhonyError !Text

Generic catch-all error constructor. Avoid using this.

Since: 0.1.0

throwGenericCompilePhonyError :: MonadError CompileError m => Text -> m a Source #

Throw a generic catch-all CompilePhonyError.

Since: 0.1.0

data CompileDefaultError Source #

The type of errors encountered while compiling a Ninja default statement.

Since: 0.1.0

Constructors

GenericCompileDefaultError !Text

Generic catch-all error constructor. Avoid using this.

Since: 0.1.0

throwGenericCompileDefaultError :: MonadError CompileError m => Text -> m a Source #

Throw a generic catch-all CompileDefaultError.

Since: 0.1.0

data CompileBuildError Source #

The type of errors encountered while compiling a Ninja build statement.

Since: 0.1.0

Constructors

GenericCompileBuildError !Text

Generic catch-all error constructor. Avoid using this.

Since: 0.1.0

BuildRuleNotFound !Text
Rule not found: text

Since: 0.1.0

throwGenericCompileBuildError :: MonadError CompileError m => Text -> m a Source #

Throw a generic catch-all CompileBuildError.

Since: 0.1.0

data CompileRuleError Source #

The type of errors encountered while compiling a Ninja rule statement.

Since: 0.1.0

Constructors

GenericCompileRuleError !Text

Generic catch-all error constructor. Avoid using this.

Since: 0.1.0

RuleLookupFailure !Text
Lookup failed on rule variable: text

Since: 0.1.0

UnknownDepsValue !Text
Unknown deps value: text

Since: 0.1.0

UnexpectedMSVCPrefix !Text
Unexpected msvc_deps_prefix for `deps = "text"`

Since: 0.1.0

Instances

Eq CompileRuleError Source # 
Show CompileRuleError Source # 
Generic CompileRuleError Source # 
ToJSON CompileRuleError Source #

Converts to {tag: …, value: …}.

Since: 0.1.0

type Rep CompileRuleError Source # 
type Rep CompileRuleError = D1 (MetaData "CompileRuleError" "Language.Ninja.Errors.Compile" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" False) ((:+:) ((:+:) (C1 (MetaCons "GenericCompileRuleError" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) (C1 (MetaCons "RuleLookupFailure" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) ((:+:) (C1 (MetaCons "UnknownDepsValue" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) (C1 (MetaCons "UnexpectedMSVCPrefix" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

throwGenericCompileRuleError :: MonadError CompileError m => Text -> m a Source #

Throw a generic catch-all CompileRuleError.

Since: 0.1.0

throwUnknownDeps :: MonadError CompileError m => Text -> m a Source #

Throw an UnknownDeps error.

Since: 0.1.0

data CompilePoolError Source #

The type of errors encountered while compiling a Ninja pool statement.

Since: 0.1.0

Constructors

GenericCompilePoolError !Text

Generic catch-all error constructor. Avoid using this.

Since: 0.1.0

InvalidPoolDepth !Int
Invalid pool depth for console: int

Since: 0.1.0

EmptyPoolName
Pool name is an empty string

Since: 0.1.0

throwGenericCompilePoolError :: MonadError CompileError m => Text -> m a Source #

Throw a generic catch-all CompilePoolError.

Since: 0.1.0

throwInvalidPoolDepth :: MonadError CompileError m => Int -> m a Source #

Throw an InvalidPoolDepth error.

Since: 0.1.0

throwEmptyPoolName :: MonadError CompileError m => m a Source #

Throw an EmptyPoolName error.

Since: 0.1.0

Language.Ninja.Errors.Parser

data ParseError Source #

The type of errors encountered during parsing.

Since: 0.1.0

Constructors

GenericParseError !Text

Generic catch-all error constructor. Avoid using this.

Since: 0.1.0

LexBindingFailure !Text
Lexer failed at binding: text

Since: 0.1.0

LexExpectedColon
Expected a colon

Since: 0.1.0

LexUnexpectedDollar
Unexpected $ followed by unexpected stuff

Since: 0.1.0

LexUnexpectedSeparator Char

Lexer expected a separator character but found something else

Since: 0.1.0

LexParsecError !(ParseError Char Dec)

Any other lexer error.

Since: 0.1.0

ParseBadDepthField !Text
Could not parse depth field in pool, got: text

Since: 0.1.0

ParseUnexpectedBinding !Text
Unexpected binding defining text

Since: 0.1.0

Instances

Eq ParseError Source # 
Show ParseError Source # 
Generic ParseError Source # 

Associated Types

type Rep ParseError :: * -> * #

ToJSON ParseError Source #

Converts to {tag: …, value: …}.

Since: 0.1.0

Exception ParseError Source #

Default instance.

Since: 0.1.0

type Rep ParseError Source # 

throwGenericParseError :: MonadError ParseError m => Text -> m a Source #

Throw a generic catch-all ParseError.

Since: 0.1.0

throwLexBindingFailure :: MonadError ParseError m => Text -> m a Source #

Throw a LexBindingFailure error.

Since: 0.1.0

throwLexExpectedColon :: MonadError ParseError m => m a Source #

Throw a LexExpectedColon error.

Since: 0.1.0

throwLexUnexpectedDollar :: MonadError ParseError m => m a Source #

Throw a LexUnexpectedColon error.

Since: 0.1.0