Copyright | (c) Kimiyuki Onaka 2020 |
---|---|
License | Apache License 2.0 |
Maintainer | kimiyuki95@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- module Control.Monad.Except
- data Responsibility
- data ErrorGroup
- data Error
- wrapError :: MonadError e m => (e -> e) -> m a -> m a
- wrapError' :: MonadError Error m => String -> m a -> m a
- wrapAt :: MonadError Error m => Loc -> m a -> m a
- wrapAt' :: MonadError Error m => Maybe Loc -> m a -> m a
- maybeToError :: MonadError a m => a -> Maybe b -> m b
- eitherToError :: MonadError a m => Either a b -> m b
- catchError' :: MonadError e m => m a -> m (Either e a)
- reportErrors :: MonadError Error m => [Either Error a] -> m [a]
- reportErrors2 :: MonadError Error m => Either Error a -> Either Error b -> m (a, b)
- reportErrors3 :: MonadError Error m => Either Error a -> Either Error b -> Either Error c -> m (a, b, c)
- reportErrors4 :: MonadError Error m => Either Error a -> Either Error b -> Either Error c -> Either Error d -> m (a, b, c, d)
- reportErrors5 :: MonadError Error m => Either Error a -> Either Error b -> Either Error c -> Either Error d -> Either Error e -> m (a, b, c, d, e)
- lexicalError :: String -> Error
- lexicalErrorAt :: Loc -> String -> Error
- syntaxError :: String -> Error
- syntaxErrorAt :: Loc -> String -> Error
- symbolError :: String -> Error
- symbolErrorAt :: Loc -> String -> Error
- typeError :: String -> Error
- semanticError :: String -> Error
- evaluationError :: String -> Error
- runtimeError :: String -> Error
- assertionError :: String -> Error
- commandLineError :: String -> Error
- wrongInputError :: String -> Error
- internalError :: String -> Error
- throwLexicalError :: MonadError Error m => String -> m a
- throwLexicalErrorAt :: MonadError Error m => Loc -> String -> m a
- throwSyntaxError :: MonadError Error m => String -> m a
- throwSyntaxErrorAt :: MonadError Error m => Loc -> String -> m a
- throwSyntaxErrorAt' :: MonadError Error m => Maybe Loc -> String -> m a
- throwSymbolError :: MonadError Error m => String -> m a
- throwSymbolErrorAt :: MonadError Error m => Loc -> String -> m a
- throwSymbolErrorAt' :: MonadError Error m => Maybe Loc -> String -> m a
- throwTypeError :: MonadError Error m => String -> m a
- throwTypeErrorAt :: MonadError Error m => Loc -> String -> m a
- throwTypeErrorAt' :: MonadError Error m => Maybe Loc -> String -> m a
- throwSemanticError :: MonadError Error m => String -> m a
- throwSemanticErrorAt :: MonadError Error m => Loc -> String -> m a
- throwSemanticErrorAt' :: MonadError Error m => Maybe Loc -> String -> m a
- throwEvaluationError :: MonadError Error m => String -> m a
- throwRuntimeError :: MonadError Error m => String -> m a
- throwRuntimeErrorAt :: MonadError Error m => Loc -> String -> m a
- throwRuntimeErrorAt' :: MonadError Error m => Maybe Loc -> String -> m a
- throwAssertionError :: MonadError Error m => String -> m a
- throwCommandLineError :: MonadError Error m => String -> m a
- throwWrongInputError :: MonadError Error m => String -> m a
- throwInternalError :: MonadError Error m => String -> m a
- throwInternalErrorAt :: MonadError Error m => Loc -> String -> m a
- throwInternalErrorAt' :: MonadError Error m => Maybe Loc -> String -> m a
- bug :: String -> a
- todo :: String -> a
Documentation
module Control.Monad.Except
error data types
data Responsibility Source #
Instances
Eq Responsibility Source # | |
Defined in Jikka.Common.Error (==) :: Responsibility -> Responsibility -> Bool # (/=) :: Responsibility -> Responsibility -> Bool # | |
Ord Responsibility Source # | |
Defined in Jikka.Common.Error compare :: Responsibility -> Responsibility -> Ordering # (<) :: Responsibility -> Responsibility -> Bool # (<=) :: Responsibility -> Responsibility -> Bool # (>) :: Responsibility -> Responsibility -> Bool # (>=) :: Responsibility -> Responsibility -> Bool # max :: Responsibility -> Responsibility -> Responsibility # min :: Responsibility -> Responsibility -> Responsibility # | |
Read Responsibility Source # | |
Defined in Jikka.Common.Error readsPrec :: Int -> ReadS Responsibility # readList :: ReadS [Responsibility] # | |
Show Responsibility Source # | |
Defined in Jikka.Common.Error showsPrec :: Int -> Responsibility -> ShowS # show :: Responsibility -> String # showList :: [Responsibility] -> ShowS # |
data ErrorGroup Source #
LexicalError | It's impossible to split the given source text into tokens. |
SyntaxError | It's impossible to construct AST from tokens. |
SymbolError | There are undefined variables or functions in AST. |
TypeError | It's impossible reconstruct types for AST. |
SemanticError | other semantic erros |
EvaluationError | User's program are not ready to evaluate. |
RuntimeError | User's program failed while running. |
AssertionError | User's program violates its assertion. |
CommandLineError | The given command line arguments are not acceptable. |
WrongInputError | User's program was correctly running but wrong input text is given. |
InternalError | It's an bug of implementation. |
Instances
Eq ErrorGroup Source # | |
Defined in Jikka.Common.Error (==) :: ErrorGroup -> ErrorGroup -> Bool # (/=) :: ErrorGroup -> ErrorGroup -> Bool # | |
Ord ErrorGroup Source # | |
Defined in Jikka.Common.Error compare :: ErrorGroup -> ErrorGroup -> Ordering # (<) :: ErrorGroup -> ErrorGroup -> Bool # (<=) :: ErrorGroup -> ErrorGroup -> Bool # (>) :: ErrorGroup -> ErrorGroup -> Bool # (>=) :: ErrorGroup -> ErrorGroup -> Bool # max :: ErrorGroup -> ErrorGroup -> ErrorGroup # min :: ErrorGroup -> ErrorGroup -> ErrorGroup # | |
Read ErrorGroup Source # | |
Defined in Jikka.Common.Error readsPrec :: Int -> ReadS ErrorGroup # readList :: ReadS [ErrorGroup] # readPrec :: ReadPrec ErrorGroup # readListPrec :: ReadPrec [ErrorGroup] # | |
Show ErrorGroup Source # | |
Defined in Jikka.Common.Error showsPrec :: Int -> ErrorGroup -> ShowS # show :: ErrorGroup -> String # showList :: [ErrorGroup] -> ShowS # |
Error String | |
ErrorAppend Error Error | |
WithGroup ErrorGroup Error | |
WithWrapped String Error | |
WithLocation Loc Error | |
WithResponsibility Responsibility Error |
general utilities for Except
wrapError :: MonadError e m => (e -> e) -> m a -> m a Source #
wrapError' :: MonadError Error m => String -> m a -> m a Source #
maybeToError :: MonadError a m => a -> Maybe b -> m b Source #
eitherToError :: MonadError a m => Either a b -> m b Source #
utilities to report multiple errors
catchError' :: MonadError e m => m a -> m (Either e a) Source #
catchError
` is the inverse of liftError
.
reportErrors :: MonadError Error m => [Either Error a] -> m [a] Source #
reportErrors2 :: MonadError Error m => Either Error a -> Either Error b -> m (a, b) Source #
reportErrors3 :: MonadError Error m => Either Error a -> Either Error b -> Either Error c -> m (a, b, c) Source #
reportErrors4 :: MonadError Error m => Either Error a -> Either Error b -> Either Error c -> Either Error d -> m (a, b, c, d) Source #
reportErrors5 :: MonadError Error m => Either Error a -> Either Error b -> Either Error c -> Either Error d -> Either Error e -> m (a, b, c, d, e) Source #
function to construct errors
lexicalError :: String -> Error Source #
syntaxError :: String -> Error Source #
symbolError :: String -> Error Source #
semanticError :: String -> Error Source #
evaluationError :: String -> Error Source #
runtimeError :: String -> Error Source #
assertionError :: String -> Error Source #
commandLineError :: String -> Error Source #
wrongInputError :: String -> Error Source #
internalError :: String -> Error Source #
actions to throw errors
throwLexicalError :: MonadError Error m => String -> m a Source #
throwLexicalErrorAt :: MonadError Error m => Loc -> String -> m a Source #
throwSyntaxError :: MonadError Error m => String -> m a Source #
throwSyntaxErrorAt :: MonadError Error m => Loc -> String -> m a Source #
throwSyntaxErrorAt' :: MonadError Error m => Maybe Loc -> String -> m a Source #
throwSymbolError :: MonadError Error m => String -> m a Source #
throwSymbolErrorAt :: MonadError Error m => Loc -> String -> m a Source #
throwSymbolErrorAt' :: MonadError Error m => Maybe Loc -> String -> m a Source #
throwTypeError :: MonadError Error m => String -> m a Source #
throwTypeErrorAt :: MonadError Error m => Loc -> String -> m a Source #
throwTypeErrorAt' :: MonadError Error m => Maybe Loc -> String -> m a Source #
throwSemanticError :: MonadError Error m => String -> m a Source #
throwSemanticErrorAt :: MonadError Error m => Loc -> String -> m a Source #
throwSemanticErrorAt' :: MonadError Error m => Maybe Loc -> String -> m a Source #
throwEvaluationError :: MonadError Error m => String -> m a Source #
throwRuntimeError :: MonadError Error m => String -> m a Source #
throwRuntimeErrorAt :: MonadError Error m => Loc -> String -> m a Source #
throwRuntimeErrorAt' :: MonadError Error m => Maybe Loc -> String -> m a Source #
throwAssertionError :: MonadError Error m => String -> m a Source #
throwCommandLineError :: MonadError Error m => String -> m a Source #
throwWrongInputError :: MonadError Error m => String -> m a Source #
throwInternalError :: MonadError Error m => String -> m a Source #
throwInternalErrorAt :: MonadError Error m => Loc -> String -> m a Source #
throwInternalErrorAt' :: MonadError Error m => Maybe Loc -> String -> m a Source #