paripari-0.1.0.0: Fast-path parser combinators with fallback for error reporting

Safe HaskellNone
LanguageHaskell2010

Text.PariPari.Combinators

Contents

Synopsis

Basics

data Text #

A space efficient, packed, unboxed Unicode text type.

Instances
type Item Text 
Instance details

Defined in Data.Text

type Item Text = Char

void :: Functor f => f a -> f () #

void value discards or ignores the result of evaluation, such as the return value of an IO action.

Examples

Expand

Replace the contents of a Maybe Int with unit:

>>> void Nothing
Nothing
>>> void (Just 3)
Just ()

Replace the contents of an Either Int Int with unit, resulting in an Either Int '()':

>>> void (Left 8675309)
Left 8675309
>>> void (Right 8675309)
Right ()

Replace every element of a list with unit:

>>> void [1,2,3]
[(),(),()]

Replace the second element of a pair with unit:

>>> void (1,2)
(1,())

Discard the result of an IO action:

>>> mapM print [1,2]
1
2
[(),()]
>>> void $ mapM print [1,2]
1
2

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

An associative binary operation

empty :: Alternative f => f a #

The identity of <|>

optional :: Alternative f => f a -> f (Maybe a) #

One or none.

Control.Monad.Combinators.NonEmpty

data NonEmpty a #

Non-empty (and non-strict) list type.

Since: base-4.9.0.0

Constructors

a :| [a] infixr 5 
Instances
Monad NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(>>=) :: NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b #

