pandoc-2.9.2.1: Conversion between markup formats
CopyrightCopyright (C) 2006-2020 John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.Pandoc.Parsing

Description

A utility library with parsers used in pandoc readers.

Synopsis

Documentation

take1WhileP :: Monad m => (Char -> Bool) -> ParserT Text st m Text #

Parse characters while a predicate is true.

takeP :: Monad m => Int -> ParserT Text st m Text #

countChar :: (Stream s m Char, Monad m) => Int -> ParsecT s st m Char -> ParsecT s st m Text #

Like count, but packs its result

textStr :: Stream s m Char => Text -> ParsecT s u m Text #

Like string, but uses Text.

anyLine :: Monad m => ParserT Text st m Text #

Parse any line of text

anyLineNewline :: Monad m => ParserT Text st m Text #

Parse any line, include the final newline in the output

indentWith :: Stream s m Char => HasReaderOptions st => Int -> ParserT s st m Text #

Parse indent by specified number of spaces (or equiv. tabs)

manyChar :: Stream s m t => ParserT s st m Char -> ParserT s st m Text #

Like many, but packs its result.

many1Char :: Stream s m t => ParserT s st m Char -> ParserT s st m Text #

Like many1, but packs its result.

manyTillChar :: Stream s m t => ParserT s st m Char -> ParserT s st m a -> ParserT s st m Text #

Like manyTill, but packs its result.

many1TillChar :: (Show end, Stream s m t) => ParserT s st m Char -> ParserT s st m end -> ParserT s st m Text #

Like many1Till, but packs its result

many1Till :: (Show end, Stream s m t) => ParserT s st m a -> ParserT s st m end -> ParserT s st m [a] #

Like manyTill, but reads at least one item.

manyUntil :: ParserT s u m a -> ParserT s u m b -> ParserT s u m ([a], b) #

Like manyTill, but also returns the result of end parser.

manyUntilChar :: ParserT s u m Char -> ParserT s u m b -> ParserT s u m (Text, b) #

Like manyUntil, but also packs its result.

sepBy1' :: ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] #

Like sepBy1 from Parsec, but does not fail if it sep succeeds and p fails.

notFollowedBy' :: (Show b, Stream s m a) => ParserT s st m b -> ParserT s st m () #

A more general form of notFollowedBy. This one allows any type of parser to be specified, and succeeds only if that parser fails. It does not consume any input.

oneOfStrings :: Stream s m Char => [Text] -> ParserT s st m Text #

Parses one of a list of strings. If the list contains two strings one of which is a prefix of the other, the longer string will be matched if possible.

oneOfStringsCI :: Stream s m Char => [Text] -> ParserT s st m Text #

Parses one of a list of strings (tried in order), case insensitive.

spaceChar :: Stream s m Char => ParserT s st m Char #

Parses a space or tab.

nonspaceChar :: Stream s m Char => ParserT s st m Char #

Parses a nonspace, nonnewline character.

skipSpaces :: Stream s m Char => ParserT s st m () #

Skips zero or more spaces or tabs.

blankline :: Stream s m Char => ParserT s st m Char #

Skips zero or more spaces or tabs, then reads a newline.

blanklines :: Stream s m Char => ParserT s st m Text #

Parses one or more blank lines and returns a string of newlines.

gobbleSpaces :: (HasReaderOptions st, Monad m) => Int -> ParserT Text st m () #

Gobble n spaces; if tabs are encountered, expand them and gobble some or all of their spaces, leaving the rest.

gobbleAtMostSpaces :: (HasReaderOptions st, Monad m) => Int -> ParserT Text st m Int #

Gobble up to n spaces; if tabs are encountered, expand them and gobble some or all of their spaces, leaving the rest.

enclosed #

Arguments

:: (Show end, Stream s m Char) 
=> ParserT s st m t

start parser

-> ParserT s st m end

end parser

-> ParserT s st m a

content parser (to be used repeatedly)

-> ParserT s st m [a] 

Parses material enclosed between start and end parsers.

stringAnyCase :: Stream s m Char => Text -> ParserT s st m Text #

Parse string, case insensitive.

parseFromString :: (Stream s m Char, IsString s) => ParserT s st m r -> Text -> ParserT s st m r #

Parse contents of str using parser and return result.

parseFromString' :: (Stream s m Char, IsString s, HasLastStrPosition u) => ParserT s u m a -> Text -> ParserT s u m a #

