Copyright | Copyright 2017 Awake Security |
---|---|
License | Apache-2.0 |
Maintainer | opensource@awakesecurity.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Language.Ninja.Errors0.1.0
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
- 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 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. |
Instances
throwNinjaError :: MonadError NinjaError m => NinjaError -> m a Source 0.1.0#
Throw a NinjaError
.
throwGenericNinjaError :: MonadError NinjaError m => Text -> m a Source 0.1.0#
Throw a generic catch-all NinjaError
.
throwNinjaParseError :: MonadError NinjaError m => ParseError -> m a Source 0.1.0#
Throw a ParseError
.
throwNinjaCompileError :: MonadError NinjaError m => CompileError -> m a Source 0.1.0#
Throw a CompileError
.
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 |
0.1.0CompileBuildError !CompileBuildError | Errors encountered while compiling a |
0.1.0CompileRuleError !CompileRuleError | Errors encountered while compiling a |
0.1.0CompilePhonyError !CompilePhonyError | Errors encountered while compiling the phony |
0.1.0CompileDefaultError !CompileDefaultError | Errors encountered while compiling the default target |
0.1.0CompilePoolError !CompilePoolError | Errors encountered while compiling a |
Instances
Eq CompileError | #Source | |
Show CompileError | #Source | |
Generic CompileError | #Source | |
ToJSON CompileError | #Source | Converts to |
Exception CompileError | #Source | Default instance.0.1.0 |
type Rep CompileError | #Source | |
throwCompileError :: MonadError CompileError m => CompileError -> m a Source 0.1.0#
Throw a 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 |
Instances
Eq CompileMetaError | #Source | |
Show CompileMetaError | #Source | |
Generic CompileMetaError | #Source | |
ToJSON CompileMetaError | #Source | Converts to |
type Rep CompileMetaError | #Source | |
throwCompileMetaError :: MonadError CompileError m => CompileMetaError -> m a Source 0.1.0#
Throw a CompileMetaError
.
throwGenericCompileMetaError :: MonadError CompileError m => Text -> m a Source 0.1.0#
Throw a generic catch-all CompileMetaError
.
throwVersionParseFailure :: MonadError CompileError m => ParsingError -> m a Source 0.1.0#
Throw a VersionParseFailure
error.
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. |
Instances
Eq CompilePhonyError | #Source | |
Show CompilePhonyError | #Source | |
Generic CompilePhonyError | #Source | |
ToJSON CompilePhonyError | #Source | Converts to |
type Rep CompilePhonyError | #Source | |
throwCompilePhonyError :: MonadError CompileError m => CompilePhonyError -> m a Source 0.1.0#
Throw a CompilePhonyError
.
throwGenericCompilePhonyError :: MonadError CompileError m => Text -> m a Source 0.1.0#
Throw a generic catch-all CompilePhonyError
.
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. |
Instances
Eq CompileDefaultError | #Source | |
Show CompileDefaultError | #Source | |
Generic CompileDefaultError | #Source | |
ToJSON CompileDefaultError | #Source | Converts to |
type Rep CompileDefaultError | #Source | |
throwCompileDefaultError :: MonadError CompileError m => CompileDefaultError -> m a Source 0.1.0#
Throw a CompileDefaultError
.
throwGenericCompileDefaultError :: MonadError CompileError m => Text -> m a Source 0.1.0#
Throw a generic catch-all CompileDefaultError
.
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 |
Instances
Eq CompileBuildError | #Source | |
Show CompileBuildError | #Source | |
Generic CompileBuildError | #Source | |
ToJSON CompileBuildError | #Source | Converts to |
type Rep CompileBuildError | #Source | |
throwCompileBuildError :: MonadError CompileError m => CompileBuildError -> m a Source 0.1.0#
Throw a CompileBuildError
.
throwGenericCompileBuildError :: MonadError CompileError m => Text -> m a Source 0.1.0#
Throw a generic catch-all CompileBuildError
.
throwBuildRuleNotFound :: MonadError CompileError m => Text -> m a Source 0.1.0#
Throw a BuildRuleNotFound
error.
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 |
0.1.0UnexpectedMSVCPrefix !Text | Unexpected |
Instances
Eq CompileRuleError | #Source | |
Show CompileRuleError | #Source | |
Generic CompileRuleError | #Source | |
ToJSON CompileRuleError | #Source | Converts to |
type Rep CompileRuleError | #Source | |
throwCompileRuleError :: MonadError CompileError m => CompileRuleError -> m a Source 0.1.0#
Throw a CompileRuleError
.
throwGenericCompileRuleError :: MonadError CompileError m => Text -> m a Source 0.1.0#
Throw a generic catch-all CompileRuleError
.
throwRuleLookupFailure :: MonadError CompileError m => Text -> m a Source 0.1.0#
Throw a RuleLookupFailure
error.
throwUnknownDeps :: MonadError CompileError m => Text -> m a Source 0.1.0#
Throw an UnknownDeps
error.
throwUnexpectedMSVCPrefix :: MonadError CompileError m => Text -> m a Source 0.1.0#
Throw an UnexpectedMSVCPrefix
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 |
Instances
Eq CompilePoolError | #Source | |
Show CompilePoolError | #Source | |
Generic CompilePoolError | #Source | |
ToJSON CompilePoolError | #Source | Converts to |
type Rep CompilePoolError | #Source | |
throwCompilePoolError :: MonadError CompileError m => CompilePoolError -> m a Source 0.1.0#
Throw a CompilePoolError
.
throwGenericCompilePoolError :: MonadError CompileError m => Text -> m a Source 0.1.0#
Throw a generic catch-all CompilePoolError
.
throwInvalidPoolDepth :: MonadError CompileError m => Int -> m a Source 0.1.0#
Throw an InvalidPoolDepth
error.
throwEmptyPoolName :: MonadError CompileError m => m a Source 0.1.0#
Throw an EmptyPoolName
error.
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 | #Source | |
Show ParseError | #Source | |
Generic ParseError | #Source | |
ToJSON ParseError | #Source | Converts to |
Exception ParseError | #Source | Default instance.0.1.0 |
type Rep ParseError | #Source | |
throwParseError :: MonadError ParseError m => ParseError -> m a Source 0.1.0#
Throw a ParseError
.
throwGenericParseError :: MonadError ParseError m => Text -> m a Source 0.1.0#
Throw a generic catch-all ParseError
.
throwLexBindingFailure :: MonadError ParseError m => Text -> m a Source 0.1.0#
Throw a LexBindingFailure
error.
throwLexExpectedColon :: MonadError ParseError m => m a Source 0.1.0#
Throw a LexExpectedColon
error.
throwLexUnexpectedDollar :: MonadError ParseError m => m a Source 0.1.0#
Throw a LexUnexpectedColon
error.
throwLexUnexpectedSeparator :: MonadError ParseError m => Char -> m a Source 0.1.0#
Throw a LexUnexpectedSeparator
error.
throwLexParsecError :: MonadError ParseError m => ParseError Char Dec -> m a Source 0.1.0#
Throw a LexParsecError
error.
throwParseBadDepthField :: MonadError ParseError m => Text -> m a Source 0.1.0#
Throw a ParseBadDepthField
error.
throwParseUnexpectedBinding :: MonadError ParseError m => Text -> m a Source 0.1.0#
Throw a ParseUnexpectedBinding
error.