(>>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

return :: a -> NonEmpty a #

fail :: String -> NonEmpty a #

Functor NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b #

(<$) :: a -> NonEmpty b -> NonEmpty a #

Applicative NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

liftA2 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Foldable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => NonEmpty m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m #

foldr :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldl :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldr1 :: (a -> a -> a) -> NonEmpty a -> a #

foldl1 :: (a -> a -> a) -> NonEmpty a -> a #

toList :: NonEmpty a -> [a] #

null :: NonEmpty a -> Bool #

length :: NonEmpty a -> Int #

elem :: Eq a => a -> NonEmpty a -> Bool #

maximum :: Ord a => NonEmpty a -> a #

minimum :: Ord a => NonEmpty a -> a #

sum :: Num a => NonEmpty a -> a #

product :: Num a => NonEmpty a -> a #

Traversable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> NonEmpty a -> f (NonEmpty b) #

sequenceA :: Applicative f => NonEmpty (f a) -> f (NonEmpty a) #

mapM :: Monad m => (a -> m b) -> NonEmpty a -> m (NonEmpty b) #

sequence :: Monad m => NonEmpty (m a) -> m (NonEmpty a) #

Eq1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> NonEmpty a -> NonEmpty b -> Bool #

Ord1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> NonEmpty a -> NonEmpty b -> Ordering #

Read1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NonEmpty a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [NonEmpty a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (NonEmpty a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [NonEmpty a] #

Show1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NonEmpty a] -> ShowS #

IsList (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item (NonEmpty a) :: * #

Methods

fromList :: [Item (NonEmpty a)] -> NonEmpty a #

fromListN :: Int -> [Item (NonEmpty a)] -> NonEmpty a #

toList :: NonEmpty a -> [Item (NonEmpty a)] #

Eq a => Eq (NonEmpty a) 
Instance details

Defined in GHC.Base

Methods

(==) :: NonEmpty a -> NonEmpty a -> Bool #

(/=) :: NonEmpty a -> NonEmpty a -> Bool #

Ord a => Ord (NonEmpty a) 
Instance details

Defined in GHC.Base

Methods

compare :: NonEmpty a -> NonEmpty a -> Ordering #

(<) :: NonEmpty a -> NonEmpty a -> Bool #

(<=) :: NonEmpty a -> NonEmpty a -> Bool #

(>) :: NonEmpty a -> NonEmpty a -> Bool #

(>=) :: NonEmpty a -> NonEmpty a -> Bool #

max :: NonEmpty a -> NonEmpty a -> NonEmpty a #

min :: NonEmpty a -> NonEmpty a -> NonEmpty a #

Read a => Read (NonEmpty a) 
Instance details

Defined in GHC.Read

Show a => Show (NonEmpty a) 
Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: * -> * #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Semigroup (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

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

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

Generic1 NonEmpty 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 NonEmpty :: k -> * #

Methods

from1 :: NonEmpty a -> Rep1 NonEmpty a #

to1 :: Rep1 NonEmpty a -> NonEmpty a #

type Rep (NonEmpty a) 
Instance details

Defined in GHC.Generics

type Item (NonEmpty a) 
Instance details

Defined in GHC.Exts

type Item (NonEmpty a) = a
type Rep1 NonEmpty 
Instance details

Defined in GHC.Generics

some :: MonadPlus m => m a -> m (NonEmpty a) #

some p applies the parser p one or more times and returns a list of the values returned by p.

word = some letter

endBy1 :: MonadPlus m => m a -> m sep -> m (NonEmpty a) #

endBy1 p sep parses one or more occurrences of p, separated and ended by sep. Returns a non-empty list of values returned by p.

someTill :: MonadPlus m => m a -> m end -> m (NonEmpty a) #

someTill p end works similarly to manyTill p end, but p should succeed at least once.

See also: skipSome, skipSomeTill.

sepBy1 :: MonadPlus m => m a -> m sep -> m (NonEmpty a) #

sepBy1 p sep parses one or more occurrences of p, separated by sep. Returns a non-empty list of values returned by p.

sepEndBy1 :: MonadPlus m => m a -> m sep -> m (NonEmpty a) #

sepEndBy1 p sep parses one or more occurrences of p, separated and optionally ended by sep. Returns a non-empty list of values returned by p.

Control.Monad.Combinators

many :: MonadPlus m => m a -> m [a] #

many p applies the parser p zero or more times and returns a list of the values returned by p.

identifier = (:) <$> letter <*> many (alphaNumChar <|> char '_')

between :: Applicative m => m open -> m close -> m a -> m a #

between open close p parses open, followed by p and close. Returns the value returned by p.

braces = between (symbol "{") (symbol "}")

choice :: (Foldable f, Alternative m) => f (m a) -> m a #

choice ps tries to apply the parsers in the list ps in order, until one of them succeeds. Returns the value of the succeeding parser.

choice = asum

count :: Monad m => Int -> m a -> m [a] #

count n p parses n occurrences of p. If n is smaller or equal to zero, the parser equals to return []. Returns a list of n values.

See also: skipCount, count'.

count' :: MonadPlus m => Int -> Int -> m a -> m [a] #

count' m n p parses from m to n occurrences of p. If n is not positive or m > n, the parser equals to return []. Returns a list of parsed values.

Please note that m may be negative, in this case effect is the same as if it were equal to zero.

See also: skipCount, count.

eitherP :: Alternative m => m a -> m b -> m (Either a b) #

Combine two alternatives.

eitherP a b = (Left <$> a) <|> (Right <$> b)

endBy :: MonadPlus m => m a -> m sep -> m [a] #

endBy p sep parses zero or more occurrences of p, separated and ended by sep. Returns a list of values returned by p.

cStatements = cStatement `endBy` semicolon

manyTill :: MonadPlus m => m a -> m end -> m [a] #

manyTill p end applies parser p zero or more times until parser end succeeds. Returns the list of values returned by p.

See also: skipMany, skipManyTill.

option :: Alternative m => a -> m a -> m a #

option x p tries to apply the parser p. If p fails without consuming input, it returns the value x, otherwise the value returned by p.

option x p = p <|> pure x

See also: optional.

sepBy :: MonadPlus m => m a -> m sep -> m [a] #

sepBy p sep parses zero or more occurrences of p, separated by sep. Returns a list of values returned by p.

commaSep p = p `sepBy` comma

sepEndBy :: MonadPlus m => m a -> m sep -> m [a] #

sepEndBy p sep parses zero or more occurrences of p, separated and optionally ended by sep. Returns a list of values returned by p.

skipMany :: MonadPlus m => m a -> m () #

skipMany p applies the parser p zero or more times, skipping its result.

See also: manyTill, skipManyTill.

skipSome :: MonadPlus m => m a -> m () #

skipSome p applies the parser p one or more times, skipping its result.

See also: someTill, skipSomeTill.

skipCount :: Monad m => Int -> m a -> m () #

skipCount n p parses n occurrences of p, skipping its result. If n is smaller or equal to zero, the parser equals to return []. Returns a list of n values.

See also: count, count'.

skipManyTill :: MonadPlus m => m a -> m end -> m end #

skipManyTill p end applies the parser p zero or more times skipping results until parser end succeeds. Result parsed by end is then returned.

See also: manyTill, skipMany.

skipSomeTill :: MonadPlus m => m a -> m end -> m end #

skipSomeTill p end applies the parser p one or more times skipping results until parser end succeeds. Result parsed by end is then returned.

See also: someTill, skipSome.

PariPari

(<?>) :: MonadParser p => p a -> String -> p a infix 0 Source #

Infix alias for label

getLine :: Parser Int Source #

Get current line number

getColumn :: Parser Int Source #

Get current column

withPos :: MonadParser p => p a -> p (Pos, a) Source #

Decorate the parser result with the current position

withSpan :: MonadParser p => p a -> p (Span, a) Source #

Decoreate the parser result with the position span

getRefColumn :: Parser Int Source #

Get column number of the reference position

getRefLine :: Parser Int Source #

Get line number of the reference position

withRefPos :: MonadParser p => p a -> p a Source #

Update reference position with current position

align :: Parser () Source #

Parser succeeds on the same column as the reference column

indented :: Parser () Source #

Parser succeeds for columns greater than the current reference column

line :: Parser () Source #

Parser succeeds on the same line as the reference line

linefold :: Parser () Source #

Parser succeeds either on the reference line or for columns greater than the current reference column

notByte :: Word8 -> Parser Word8 Source #

Parser a single byte different from the given one

anyByte :: Parser Word8 Source #

Parse an arbitrary byte

digitByte :: Int -> Parser Word8 Source #

Parse a digit byte for the given base. Bases 2 to 36 are supported.

asciiByte :: Parser Word8 Source #

Parse a byte of the ASCII charset (< 128)

integer :: (Num a, MonadParser p) => p sep -> Int -> p a Source #

Parse an integer of the given base. Bases 2 to 36 are supported. Digits can be separated by separator, e.g. `optional (char '_')`.

integer' :: (Num a, MonadParser p) => p sep -> Int -> p (a, Int) Source #

Parse an integer of the given base. Returns the integer and the number of digits. Bases 2 to 36 are supported. Digits can be separated by separator, e.g. `optional (char '_')`.

octal :: Num a => Parser a Source #

digit :: Int -> Parser Word Source #

Parse a single digit of the given base and return its value. Bases 2 to 36 are supported.

signed :: (Num a, MonadParser p) => p a -> p a Source #

Parse a number with a plus or minus sign.

fractionHex :: (Num a, MonadParser p) => p digitSep -> p (a, Int, a) Source #

Parse a hexadecimal fraction, returning (coefficient, 2, exponent), corresponding to coefficient * 2^exponent. Digits can be separated by separator, e.g. `optional (char '_')`.

fractionDec :: (Num a, MonadParser p) => p digitSep -> p (a, Int, a) Source #

Parse a decimal fraction, returning (coefficient, 10, exponent), corresponding to coefficient * 10^exponent. Digits can be separated by separator, e.g. `optional (char '_')`.

char' :: Char -> Parser Char Source #

Parse a case-insensitive character

notChar :: Char -> Parser Char Source #

Parse a character different from the given one.

anyChar :: Parser Char Source #

Parse an arbitrary character.

alphaNumChar :: Parser Char Source #

Parse an alphanumeric character, including Unicode.

digitChar :: Int -> Parser Char Source #

Parse a digit character of the given base. Bases 2 to 36 are supported.

letterChar :: Parser Char Source #

Parse a letter character, including Unicode.

lowerChar :: Parser Char Source #

Parse a lowercase letter, including Unicode.

upperChar :: Parser Char Source #

Parse a uppercase letter, including Unicode.

symbolChar :: Parser Char Source #

Parse a symbol character, including Unicode.

categoryChar :: GeneralCategory -> Parser Char Source #

Parse a character belonging to the given Unicode category

punctuationChar :: Parser Char Source #

Parse a punctuation character, including Unicode.

spaceChar :: Parser Char Source #

Parse a space character, including Unicode.

asciiChar :: Int -> Parser Char Source #

Parse a character beloning to the ASCII charset (< 128)

string :: Text -> Parser Text Source #

Parse a text string

asString :: MonadParser p => p () -> p Text Source #

Run the given parser but return the result as a Text string

takeBytes :: Int -> Parser ByteString Source #

Take the next n bytes and advance the position by n bytes

skipChars :: Int -> Parser () Source #

Skip the next n characters

skipBytes :: Int -> Parser () Source #

Skip the next n bytes

takeChars :: Int -> Parser Text Source #

Take the next n characters and advance the position by n characters

skipCharsWhile :: (Char -> Bool) -> Parser () Source #

Skip char while predicate is true

takeCharsWhile :: (Char -> Bool) -> Parser Text Source #

Take chars while predicate is true

skipBytesWhile :: (Word8 -> Bool) -> Parser () Source #

Skip bytes while predicate is true

takeBytesWhile :: (Word8 -> Bool) -> Parser ByteString Source #

Takes bytes while predicate is true

skipBytesWhile1 :: (Word8 -> Bool) -> Parser () Source #

Skip at least one byte while predicate is true

takeBytesWhile1 :: (Word8 -> Bool) -> Parser ByteString Source #

Take at least one byte while predicate is true

skipCharsWhile1 :: (Char -> Bool) -> Parser () Source #

Skip at least one byte while predicate is true

takeCharsWhile1 :: (Char -> Bool) -> Parser Text Source #

Take at least one byte while predicate is true