paripari-0.2.1.0: Parser combinators with fast-path and slower fallback for error reporting

Safe HaskellNone
LanguageHaskell2010

Text.PariPari

Synopsis

Documentation

class (MonadFail p, MonadPlus p, Chunk k) => ChunkParser k p | p -> k where Source #

Parser class, which specifies the necessary primitives for parsing. All other parser combinators rely on these primitives.

Methods

getFile :: p FilePath Source #

Get file name associated with current parser

getPos :: p Pos Source #

Get current position of the parser

getRefPos :: p Pos Source #

Get reference position used for indentation-sensitive parsing

withRefPos :: p a -> p a Source #

Update reference position with current position

notFollowedBy :: Show a => p a -> p () Source #

Parser which succeeds when the given parser fails

lookAhead :: p a -> p a Source #

Look ahead and return result of the given parser The current position stays the same.

failWith :: Error -> p a Source #

Parser failure with detailled Error

eof :: p () Source #

Parser which succeeds at the end of file

label :: String -> p a -> p a Source #

Annotate the given parser with a label used for error reporting

hidden :: p a -> p a Source #

Hide errors occurring within the given parser from the error report. Based on the given labels an Error is constructed instead.

commit :: p a -> p a Source #

Commit to the given branch, increasing the priority of the errors within this branch in contrast to other branches.

This is basically the opposite of the try combinator provided by other parser combinator libraries, which decreases the error priority within the given branch (and usually also influences backtracking).

Note: commit only applies to the reported errors, it has no effect on the backtracking behavior of the parser.

element :: Element k -> p (Element k) Source #

Parse a single element

elementSatisfy :: (Element k -> Bool) -> p (Element k) Source #

Parse a single byte with the given predicate

chunk :: k -> p k Source #

Parse a chunk of elements. The chunk must not contain multiple lines, otherwise the position information will be invalid.

asChunk :: p () -> p k Source #

Run the given parser and return the result as buffer

Instances
Chunk k => ChunkParser k (Acceptor k) Source # 
Instance details

Defined in Text.PariPari.Internal.Acceptor

Chunk k => ChunkParser k (Reporter k) Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

CharChunk k => ChunkParser k (Tracer k) Source # 
Instance details

Defined in Text.PariPari.Internal.Tracer

class (ChunkParser k p, CharChunk k) => CharParser k p | p -> k where Source #

Minimal complete definition

char, satisfy, asciiByte, asciiSatisfy

Methods

char :: Char -> p Char Source #

Parse a single character

Note: The character '\0' cannot be parsed using this combinator since it is used as decoding sentinel. Use element instead.

satisfy :: (Char -> Bool) -> p Char Source #

Parse a single character with the given predicate

Note: The character '\0' cannot be parsed using this combinator since it is used as decoding sentinel. Use elementSatisfy instead.

asciiByte :: Word8 -> p Word8 Source #

Parse a single character within the ASCII charset

Note: The character '\0' cannot be parsed using this combinator since it is used as decoding sentinel. Use element instead.

asciiSatisfy :: (Word8 -> Bool) -> p Word8 Source #

Parse a single character within the ASCII charset with the given predicate

Note: The character '\0' cannot be parsed using this combinator since it is used as decoding sentinel. Use elementSatisfy instead.

data Error Source #

Parsing errors

Instances
Eq Error Source # 
Instance details

Defined in Text.PariPari.Internal.Class

Methods

(==) :: Error -> Error -> Bool #

(/=) :: Error -> Error -> Bool #

Ord Error Source # 
Instance details

Defined in Text.PariPari.Internal.Class

Methods

compare :: Error -> Error -> Ordering #

(<) :: Error -> Error -> Bool #

(<=) :: Error -> Error -> Bool #

(>) :: Error -> Error -> Bool #

(>=) :: Error -> Error -> Bool #

max :: Error -> Error -> Error #

min :: Error -> Error -> Error #

Show Error Source # 
Instance details

Defined in Text.PariPari.Internal.Class

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Generic Error Source # 
Instance details

Defined in Text.PariPari.Internal.Class

Associated Types

type Rep Error :: * -> * #

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

type Rep Error Source # 
Instance details

Defined in Text.PariPari.Internal.Class

