Copyright | Copyright (C) 2006-2014 John MacFarlane |
---|---|
License | GNU GPL, version 2 or above |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Stability | alpha |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
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')
.
- module Text.Pandoc.Options
- readers :: [(String, ReaderOptions -> String -> IO Pandoc)]
- writers :: [(String, Writer)]
- readMarkdown :: ReaderOptions -> String -> Pandoc
- readMediaWiki :: ReaderOptions -> String -> Pandoc
- readRST :: ReaderOptions -> String -> Pandoc
- readOrg :: ReaderOptions -> String -> Pandoc
- readLaTeX :: ReaderOptions -> String -> Pandoc
- readHtml :: ReaderOptions -> String -> Pandoc
- readTextile :: ReaderOptions -> String -> Pandoc
- readDocBook :: ReaderOptions -> String -> Pandoc
- readOPML :: ReaderOptions -> String -> Pandoc
- readHaddock :: ReaderOptions -> String -> Pandoc
- readNative :: String -> Pandoc
- readJSON :: ReaderOptions -> String -> Pandoc
- data Writer
- = PureStringWriter (WriterOptions -> Pandoc -> String)
- | IOStringWriter (WriterOptions -> Pandoc -> IO String)
- | IOByteStringWriter (WriterOptions -> Pandoc -> IO ByteString)
- writeNative :: WriterOptions -> Pandoc -> String
- writeJSON :: WriterOptions -> Pandoc -> String
- writeMarkdown :: WriterOptions -> Pandoc -> String
- writePlain :: WriterOptions -> Pandoc -> String
- writeRST :: WriterOptions -> Pandoc -> String
- writeLaTeX :: WriterOptions -> Pandoc -> String
- writeConTeXt :: WriterOptions -> Pandoc -> String
- writeTexinfo :: WriterOptions -> Pandoc -> String
- writeHtml :: WriterOptions -> Pandoc -> Html
- writeHtmlString :: WriterOptions -> Pandoc -> String
- writeICML :: WriterOptions -> Pandoc -> String
- writeDocbook :: WriterOptions -> Pandoc -> String
- writeOPML :: WriterOptions -> Pandoc -> String
- writeOpenDocument :: WriterOptions -> Pandoc -> String
- writeMan :: WriterOptions -> Pandoc -> String
- writeMediaWiki :: WriterOptions -> Pandoc -> String
- writeTextile :: WriterOptions -> Pandoc -> String
- writeRTF :: WriterOptions -> Pandoc -> String
- writeODT :: WriterOptions -> Pandoc -> IO ByteString
- writeDocx :: WriterOptions -> Pandoc -> IO ByteString
- writeEPUB :: WriterOptions -> Pandoc -> IO ByteString
- writeFB2 :: WriterOptions -> Pandoc -> IO String
- writeOrg :: WriterOptions -> Pandoc -> String
- writeAsciiDoc :: WriterOptions -> Pandoc -> String
- writeCustom :: FilePath -> WriterOptions -> Pandoc -> IO String
- module Text.Pandoc.Templates
- pandocVersion :: String
- getReader :: String -> Either String (ReaderOptions -> String -> IO Pandoc)
- getWriter :: String -> Either String Writer
- class ToJSONFilter a => ToJsonFilter a where
- toJsonFilter :: a -> IO ()
Definitions
Generics
Options
module Text.Pandoc.Options
Lists of readers and writers
readers :: [(String, ReaderOptions -> String -> IO Pandoc)]
Association list of formats and readers.
Readers: converting to Pandoc format
:: ReaderOptions | Reader options |
-> String | String to parse (assuming |
-> Pandoc |
Read markdown from an input string and return a Pandoc document.
:: ReaderOptions | Reader options |
-> String | String to parse (assuming |
-> Pandoc |
Read mediawiki from an input string and return a Pandoc document.
:: ReaderOptions | Reader options |
-> String | String to parse (assuming |
-> Pandoc |
Parse reStructuredText string and return Pandoc document.
:: ReaderOptions | Reader options |
-> String | String to parse (assuming |
-> Pandoc |
Parse org-mode string and return a Pandoc document.
:: ReaderOptions | Reader options |
-> String | String to parse (assumes |
-> Pandoc |
Parse LaTeX from string and return Pandoc
document.
:: ReaderOptions | Reader options |
-> String | String to parse (assumes |
-> Pandoc |
Convert HTML-formatted string to Pandoc
document.
:: ReaderOptions | Reader options |
-> String | String to parse (assuming |
-> Pandoc |
Parse a Textile text and return a Pandoc document.
readDocBook :: ReaderOptions -> String -> Pandoc
readOPML :: ReaderOptions -> String -> Pandoc
:: ReaderOptions | Reader options |
-> String | String to parse |
-> Pandoc |
Parse Haddock markup and return a Pandoc
document.
:: String | String to parse (assuming |
-> 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
data Writer
PureStringWriter (WriterOptions -> Pandoc -> String) | |
IOStringWriter (WriterOptions -> Pandoc -> IO String) | |
IOByteStringWriter (WriterOptions -> Pandoc -> IO ByteString) |
writeNative :: WriterOptions -> Pandoc -> String
Prettyprint Pandoc document.
writeJSON :: WriterOptions -> Pandoc -> String
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.
:: WriterOptions | Writer options |
-> Pandoc | Document to convert |
-> IO ByteString |
Produce an ODT file from a Pandoc document.
:: WriterOptions | Writer options |
-> Pandoc | Document to convert |
-> IO ByteString |
Produce an Docx file from a Pandoc document.
:: WriterOptions | Writer options |
-> Pandoc | Document to convert |
-> IO ByteString |
Produce an EPUB file from a Pandoc document.
:: 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
module Text.Pandoc.Templates
Version
Version number of pandoc library.
Miscellaneous
getReader :: String -> Either String (ReaderOptions -> String -> IO Pandoc)
Retrieve reader based on formatSpec (format+extensions).
class ToJSONFilter a => ToJsonFilter a where
Deprecated. Use toJSONFilter
from Text.Pandoc.JSON
instead.
Nothing
toJsonFilter :: a -> IO ()
Deprecated: Use toJSONFilter
from JSON
instead