pandoc-1.6: Conversion between markup formats

Portabilityportable
Stabilityalpha
MaintainerJohn MacFarlane <jgm@berkeley.edu>

Text.Pandoc.Parsing

Description

A utility library with parsers used in pandoc readers.

Synopsis

Documentation

(>>~) :: Monad m => m a -> m b -> m aSource

Like >>, but returns the operation on the left. (Suggested by Tillmann Rendel on Haskell-cafe list.)

anyLine :: GenParser Char st [Char]Source

Parse any line of text

many1Till :: GenParser tok st a -> GenParser tok st end -> GenParser tok st [a]Source

Like manyTill, but reads at least one item.

notFollowedBy' :: Show b => GenParser a st b -> GenParser a st ()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 :: [String] -> GenParser Char st StringSource

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

spaceChar :: CharParser st CharSource

Parses a space or tab.

skipSpaces :: GenParser Char st ()Source

Skips zero or more spaces or tabs.

blankline :: GenParser Char st CharSource

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

blanklines :: GenParser Char st [Char]Source

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

enclosedSource

Arguments

:: GenParser Char st t

start parser

-> GenParser Char st end

end parser

-> GenParser Char st a

content parser (to be used repeatedly)

-> GenParser Char st [a] 

Parses material enclosed between start and end parsers.

stringAnyCase :: [Char] -> CharParser st StringSource

Parse string, case insensitive.

parseFromString :: GenParser tok st a -> [tok] -> GenParser tok st aSource

Parse contents of str using parser and return result.

lineClump :: GenParser Char st StringSource

Parse raw line block up to and including blank lines.

charsInBalanced :: Char -> Char -> GenParser Char st StringSource

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 '(' ')' will parse (hello (there)) and return hello (there). Stop if a blank line is encountered.

charsInBalanced' :: Char -> Char -> GenParser Char st StringSource

Like charsInBalanced, but allow blank lines in the content.

romanNumeralSource

Arguments

:: Bool

Uppercase if true

-> GenParser Char st Int 

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

emailAddress :: GenParser Char st (String, String)Source

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

uri :: GenParser Char st (String, String)Source

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

withHorizDisplacementSource

Arguments

:: GenParser Char st a

Parser to apply

-> GenParser Char st (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.

nullBlock :: GenParser Char st BlockSource

Parses a character and returns Null (so that the parser can move on if it gets stuck).

failIfStrict :: GenParser Char ParserState ()Source

Fail if reader is in strict markdown syntax mode.

failUnlessLHS :: GenParser tok ParserState ()Source

Fail unless we're in literate haskell mode.

escapedSource

Arguments

:: GenParser Char st Char

Parser for character to escape

-> GenParser Char st Inline 

Parses backslash, then applies character parser.

anyOrderedListMarker :: GenParser Char ParserState ListAttributesSource

Parses an ordered list marker and returns list attributes.

orderedListMarker :: ListNumberStyle -> ListNumberDelim -> GenParser Char ParserState IntSource

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

charRef :: GenParser Char st InlineSource

Parses a character reference and returns a Str element.

tableWith :: GenParser Char ParserState ([[Block]], [Alignment], [Int]) -> ([Int] -> GenParser Char ParserState [[Block]]) -> GenParser Char ParserState sep -> GenParser Char ParserState end -> GenParser Char ParserState [Inline] -> GenParser Char ParserState BlockSource

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

gridTableWithSource

Arguments

:: GenParser Char ParserState Block

Block parser

-> GenParser Char ParserState [Inline]

Caption parser

-> Bool

Headerless table

-> GenParser Char ParserState Block 

readWithSource

Arguments

:: GenParser Char ParserState a

parser

-> ParserState

initial state

-> String

input string

-> a 

Parse a string with a given parser and state.

testStringWith :: Show a => GenParser Char ParserState a -> String -> IO ()Source

Parse a string with parser (for testing).

data ParserState Source

Parsing options.

Constructors

ParserState 

Fields

stateParseRaw :: Bool

Parse raw HTML and LaTeX?

stateParserContext :: ParserContext

Inside list?

stateQuoteContext :: QuoteContext

Inside quoted environment?

stateSanitizeHTML :: Bool

Sanitize HTML?

stateKeys :: KeyTable

List of reference keys

stateNotes :: NoteTable

List of notes

stateTabStop :: Int

Tab stop

stateStandalone :: Bool

Parse bibliographic info?

stateTitle :: [Inline]

Title of document

stateAuthors :: [[Inline]]

Authors of document

stateDate :: [Inline]

Date of document

stateStrict :: Bool

Use strict markdown syntax?

stateSmart :: Bool

Use smart typography?

stateLiterateHaskell :: Bool

Treat input as literate haskell

stateColumns :: Int

Number of columns in terminal

stateHeaderTable :: [HeaderType]

Ordered list of header types used

stateIndentedCodeClasses :: [String]

Classes to use for indented code blocks

stateNextExample :: Int

Number of next example

stateExamples :: Map String Int

Map from example labels to numbers

stateHasChapters :: Bool

True if chapter encountered

Instances

data HeaderType Source

Constructors

SingleHeader Char

Single line of characters underneath

DoubleHeader Char

Lines of characters above and below

data ParserContext Source

Constructors

ListItemState

Used when running parser on list item contents

NullState

Default state

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

newtype Key Source

Constructors

Key [Inline] 

Instances

lookupKeySrcSource

Arguments

:: KeyTable

Key table

-> Key

Key

-> Maybe Target 

Look up key in key table and return target object.

refsMatch :: [Inline] -> [Inline] -> BoolSource

Returns True if keys match (case insensitive).