pandoc-0.44: Conversion between markup formatsContentsIndex
Text.Pandoc
Portabilityportable
Stabilityalpha
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Contents
Definitions
Readers: converting to Pandoc format
Parser state used in readers
Writers: converting from Pandoc format
Writer options used in writers
Default headers for various output formats
Functions for converting to and from UTF-8
Description

This helper module exports the main writers, readers, and data structure definitions from the Pandoc libraries.

A typical application will chain together a reader and a writer to convert strings from one format to another. For example, the following simple program will act as a filter converting markdown fragments to reStructuredText, using reference-style links instead of inline links:

 module Main where
 import Text.Pandoc
 
 markdownToRST :: String -> String
 markdownToRST = toUTF8 .
   (writeRST defaultWriterOptions {writerReferenceLinks = True}) .
   (readMarkdown defaultParserState) .  fromUTF8
 
 main = interact markdownToRST
Synopsis
module Text.Pandoc.Definition
readMarkdown :: ParserState -> String -> Pandoc
readRST :: ParserState -> String -> Pandoc
readLaTeX :: ParserState -> String -> Pandoc
readHtml :: ParserState -> String -> Pandoc
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 ParserContext
= ListItemState
| NullState
data QuoteContext
= InSingleQuote
| InDoubleQuote
| NoQuote
type KeyTable = [([Inline], Target)]
type NoteTable = [(String, [Block])]
data HeaderType
= SingleHeader Char
| DoubleHeader Char
writeMarkdown :: WriterOptions -> Pandoc -> String
writeRST :: WriterOptions -> Pandoc -> String
writeLaTeX :: WriterOptions -> Pandoc -> String
writeConTeXt :: WriterOptions -> Pandoc -> String
writeHtml :: WriterOptions -> Pandoc -> Html
writeHtmlString :: WriterOptions -> Pandoc -> String
writeS5 :: WriterOptions -> Pandoc -> Html
writeS5String :: WriterOptions -> Pandoc -> String
writeDocbook :: WriterOptions -> Pandoc -> String
writeMan :: WriterOptions -> Pandoc -> String
writeRTF :: WriterOptions -> Pandoc -> String
prettyPandoc :: Pandoc -> String
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
}
defaultWriterOptions :: WriterOptions
module Text.Pandoc.Writers.DefaultHeaders
module Text.Pandoc.UTF8
Definitions
module Text.Pandoc.Definition
Readers: converting to Pandoc format
readMarkdown :: ParserState -> String -> Pandoc
Read markdown from an input string and return a Pandoc document.
readRST :: ParserState -> String -> Pandoc
Parse reStructuredText string and return Pandoc document.
readLaTeX
:: ParserStateParser state, including options for parser
-> StringString to parse
-> Pandoc
Parse LaTeX from string and return Pandoc document.
readHtml
:: ParserStateParser state
-> StringString to parse
-> Pandoc
Convert HTML-formatted string to Pandoc document.
Parser state used in readers
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 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 KeyTable = [([Inline], Target)]
type NoteTable = [(String, [Block])]
data HeaderType
Constructors
SingleHeader CharSingle line of characters underneath
DoubleHeader CharLines of characters above and below
show/hide Instances
Writers: converting from Pandoc format
writeMarkdown :: WriterOptions -> Pandoc -> String
Convert Pandoc to Markdown.
writeRST :: WriterOptions -> Pandoc -> String
Convert Pandoc to RST.
writeLaTeX :: WriterOptions -> Pandoc -> String
Convert Pandoc to LaTeX.
writeConTeXt :: WriterOptions -> Pandoc -> String
Convert Pandoc to ConTeXt.
writeHtml :: WriterOptions -> Pandoc -> Html
Convert Pandoc document to Html structure.
writeHtmlString :: WriterOptions -> Pandoc -> String
Convert Pandoc document to Html string.
writeS5 :: WriterOptions -> Pandoc -> Html
Converts Pandoc document to an S5 HTML presentation (Html structure).
writeS5String :: WriterOptions -> Pandoc -> String
Converts Pandoc document to an S5 HTML presentation (string).
writeDocbook :: WriterOptions -> Pandoc -> String
Convert Pandoc document to string in Docbook format.
writeMan :: WriterOptions -> Pandoc -> String
Convert Pandoc to Man.
writeRTF :: WriterOptions -> Pandoc -> String
Convert Pandoc to a string in rich text format.
prettyPandoc :: Pandoc -> String
Prettyprint Pandoc document.
Writer options used in writers
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
defaultWriterOptions :: WriterOptions
Default writer options.
Default headers for various output formats
module Text.Pandoc.Writers.DefaultHeaders
Functions for converting to and from UTF-8
module Text.Pandoc.UTF8
Produced by Haddock version 0.8