pandoc-2.7.3: Conversion between markup formats

CopyrightCopyright (C) 2006-2019 John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.Pandoc.Parsing

Contents

Description

A utility library with parsers used in pandoc readers.

Synopsis

Documentation

takeWhileP :: Monad m => (Char -> Bool) -> ParserT [Char] st m [Char] Source #

Parse characters while a predicate is true.

takeP :: Monad m => Int -> ParserT [Char] st m [Char] Source #

anyLine :: Monad m => ParserT [Char] st m [Char] Source #

Parse any line of text

anyLineNewline :: Monad m => ParserT [Char] st m [Char] Source #

Parse any line, include the final newline in the output

indentWith :: Stream s m Char => HasReaderOptions st => Int -> ParserT s st m [Char] Source #

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

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

Like manyTill, but reads at least one item.

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

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

sepBy1' :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] Source #

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 () Source #

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 => [String] -> ParserT s st m String Source #

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 => [String] -> ParserT s st m String Source #

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

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

Parses a space or tab.

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

Parses a nonspace, nonnewline character.

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

Skips zero or more spaces or tabs.

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

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

blanklines :: Stream s m Char => ParserT s st m [Char] Source #

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

gobbleSpaces :: (HasReaderOptions st, Monad m) => Int -> ParserT [Char] st m () Source #

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 [Char] st m Int Source #

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

enclosed Source #

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 => [Char] -> ParserT s st m String Source #

Parse string, case insensitive.

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

Parse contents of str using parser and return result.

parseFromString' :: (Monad m, Stream s m Char, IsString s) => ParserT s ParserState m a -> String -> ParserT s ParserState m a Source #

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

lineClump :: Monad m => ParserT [Char] st m String Source #

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 String Source #

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

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 (String, String) Source #

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

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

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

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

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

withHorizDisplacement Source #

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 [Char] st m a -> ParsecT [Char] st m (a, [Char]) Source #

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

escaped Source #

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

Parse character entity.

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

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

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

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

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

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

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

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

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

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

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

Parses an ordered list marker and returns list attributes.

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

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

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

Parses a character reference and returns a Str element.

lineBlockLines :: Monad m => ParserT [Char] st m [String] Source #

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) Source #

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

widthsFromIndices :: Int -> [Int] -> [Double] Source #

gridTableWith Source #

Arguments

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

Block list parser

-> Bool

Headerless table

-> ParserT s st m (mf Blocks) 

gridTableWith' Source #

Arguments

:: (Stream s m Char, HasReaderOptions 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 [Char] st a -> st -> String -> Either PandocError a Source #

Parse a string with a given parser and state

readWithM Source #

Arguments

:: (Monad m, Stream s m Char, ToString 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 [Char] ParserState Identity a -> [Char] -> IO () Source #

Parse a string with parser (for testing).

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

Succeed only if the extension is enabled.

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

Succeed only if the extension is disabled.

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

Update the position on which the last string ended.

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

Whether we are right after the end of a string.

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

Add a log message.

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

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

data ParserState Source #

Parsing options.

Constructors

ParserState 

Fields

Instances
HasMeta ParserState Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

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

deleteMeta :: String -> ParserState -> ParserState

Default ParserState Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

def :: ParserState #

HasIncludeFiles ParserState Source # 
Instance details

Defined in Text.Pandoc.Parsing

HasLogMessages ParserState Source # 
Instance details

Defined in Text.Pandoc.Parsing

HasLastStrPosition ParserState Source # 
Instance details

Defined in Text.Pandoc.Parsing

HasMacros ParserState Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

extractMacros :: ParserState -> Map Text Macro Source #

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

HasIdentifierList ParserState Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

extractIdentifierList :: ParserState -> Set String Source #

updateIdentifierList :: (Set String -> Set String) -> ParserState -> ParserState Source #

HasReaderOptions ParserState Source # 
Instance details

Defined in Text.Pandoc.Parsing

Monad m => HasQuoteContext ParserState m Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

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

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

class HasReaderOptions st where Source #

Minimal complete definition

extractReaderOptions

Methods

extractReaderOptions :: st -> ReaderOptions Source #

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

class HasIdentifierList st where Source #

Methods

extractIdentifierList :: st -> Set String Source #

updateIdentifierList :: (Set String -> Set String) -> st -> st Source #

Instances
HasIdentifierList ParserState Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

extractIdentifierList :: ParserState -> Set String Source #

updateIdentifierList :: (Set String -> Set String) -> ParserState -> ParserState Source #

class HasMacros st where Source #

Methods

extractMacros :: st -> Map Text Macro Source #

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

Instances
HasMacros ParserState Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

extractMacros :: ParserState -> Map Text Macro Source #

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

data HeaderType Source #

Constructors

SingleHeader Char

Single line of characters underneath

DoubleHeader Char

Lines of characters above and below

Instances
Eq HeaderType Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

(==) :: HeaderType -> HeaderType -> Bool

(/=) :: HeaderType -> HeaderType -> Bool

Show HeaderType Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

showsPrec :: Int -> HeaderType -> ShowS

show :: HeaderType -> String

showList :: [HeaderType] -> ShowS

data ParserContext Source #

Constructors

ListItemState

Used when running parser on list item contents

NullState

Default state

Instances
Eq ParserContext Source # 
Instance details

Defined in Text.Pandoc.Parsing

Show ParserContext Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

showsPrec :: Int -> ParserContext -> ShowS

show :: ParserContext -> String

showList :: [ParserContext] -> ShowS

data QuoteContext Source #

Constructors

InSingleQuote

Used when parsing inside single quotes

InDoubleQuote

Used when parsing inside double quotes

NoQuote

Used when not parsing inside quotes

Instances
Eq QuoteContext Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

(==) :: QuoteContext -> QuoteContext -> Bool

(/=) :: QuoteContext -> QuoteContext -> Bool

Show QuoteContext Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

showsPrec :: Int -> QuoteContext -> ShowS

show :: QuoteContext -> String

showList :: [QuoteContext] -> ShowS

class HasQuoteContext st m where Source #

Methods

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

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

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

Defined in Text.Pandoc.Parsing

Methods

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

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

type NoteTable = [(String, String)] Source #

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

type KeyTable = Map Key (Target, Attr) Source #

type SubstTable = Map Key Inlines Source #

newtype Key Source #

Constructors

Key String 
Instances
Eq Key Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

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

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

Ord Key Source # 
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 Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

readsPrec :: Int -> ReadS Key

readList :: ReadS [Key]

readPrec :: ReadPrec Key

readListPrec :: ReadPrec [Key]

Show Key Source # 
Instance details

Defined in Text.Pandoc.Parsing

Methods

showsPrec :: Int -> Key -> ShowS

show :: Key -> String

showList :: [Key] -> ShowS

toKey :: String -> Key Source #

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

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

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

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

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

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

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

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

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

type Parser t s = Parsec t s Source #

type ParserT = ParsecT Source #

newtype Future s a Source #

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
Monad (Future s) Source # 
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

fail :: String -> Future s a

Functor (Future s) Source # 
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) Source # 
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) Source # 
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) Source # 
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 Source #

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

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

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

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

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

