simple-parser-0.12.1: Simple parser combinators
Safe HaskellSafe-Inferred
LanguageHaskell2010

SimpleParser.Common

Description

Common parsers. See Text.Megaparsec.Char.Lexer.

Synopsis

Documentation

data TextLabel Source #

Enumeration of common labels in textual parsing.

Instances

Instances details
Show TextLabel Source # 
Instance details

Defined in SimpleParser.Common

Eq TextLabel Source # 
Instance details

Defined in SimpleParser.Common

EmbedTextLabel TextLabel Source # 
Instance details

Defined in SimpleParser.Common

ExplainLabel TextLabel Source # 
Instance details

Defined in SimpleParser.Explain

data CompoundTextLabel l Source #

Union of text and custom labels

Instances

Instances details
Foldable CompoundTextLabel Source # 
Instance details

Defined in SimpleParser.Common

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> CompoundTextLabel a -> m #

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

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

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

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

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

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

toList :: CompoundTextLabel a -> [a] #

null :: CompoundTextLabel a -> Bool #

length :: CompoundTextLabel a -> Int #

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

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

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

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

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

Traversable CompoundTextLabel Source # 
Instance details

Defined in SimpleParser.Common

Methods

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

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

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

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

Functor CompoundTextLabel Source # 
Instance details

Defined in SimpleParser.Common

Show l => Show (CompoundTextLabel l) Source # 
Instance details

Defined in SimpleParser.Common

Eq l => Eq (CompoundTextLabel l) Source # 
Instance details

Defined in SimpleParser.Common

EmbedTextLabel (CompoundTextLabel l) Source # 
Instance details

Defined in SimpleParser.Common

ExplainLabel l => ExplainLabel (CompoundTextLabel l) Source # 
Instance details

Defined in SimpleParser.Explain

sepByParser Source #

Arguments

:: (Chunked seq elem, Monad m) 
=> ParserT l s e m elem

How to parse item

-> ParserT l s e m ()

How to parse separator

-> ParserT l s e m seq 

Yields the maximal list of separated items. May return an empty list.

betweenParser Source #

Arguments

:: Monad m 
=> ParserT l s e m ()

How to parse start

-> ParserT l s e m ()

How to parse end

-> ParserT l s e m a

How to parse inside

-> ParserT l s e m a 

Parses between start and end markers.

lexemeParser Source #

Arguments

:: Monad m 
=> ParserT l s e m ()

How to consume white space after lexeme

-> ParserT l s e m a

How to parse actual lexeme

-> ParserT l s e m a 

A wrapper for lexemes (equivalent to Megaparsec's lexeme).

newlineParser :: (Stream s, Token s ~ Char, Monad m) => ParserT l s e m () Source #

Consumes a newline character.

spaceParser :: (Stream s, Token s ~ Char, Monad m) => ParserT l s e m () Source #

Consumes 0 or more space characters.

hspaceParser :: (Stream s, Token s ~ Char, Monad m) => ParserT l s e m () Source #

Consumes 0 or more non-line-break space characters

spaceParser1 :: (EmbedTextLabel l, Stream s, Token s ~ Char, Monad m) => ParserT l s e m () Source #

Consumes 1 or more space characters.

hspaceParser1 :: (EmbedTextLabel l, Stream s, Token s ~ Char, Monad m) => ParserT l s e m () Source #

Consumes 1 or more non-line-break space characters

decimalParser :: (EmbedTextLabel l, Stream s, Token s ~ Char, Monad m, Num a) => ParserT l s e m a Source #

Parses an integer in decimal representation (equivalent to Megaparsec's decimal).

signedNumStartPred :: Char -> Bool Source #

Predicate for satisfying the start of signed numbers

scientificParser :: (EmbedTextLabel l, Stream s, Token s ~ Char, Monad m) => ParserT l s e m Scientific Source #

Parses a floating point value as a Scientific number (equivalent to Megaparsec's scientific).

numParser :: (EmbedTextLabel l, Stream s, Token s ~ Char, Monad m) => ParserT l s e m (Either Integer Scientific) Source #

Parses a number as a literal integer or a Scientific number. Though Scientific can represent integers, this allows you to distinugish integer literals from scientific literals since that information is lost after parsing.

data Sign Source #

Constructors

SignPos 
SignNeg 

Instances

Instances details
Show Sign Source # 
Instance details

Defined in SimpleParser.Common

Methods

showsPrec :: Int -> Sign -> ShowS #

show :: Sign -> String #

showList :: [Sign] -> ShowS #

Eq Sign Source # 
Instance details

Defined in SimpleParser.Common

Methods

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

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

signParser :: (Stream s, Token s ~ Char, Monad m) => ParserT l s e m (Maybe Sign) Source #

Consumes an optional + or - representing the sign of a number.

applySign :: Num a => Maybe Sign -> a -> a Source #

Optionally negate the number according to the sign (treating Nothing as positive sign).

signedParser Source #

Arguments

:: (Stream s, Token s ~ Char, Monad m, Num a) 
=> ParserT l s e m ()

How to consume white space after the sign

-> ParserT l s e m a

How to parse the number itself

-> ParserT l s e m a

Parser for signed numbers

Parses an optional sign character followed by a number and yields a correctly-signed number (equivalend to Megaparsec's signed).

escapedStringParser :: (Stream s, Token s ~ Char, Monad m) => Char -> ParserT l s e m (Chunk s) Source #

Given a quote charcter (like a single or double quote), yields the contents of the string bounded by those quotes. The contents may contain backslash-escaped quotes. Returns nothing if outside quotes are missing or the stream ends before unquote.

spanParser :: (PosStream s, Monad m) => (Span (Pos s) -> a -> b) -> ParserT l s e m a -> ParserT l s e m b Source #

Adds span information to parsed values.

getStreamPos :: (PosStream s, Monad m) => ParserT l s e m (Pos s) Source #

Gets the current stream position