Safe Haskell | None |
---|---|
Language | Haskell2010 |
Technique.Failure
Description
Error messages from compiling.
Synopsis
- data Status
- data Source = Source {}
- emptySource :: Source
- data FailureReason
- data CompilationError = CompilationError Source FailureReason
- exitCodeFor :: CompilationError -> Int
- fancyPunctuate :: [Doc ann] -> [Doc ann]
- formatErrorItem :: TechniqueToken -> ErrorItem Char -> Doc TechniqueToken
- numberOfCarots :: FailureReason -> Int
- extractErrorBundle :: Source -> ParseErrorBundle Text Void -> CompilationError
- extractParseError :: ParseError Text Void -> (Int, [ErrorItem Char], [ErrorItem Char])
Documentation
Constructors
Ok | |
Failed CompilationError | |
Reload |
Constructors
Source | |
Fields
|
emptySource :: Source Source #
data FailureReason Source #
Constructors
Instances
data CompilationError Source #
Constructors
CompilationError Source FailureReason |
Instances
Show CompilationError Source # | |
Defined in Technique.Failure Methods showsPrec :: Int -> CompilationError -> ShowS # show :: CompilationError -> String # showList :: [CompilationError] -> ShowS # | |
Exception CompilationError Source # | |
Defined in Technique.Failure Methods toException :: CompilationError -> SomeException # | |
Render CompilationError Source # | |
Defined in Technique.Failure Associated Types type Token CompilationError # Methods colourize :: Token CompilationError -> AnsiColour # highlight :: CompilationError -> Doc (Token CompilationError) # | |
MonadError CompilationError Translate Source # | |
Defined in Technique.Translate Methods throwError :: CompilationError -> Translate a # catchError :: Translate a -> (CompilationError -> Translate a) -> Translate a # | |
type Token CompilationError Source # | |
Defined in Technique.Failure |
exitCodeFor :: CompilationError -> Int Source #
fancyPunctuate :: [Doc ann] -> [Doc ann] Source #
formatErrorItem :: TechniqueToken -> ErrorItem Char -> Doc TechniqueToken Source #
ErrorItem is a bit overbearing, but we handle its four cases by saying single quotes around characters, double quotes around strings, no quotes around labels (descriptive text) and hard code the end of input and newline cases.
numberOfCarots :: FailureReason -> Int Source #
extractErrorBundle :: Source -> ParseErrorBundle Text Void -> CompilationError Source #
When we get a failure in the parsing stage **megaparsec** returns a ParseErrorBundle. Extract the first error message therein (later handle more? Yeah nah), and convert it into something we can use.