Like parseFromString but specialized for ParserState. This resets stateLastStrPos, which is almost always what we want.

lineClump :: Monad m => ParserT Text st m Text #

Parse raw line block up to and including blank lines.

charsInBalanced :: Stream s m Char => Char -> Char -> ParserT s st m Char -> ParserT s st m Text #

Parse a string of characters between an open character and a close character, including text between balanced pairs of open and close, which must be different. For example, charsInBalanced '(' ')' anyChar will parse "(hello (there))" and return "hello (there)".

romanNumeral #

Arguments

:: Stream s m Char 
=> Bool

Uppercase if true

-> ParserT s st m Int 

Parses a roman numeral (uppercase or lowercase), returns number.

emailAddress :: Stream s m Char => ParserT s st m (Text, Text) #

Parses an email address; returns original and corresponding escaped mailto: URI.

uri :: Stream s m Char => ParserT s st m (Text, Text) #

Parses a URI. Returns pair of original and URI-escaped version.

mathInline :: (HasReaderOptions st, Stream s m Char) => ParserT s st m Text #

mathDisplay :: (HasReaderOptions st, Stream s m Char) => ParserT s st m Text #

withHorizDisplacement #

Arguments

:: Stream s m Char 
=> ParserT s st m a

Parser to apply

-> ParserT s st m (a, Int)

(result, displacement)

Applies a parser, returns tuple of its results and its horizontal displacement (the difference between the source column at the end and the source column at the beginning). Vertical displacement (source row) is ignored.

withRaw :: Monad m => ParsecT Text st m a -> ParsecT Text st m (a, Text) #

Applies a parser and returns the raw string that was parsed, along with the value produced by the parser.

escaped #

Arguments

:: Stream s m Char 
=> ParserT s st m Char

Parser for character to escape

-> ParserT s st m Char 

Parses backslash, then applies character parser.

characterReference :: Stream s m Char => ParserT s st m Char #

Parse character entity.

upperRoman :: Stream s m Char => ParserT s st m (ListNumberStyle, Int) #

Parses an uppercase roman numeral and returns (UpperRoman, number).

lowerRoman :: Stream s m Char => ParserT s st m (ListNumberStyle, Int) #

Parses a lowercase roman numeral and returns (LowerRoman, number).

decimal :: Stream s m Char => ParserT s st m (ListNumberStyle, Int) #

Parses a decimal numeral and returns (Decimal, number).

lowerAlpha :: Stream s m Char => ParserT s st m (ListNumberStyle, Int) #

Parses a lowercase letter and returns (LowerAlpha, number).

upperAlpha :: Stream s m Char => ParserT s st m (ListNumberStyle, Int) #

Parses an uppercase letter and returns (UpperAlpha, number).

anyOrderedListMarker :: Stream s m Char => ParserT s ParserState m ListAttributes #

Parses an ordered list marker and returns list attributes.

orderedListMarker :: Stream s m Char => ListNumberStyle -> ListNumberDelim -> ParserT s ParserState m Int #

Parses an ordered list marker with a given style and delimiter, returns number.

charRef :: Stream s m Char => ParserT s st m Inline #

Parses a character reference and returns a Str element.

lineBlockLines :: Monad m => ParserT Text st m [Text] #

Parses an RST-style line block and returns a list of strings.

tableWith :: (Stream s m Char, HasReaderOptions st, Monad mf) => ParserT s st m (mf [Blocks], [Alignment], [Int]) -> ([Int] -> ParserT s st m (mf [Blocks])) -> ParserT s st m sep -> ParserT s st m end -> ParserT s st m (mf Blocks) #

Parse a table using headerParser, rowParser, lineParser, and footerParser.

gridTableWith #

Arguments

:: (Stream s m Char, HasReaderOptions st, HasLastStrPosition st, Monad mf, IsString s) 
=> ParserT s st m (mf Blocks)

Block list parser

-> Bool

Headerless table

-> ParserT s st m (mf Blocks) 

gridTableWith' #

Arguments

:: (Stream s m Char, HasReaderOptions st, HasLastStrPosition st, Monad mf, IsString s) 
=> ParserT s st m (mf Blocks)

Block list parser

-> Bool

Headerless table

-> ParserT s st m (TableComponents mf) 

readWith :: Parser Text st a -> st -> Text -> Either PandocError a #

Parse a string with a given parser and state

readWithM #

Arguments

:: (Stream s m Char, ToText s) 
=> ParserT s st m a

