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

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

Synopsis

Language.Ninja.Errors

data NinjaError Source 0.1.0#

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

Constructors

0.1.0GenericNinjaError !Text

Generic catch-all error constructor. Avoid using this.

0.1.0NinjaParseError !ParseError

Errors encountered during parsing.

0.1.0NinjaCompileError !CompileError

Errors encountered during compilation.

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

Throw a generic catch-all NinjaError.

Language.Ninja.Errors.Compile

data CompileError Source 0.1.0#

The type of errors encountered during compilation.

Constructors

0.1.0GenericCompileError !Text

Generic catch-all error constructor. Avoid using this.

0.1.0CompileMetaError !CompileMetaError

Errors encountered while compiling a Meta.

0.1.0CompileBuildError !CompileBuildError

Errors encountered while compiling a Build.

0.1.0CompileRuleError !CompileRuleError

Errors encountered while compiling a Rule.

0.1.0CompilePhonyError !CompilePhonyError

Errors encountered while compiling the phony HashMap.

0.1.0CompileDefaultError !CompileDefaultError

Errors encountered while compiling the default target HashSet.

0.1.0CompilePoolError !CompilePoolError

Errors encountered while compiling a Pool.

Instances

Eq CompileError  
Show CompileError  
Generic CompileError  

Associated Types

type Rep CompileError :: * -> * #

ToJSON CompileError

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

Exception CompileError

Default instance.0.1.0

type Rep CompileError  

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

Throw a generic catch-all CompileError.

data CompileMetaError Source 0.1.0#

The type of errors encountered while compiling Ninja metadata.

Constructors

0.1.0GenericCompileMetaError !Text

Generic catch-all error constructor. Avoid using this.

0.1.0VersionParseFailure !ParsingError
Failed to parse ninja_required_version: …

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

Throw a generic catch-all CompileMetaError.

data CompilePhonyError Source 0.1.0#

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

Constructors

0.1.0GenericCompilePhonyError !Text

Generic catch-all error constructor. Avoid using this.

data CompileDefaultError Source 0.1.0#

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

Constructors

0.1.0GenericCompileDefaultError !Text

Generic catch-all error constructor. Avoid using this.

data CompileBuildError Source 0.1.0#

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

Constructors

0.1.0GenericCompileBuildError !Text

Generic catch-all error constructor. Avoid using this.

0.1.0BuildRuleNotFound !Text
Rule not found: text

data CompileRuleError Source 0.1.0#

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

Constructors

0.1.0GenericCompileRuleError !Text

Generic catch-all error constructor. Avoid using this.

0.1.0RuleLookupFailure !Text
Lookup failed on rule variable: text
0.1.0UnknownDepsValue !Text
Unknown deps value: text
0.1.0UnexpectedMSVCPrefix !Text
Unexpected msvc_deps_prefix for `deps = "text"`

Instances

Eq CompileRuleError  
Show CompileRuleError  
Generic CompileRuleError  
ToJSON CompileRuleError

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

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

Throw a generic catch-all CompileRuleError.

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

Throw an UnknownDeps error.

data CompilePoolError Source 0.1.0#

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

Constructors

0.1.0GenericCompilePoolError !Text

Generic catch-all error constructor. Avoid using this.

0.1.0InvalidPoolDepth !Int
Invalid pool depth for console: int
0.1.0EmptyPoolName
Pool name is an empty string

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

Throw a generic catch-all CompilePoolError.

Language.Ninja.Errors.Parser

data ParseError Source 0.1.0#

The type of errors encountered during parsing.

Constructors

0.1.0GenericParseError !Text

Generic catch-all error constructor. Avoid using this.

0.1.0LexBindingFailure !Text
Lexer failed at binding: text
0.1.0LexExpectedColon
Expected a colon
0.1.0LexUnexpectedDollar
Unexpected $ followed by unexpected stuff
0.1.0LexUnexpectedSeparator Char

Lexer expected a separator character but found something else

0.1.0LexParsecError !(ParseError Char Dec)

Any other lexer error.

0.1.0ParseBadDepthField !Text
Could not parse depth field in pool, got: text
0.1.0ParseUnexpectedBinding !Text
Unexpected binding defining text

Instances

Eq ParseError  
Show ParseError  
Generic ParseError  

Associated Types

type Rep ParseError :: * -> * #

ToJSON ParseError

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

Exception ParseError

Default instance.0.1.0

type Rep ParseError  

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

Throw a generic catch-all ParseError.

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

Throw a LexUnexpectedColon error.