pandoc-0.41: Conversion between markup formatsContentsIndex
Text.Pandoc.Shared
Portabilityportable
Stabilityalpha
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Contents
List processing
Text processing
Parsing
Native format prettyprinting
Pandoc block and inline list processing
Writer options
Description
Utility functions and definitions used by the various Pandoc modules.
Synopsis
splitBy :: Eq a => a -> [a] -> [[a]]
splitByIndices :: [Int] -> [a] -> [[a]]
substitute :: Eq a => [a] -> [a] -> [a] -> [a]
joinWithSep :: [a] -> [[a]] -> [a]
tabsToSpaces :: Int -> String -> String
backslashEscapes :: [Char] -> [(Char, String)]
escapeStringUsing :: [(Char, String)] -> String -> String
stripTrailingNewlines :: String -> String
removeLeadingTrailingSpace :: String -> String
removeLeadingSpace :: String -> String
removeTrailingSpace :: String -> String
stripFirstAndLast :: String -> String
camelCaseToHyphenated :: String -> String
toRomanNumeral :: Int -> String
(>>~) :: Monad m => m a -> m b -> m a
anyLine :: GenParser Char st [Char]
many1Till :: GenParser tok st a -> GenParser tok st end -> GenParser tok st [a]
notFollowedBy' :: Show b => GenParser a st b -> GenParser a st ()
oneOfStrings :: [String] -> GenParser Char st String
spaceChar :: CharParser st Char
skipSpaces :: GenParser Char st ()
blankline :: GenParser Char st Char
blanklines :: GenParser Char st [Char]
enclosed :: GenParser Char st t -> GenParser Char st end -> GenParser Char st a -> GenParser Char st [a]
stringAnyCase :: [Char] -> CharParser st String
parseFromString :: GenParser tok st a -> [tok] -> GenParser tok st a
lineClump :: GenParser Char st String
charsInBalanced :: Char -> Char -> GenParser Char st String
charsInBalanced' :: Char -> Char -> GenParser Char st String
romanNumeral :: Bool -> GenParser Char st Int
withHorizDisplacement :: GenParser Char st a -> GenParser Char st (a, Int)
nullBlock :: GenParser Char st Block
failIfStrict :: GenParser Char ParserState ()
escaped :: GenParser Char st Char -> GenParser Char st Inline
anyOrderedListMarker :: GenParser Char st ListAttributes
orderedListMarker :: ListNumberStyle -> ListNumberDelim -> GenParser Char st Int
charRef :: GenParser Char st Inline
readWith :: GenParser Char ParserState a -> ParserState -> String -> a
testStringWith :: Show a => GenParser Char ParserState a -> String -> IO ()
data ParserState = ParserState {
stateParseRaw :: Bool
stateParserContext :: ParserContext
stateQuoteContext :: QuoteContext
stateKeys :: KeyTable
stateNotes :: NoteTable
stateTabStop :: Int
stateStandalone :: Bool
stateTitle :: [Inline]
stateAuthors :: [String]
stateDate :: String
stateStrict :: Bool
stateSmart :: Bool
stateColumns :: Int
stateHeaderTable :: [HeaderType]
}
defaultParserState :: ParserState
data Reference
= KeyBlock [Inline] Target
| NoteBlock String [Block]
| LineClump String
isNoteBlock :: Reference -> Bool
isKeyBlock :: Reference -> Bool
isLineClump :: Reference -> Bool
data HeaderType
= SingleHeader Char
| DoubleHeader Char
data ParserContext
= ListItemState
| NullState
data QuoteContext
= InSingleQuote
| InDoubleQuote
| NoQuote
type NoteTable = [(String, [Block])]
type KeyTable = [([Inline], Target)]
lookupKeySrc :: KeyTable -> [Inline] -> Maybe Target
refsMatch :: [Inline] -> [Inline] -> Bool
prettyPandoc :: Pandoc -> String
orderedListMarkers :: (Int, ListNumberStyle, ListNumberDelim) -> [String]
normalizeSpaces :: [Inline] -> [Inline]
compactify :: [[Block]] -> [[Block]]
data Element
= Blk Block
| Sec [Inline] [Element]
hierarchicalize :: [Block] -> [Element]
isHeaderBlock :: Block -> Bool
data WriterOptions = WriterOptions {
writerStandalone :: Bool
writerHeader :: String
writerTitlePrefix :: String
writerTabStop :: Int
writerTableOfContents :: Bool
writerS5 :: Bool
writerUseASCIIMathML :: Bool
writerASCIIMathMLURL :: (Maybe String)
writerIgnoreNotes :: Bool
writerIncremental :: Bool
writerNumberSections :: Bool
writerIncludeBefore :: String
writerIncludeAfter :: String
writerStrictMarkdown :: Bool
writerReferenceLinks :: Bool
}
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
:: IntTabstop
-> StringString 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
:: GenParser Char st tstart parser
-> GenParser Char st endend parser
-> GenParser Char st acontent parser (to be used repeatedly)
-> GenParser Char st [a]
Parses material enclosed between start and end parsers.
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
:: BoolUppercase if true
-> GenParser Char st Int
Parses a roman numeral (uppercase or lowercase), returns number.
withHorizDisplacement
:: GenParser Char st aParser 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
:: GenParser Char st CharParser for character to escape
-> GenParser Char st Inline
Parses backslash, then applies character parser.
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
:: GenParser Char ParserState aparser
-> ParserStateinitial state
-> Stringinput string
-> a
Parse a string with a given parser and state.
testStringWith :: Show a => GenParser Char ParserState a -> String -> IO ()
Parse a string with parser (for testing).
data ParserState
Parsing options.
Constructors
ParserState
stateParseRaw :: BoolParse raw HTML and LaTeX?
stateParserContext :: ParserContextInside list?
stateQuoteContext :: QuoteContextInside quoted environment?
stateKeys :: KeyTableList of reference keys
stateNotes :: NoteTableList of notes
stateTabStop :: IntTab stop
stateStandalone :: BoolParse bibliographic info?
stateTitle :: [Inline]Title of document
stateAuthors :: [String]Authors of document
stateDate :: StringDate of document
stateStrict :: BoolUse strict markdown syntax?
stateSmart :: BoolUse smart typography?
stateColumns :: IntNumber of columns in terminal
stateHeaderTable :: [HeaderType]Ordered list of header types used
show/hide Instances
defaultParserState :: ParserState
data Reference
References from preliminary parsing.
Constructors
KeyBlock [Inline] TargetKey for reference-style link (label URL title)
NoteBlock String [Block]Footnote reference and contents
LineClump StringRaw clump of lines with blanks at end
show/hide Instances
isNoteBlock :: Reference -> Bool
Auxiliary functions used in preliminary parsing.
isKeyBlock :: Reference -> Bool
isLineClump :: Reference -> Bool
data HeaderType
Constructors
SingleHeader CharSingle line of characters underneath
DoubleHeader CharLines of characters above and below
show/hide Instances
data ParserContext
Constructors
ListItemStateUsed when running parser on list item contents
NullStateDefault state
show/hide Instances
data QuoteContext
Constructors
InSingleQuoteUsed when parsing inside single quotes
InDoubleQuoteUsed when parsing inside double quotes
NoQuoteUsed when not parsing inside quotes
show/hide Instances
type NoteTable = [(String, [Block])]
type KeyTable = [([Inline], Target)]
lookupKeySrc
:: KeyTableKey table
-> [Inline]Key
-> Maybe Target
Look up key in key table and return target object.
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
Blk Block
Sec [Inline] [Element]
show/hide 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 :: BoolInclude header and footer
writerHeader :: StringHeader for the document
writerTitlePrefix :: StringPrefix for HTML titles
writerTabStop :: IntTabstop for conversion btw spaces and tabs
writerTableOfContents :: BoolInclude table of contents
writerS5 :: BoolWe're writing S5
writerUseASCIIMathML :: BoolUse ASCIIMathML
writerASCIIMathMLURL :: (Maybe String)URL to asciiMathML.js
writerIgnoreNotes :: BoolIgnore footnotes (used in making toc)
writerIncremental :: BoolIncremental S5 lists
writerNumberSections :: BoolNumber sections in LaTeX
writerIncludeBefore :: StringString to include before the body
writerIncludeAfter :: StringString to include after the body
writerStrictMarkdown :: BoolUse strict markdown syntax
writerReferenceLinks :: BoolUse reference links in writing markdown, rst
show/hide Instances
Produced by Haddock version 0.8