boomerang-1.4.5.3: Library for invertible parsing and printing

Safe HaskellNone
LanguageHaskell98

Text.Boomerang.Error

Description

An Error handling scheme that can be used with Boomerang

Synopsis

Documentation

data ErrorMsg Source #

Instances

Eq ErrorMsg Source # 
Data ErrorMsg Source # 

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 # 
Read ErrorMsg Source # 
Show ErrorMsg Source # 

messageString :: ErrorMsg -> String Source #

extract the String from an ErrorMsg. Note: the resulting String will not include any information about what constructor it came from.

data ParserError pos Source #

Constructors

ParserError (Maybe pos) [ErrorMsg] 

Instances

Eq pos => Eq (ParserError pos) Source # 

Methods

(==) :: ParserError pos -> ParserError pos -> Bool #

(/=) :: ParserError pos -> ParserError pos -> Bool #

Data pos => Data (ParserError pos) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParserError pos -> c (ParserError pos) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParserError pos) #

toConstr :: ParserError pos -> Constr #

dataTypeOf :: ParserError pos -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ParserError pos)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParserError pos)) #

gmapT :: (forall b. Data b => b -> b) -> ParserError pos -> ParserError pos #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParserError pos -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParserError pos -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParserError pos -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParserError pos -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParserError pos -> m (ParserError pos) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParserError pos -> m (ParserError pos) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParserError pos -> m (ParserError pos) #

Ord pos => Ord (ParserError pos) Source # 

Methods

compare :: ParserError pos -> ParserError pos -> Ordering #

(<) :: ParserError pos -> ParserError pos -> Bool #

(<=) :: ParserError pos -> ParserError pos -> Bool #

(>) :: ParserError pos -> ParserError pos -> Bool #

(>=) :: ParserError pos -> ParserError pos -> Bool #

max :: ParserError pos -> ParserError pos -> ParserError pos #

min :: ParserError pos -> ParserError pos -> ParserError pos #

Show pos => Show (ParserError pos) Source # 

Methods

showsPrec :: Int -> ParserError pos -> ShowS #

show :: ParserError pos -> String #

showList :: [ParserError pos] -> ShowS #

Error (ParserError p) Source # 
ErrorPosition (ParserError p) Source # 
type Pos (ParserError p) Source # 
type Pos (ParserError p) = p

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

showParserError Source #

Arguments

:: (pos -> String)

function to turn the error position into a String

-> ParserError pos

the ParserError

-> String 

turn a parse error into a user-friendly error message