type Rep Error = D1 (MetaData "Error" "Text.PariPari.Internal.Class" "paripari-0.2.1.0-4FCwezXdBTxCCPjvUHBJSj" False) (((C1 (MetaCons "EInvalidUtf8" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "EExpected" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]))) :+: (C1 (MetaCons "EUnexpected" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "EFail" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) :+: ((C1 (MetaCons "ECombinator" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "EIndentNotAligned" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) :+: (C1 (MetaCons "EIndentOverLine" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :+: C1 (MetaCons "ENotEnoughIndent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))))

showError :: Error -> String Source #

Pretty string representation of Error

class (Ord (Element k), Ord k) => Chunk k where Source #

Associated Types

type Element k Source #

data Pos Source #

Line and column position starting at (1,1)

Constructors

Pos 

Fields

Instances
Eq Pos Source # 
Instance details

Defined in Text.PariPari.Internal.Chunk

Methods

(==) :: Pos -> Pos -> Bool #

(/=) :: Pos -> Pos -> Bool #

Show Pos Source # 
Instance details

Defined in Text.PariPari.Internal.Chunk

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Generic Pos Source # 
Instance details

Defined in Text.PariPari.Internal.Chunk

Associated Types

type Rep Pos :: * -> * #

Methods

from :: Pos -> Rep Pos x #

to :: Rep Pos x -> Pos #

type Rep Pos Source # 
Instance details

Defined in Text.PariPari.Internal.Chunk

type Rep Pos = D1 (MetaData "Pos" "Text.PariPari.Internal.Chunk" "paripari-0.2.1.0-4FCwezXdBTxCCPjvUHBJSj" False) (C1 (MetaCons "Pos" PrefixI True) (S1 (MetaSel (Just "_posLine") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_posColumn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))

runCharParser :: CharChunk k => (forall p. CharParser k p => p a) -> FilePath -> k -> Either Report a Source #

Run fast Acceptor and slower Reporter on the given ByteString **in parallel**. The FilePath is used for error reporting. When the acceptor does not return successfully, the result from the reporter is awaited.

runSeqCharParser :: CharChunk k => (forall p. CharParser k p => p a) -> FilePath -> k -> Either Report a Source #

Run fast Acceptor and slower Reporter on the given ByteString **sequentially**. The FilePath is used for error reporting. When the acceptor does not return successfully, the result from the reporter is awaited.

runCharParserWithOptions :: CharChunk k => ReportOptions -> (forall p. CharParser k p => p a) -> FilePath -> k -> Either Report a Source #

Run parsers **in parallel** with additional ReportOptions.

runSeqCharParserWithOptions :: CharChunk k => ReportOptions -> (forall p. CharParser k p => p a) -> FilePath -> k -> Either Report a Source #

Run parsers **sequentially** with additional ReportOptions.

runChunkParser :: CharChunk k => (forall p. ChunkParser k p => p a) -> FilePath -> k -> Either Report a Source #

Run fast Acceptor and slower Reporter on the given ByteString **in parallel**. The FilePath is used for error reporting. When the acceptor does not return successfully, the result from the reporter is awaited.

runSeqChunkParser :: Chunk k => (forall p. ChunkParser k p => p a) -> FilePath -> k -> Either Report a Source #

Run fast Acceptor and slower Reporter on the given ByteString **sequentially**. The FilePath is used for error reporting. When the acceptor does not return successfully, the result from the reporter is awaited.

runChunkParserWithOptions :: Chunk k => ReportOptions -> (forall p. ChunkParser k p => p a) -> FilePath -> k -> Either Report a Source #

Run parsers **in parallel** with additional ReportOptions.

runSeqChunkParserWithOptions :: Chunk k => ReportOptions -> (forall p. ChunkParser k p => p a) -> FilePath -> k -> Either Report a Source #

Run parsers **sequentially** with additional ReportOptions.

data Acceptor k a Source #

Parser which is optimised for fast parsing. Error reporting is minimal.

Instances
CharChunk k => CharParser k (Acceptor k) Source # 
Instance details

Defined in Text.PariPari.Internal.Acceptor

Chunk k => ChunkParser k (Acceptor k) Source # 
Instance details

Defined in Text.PariPari.Internal.Acceptor

Chunk k => Monad (Acceptor k) Source # 
Instance details

Defined in Text.PariPari.Internal.Acceptor

Methods

(>>=) :: Acceptor k a -> (a -> Acceptor k b) -> Acceptor k b #

(>>) :: Acceptor k a -> Acceptor k b -> Acceptor k b #

return :: a -> Acceptor k a #

fail :: String -> Acceptor k a #

Functor (Acceptor k) Source # 
Instance details

Defined in Text.PariPari.Internal.Acceptor

Methods

fmap :: (a -> b) -> Acceptor k a -> Acceptor k b #

(<$) :: a -> Acceptor k b -> Acceptor k a #

Chunk k => MonadFail (Acceptor k) Source # 
Instance details

Defined in Text.PariPari.Internal.Acceptor

Methods

fail :: String -> Acceptor k a #

Chunk k => Applicative (Acceptor k) Source # 
Instance details

Defined in Text.PariPari.Internal.Acceptor

Methods

pure :: a -> Acceptor k a #

(<*>) :: Acceptor k (a -> b) -> Acceptor k a -> Acceptor k b #

liftA2 :: (a -> b -> c) -> Acceptor k a -> Acceptor k b -> Acceptor k c #

(*>) :: Acceptor k a -> Acceptor k b -> Acceptor k b #

(<*) :: Acceptor k a -> Acceptor k b -> Acceptor k a #

Chunk k => Alternative (Acceptor k) Source # 
Instance details

Defined in Text.PariPari.Internal.Acceptor

Methods

empty :: Acceptor k a #

(<|>) :: Acceptor k a -> Acceptor k a -> Acceptor k a #

some :: Acceptor k a -> Acceptor k [a] #

many :: Acceptor k a -> Acceptor k [a] #

Chunk k => MonadPlus (Acceptor k) Source # 
Instance details

Defined in Text.PariPari.Internal.Acceptor

Methods

mzero :: Acceptor k a #

mplus :: Acceptor k a -> Acceptor k a -> Acceptor k a #

(Chunk k, Semigroup a) => Semigroup (Acceptor k a) Source # 
Instance details

Defined in Text.PariPari.Internal.Acceptor

Methods

(<>) :: Acceptor k a -> Acceptor k a -> Acceptor k a #

sconcat :: NonEmpty (Acceptor k a) -> Acceptor k a #

stimes :: Integral b => b -> Acceptor k a -> Acceptor k a #

(Chunk k, Monoid a) => Monoid (Acceptor k a) Source # 
Instance details

Defined in Text.PariPari.Internal.Acceptor

Methods

mempty :: Acceptor k a #

mappend :: Acceptor k a -> Acceptor k a -> Acceptor k a #

mconcat :: [Acceptor k a] -> Acceptor k a #

runAcceptor :: Chunk k => Acceptor k a -> FilePath -> k -> Either Error a Source #

Run Acceptor on the given chunk, returning either a simple Error or, if successful, the result.

data Reporter k a Source #

Parser which is optimised for good error reports. Performance is secondary, since the Reporter is used as a fallback to the Acceptor.

Instances
CharChunk k => CharParser k (Reporter k) Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Chunk k => ChunkParser k (Reporter k) Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Chunk k => Monad (Reporter k) Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Methods

(>>=) :: Reporter k a -> (a -> Reporter k b) -> Reporter k b #

(>>) :: Reporter k a -> Reporter k b -> Reporter k b #

return :: a -> Reporter k a #

fail :: String -> Reporter k a #

Chunk k => Functor (Reporter k) Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Methods

fmap :: (a -> b) -> Reporter k a -> Reporter k b #

(<$) :: a -> Reporter k b -> Reporter k a #

Chunk k => MonadFail (Reporter k) Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Methods

fail :: String -> Reporter k a #

Chunk k => Applicative (Reporter k) Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Methods

pure :: a -> Reporter k a #

(<*>) :: Reporter k (a -> b) -> Reporter k a -> Reporter k b #

liftA2 :: (a -> b -> c) -> Reporter k a -> Reporter k b -> Reporter k c #

(*>) :: Reporter k a -> Reporter k b -> Reporter k b #

(<*) :: Reporter k a -> Reporter k b -> Reporter k a #

Chunk k => Alternative (Reporter k) Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Methods

empty :: Reporter k a #

(<|>) :: Reporter k a -> Reporter k a -> Reporter k a #

some :: Reporter k a -> Reporter k [a] #

many :: Reporter k a -> Reporter k [a] #

Chunk k => MonadPlus (Reporter k) Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Methods

mzero :: Reporter k a #

mplus :: Reporter k a -> Reporter k a -> Reporter k a #

(Chunk k, Semigroup a) => Semigroup (Reporter k a) Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Methods

(<>) :: Reporter k a -> Reporter k a -> Reporter k a #

sconcat :: NonEmpty (Reporter k a) -> Reporter k a #

stimes :: Integral b => b -> Reporter k a -> Reporter k a #

(Chunk k, Monoid a) => Monoid (Reporter k a) Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Methods

mempty :: Reporter k a #

mappend :: Reporter k a -> Reporter k a -> Reporter k a #

mconcat :: [Reporter k a] -> Reporter k a #

data Report Source #

Instances
Eq Report Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Methods

(==) :: Report -> Report -> Bool #

(/=) :: Report -> Report -> Bool #

Show Report Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Generic Report Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Associated Types

type Rep Report :: * -> * #

Methods

from :: Report -> Rep Report x #

to :: Rep Report x -> Report #

type Rep Report Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

type Rep Report = D1 (MetaData "Report" "Text.PariPari.Internal.Reporter" "paripari-0.2.1.0-4FCwezXdBTxCCPjvUHBJSj" False) (C1 (MetaCons "Report" PrefixI True) ((S1 (MetaSel (Just "_reportFile") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilePath) :*: S1 (MetaSel (Just "_reportLine") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :*: (S1 (MetaSel (Just "_reportCol") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_reportErrors") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ErrorContext]))))

data ErrorContext Source #

Constructors

ErrorContext 

Fields

Instances
Eq ErrorContext Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Show ErrorContext Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Generic ErrorContext Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Associated Types

type Rep ErrorContext :: * -> * #

type Rep ErrorContext Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

type Rep ErrorContext = D1 (MetaData "ErrorContext" "Text.PariPari.Internal.Reporter" "paripari-0.2.1.0-4FCwezXdBTxCCPjvUHBJSj" False) (C1 (MetaCons "ErrorContext" PrefixI True) (S1 (MetaSel (Just "_ecErrors") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Error]) :*: S1 (MetaSel (Just "_ecContext") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])))

data ReportOptions Source #

Instances
Eq ReportOptions Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Show ReportOptions Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Generic ReportOptions Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

Associated Types

type Rep ReportOptions :: * -> * #

type Rep ReportOptions Source # 
Instance details

Defined in Text.PariPari.Internal.Reporter

type Rep ReportOptions = D1 (MetaData "ReportOptions" "Text.PariPari.Internal.Reporter" "paripari-0.2.1.0-4FCwezXdBTxCCPjvUHBJSj" False) (C1 (MetaCons "ReportOptions" PrefixI True) (S1 (MetaSel (Just "_optMaxContexts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "_optMaxErrorsPerContext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_optMaxLabelsPerContext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))))

runReporter :: Chunk k => Reporter k a -> FilePath -> k -> Either Report a Source #

Run Reporter on the given ByteString, returning either an error Report or, if successful, the result.

showReport :: Report -> String Source #

Pretty string representation of Report.

showErrors :: [ErrorContext] -> String Source #

Pretty string representation of '[ErrorContext]'.

data Tracer k a Source #

Parser which prints trace messages, when backtracking occurs.

Instances
CharChunk k => CharParser k (Tracer k) Source # 
Instance details

Defined in Text.PariPari.Internal.Tracer

CharChunk k => ChunkParser k (Tracer k) Source # 
Instance details

Defined in Text.PariPari.Internal.Tracer

Chunk k => Monad (Tracer k) Source # 
Instance details

Defined in Text.PariPari.Internal.Tracer

Methods

(>>=) :: Tracer k a -> (a -> Tracer k b) -> Tracer k b #

(>>) :: Tracer k a -> Tracer k b -> Tracer k b #

return :: a -> Tracer k a #

fail :: String -> Tracer k a #

Chunk k => Functor (Tracer k) Source # 
Instance details

Defined in Text.PariPari.Internal.Tracer

Methods

fmap :: (a -> b) -> Tracer k a -> Tracer k b #

(<$) :: a -> Tracer k b -> Tracer k a #

Chunk k => MonadFail (Tracer k) Source # 
Instance details

Defined in Text.PariPari.Internal.Tracer

Methods

fail :: String -> Tracer k a #

Chunk k => Applicative (Tracer k) Source # 
Instance details

Defined in Text.PariPari.Internal.Tracer

Methods

pure :: a -> Tracer k a #

(<*>) :: Tracer k (a -> b) -> Tracer k a -> Tracer k b #

liftA2 :: (a -> b -> c) -> Tracer k a -> Tracer k b -> Tracer k c #

(*>) :: Tracer k a -> Tracer k b -> Tracer k b #

(<*) :: Tracer k a -> Tracer k b -> Tracer k a #

Chunk k => Alternative (Tracer k) Source # 
Instance details

Defined in Text.PariPari.Internal.Tracer

Methods

empty :: Tracer k a #

(<|>) :: Tracer k a -> Tracer k a -> Tracer k a #

some :: Tracer k a -> Tracer k [a] #

many :: Tracer k a -> Tracer k [a] #

Chunk k => MonadPlus (Tracer k) Source # 
Instance details

Defined in Text.PariPari.Internal.Tracer

Methods

mzero :: Tracer k a #

mplus :: Tracer k a -> Tracer k a -> Tracer k a #

(Chunk k, Semigroup a) => Semigroup (Tracer k a) Source # 
Instance details

Defined in Text.PariPari.Internal.Tracer

Methods

(<>) :: Tracer k a -> Tracer k a -> Tracer k a #

sconcat :: NonEmpty (Tracer k a) -> Tracer k a #

stimes :: Integral b => b -> Tracer k a -> Tracer k a #

(Chunk k, Monoid a) => Monoid (Tracer k a) Source # 
Instance details

Defined in Text.PariPari.Internal.Tracer

Methods

mempty :: Tracer k a #

mappend :: Tracer k a -> Tracer k a -> Tracer k a #

mconcat :: [Tracer k a] -> Tracer k a #

runTracer :: Chunk k => Tracer k a -> FilePath -> k -> Either Report a Source #

Run Tracer on the given ByteString, returning either an error Report or, if successful, the result.