pandoc-1.19.1: Conversion between markup formats

CopyrightCopyright (C) 2006-2016 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} .
  handleError . 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

Error handling

Lists of readers and writers

readers :: [(String, Reader)] Source #

Association list of formats and readers.

writers :: [(String, Writer)] Source #

Association list of formats and writers.

Readers: converting to Pandoc format

readMarkdown Source #

Arguments

:: ReaderOptions

Reader options

-> String

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

-> Either PandocError Pandoc 

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

readCommonMark :: ReaderOptions -> String -> Either PandocError Pandoc Source #

Parse a CommonMark formatted string into a Pandoc structure.

readMediaWiki Source #

Arguments

:: ReaderOptions

Reader options

-> String

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

-> Either PandocError Pandoc 

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

readRST Source #

Arguments

:: ReaderOptions

Reader options

-> String

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

-> Either PandocError Pandoc 

Parse reStructuredText string and return Pandoc document.

readOrg Source #

Arguments

:: ReaderOptions

Reader options

-> String

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

-> Either PandocError Pandoc 

Parse org-mode string and return a Pandoc document.

readLaTeX Source #

Arguments

:: ReaderOptions

Reader options

-> String

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

-> Either PandocError Pandoc 

Parse LaTeX from string and return Pandoc document.

readHtml Source #

Arguments

:: ReaderOptions

Reader options

-> String

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

-> Either PandocError Pandoc 

Convert HTML-formatted string to Pandoc document.

readTextile Source #

Arguments

:: ReaderOptions

Reader options

-> String

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

-> Either PandocError Pandoc 

Parse a Textile text and return a Pandoc document.

readHaddock Source #

Arguments

:: ReaderOptions

Reader options

-> String

String to parse

-> Either PandocError Pandoc 

Parse Haddock markup and return a Pandoc document.

readNative Source #

Arguments

:: String

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

-> Either PandocError 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"]]

readTWiki Source #

Arguments

:: ReaderOptions

Reader options

-> String

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

-> Either PandocError Pandoc 

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

readTxt2Tags :: T2TMeta -> ReaderOptions -> String -> Either PandocError Pandoc Source #

Read Txt2Tags from an input string returning a Pandoc document

readTxt2TagsNoMacros :: ReaderOptions -> String -> Either PandocError Pandoc Source #

Read Txt2Tags (ignoring all macros) from an input string returning a Pandoc document

Writers: converting from Pandoc format

writeNative :: WriterOptions -> Pandoc -> String Source #

Prettyprint Pandoc document.

writeMarkdown :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc to Markdown.

writePlain :: WriterOptions -> Pandoc -> String Source #

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

writeRST :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc to RST.

writeLaTeX :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc to LaTeX.

writeConTeXt :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc to ConTeXt.

writeTexinfo :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc to Texinfo.

writeHtml :: WriterOptions -> Pandoc -> Html Source #

Convert Pandoc document to Html structure.

writeHtmlString :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc document to Html string.

writeICML :: WriterOptions -> Pandoc -> IO String Source #

Convert Pandoc document to string in ICML format.

writeDocbook :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc document to string in Docbook format.

writeOPML :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc document to string in OPML format.

writeOpenDocument :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc document to string in OpenDocument format.

writeMan :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc to Man.

writeMediaWiki :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc to MediaWiki.

writeDokuWiki :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc to DokuWiki.

writeZimWiki :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc to ZimWiki.

writeTextile :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc to Textile.

writeRTF :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc to a string in rich text format.

writeODT Source #

Arguments

:: WriterOptions

Writer options

-> Pandoc

Document to convert

-> IO ByteString 

Produce an ODT file from a Pandoc document.

writeDocx Source #

Arguments

:: WriterOptions

Writer options

-> Pandoc

Document to convert

-> IO ByteString 

Produce an Docx file from a Pandoc document.

writeEPUB Source #

Arguments

:: WriterOptions

Writer options

-> Pandoc

Document to convert

-> IO ByteString 

Produce an EPUB file from a Pandoc document.

writeFB2 Source #

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

Convert Pandoc to Org.

writeAsciiDoc :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc to AsciiDoc.

writeHaddock :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc to Haddock.

writeCommonMark :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc to CommonMark.

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

Convert Pandoc to custom markup.

writeTEI :: WriterOptions -> Pandoc -> String Source #

Convert Pandoc document to string in Docbook format.

Rendering templates and default templates

Miscellaneous

getReader :: String -> Either String Reader Source #

Retrieve reader based on formatSpec (format+extensions).

getWriter :: String -> Either String Writer Source #

Retrieve writer based on formatSpec (format+extensions).

class ToJSONFilter a => ToJsonFilter a where Source #

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

Methods

toJsonFilter :: a -> IO () Source #

Deprecated: Use toJSONFilter from JSON instead

pandocVersion :: String Source #

Version number of pandoc library.