parser

-> st

initial state

-> s

input

-> m (Either PandocError a) 

Removes the ParsecT layer from the monad transformer stack

testStringWith :: Show a => ParserT Text ParserState Identity a -> Text -> IO () #

Parse a string with parser (for testing).

guardEnabled :: (Stream s m a, HasReaderOptions st) => Extension -> ParserT s st m () #

Succeed only if the extension is enabled.

guardDisabled :: (Stream s m a, HasReaderOptions st) => Extension -> ParserT s st m () #

Succeed only if the extension is disabled.

updateLastStrPos :: (Stream s m a, HasLastStrPosition st) => ParserT s st m () #

Update the position on which the last string ended.

notAfterString :: (Stream s m a, HasLastStrPosition st) => ParserT s st m Bool #

Whether we are right after the end of a string.

logMessage :: (Stream s m a, HasLogMessages st) => LogMessage -> ParserT s st m () #

Add a log message.

reportLogMessages :: (PandocMonad m, HasLogMessages st) => ParserT s st m () #

Report all the accumulated log messages, according to verbosity level.

data ParserState #

Parsing options.

Constructors

ParserState 

Fields

Instances

Instances details
HasMeta ParserState # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

setMeta :: ToMetaValue b => Text -> b -> ParserState -> ParserState

deleteMeta :: Text -> ParserState -> ParserState

Default ParserState # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

def :: ParserState #

HasIncludeFiles ParserState # 
Instance details

Defined in Text.Pandoc.Parsing

HasLogMessages ParserState # 
Instance details

Defined in Text.Pandoc.Parsing

HasLastStrPosition ParserState # 
Instance details

Defined in Text.Pandoc.Parsing

HasMacros ParserState # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

extractMacros :: ParserState -> Map Text Macro #

updateMacros :: (Map Text Macro -> Map Text Macro) -> ParserState -> ParserState #

HasIdentifierList ParserState # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

extractIdentifierList :: ParserState -> Set Text #

updateIdentifierList :: (Set Text -> Set Text) -> ParserState -> ParserState #

HasReaderOptions ParserState # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

extractReaderOptions :: ParserState -> ReaderOptions #

getOption :: forall s (m :: Type -> Type) t b. Stream s m t => (ReaderOptions -> b) -> ParserT s ParserState m b #

Monad m => HasQuoteContext ParserState m # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

getQuoteContext :: Stream s m t => ParsecT s ParserState m QuoteContext #

withQuoteContext :: QuoteContext -> ParsecT s ParserState m a -> ParsecT s ParserState m a #

class HasReaderOptions st where #

Minimal complete definition

extractReaderOptions

Methods

extractReaderOptions :: st -> ReaderOptions #

getOption :: Stream s m t => (ReaderOptions -> b) -> ParserT s st m b #

Instances

Instances details
HasReaderOptions ParserState # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

extractReaderOptions :: ParserState -> ReaderOptions #

getOption :: forall s (m :: Type -> Type) t b. Stream s m t => (ReaderOptions -> b) -> ParserT s ParserState m b #

class HasIdentifierList st where #

Methods

extractIdentifierList :: st -> Set Text #

updateIdentifierList :: (Set Text -> Set Text) -> st -> st #

Instances

Instances details
HasIdentifierList ParserState # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

extractIdentifierList :: ParserState -> Set Text #

updateIdentifierList :: (Set Text -> Set Text) -> ParserState -> ParserState #

class HasMacros st where #

Methods

extractMacros :: st -> Map Text Macro #

updateMacros :: (Map Text Macro -> Map Text Macro) -> st -> st #

Instances

Instances details
HasMacros ParserState # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

extractMacros :: ParserState -> Map Text Macro #

updateMacros :: (Map Text Macro -> Map Text Macro) -> ParserState -> ParserState #

class HasLogMessages st where #

Methods

addLogMessage :: LogMessage -> st -> st #

getLogMessages :: st -> [LogMessage] #

Instances

Instances details
HasLogMessages ParserState # 
Instance details

Defined in Text.Pandoc.Parsing

class HasLastStrPosition st where #

class HasIncludeFiles st where #

Methods

getIncludeFiles :: st -> [Text] #

addIncludeFile :: Text -> st -> st #

dropLatestIncludeFile :: st -> st #

Instances

Instances details
HasIncludeFiles ParserState # 
Instance details

Defined in Text.Pandoc.Parsing

