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

Safe HaskellNone
LanguageHaskell2010

Text.PariPari.Internal.Class

Synopsis

Documentation

class (MonadFail p, MonadPlus p, Chunk k, IsString (p k)) => Parser 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.

Note: This function has zero cost in the Acceptor. You can use it to improve the error reports without slowing down the fast path of your parser.

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.

Note: This function has zero cost in the Acceptor. You can use it to improve the error reports without slowing down the fast path of your parser.

try :: p a -> p a Source #

Reset position if parser fails

(<!>) :: p a -> p a -> p a infixl 3 Source #

Alternative which does not backtrack.

recover :: p a -> p a -> p a Source #

Parse with error recovery. If the parser p fails in `recover p r` the parser r continues at the position where p failed. If the recovering parser r fails too, the whole parser fails. The errors reported by the recovering parser are ignored in any case. Error recovery support is only available in the Reporter instance.

Note: This function has zero cost in the Acceptor. You can use it to improve the error reports without slowing down the fast path of your parser.

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

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.

scan :: (Char -> Maybe a) -> p a Source #

Scan a single character

Note: The character '\0' cannot be parsed using this combinator since it is used as decoding sentinel. Use elementScan 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.

asciiScan :: (Word8 -> Maybe a) -> p a Source #

Scan 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 elementScan instead.

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

Defined in Text.PariPari.Internal.Acceptor

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

Defined in Text.PariPari.Internal.Reporter

class Applicative f => Alternative (f :: Type -> Type) where #

A monoid on applicative functors.

If defined, some and many should be the least solutions of the equations:

Methods

empty :: f a #

The identity of <|>

(<|>) :: f a -> f a -> f a infixl 3 #

An associative binary operation

Instances
Alternative []

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

empty :: [a] #

(<|>) :: [a] -> [a] -> [a] #

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

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

Alternative Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

empty :: Maybe a #

(<|>) :: Maybe a -> Maybe a -> Maybe a #

some :: Maybe a -> Maybe [a] #

many :: Maybe a -> Maybe [a] #

Alternative IO

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

empty :: IO a #

(<|>) :: IO a -> IO a -> IO a #

some :: IO a -> IO [a] #

many :: IO a -> IO [a] #

Alternative Option

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

empty :: Option a #

(<|>) :: Option a -> Option a -> Option a #

some :: Option a -> Option [a] #

many :: Option a -> Option [a] #

Alternative ZipList

Since: base-4.11.0.0

Instance details

Defined in Control.Applicative

Methods

empty :: ZipList a #

(<|>) :: ZipList a -> ZipList a -> ZipList a #

some :: ZipList a -> ZipList [a] #

many :: ZipList a -> ZipList [a] #

Alternative ReadP

Since: base-4.6.0.0

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

empty :: ReadP a #

(<|>) :: ReadP a -> ReadP a -> ReadP a #

some :: ReadP a -> ReadP [a] #

many :: ReadP a -> ReadP [a] #

Alternative Seq

Since: containers-0.5.4

Instance details

Defined in Data.Sequence.Internal

Methods

empty :: Seq a #

(<|>) :: Seq a -> Seq a -> Seq a #

some :: Seq a -> Seq [a] #

many :: Seq a -> Seq [a] #

Alternative P

Since: base-4.5.0.0

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

empty :: P a #

(<|>) :: P a -> P a -> P a #

some :: P a -> P [a] #

many :: P a -> P [a] #

Alternative (U1 :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: U1 a #

(<|>) :: U1 a -> U1 a -> U1 a #

some :: U1 a -> U1 [a] #

many :: U1 a -> U1 [a] #

MonadPlus m => Alternative (WrappedMonad m)

Since: base-2.1

Instance details

Defined in Control.Applicative

Methods

empty :: WrappedMonad m a #

(<|>) :: WrappedMonad m a -> WrappedMonad m a -> WrappedMonad m a #

some :: WrappedMonad m a -> WrappedMonad m [a] #

many :: WrappedMonad m a -> WrappedMonad m [a] #

ArrowPlus a => Alternative (ArrowMonad a)

Since: base-4.6.0.0

Instance details

Defined in Control.Arrow

Methods

empty :: ArrowMonad a a0 #

(<|>) :: ArrowMonad a a0 -> ArrowMonad a a0 -> ArrowMonad a a0 #

some :: ArrowMonad a a0 -> ArrowMonad a [a0] #

many :: ArrowMonad a a0 -> ArrowMonad a [a0] #

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 => 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] #

