Portability | portable |
---|---|
Stability | alpha |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Utility functions and definitions used by the various Pandoc modules.
- splitBy :: Eq a => a -> [a] -> [[a]]
- splitByIndices :: [Int] -> [a] -> [[a]]
- substitute :: Eq a => [a] -> [a] -> [a] -> [a]
- 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
- wrapped :: Monad m => ([Inline] -> m Doc) -> [Inline] -> m Doc
- wrapIfNeeded :: Monad m => WriterOptions -> ([Inline] -> m Doc) -> [Inline] -> m Doc
- wrappedTeX :: Monad m => Bool -> ([Inline] -> m Doc) -> [Inline] -> m Doc
- wrapTeXIfNeeded :: Monad m => WriterOptions -> Bool -> ([Inline] -> m Doc) -> [Inline] -> m Doc
- data BlockWrapper
- wrappedBlocksToDoc :: [BlockWrapper] -> Doc
- (>>~) :: 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
- emailAddress :: GenParser Char st [Char]
- uri :: GenParser Char st String
- 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
- stateSanitizeHTML :: Bool
- 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 HeaderType
- data ParserContext
- data QuoteContext
- 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
- hierarchicalize :: [Block] -> [Element]
- isHeaderBlock :: Block -> Bool
- data HTMLMathMethod
- data WriterOptions = WriterOptions {
- writerStandalone :: Bool
- writerHeader :: String
- writerTitlePrefix :: String
- writerTabStop :: Int
- writerTableOfContents :: Bool
- writerS5 :: Bool
- writerHTMLMathMethod :: HTMLMathMethod
- writerIgnoreNotes :: Bool
- writerIncremental :: Bool
- writerNumberSections :: Bool
- writerIncludeBefore :: String
- writerIncludeAfter :: String
- writerStrictMarkdown :: Bool
- writerReferenceLinks :: Bool
- writerWrapText :: Bool
- defaultWriterOptions :: WriterOptions
- inDirectory :: FilePath -> IO a -> IO a
List processing
splitByIndices :: [Int] -> [a] -> [[a]]Source
Split list into chunks divided at specified indices.
substitute :: Eq a => [a] -> [a] -> [a] -> [a]Source
Replace each occurrence of one sublist in a list with another.
Text processing
Returns an association list of backslash escapes for the designated characters.
escapeStringUsing :: [(Char, String)] -> String -> StringSource
Escape a string of characters, using an association list of characters and strings.
stripTrailingNewlines :: String -> StringSource
Strip trailing newlines from string.
removeLeadingTrailingSpace :: String -> StringSource
Remove leading and trailing space (including newlines) from string.
removeLeadingSpace :: String -> StringSource
Remove leading space (including newlines) from string.
removeTrailingSpace :: String -> StringSource
Remove trailing space (including newlines) from string.
stripFirstAndLast :: String -> StringSource
Strip leading and trailing characters from string
camelCaseToHyphenated :: String -> StringSource
Change CamelCase word to hyphenated lowercase (e.g., camel-case).
toRomanNumeral :: Int -> StringSource
Convert number < 4000 to uppercase roman numeral.
wrapIfNeeded :: Monad m => WriterOptions -> ([Inline] -> m Doc) -> [Inline] -> m DocSource
Wrap inlines if the text wrap option is selected.
wrappedTeX :: Monad m => Bool -> ([Inline] -> m Doc) -> [Inline] -> m DocSource
Wrap inlines to line length, treating footnotes in a way that makes sense in LaTeX and ConTeXt.
wrapTeXIfNeeded :: Monad m => WriterOptions -> Bool -> ([Inline] -> m Doc) -> [Inline] -> m DocSource
Wrap inlines if the text wrap option is selected, specialized for LaTeX and ConTeXt.
data BlockWrapper Source
Indicates whether block should be surrounded by blank lines (Pad
) or not (Reg
).
wrappedBlocksToDoc :: [BlockWrapper] -> DocSource
Converts a list of wrapped blocks to a Doc, with appropriate spaces around blocks.
Parsing
(>>~) :: Monad m => m a -> m b -> m aSource
Like >>, but returns the operation on the left. (Suggested by Tillmann Rendel on Haskell-cafe list.)
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.
blanklines :: GenParser Char st [Char]Source
Parses one or more blank lines and returns a string of newlines.
:: 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.
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.
Parses a roman numeral (uppercase or lowercase), returns number.
emailAddress :: GenParser Char st [Char]Source
Parses an email address; returns string.
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.
Parses backslash, then applies character parser.
anyOrderedListMarker :: GenParser Char st ListAttributesSource
Parses an ordered list marker and returns list attributes.
orderedListMarker :: ListNumberStyle -> ListNumberDelim -> GenParser Char st IntSource
Parses an ordered list marker with a given style and delimiter, returns number.
:: 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.
ParserState | |
|
data HeaderType Source
SingleHeader Char | Single line of characters underneath |
DoubleHeader Char | Lines of characters above and below |
data ParserContext Source
ListItemState | Used when running parser on list item contents |
NullState | Default state |
data QuoteContext Source
InSingleQuote | Used when parsing inside single quotes |
InDoubleQuote | Used when parsing inside double quotes |
NoQuote | Used when not parsing inside quotes |
Look up key in key table and return target object.
Native format prettyprinting
prettyPandoc :: Pandoc -> StringSource
Prettyprint Pandoc document.
Pandoc block and inline list processing
orderedListMarkers :: (Int, ListNumberStyle, ListNumberDelim) -> [String]Source
Generate infinite lazy list of markers for an ordered list, depending on list attributes.
normalizeSpaces :: [Inline] -> [Inline]Source
Normalize a list of inline elements: remove leading and trailing
Space
elements, collapse double Space
s into singles, and
remove empty Str elements.
Change final list item from Para
to Plain
if the list should
be compact.
Data structure for defining hierarchical Pandoc documents
hierarchicalize :: [Block] -> [Element]Source
Convert list of Pandoc blocks into (hierarchical) list of Elements
isHeaderBlock :: Block -> BoolSource
True if block is a Header block.
Writer options
data HTMLMathMethod Source
data WriterOptions Source
Options for writers
WriterOptions | |
|
defaultWriterOptions :: WriterOptionsSource
Default writer options.
File handling
inDirectory :: FilePath -> IO a -> IO aSource
Perform an IO action in a directory, returning to starting directory.