data HeaderType #

Constructors

SingleHeader Char

Single line of characters underneath

DoubleHeader Char

Lines of characters above and below

Instances

Instances details
Eq HeaderType # 
Instance details

Defined in Text.Pandoc.Parsing

Show HeaderType # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

showsPrec :: Int -> HeaderType -> ShowS #

show :: HeaderType -> String #

showList :: [HeaderType] -> ShowS #

data ParserContext #

Constructors

ListItemState

Used when running parser on list item contents

NullState

Default state

Instances

Instances details
Eq ParserContext # 
Instance details

Defined in Text.Pandoc.Parsing

Show ParserContext # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

showsPrec :: Int -> ParserContext -> ShowS #

show :: ParserContext -> String #

showList :: [ParserContext] -> ShowS #

data QuoteContext #

Constructors

InSingleQuote

Used when parsing inside single quotes

InDoubleQuote

Used when parsing inside double quotes

NoQuote

Used when not parsing inside quotes

Instances

Instances details
Eq QuoteContext # 
Instance details

Defined in Text.Pandoc.Parsing

Show QuoteContext # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

showsPrec :: Int -> QuoteContext -> ShowS #

show :: QuoteContext -> String #

showList :: [QuoteContext] -> ShowS #

class HasQuoteContext st m where #

Methods

getQuoteContext :: Stream s m t => ParsecT s st m QuoteContext #

withQuoteContext :: QuoteContext -> ParsecT s st m a -> ParsecT s st m a #

Instances

Instances details
Monad m => HasQuoteContext ParserState m # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

getQuoteContext :: Stream s m t => ParsecT s ParserState m QuoteContext #

withQuoteContext :: QuoteContext -> ParsecT s ParserState m a -> ParsecT s ParserState m a #

type NoteTable = [(Text, Text)] #

type NoteTable' = Map Text (SourcePos, F Blocks) #

type KeyTable = Map Key (Target, Attr) #

type SubstTable = Map Key Inlines #

newtype Key #

Constructors

Key Text 

Instances

Instances details
Eq Key # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

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

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

Ord Key # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

compare :: Key -> Key -> Ordering #

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

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

(>) :: Key -> Key -> Bool #

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Read Key # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

readsPrec :: Int -> ReadS Key #

readList :: ReadS [Key] #

readPrec :: ReadPrec Key #

readListPrec :: ReadPrec [Key] #

Show Key # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

toKey :: Text -> Key #

registerHeader :: (Stream s m a, HasReaderOptions st, HasLogMessages st, HasIdentifierList st) => Attr -> Inlines -> ParserT s st m Attr #

smartPunctuation :: (HasReaderOptions st, HasLastStrPosition st, HasQuoteContext st m, Stream s m Char) => ParserT s st m Inlines -> ParserT s st m Inlines #

singleQuoteEnd :: Stream s m Char => ParserT s st m () #

doubleQuoteStart :: (HasQuoteContext st m, Stream s m Char) => ParserT s st m () #

doubleQuoteEnd :: Stream s m Char => ParserT s st m () #

ellipses :: Stream s m Char => ParserT s st m Inlines #

apostrophe :: Stream s m Char => ParserT s st m Inlines #

dash :: (HasReaderOptions st, Stream s m Char) => ParserT s st m Inlines #

nested :: Stream s m a => ParserT s ParserState m a -> ParserT s ParserState m a #

citeKey :: (Stream s m Char, HasLastStrPosition st) => ParserT s st m (Bool, Text) #

type Parser t s = Parsec t s #

type ParserT = ParsecT #

newtype Future s a #

Reader monad wrapping the parser state. This is used to possibly delay evaluation until all relevant information has been parsed and made available in the parser state.

Constructors

Future 

Fields

Instances

Instances details
Monad (Future s) # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

(>>=) :: Future s a -> (a -> Future s b) -> Future s b #

(>>) :: Future s a -> Future s b -> Future s b #

return :: a -> Future s a #

Functor (Future s) # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

fmap :: (a -> b) -> Future s a -> Future s b #

(<$) :: a -> Future s b -> Future s a #

Applicative (Future s) # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

pure :: a -> Future s a #

(<*>) :: Future s (a -> b) -> Future s a -> Future s b #

liftA2 :: (a -> b -> c) -> Future s a -> Future s b -> Future s c #

(*>) :: Future s a -> Future s b -> Future s b #

(<*) :: Future s a -> Future s b -> Future s a #

