pandoc-1.12.4.1: Conversion between markup formats

CopyrightCopyright (C) 2006-2014 John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellNone
LanguageHaskell98

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

markdownToRST :: String -> String
markdownToRST =
  (writeRST def {writerReferenceLinks = True}) . readMarkdown def

main = getContents >>= putStrLn . markdownToRST

Note: all of the readers assume that the input text has '\n' line endings. So if you get your input text from a web form, you should remove '\r' characters using filter (/='\r').

Synopsis

Definitions

Generics

Options

Lists of readers and writers

readers :: [(String, ReaderOptions -> String -> IO Pandoc)]

Association list of formats and readers.

writers :: [(String, Writer)]

Association list of formats and writers.

Readers: converting to Pandoc format

readMarkdown

Arguments

:: ReaderOptions

Reader options

-> String

String to parse (assuming '\n' line endings)

-> Pandoc 

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

readMediaWiki

Arguments

:: ReaderOptions

Reader options

-> String

String to parse (assuming '\n' line endings)

-> Pandoc 

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

readRST

Arguments

:: ReaderOptions

Reader options

-> String

String to parse (assuming '\n' line endings)

-> Pandoc 

Parse reStructuredText string and return Pandoc document.

readOrg

Arguments

:: ReaderOptions

Reader options

-> String

String to parse (assuming '\n' line endings)

-> Pandoc 

Parse org-mode string and return a Pandoc document.

readLaTeX

Arguments

:: ReaderOptions

Reader options

-> String

String to parse (assumes '\n' line endings)

-> Pandoc 

Parse LaTeX from string and return Pandoc document.

readHtml

Arguments

:: ReaderOptions

Reader options

-> String

String to parse (assumes '\n' line endings)

-> Pandoc 

Convert HTML-formatted string to Pandoc document.

readTextile

Arguments

:: ReaderOptions

Reader options

-> String

String to parse (assuming '\n' line endings)

-> Pandoc 

Parse a Textile text and return a Pandoc document.

readOPML :: ReaderOptions -> String -> Pandoc

readHaddock

Arguments

:: ReaderOptions

Reader options

-> String

String to parse

-> Pandoc 

Parse Haddock markup and return a Pandoc document.

readNative

Arguments

:: String

String to parse (assuming '\n' line endings)

-> Pandoc 

Read native formatted text and return a Pandoc document. The input may be a full pandoc document, a block list, a block, an inline list, or an inline. Thus, for example,

Str "hi"

will be treated as if it were

Pandoc nullMeta [Plain [Str "hi"]]

readJSON :: ReaderOptions -> String -> Pandoc

Writers: converting from Pandoc format

writeNative :: WriterOptions -> Pandoc -> String

Prettyprint Pandoc document.

writeMarkdown :: WriterOptions -> Pandoc -> String

Convert Pandoc to Markdown.

writePlain :: WriterOptions -> Pandoc -> String

Convert Pandoc to plain text (like markdown, but without links, pictures, or inline formatting).

writeRST :: WriterOptions -> Pandoc -> String

Convert Pandoc to RST.

writeLaTeX :: WriterOptions -> Pandoc -> String

Convert Pandoc to LaTeX.

writeConTeXt :: WriterOptions -> Pandoc -> String

Convert Pandoc to ConTeXt.

writeTexinfo :: WriterOptions -> Pandoc -> String

Convert Pandoc to Texinfo.

writeHtml :: WriterOptions -> Pandoc -> Html

Convert Pandoc document to Html structure.

writeHtmlString :: WriterOptions -> Pandoc -> String

Convert Pandoc document to Html string.

writeICML :: WriterOptions -> Pandoc -> String

Convert Pandoc document to string in ICML format.

writeDocbook :: WriterOptions -> Pandoc -> String

Convert Pandoc document to string in Docbook format.

writeOPML :: WriterOptions -> Pandoc -> String

Convert Pandoc document to string in OPML format.

writeOpenDocument :: WriterOptions -> Pandoc -> String

Convert Pandoc document to string in OpenDocument format.

writeMan :: WriterOptions -> Pandoc -> String

Convert Pandoc to Man.

writeMediaWiki :: WriterOptions -> Pandoc -> String

Convert Pandoc to MediaWiki.

writeTextile :: WriterOptions -> Pandoc -> String

Convert Pandoc to Textile.

writeRTF :: WriterOptions -> Pandoc -> String

Convert Pandoc to a string in rich text format.

writeODT

Arguments

:: WriterOptions

Writer options

-> Pandoc

Document to convert

-> IO ByteString 

Produce an ODT file from a Pandoc document.

writeDocx

Arguments

:: WriterOptions

Writer options

-> Pandoc

Document to convert

-> IO ByteString 

Produce an Docx file from a Pandoc document.

writeEPUB

Arguments

:: WriterOptions

Writer options

-> Pandoc

Document to convert

-> IO ByteString 

Produce an EPUB file from a Pandoc document.

writeFB2

Arguments

:: WriterOptions

conversion options

-> Pandoc

document to convert

-> IO String

FictionBook2 document (not encoded yet)

Produce an FB2 document from a Pandoc document.

writeOrg :: WriterOptions -> Pandoc -> String

Convert Pandoc to Org.

writeAsciiDoc :: WriterOptions -> Pandoc -> String

Convert Pandoc to AsciiDoc.

writeCustom :: FilePath -> WriterOptions -> Pandoc -> IO String

Convert Pandoc to custom markup.

Rendering templates and default templates

Version

pandocVersion :: String

Version number of pandoc library.

Miscellaneous

getReader :: String -> Either String (ReaderOptions -> String -> IO Pandoc)

Retrieve reader based on formatSpec (format+extensions).

getWriter :: String -> Either String Writer

Retrieve writer based on formatSpec (format+extensions).

class ToJSONFilter a => ToJsonFilter a where

Deprecated. Use toJSONFilter from Text.Pandoc.JSON instead.

Minimal complete definition

Nothing

Methods

toJsonFilter :: a -> IO ()

Deprecated: Use toJSONFilter from JSON instead