pandoc-1.0: Conversion between markup formats

Portabilityportable
Stabilityalpha
MaintainerJohn MacFarlane <jgm@berkeley.edu>

Text.Pandoc

Contents

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
 import qualified System.IO.UTF8 as U

 markdownToRST :: String -> String
 markdownToRST =
   (writeRST defaultWriterOptions {writerReferenceLinks = True}) .
   readMarkdown defaultParserState
 
 main = U.getContents >>= U.putStrLn . markdownToRST

Synopsis

Definitions

Readers: converting to Pandoc format

readMarkdown :: ParserState -> String -> PandocSource

Read markdown from an input string and return a Pandoc document.

readRST :: ParserState -> String -> PandocSource

Parse reStructuredText string and return Pandoc document.

readLaTeXSource

Arguments

:: ParserState

Parser state, including options for parser

-> String

String to parse

-> Pandoc 

Parse LaTeX from string and return Pandoc document.

readHtmlSource

Arguments

:: ParserState

Parser state

-> String

String to parse

-> Pandoc 

Convert HTML-formatted string to Pandoc document.

Parser state used in readers

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 :: [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

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

data HeaderType Source

Constructors

SingleHeader Char

Single line of characters underneath

DoubleHeader Char

Lines of characters above and below

Writers: converting from Pandoc format

writeMarkdown :: WriterOptions -> Pandoc -> StringSource

Convert Pandoc to Markdown.

writeRST :: WriterOptions -> Pandoc -> StringSource

Convert Pandoc to RST.

writeLaTeX :: WriterOptions -> Pandoc -> StringSource

Convert Pandoc to LaTeX.

writeConTeXt :: WriterOptions -> Pandoc -> StringSource

Convert Pandoc to ConTeXt.

writeTexinfo :: WriterOptions -> Pandoc -> StringSource

Convert Pandoc to Texinfo.

writeHtml :: WriterOptions -> Pandoc -> HtmlSource

Convert Pandoc document to Html structure.

writeHtmlString :: WriterOptions -> Pandoc -> StringSource

Convert Pandoc document to Html string.

writeS5 :: WriterOptions -> Pandoc -> HtmlSource

Converts Pandoc document to an S5 HTML presentation (Html structure).

writeS5String :: WriterOptions -> Pandoc -> StringSource

Converts Pandoc document to an S5 HTML presentation (string).

writeDocbook :: WriterOptions -> Pandoc -> StringSource

Convert Pandoc document to string in Docbook format.

writeOpenDocument :: WriterOptions -> Pandoc -> StringSource

Convert Pandoc document to string in OpenDocument format.

writeMan :: WriterOptions -> Pandoc -> StringSource

Convert Pandoc to Man.

writeMediaWiki :: WriterOptions -> Pandoc -> StringSource

Convert Pandoc to MediaWiki.

writeRTF :: WriterOptions -> Pandoc -> StringSource

Convert Pandoc to a string in rich text format.

prettyPandoc :: Pandoc -> StringSource

Prettyprint Pandoc document.

Writer options used in writers

data WriterOptions Source

Options for writers

Constructors

WriterOptions 

Fields

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

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

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

writerWrapText :: Bool

Wrap text to line length

Instances

defaultWriterOptions :: WriterOptionsSource

Default writer options.

Default headers for various output formats

Version

pandocVersion :: StringSource

Version number of pandoc library.