|
Text.Pandoc.Shared | Portability | portable | Stability | alpha | Maintainer | John MacFarlane <jgm@berkeley.edu> |
|
|
|
|
|
Description |
Utility functions and definitions used by the various Pandoc modules.
|
|
Synopsis |
|
|
|
|
List processing
|
|
splitBy :: Eq a => a -> [a] -> [[a]] |
Split list by groups of one or more sep.
|
|
splitByIndices :: [Int] -> [a] -> [[a]] |
Split list into chunks divided at specified indices.
|
|
substitute :: Eq a => [a] -> [a] -> [a] -> [a] |
Replace each occurrence of one sublist in a list with another.
|
|
joinWithSep |
:: [a] | List to use as separator
| -> [[a]] | Lists to join
| -> [a] | | Joins a list of lists, separated by another list.
|
|
|
Text processing
|
|
tabsToSpaces |
:: Int | Tabstop
| -> String | String to convert
| -> String | | Convert tabs to spaces (with adjustable tab stop).
|
|
|
backslashEscapes |
:: [Char] | list of special characters to escape
| -> [(Char, String)] | | Returns an association list of backslash escapes for the
designated characters.
|
|
|
escapeStringUsing :: [(Char, String)] -> String -> String |
Escape a string of characters, using an association list of
characters and strings.
|
|
stripTrailingNewlines :: String -> String |
Strip trailing newlines from string.
|
|
removeLeadingTrailingSpace :: String -> String |
Remove leading and trailing space (including newlines) from string.
|
|
removeLeadingSpace :: String -> String |
Remove leading space (including newlines) from string.
|
|
removeTrailingSpace :: String -> String |
Remove trailing space (including newlines) from string.
|
|
stripFirstAndLast :: String -> String |
Strip leading and trailing characters from string
|
|
camelCaseToHyphenated :: String -> String |
Change CamelCase word to hyphenated lowercase (e.g., camel-case).
|
|
toRomanNumeral :: Int -> String |
Convert number < 4000 to uppercase roman numeral.
|
|
Parsing
|
|
(>>~) :: Monad m => m a -> m b -> m a |
Like >>, but returns the operation on the left.
(Suggested by Tillmann Rendel on Haskell-cafe list.)
|
|
anyLine :: GenParser Char st [Char] |
Parse any line of text
|
|
many1Till :: GenParser tok st a -> GenParser tok st end -> GenParser tok st [a] |
Like manyTill, but reads at least one item.
|
|
notFollowedBy' :: Show b => GenParser a st b -> GenParser a st () |
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 String |
Parses one of a list of strings (tried in order).
|
|
spaceChar :: CharParser st Char |
Parses a space or tab.
|
|
skipSpaces :: GenParser Char st () |
Skips zero or more spaces or tabs.
|
|
blankline :: GenParser Char st Char |
Skips zero or more spaces or tabs, then reads a newline.
|
|
blanklines :: GenParser Char st [Char] |
Parses one or more blank lines and returns a string of newlines.
|
|
enclosed |
|
|
stringAnyCase :: [Char] -> CharParser st String |
Parse string, case insensitive.
|
|
parseFromString :: GenParser tok st a -> [tok] -> GenParser tok st a |
Parse contents of str using parser and return result.
|
|
lineClump :: GenParser Char st String |
Parse raw line block up to and including blank lines.
|
|
charsInBalanced :: Char -> Char -> GenParser Char st String |
Parse a string of characters between an open character
and a close character, including text between balanced
pairs of open and close. For example,
charsInBalanced '(' ')' will parse (hello (there))
and return hello (there). Stop if a blank line is
encountered.
|
|
charsInBalanced' :: Char -> Char -> GenParser Char st String |
Like charsInBalanced, but allow blank lines in the content.
|
|
romanNumeral |
:: Bool | Uppercase if true
| -> GenParser Char st Int | | Parses a roman numeral (uppercase or lowercase), returns number.
|
|
|
withHorizDisplacement |
:: 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 Block |
Parses a character and returns Null (so that the parser can move on
if it gets stuck).
|
|
failIfStrict :: GenParser Char ParserState () |
Fail if reader is in strict markdown syntax mode.
|
|
escaped |
|
|
anyOrderedListMarker :: GenParser Char st ListAttributes |
Parses an ordered list marker and returns list attributes.
|
|
orderedListMarker :: ListNumberStyle -> ListNumberDelim -> GenParser Char st Int |
Parses an ordered list marker with a given style and delimiter,
returns number.
|
|
charRef :: GenParser Char st Inline |
Parses a character reference and returns a Str element.
|
|
readWith |
|
|
testStringWith :: Show a => GenParser Char ParserState a -> String -> IO () |
Parse a string with parser (for testing).
|
|
data ParserState |
Parsing options.
| Constructors | ParserState | | stateParseRaw :: Bool | Parse raw HTML and LaTeX?
| stateParserContext :: ParserContext | Inside list?
| stateQuoteContext :: QuoteContext | Inside quoted environment?
| 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 :: [String] | Authors of document
| stateDate :: String | Date of document
| stateStrict :: Bool | Use strict markdown syntax?
| stateSmart :: Bool | Use smart typography?
| stateColumns :: Int | Number of columns in terminal
| stateHeaderTable :: [HeaderType] | Ordered list of header types used
|
|
| Instances | |
|
|
defaultParserState :: ParserState |
|
data Reference |
References from preliminary parsing.
| Constructors | KeyBlock [Inline] Target | Key for reference-style link (label URL title)
| NoteBlock String [Block] | Footnote reference and contents
| LineClump String | Raw clump of lines with blanks at end
|
| Instances | |
|
|
isNoteBlock :: Reference -> Bool |
Auxiliary functions used in preliminary parsing.
|
|
isKeyBlock :: Reference -> Bool |
|
isLineClump :: Reference -> Bool |
|
data HeaderType |
Constructors | SingleHeader Char | Single line of characters underneath
| DoubleHeader Char | Lines of characters above and below
|
| Instances | |
|
|
data ParserContext |
Constructors | ListItemState | Used when running parser on list item contents
| NullState | Default state
|
| Instances | |
|
|
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 | |
|
|
type NoteTable = [(String, [Block])] |
|
type KeyTable = [([Inline], Target)] |
|
lookupKeySrc |
|
|
refsMatch :: [Inline] -> [Inline] -> Bool |
Returns True if keys match (case insensitive).
|
|
Native format prettyprinting
|
|
prettyPandoc :: Pandoc -> String |
Prettyprint Pandoc document.
|
|
Pandoc block and inline list processing
|
|
orderedListMarkers :: (Int, ListNumberStyle, ListNumberDelim) -> [String] |
Generate infinite lazy list of markers for an ordered list,
depending on list attributes.
|
|
normalizeSpaces :: [Inline] -> [Inline] |
Normalize a list of inline elements: remove leading and trailing
Space elements, collapse double Spaces into singles, and
remove empty Str elements.
|
|
compactify |
:: [[Block]] | List of list items (each a list of blocks)
| -> [[Block]] | | Change final list item from Para to Plain if the list should
be compact.
|
|
|
data Element |
Data structure for defining hierarchical Pandoc documents
| Constructors | | Instances | |
|
|
hierarchicalize :: [Block] -> [Element] |
Convert list of Pandoc blocks into (hierarchical) list of Elements
|
|
isHeaderBlock :: Block -> Bool |
True if block is a Header block.
|
|
Writer options
|
|
data WriterOptions |
Options for writers
| Constructors | WriterOptions | | writerStandalone :: Bool | Include header and footer
| writerHeader :: String | Header for the document
| writerTitlePrefix :: String | Prefix for HTML titles
| writerTabStop :: Int | Tabstop for conversion btw spaces and tabs
| writerTableOfContents :: Bool | Include table of contents
| writerS5 :: Bool | We're writing S5
| writerUseASCIIMathML :: Bool | Use ASCIIMathML
| writerASCIIMathMLURL :: (Maybe String) | URL to asciiMathML.js
| writerIgnoreNotes :: Bool | Ignore footnotes (used in making toc)
| writerIncremental :: Bool | Incremental S5 lists
| writerNumberSections :: Bool | Number sections in LaTeX
| writerIncludeBefore :: String | String to include before the body
| writerIncludeAfter :: String | String to include after the body
| writerStrictMarkdown :: Bool | Use strict markdown syntax
| writerReferenceLinks :: Bool | Use reference links in writing markdown, rst
|
|
| Instances | |
|
|
Produced by Haddock version 0.8 |