Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Reporter k a = Reporter {
- unReporter :: forall b. Env k -> State -> (a -> State -> b) -> (State -> b) -> b
- data Env k = Env {
- _envBuf :: !(Buffer k)
- _envFile :: !FilePath
- _envOptions :: !ReportOptions
- _envHidden :: !Bool
- _envContext :: ![String]
- _envRefLine :: Int#
- _envRefCol :: Int#
- data State = State {}
- local :: (State -> Env k -> Env k) -> Reporter k a -> Reporter k a
- get :: (Env k -> State -> a) -> Reporter k a
- raiseError :: Env k -> State -> (State -> b) -> Error -> b
- mergeErrorState :: Env k -> State -> State -> State
- data Report = Report {
- _reportFile :: !FilePath
- _reportErrors :: ![ErrorContext]
- _reportLine :: !Int
- _reportCol :: !Int
- runReporter :: Chunk k => Reporter k a -> FilePath -> k -> (Maybe a, [Report])
- runReporterWithOptions :: Chunk k => ReportOptions -> Reporter k a -> FilePath -> k -> (Maybe a, [Report])
- data ErrorContext = ErrorContext {
- _ecErrors :: ![Error]
- _ecContext :: ![String]
- showReport :: Report -> String
- showErrors :: [ErrorContext] -> String
- data ReportOptions = ReportOptions {}
- defaultReportOptions :: ReportOptions
Documentation
Parser which is optimised for good error reports.
Performance is secondary, since the Reporter
is used
as a fallback to the Acceptor
.
Instances
Env | |
|
local :: (State -> Env k -> Env k) -> Reporter k a -> Reporter k a Source #
Reader monad, modify environment locally
get :: (Env k -> State -> a) -> Reporter k a Source #
Reader monad, get something from the environment
mergeErrorState :: Env k -> State -> State -> State Source #
Merge errors of two states, used when backtracking
Report | |
|
Instances
Eq Report Source # | |
Show Report Source # | |
Generic Report Source # | |
type Rep Report Source # | |
Defined in Text.PariPari.Internal.Reporter type Rep Report = D1 (MetaData "Report" "Text.PariPari.Internal.Reporter" "paripari-0.7.0.0-IvEurrnvmehFR9IQGtFHTg" False) (C1 (MetaCons "Report" PrefixI True) ((S1 (MetaSel (Just "_reportFile") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilePath) :*: S1 (MetaSel (Just "_reportErrors") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [ErrorContext])) :*: (S1 (MetaSel (Just "_reportLine") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_reportCol") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int)))) |
runReporterWithOptions :: Chunk k => ReportOptions -> Reporter k a -> FilePath -> k -> (Maybe a, [Report]) Source #
Run Reporter
with additional ReportOptions
.
data ErrorContext Source #
ErrorContext | |
|
Instances
Eq ErrorContext Source # | |
Defined in Text.PariPari.Internal.Reporter (==) :: ErrorContext -> ErrorContext -> Bool # (/=) :: ErrorContext -> ErrorContext -> Bool # | |
Show ErrorContext Source # | |
Defined in Text.PariPari.Internal.Reporter showsPrec :: Int -> ErrorContext -> ShowS # show :: ErrorContext -> String # showList :: [ErrorContext] -> ShowS # | |
Generic ErrorContext Source # | |
Defined in Text.PariPari.Internal.Reporter type Rep ErrorContext :: Type -> Type # from :: ErrorContext -> Rep ErrorContext x # to :: Rep ErrorContext x -> ErrorContext # | |
type Rep ErrorContext Source # | |
Defined in Text.PariPari.Internal.Reporter type Rep ErrorContext = D1 (MetaData "ErrorContext" "Text.PariPari.Internal.Reporter" "paripari-0.7.0.0-IvEurrnvmehFR9IQGtFHTg" False) (C1 (MetaCons "ErrorContext" PrefixI True) (S1 (MetaSel (Just "_ecErrors") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Error]) :*: S1 (MetaSel (Just "_ecContext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [String]))) |
showErrors :: [ErrorContext] -> String Source #
Pretty string representation of '[ErrorContext]'.
data ReportOptions Source #