open-pandoc-1.4: Conversion between markup formats

Portabilityportable
Stabilityalpha
MaintainerJohn MacFarlane <jgm@berkeley.edu>

Text.Pandoc.Shared

Contents

Description

Utility functions and definitions used by the various Pandoc modules.

Synopsis

List processing

splitBy :: Eq a => a -> [a] -> [[a]]Source

Split list by groups of one or more sep.

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

backslashEscapesSource

Arguments

:: [Char]

list of special characters to escape

-> [(Char, String)] 

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.

wrapped :: Monad m => ([Inline] -> m Doc) -> [Inline] -> m DocSource

Wrap inlines to line length.

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).

Constructors

Pad Doc 
Reg Doc 

wrappedBlocksToDoc :: [BlockWrapper] -> DocSource

Converts a list of wrapped blocks to a Doc, with appropriate spaces around blocks.

tabFilterSource

Arguments

:: Int

Tab stop

-> String

Input

-> String 

Convert tabs to spaces and filter out DOS line endings. Tabs will be preserved if tab stop is set to 0.

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.)

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 [Char]Source

Parses an email address; returns string.

uri :: GenParser Char st StringSource

Parses a URI.

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 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.

charRef :: GenParser Char st InlineSource

Parses a character reference and returns a Str element.

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

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

lookupKeySrcSource

Arguments

:: KeyTable

Key table

-> [Inline]

Key

-> Maybe Target 

Look up key in key table and return target object.

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

Returns True if keys match (case insensitive).

Prettyprinting

hang' :: Doc -> Int -> Doc -> DocSource

A version of hang that works like the version in pretty-1.0.0.0

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 Spaces into singles, and remove empty Str elements.

compactifySource

Arguments

:: [[Block]]

List of list items (each a list of blocks)

-> [[Block]] 

Change final list item from Para to Plain if the list contains no other Para blocks.

data Element Source

Data structure for defining hierarchical Pandoc documents

Constructors

Blk Block 
Sec Int [Int] String [Inline] [Element] 

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

Options for writers

Constructors

WriterOptions 

Fields

writerStandalone :: Bool

Include header and footer

writerTemplate :: String

Template to use in standalone mode

writerVariables :: [(String, String)]

Variables to set in template

writerIncludeBefore :: String

Text to include before the body

writerIncludeAfter :: String

Text to include after the body

writerTabStop :: Int

Tabstop for conversion btw spaces and tabs

writerTableOfContents :: Bool

Include table of contents

writerS5 :: Bool

We're writing S5

writerXeTeX :: Bool

Create latex suitable for use by xetex

writerHTMLMathMethod :: HTMLMathMethod

How to print math in HTML

writerIgnoreNotes :: Bool

Ignore footnotes (used in making toc)

writerIncremental :: Bool

Incremental S5 lists

writerNumberSections :: Bool

Number sections in LaTeX

writerStrictMarkdown :: Bool

Use strict markdown syntax

writerReferenceLinks :: Bool

Use reference links in writing markdown, rst

writerWrapText :: Bool

Wrap text to line length

writerLiterateHaskell :: Bool

Write as literate haskell

writerEmailObfuscation :: ObfuscationMethod

How to obfuscate emails

writerIdentifierPrefix :: String

Prefix for section & note ids in HTML

Instances

defaultWriterOptions :: WriterOptionsSource

Default writer options.

File handling

inDirectory :: FilePath -> IO a -> IO aSource

Perform an IO action in a directory, returning to starting directory.

readDataFile :: FilePath -> IO StringSource

Read file from user data directory or, if not found there, from Cabal data directory. On unix the user data directory is $HOME/.pandoc.