extractIdClass :: Attr -> Attr Source #

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

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

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

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
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 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 [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 :: Stream s m t => (t -> String) -> (SourcePos -> t -> s -> SourcePos) -> (t -> Maybe a) -> ParsecT s u m a #

anyToken :: (Stream s m t, Show t) => ParsecT s u m t #

getInput :: Monad m => ParsecT s u m s #

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

unexpected :: Stream s m t => String -> ParsecT s u m a #

char :: Stream s m Char => Char -> ParsecT s u m Char #

letter :: Stream s m Char => ParsecT s u m Char #

digit :: Stream s m Char => ParsecT s u m Char #

alphaNum :: Stream s m Char => ParsecT s u m Char #

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

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

spaces :: Stream s m Char => ParsecT s u m () #

space :: Stream s m Char => ParsecT s u m Char #

anyChar :: Stream s m Char => ParsecT s u m Char #

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

newline :: Stream s m Char => ParsecT s u m Char #

string :: Stream s m Char => String -> ParsecT s u m String #

count :: Stream s m t => Int -> ParsecT s u m a -> ParsecT s u m [a] #

eof :: (Stream s m t, Show t) => ParsecT s u m () #

noneOf :: Stream s m Char => [Char] -> ParsecT s u m Char #

oneOf :: Stream s m Char => [Char] -> ParsecT s u m Char #

lookAhead :: Stream s m t => ParsecT s u m a -> ParsecT s u m a #

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

many :: ParsecT s u m a -> ParsecT s u m [a] #

many1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m [a] #

manyTill :: Stream s m t => ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a] #

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

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

choice :: Stream s m t => [ParsecT s u m a] -> ParsecT s u m a #

try :: ParsecT s u m a -> ParsecT s u m a #

sepBy :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] #

sepBy1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] #

sepEndBy :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] #

sepEndBy1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] #

endBy :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] #

endBy1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] #

option :: Stream s m t => a -> ParsecT s u m a -> ParsecT s u m a #

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

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

getState :: Monad m => ParsecT s u m u #

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

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

data SourcePos #

Instances
Eq SourcePos 
Instance details

Defined in Text.Parsec.Pos

Methods

(==) :: SourcePos -> SourcePos -> Bool

(/=) :: SourcePos -> SourcePos -> Bool

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 :: (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

Methods

compare :: SourcePos -> SourcePos -> Ordering

(<) :: SourcePos -> SourcePos -> Bool

(<=) :: SourcePos -> SourcePos -> Bool

(>) :: SourcePos -> SourcePos -> Bool

(>=) :: SourcePos -> SourcePos -> Bool

max :: SourcePos -> SourcePos -> SourcePos

min :: SourcePos -> SourcePos -> SourcePos

Show SourcePos 
Instance details

Defined in Text.Parsec.Pos

Methods

showsPrec :: Int -> SourcePos -> ShowS

show :: SourcePos -> String

showList :: [SourcePos] -> ShowS

getPosition :: Monad m => ParsecT s u m SourcePos #

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

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

type Line = Int #

type Column = Int #