Alternative f => Alternative (Rec1 f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: Rec1 f a #

(<|>) :: Rec1 f a -> Rec1 f a -> Rec1 f a #

some :: Rec1 f a -> Rec1 f [a] #

many :: Rec1 f a -> Rec1 f [a] #

(ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b)

Since: base-2.1

Instance details

Defined in Control.Applicative

Methods

empty :: WrappedArrow a b a0 #

(<|>) :: WrappedArrow a b a0 -> WrappedArrow a b a0 -> WrappedArrow a b a0 #

some :: WrappedArrow a b a0 -> WrappedArrow a b [a0] #

many :: WrappedArrow a b a0 -> WrappedArrow a b [a0] #

Alternative f => Alternative (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

empty :: Ap f a #

(<|>) :: Ap f a -> Ap f a -> Ap f a #

some :: Ap f a -> Ap f [a] #

many :: Ap f a -> Ap f [a] #

Alternative f => Alternative (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

empty :: Alt f a #

(<|>) :: Alt f a -> Alt f a -> Alt f a #

some :: Alt f a -> Alt f [a] #

many :: Alt f a -> Alt f [a] #

(Alternative f, Alternative g) => Alternative (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: (f :*: g) a #

(<|>) :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a #

some :: (f :*: g) a -> (f :*: g) [a] #

many :: (f :*: g) a -> (f :*: g) [a] #

(Alternative f, Alternative g) => Alternative (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

empty :: Product f g a #

(<|>) :: Product f g a -> Product f g a -> Product f g a #

some :: Product f g a -> Product f g [a] #

many :: Product f g a -> Product f g [a] #

Alternative f => Alternative (M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: M1 i c f a #

(<|>) :: M1 i c f a -> M1 i c f a -> M1 i c f a #

some :: M1 i c f a -> M1 i c f [a] #

many :: M1 i c f a -> M1 i c f [a] #

(Alternative f, Applicative g) => Alternative (f :.: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: (f :.: g) a #

(<|>) :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a #

some :: (f :.: g) a -> (f :.: g) [a] #

many :: (f :.: g) a -> (f :.: g) [a] #

(Alternative f, Applicative g) => Alternative (Compose f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

empty :: Compose f g a #

(<|>) :: Compose f g a -> Compose f g a -> Compose f g a #

some :: Compose f g a -> Compose f g [a] #

many :: Compose f g a -> Compose f g [a] #

class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) #

Monads that also support choice and failure.

Instances
MonadPlus []

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mzero :: [a] #

mplus :: [a] -> [a] -> [a] #

MonadPlus Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mzero :: Maybe a #

mplus :: Maybe a -> Maybe a -> Maybe a #

MonadPlus IO

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

mzero :: IO a #

mplus :: IO a -> IO a -> IO a #

MonadPlus Option

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mzero :: Option a #

mplus :: Option a -> Option a -> Option a #

MonadPlus ReadP

Since: base-2.1

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

mzero :: ReadP a #

mplus :: ReadP a -> ReadP a -> ReadP a #

MonadPlus Seq 
Instance details

Defined in Data.Sequence.Internal

Methods

mzero :: Seq a #

mplus :: Seq a -> Seq a -> Seq a #

MonadPlus P

Since: base-2.1

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

mzero :: P a #

mplus :: P a -> P a -> P a #

MonadPlus (U1 :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

mzero :: U1 a #

mplus :: U1 a -> U1 a -> U1 a #

(ArrowApply a, ArrowPlus a) => MonadPlus (ArrowMonad a)

Since: base-4.6.0.0

Instance details

Defined in Control.Arrow

Methods

mzero :: ArrowMonad a a0 #

mplus :: ArrowMonad a a0 -> ArrowMonad a a0 -> ArrowMonad a a0 #

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 => 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 #

MonadPlus f => MonadPlus (Rec1 f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

mzero :: Rec1 f a #

mplus :: Rec1 f a -> Rec1 f a -> Rec1 f a #

MonadPlus f => MonadPlus (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mzero :: Ap f a #

mplus :: Ap f a -> Ap f a -> Ap f a #

MonadPlus f => MonadPlus (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mzero :: Alt f a #

mplus :: Alt f a -> Alt f a -> Alt f a #

(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

mzero :: (f :*: g) a #

mplus :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a #

(MonadPlus f, MonadPlus g) => MonadPlus (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

mzero :: Product f g a #

mplus :: Product f g a -> Product f g a -> Product f g a #

MonadPlus f => MonadPlus (M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

mzero :: M1 i c f a #

mplus :: M1 i c f a -> M1 i c f a -> M1 i c f a #

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.Class

Methods

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

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

Show Pos Source # 
Instance details

Defined in Text.PariPari.Internal.Class

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Generic Pos Source # 
Instance details

Defined in Text.PariPari.Internal.Class

Associated Types

type Rep Pos :: Type -> Type #

Methods

from :: Pos -> Rep Pos x #

to :: Rep Pos x -> Pos #

type Rep Pos Source # 
Instance details

Defined in Text.PariPari.Internal.Class

type Rep Pos = D1 (MetaData "Pos" "Text.PariPari.Internal.Class" "paripari-0.7.0.0-IvEurrnvmehFR9IQGtFHTg" False) (C1 (MetaCons "Pos" PrefixI True) (S1 (MetaSel (Just "_posLine") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "_posCol") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int)))

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 :: Type -> Type #

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

type Rep Error Source # 
Instance details

Defined in Text.PariPari.Internal.Class

showError :: Error -> String Source #

Pretty string representation of Error

string :: Parser k p => String -> p k Source #

Parse a string