Copyright | Copyright 2017 Awake Security |
---|---|
License | Apache-2.0 |
Maintainer | opensource@awakesecurity.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
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
- data NinjaError
- throwNinjaError :: MonadError NinjaError m => NinjaError -> m a
- throwGenericNinjaError :: MonadError NinjaError m => Text -> m a
- throwNinjaParseError :: MonadError NinjaError m => ParseError -> m a
- throwNinjaCompileError :: MonadError NinjaError m => CompileError -> m a
- data CompileError
- throwCompileError :: MonadError CompileError m => CompileError -> m a
- throwGenericCompileError :: MonadError CompileError m => Text -> m a
- data CompileMetaError
- throwCompileMetaError :: MonadError CompileError m => CompileMetaError -> m a
- throwGenericCompileMetaError :: MonadError CompileError m => Text -> m a
- throwVersionParseFailure :: MonadError CompileError m => ParsingError -> m a
- data CompilePhonyError = GenericCompilePhonyError !Text
- throwCompilePhonyError :: MonadError CompileError m => CompilePhonyError -> m a
- throwGenericCompilePhonyError :: MonadError CompileError m => Text -> m a
- data CompileDefaultError = GenericCompileDefaultError !Text
- throwCompileDefaultError :: MonadError CompileError m => CompileDefaultError -> m a
- throwGenericCompileDefaultError :: MonadError CompileError m => Text -> m a
- data CompileBuildError
- throwCompileBuildError :: MonadError CompileError m => CompileBuildError -> m a
- throwGenericCompileBuildError :: MonadError CompileError m => Text -> m a
- throwBuildRuleNotFound :: MonadError CompileError m => Text -> m a
- data CompileRuleError
- throwCompileRuleError :: MonadError CompileError m => CompileRuleError -> m a
- throwGenericCompileRuleError :: MonadError CompileError m => Text -> m a
- throwRuleLookupFailure :: MonadError CompileError m => Text -> m a
- throwUnknownDeps :: MonadError CompileError m => Text -> m a
- throwUnexpectedMSVCPrefix :: MonadError CompileError m => Text -> m a
- data CompilePoolError
- throwCompilePoolError :: MonadError CompileError m => CompilePoolError -> m a
- throwGenericCompilePoolError :: MonadError CompileError m => Text -> m a
- throwInvalidPoolDepth :: MonadError CompileError m => Int -> m a
- throwEmptyPoolName :: MonadError CompileError m => m a
- data ParseError
- throwParseError :: MonadError ParseError m => ParseError -> m a
- throwGenericParseError :: MonadError ParseError m => Text -> m a
- throwLexBindingFailure :: MonadError ParseError m => Text -> m a
- throwLexExpectedColon :: MonadError ParseError m => m a
- throwLexUnexpectedDollar :: MonadError ParseError m => m a
- throwLexUnexpectedSeparator :: MonadError ParseError m => Char -> m a
- throwLexParsecError :: MonadError ParseError m => ParseError Char Dec -> m a
- throwParseBadDepthField :: MonadError ParseError m => Text -> m a
- throwParseUnexpectedBinding :: MonadError ParseError m => Text -> m a
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
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 |
throwNinjaError :: MonadError NinjaError m => NinjaError -> m a Source #
Throw a NinjaError
.
Since: 0.1.0
throwGenericNinjaError :: MonadError NinjaError m => Text -> m a Source #
Throw a generic catch-all NinjaError
.
Since: 0.1.0
throwNinjaParseError :: MonadError NinjaError m => ParseError -> m a Source #
Throw a ParseError
.
Since: 0.1.0
throwNinjaCompileError :: MonadError NinjaError m => CompileError -> m a Source #
Throw a CompileError
.
Since: 0.1.0
Language.Ninja.Errors.Compile
data CompileError Source #
The type of errors encountered during compilation.
Since: 0.1.0
GenericCompileError !Text | Generic catch-all error constructor. Avoid using this. Since: 0.1.0 |
CompileMetaError !CompileMetaError | Errors encountered while compiling a Since: 0.1.0 |
CompileBuildError !CompileBuildError | Errors encountered while compiling a Since: 0.1.0 |
CompileRuleError !CompileRuleError | Errors encountered while compiling a Since: 0.1.0 |
CompilePhonyError !CompilePhonyError | Errors encountered while compiling the phony Since: 0.1.0 |
CompileDefaultError !CompileDefaultError | Errors encountered while compiling the default target Since: 0.1.0 |
CompilePoolError !CompilePoolError | Errors encountered while compiling a Since: 0.1.0 |
Eq CompileError Source # | |
Show CompileError Source # | |
Generic CompileError Source # | |
ToJSON CompileError Source # | Converts to Since: 0.1.0 |
Exception CompileError Source # | Default instance. Since: 0.1.0 |
type Rep CompileError Source # | |
throwCompileError :: MonadError CompileError m => CompileError -> m a Source #
Throw a CompileError
.
Since: 0.1.0
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
GenericCompileMetaError !Text | Generic catch-all error constructor. Avoid using this. Since: 0.1.0 |
VersionParseFailure !ParsingError | Failed to parse Since: 0.1.0 |
Eq CompileMetaError Source # | |
Show CompileMetaError Source # | |
Generic CompileMetaError Source # | |
ToJSON CompileMetaError Source # | Converts to Since: 0.1.0 |
type Rep CompileMetaError Source # | |
throwCompileMetaError :: MonadError CompileError m => CompileMetaError -> m a Source #
Throw a CompileMetaError
.
Since: 0.1.0
throwGenericCompileMetaError :: MonadError CompileError m => Text -> m a Source #
Throw a generic catch-all CompileMetaError
.
Since: 0.1.0
throwVersionParseFailure :: MonadError CompileError m => ParsingError -> m a Source #
Throw a VersionParseFailure
error.
Since: 0.1.0
data CompilePhonyError Source #
The type of errors encountered while compiling a Ninja phony build
.
Since: 0.1.0
GenericCompilePhonyError !Text | Generic catch-all error constructor. Avoid using this. Since: 0.1.0 |
Eq CompilePhonyError Source # | |
Show CompilePhonyError Source # | |
Generic CompilePhonyError Source # | |
ToJSON CompilePhonyError Source # | Converts to Since: 0.1.0 |
type Rep CompilePhonyError Source # | |
throwCompilePhonyError :: MonadError CompileError m => CompilePhonyError -> m a Source #
Throw a CompilePhonyError
.
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
GenericCompileDefaultError !Text | Generic catch-all error constructor. Avoid using this. Since: 0.1.0 |
Eq CompileDefaultError Source # | |
Show CompileDefaultError Source # | |
Generic CompileDefaultError Source # | |
ToJSON CompileDefaultError Source # | Converts to Since: 0.1.0 |
type Rep CompileDefaultError Source # | |
throwCompileDefaultError :: MonadError CompileError m => CompileDefaultError -> m a Source #
Throw a CompileDefaultError
.
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
GenericCompileBuildError !Text | Generic catch-all error constructor. Avoid using this. Since: 0.1.0 |
BuildRuleNotFound !Text | Rule not found: text Since: 0.1.0 |
Eq CompileBuildError Source # | |
Show CompileBuildError Source # | |
Generic CompileBuildError Source # | |
ToJSON CompileBuildError Source # | Converts to Since: 0.1.0 |
type Rep CompileBuildError Source # | |
throwCompileBuildError :: MonadError CompileError m => CompileBuildError -> m a Source #
Throw a CompileBuildError
.
Since: 0.1.0
throwGenericCompileBuildError :: MonadError CompileError m => Text -> m a Source #
Throw a generic catch-all CompileBuildError
.
Since: 0.1.0
throwBuildRuleNotFound :: MonadError CompileError m => Text -> m a Source #
Throw a BuildRuleNotFound
error.
Since: 0.1.0
data CompileRuleError Source #
The type of errors encountered while compiling a Ninja rule
statement.
Since: 0.1.0
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 Since: 0.1.0 |
UnexpectedMSVCPrefix !Text | Unexpected Since: 0.1.0 |
Eq CompileRuleError Source # | |
Show CompileRuleError Source # | |
Generic CompileRuleError Source # | |
ToJSON CompileRuleError Source # | Converts to Since: 0.1.0 |
type Rep CompileRuleError Source # | |
throwCompileRuleError :: MonadError CompileError m => CompileRuleError -> m a Source #
Throw a CompileRuleError
.
Since: 0.1.0
throwGenericCompileRuleError :: MonadError CompileError m => Text -> m a Source #
Throw a generic catch-all CompileRuleError
.
Since: 0.1.0
throwRuleLookupFailure :: MonadError CompileError m => Text -> m a Source #
Throw a RuleLookupFailure
error.
Since: 0.1.0
throwUnknownDeps :: MonadError CompileError m => Text -> m a Source #
Throw an UnknownDeps
error.
Since: 0.1.0
throwUnexpectedMSVCPrefix :: MonadError CompileError m => Text -> m a Source #
Throw an UnexpectedMSVCPrefix
error.
Since: 0.1.0
data CompilePoolError Source #
The type of errors encountered while compiling a Ninja pool
statement.
Since: 0.1.0
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 |
Eq CompilePoolError Source # | |
Show CompilePoolError Source # | |
Generic CompilePoolError Source # | |
ToJSON CompilePoolError Source # | Converts to Since: 0.1.0 |
type Rep CompilePoolError Source # | |
throwCompilePoolError :: MonadError CompileError m => CompilePoolError -> m a Source #
Throw a CompilePoolError
.
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
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 |
Eq ParseError Source # | |
Show ParseError Source # | |
Generic ParseError Source # | |
ToJSON ParseError Source # | Converts to Since: 0.1.0 |
Exception ParseError Source # | Default instance. Since: 0.1.0 |
type Rep ParseError Source # | |
throwParseError :: MonadError ParseError m => ParseError -> m a Source #
Throw a ParseError
.
Since: 0.1.0
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
throwLexUnexpectedSeparator :: MonadError ParseError m => Char -> m a Source #
Throw a LexUnexpectedSeparator
error.
Since: 0.1.0
throwLexParsecError :: MonadError ParseError m => ParseError Char Dec -> m a Source #
Throw a LexParsecError
error.
Since: 0.1.0
throwParseBadDepthField :: MonadError ParseError m => Text -> m a Source #
Throw a ParseBadDepthField
error.
Since: 0.1.0
throwParseUnexpectedBinding :: MonadError ParseError m => Text -> m a Source #
Throw a ParseUnexpectedBinding
error.
Since: 0.1.0