Semigroup a => Semigroup (Future s a) # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

(<>) :: Future s a -> Future s a -> Future s a #

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

stimes :: Integral b => b -> Future s a -> Future s a #

(Semigroup a, Monoid a) => Monoid (Future s a) # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

mempty :: Future s a #

mappend :: Future s a -> Future s a -> Future s a #

mconcat :: [Future s a] -> Future s a #

runF :: Future s a -> s -> a #

askF :: Future s s #

asksF :: (s -> a) -> Future s a #

returnF :: Monad m => a -> m (Future s a) #

trimInlinesF :: Future s Inlines -> Future s Inlines #

token :: Stream s m t => (t -> Text) -> (t -> SourcePos) -> (t -> Maybe a) -> ParsecT s st m a #

(<+?>) :: Monoid a => ParserT s st m a -> ParserT s st m a -> ParserT s st m a infixr 5 #

extractIdClass :: Attr -> Attr #

insertIncludedFile :: (PandocMonad m, HasIncludeFiles st) => ParserT [a] st m Blocks -> (Text -> [a]) -> [FilePath] -> FilePath -> ParserT [a] st m Blocks #

Parse content of include file as blocks. Circular includes result in an PandocParseError.

insertIncludedFileF :: (PandocMonad m, HasIncludeFiles st) => ParserT Text st m (Future st Blocks) -> [FilePath] -> FilePath -> ParserT Text st m (Future st Blocks) #

Parse content of include file as future blocks. Circular includes result in an PandocParseError.

Re-exports from Text.Parsec

class Monad m => Stream s (m :: Type -> Type) t | s -> t #

Minimal complete definition

uncons

Instances

Instances details
Monad m => Stream Text m Char 
Instance details

Defined in Text.Parsec.Prim

Methods

uncons :: Text -> m (Maybe (Char, Text))

Monad m => Stream Text m Char 
Instance details

Defined in Text.Parsec.Prim

Methods

uncons :: Text -> m (Maybe (Char, Text))

Monad m => Stream ByteString m Char 
Instance details

Defined in Text.Parsec.Prim

Methods

uncons :: ByteString -> m (Maybe (Char, ByteString))

Monad m => Stream ByteString m Char 
Instance details

Defined in Text.Parsec.Prim

Methods

uncons :: ByteString -> m (Maybe (Char, ByteString))

Monad m => Stream [tok] m tok 
Instance details

Defined in Text.Parsec.Prim

Methods

uncons :: [tok] -> m (Maybe (tok, [tok]))

runParser :: Stream s Identity t => Parsec s u a -> u -> SourceName -> s -> Either ParseError a #

runParserT :: Stream s m t => ParsecT s u m a -> u -> SourceName -> s -> m (Either ParseError a) #

parse :: Stream s Identity t => Parsec s () a -> SourceName -> s -> Either ParseError a #

tokenPrim :: forall s (m :: Type -> Type) t a u. Stream s m t => (t -> String) -> (SourcePos -> t -> s -> SourcePos) -> (t -> Maybe a) -> ParsecT s u m a #

anyToken :: forall s (m :: Type -> Type) t u. (Stream s m t, Show t) => ParsecT s u m t #

getInput :: forall (m :: Type -> Type) s u. Monad m => ParsecT s u m s #

setInput :: forall (m :: Type -> Type) s u. Monad m => s -> ParsecT s u m () #

unexpected :: forall s (m :: Type -> Type) t u a. Stream s m t => String -> ParsecT s u m a #

char :: forall s (m :: Type -> Type) u. Stream s m Char => Char -> ParsecT s u m Char #

letter :: forall s (m :: Type -> Type) u. Stream s m Char => ParsecT s u m Char #

digit :: forall s (m :: Type -> Type) u. Stream s m Char => ParsecT s u m Char #

alphaNum :: forall s (m :: Type -> Type) u. Stream s m Char => ParsecT s u m Char #

skipMany :: forall s u (m :: Type -> Type) a. ParsecT s u m a -> ParsecT s u m () #

skipMany1 :: forall s (m :: Type -> Type) t u a. Stream s m t => ParsecT s u m a -> ParsecT s u m () #

spaces :: forall s (m :: Type -> Type) u. Stream s m Char => ParsecT s u m () #

space :: forall s (m :: Type -> Type) u. Stream s m Char => ParsecT s u m Char #

