| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Text.Boomerang.Error
Description
An Error handling scheme that can be used with Boomerang
Synopsis
- data ErrorMsg
- messageString :: ErrorMsg -> String
- data ParserError pos = ParserError (Maybe pos) [ErrorMsg]
- mkParserError :: pos -> [ErrorMsg] -> [Either (ParserError pos) a]
- (<?>) :: Boomerang (ParserError p) tok a b -> String -> Boomerang (ParserError p) tok a b
- condenseErrors :: Ord pos => [ParserError pos] -> ParserError pos
- showErrorMessages :: String -> String -> String -> String -> String -> [ErrorMsg] -> String
- showParserError :: (pos -> String) -> ParserError pos -> String
Documentation
Instances
| Eq ErrorMsg Source # | |
| Data ErrorMsg Source # | |
| Defined in Text.Boomerang.Error Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ErrorMsg -> c ErrorMsg # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ErrorMsg # toConstr :: ErrorMsg -> Constr # dataTypeOf :: ErrorMsg -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ErrorMsg) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ErrorMsg) # gmapT :: (forall b. Data b => b -> b) -> ErrorMsg -> ErrorMsg # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ErrorMsg -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ErrorMsg -> r # gmapQ :: (forall d. Data d => d -> u) -> ErrorMsg -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ErrorMsg -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ErrorMsg -> m ErrorMsg # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorMsg -> m ErrorMsg # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ErrorMsg -> m ErrorMsg # | |
| Ord ErrorMsg Source # | |
| Defined in Text.Boomerang.Error | |
| Read ErrorMsg Source # | |
| Show ErrorMsg Source # | |
messageString :: ErrorMsg -> String Source #
data ParserError pos Source #
Constructors
| ParserError (Maybe pos) [ErrorMsg] | 
Instances
mkParserError :: pos -> [ErrorMsg] -> [Either (ParserError pos) a] Source #
lift a pos and '[ErrorMsg]' into a parse error
This is intended to be used inside a Parser like this:
Parser $ \tok pos -> mkParserError pos [Message "just some error..."]
(<?>) :: Boomerang (ParserError p) tok a b -> String -> Boomerang (ParserError p) tok a b infix 0 Source #
annotate a parse error with an additional Expect message
satisfy isUpper <?> 'an uppercase character'
condenseErrors :: Ord pos => [ParserError pos] -> ParserError pos Source #
condense the ParserErrors with the highest parse position into a single ParserError
showErrorMessages :: String -> String -> String -> String -> String -> [ErrorMsg] -> String Source #
Helper function for turning '[ErrorMsg]' into a user-friendly String
Arguments
| :: (pos -> String) | function to turn the error position into a  | 
| -> ParserError pos | the  | 
| -> String | 
turn a parse error into a user-friendly error message