anyChar :: forall s (m :: Type -> Type) u. Stream s m Char => ParsecT s u m Char #

satisfy :: forall s (m :: Type -> Type) u. Stream s m Char => (Char -> Bool) -> ParsecT s u m Char #

newline :: forall s (m :: Type -> Type) u. Stream s m Char => ParsecT s u m Char #

string :: forall s (m :: Type -> Type) u. Stream s m Char => String -> ParsecT s u m String #

count :: forall s (m :: Type -> Type) t u a. Stream s m t => Int -> ParsecT s u m a -> ParsecT s u m [a] #

eof :: forall s (m :: Type -> Type) t u. (Stream s m t, Show t) => ParsecT s u m () #

noneOf :: forall s (m :: Type -> Type) u. Stream s m Char => [Char] -> ParsecT s u m Char #

oneOf :: forall s (m :: Type -> Type) u. Stream s m Char => [Char] -> ParsecT s u m Char #

lookAhead :: forall s (m :: Type -> Type) t u a. Stream s m t => ParsecT s u m a -> ParsecT s u m a #

notFollowedBy :: forall s (m :: Type -> Type) t a u. (Stream s m t, Show a) => ParsecT s u m a -> ParsecT s u m () #

many :: forall s u (m :: Type -> Type) a. ParsecT s u m a -> ParsecT s u m [a] #

many1 :: forall s (m :: Type -> Type) t u a. Stream s m t => ParsecT s u m a -> ParsecT s u m [a] #

manyTill :: forall s (m :: Type -> Type) t u a end. Stream s m t => ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a] #

(<|>) :: forall s u (m :: Type -> Type) a. ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a #

(<?>) :: forall s u (m :: Type -> Type) a. ParsecT s u m a -> String -> ParsecT s u m a #

choice :: forall s (m :: Type -> Type) t u a. Stream s m t => [ParsecT s u m a] -> ParsecT s u m a #

try :: forall s u (m :: Type -> Type) a. ParsecT s u m a -> ParsecT s u m a #

sepBy :: forall s (m :: Type -> Type) t u a sep. Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] #

sepBy1 :: forall s (m :: Type -> Type) t u a sep. Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] #

sepEndBy :: forall s (m :: Type -> Type) t u a sep. Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] #

sepEndBy1 :: forall s (m :: Type -> Type) t u a sep. Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] #

endBy :: forall s (m :: Type -> Type) t u a sep. Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] #

endBy1 :: forall s (m :: Type -> Type) t u a sep. Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] #

option :: forall s (m :: Type -> Type) t a u. Stream s m t => a -> ParsecT s u m a -> ParsecT s u m a #

optional :: forall s (m :: Type -> Type) t u a. Stream s m t => ParsecT s u m a -> ParsecT s u m () #

optionMaybe :: forall s (m :: Type -> Type) t u a. Stream s m t => ParsecT s u m a -> ParsecT s u m (Maybe a) #

getState :: forall (m :: Type -> Type) s u. Monad m => ParsecT s u m u #

setState :: forall (m :: Type -> Type) u s. Monad m => u -> ParsecT s u m () #

updateState :: forall (m :: Type -> Type) u s. Monad m => (u -> u) -> ParsecT s u m () #

data SourcePos #

Instances

Instances details
Eq SourcePos 
Instance details

Defined in Text.Parsec.Pos

Data SourcePos 
Instance details

Defined in Text.Parsec.Pos

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourcePos -> c SourcePos #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourcePos #

toConstr :: SourcePos -> Constr #

dataTypeOf :: SourcePos -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourcePos) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourcePos) #

gmapT :: (forall b. Data b => b -> b) -> SourcePos -> SourcePos #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourcePos -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourcePos -> r #

gmapQ :: (forall d. Data d => d -> u) -> SourcePos -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SourcePos -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourcePos -> m SourcePos #

Ord SourcePos 
Instance details

Defined in Text.Parsec.Pos

Show SourcePos 
Instance details

Defined in Text.Parsec.Pos

Methods

showsPrec :: Int -> SourcePos -> ShowS #

show :: SourcePos -> String #

showList :: [SourcePos] -> ShowS #

getPosition :: forall (m :: Type -> Type) s u. Monad m => ParsecT s u m SourcePos #

setPosition :: forall (m :: Type -> Type) s u. Monad m => SourcePos -> ParsecT s u m () #

newPos :: SourceName -> Line -> Column -> SourcePos #

type Line = Int #

type Column = Int #