Portability | portable |
---|---|
Stability | alpha |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Safe Haskell | None |
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 -- include the following two lines only if you're using ghc < 6.12: import Prelude hiding (getContents, putStrLn) import System.IO.UTF8 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.Definition
- module Text.Pandoc.Generic
- 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
- readLaTeX :: ReaderOptions -> String -> Pandoc
- readHtml :: ReaderOptions -> String -> Pandoc
- readTextile :: ReaderOptions -> String -> Pandoc
- readDocBook :: ReaderOptions -> String -> Pandoc
- readNative :: String -> Pandoc
- data Writer
- = PureStringWriter (WriterOptions -> Pandoc -> String)
- | IOStringWriter (WriterOptions -> Pandoc -> IO String)
- | IOByteStringWriter (WriterOptions -> Pandoc -> IO ByteString)
- writeNative :: 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
- writeDocbook :: 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
- module Text.Pandoc.Templates
- pandocVersion :: String
- getReader :: String -> Either String (ReaderOptions -> String -> IO Pandoc)
- getWriter :: String -> Either String Writer
- jsonFilter :: (Pandoc -> Pandoc) -> String -> String
- class ToJsonFilter a where
- toJsonFilter :: a -> IO ()
Definitions
module Text.Pandoc.Definition
Generics
module Text.Pandoc.Generic
Options
module Text.Pandoc.Options
Lists of readers and writers
readers :: [(String, ReaderOptions -> String -> IO Pandoc)]Source
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 (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 -> PandocSource
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 (Meta [] [] []) [Plain [Str "hi"]]
Writers: converting from Pandoc format
PureStringWriter (WriterOptions -> Pandoc -> String) | |
IOStringWriter (WriterOptions -> Pandoc -> IO String) | |
IOByteStringWriter (WriterOptions -> Pandoc -> IO ByteString) |
writeNative :: WriterOptions -> Pandoc -> StringSource
Prettyprint Pandoc document.
writeMarkdown :: WriterOptions -> Pandoc -> StringSource
Convert Pandoc to Markdown.
writePlain :: WriterOptions -> Pandoc -> StringSource
Convert Pandoc to plain text (like markdown, but without links, pictures, or inline formatting).
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.
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.
writeTextile :: WriterOptions -> Pandoc -> StringSource
Convert Pandoc to Textile.
writeRTF :: WriterOptions -> Pandoc -> StringSource
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 -> StringSource
Convert Pandoc to Org.
writeAsciiDoc :: WriterOptions -> Pandoc -> StringSource
Convert Pandoc to AsciiDoc.
Rendering templates and default templates
module Text.Pandoc.Templates
Version
Version number of pandoc library.
Miscellaneous
getReader :: String -> Either String (ReaderOptions -> String -> IO Pandoc)Source
Retrieve reader based on formatSpec (format+extensions).
getWriter :: String -> Either String WriterSource
Retrieve writer based on formatSpec (format+extensions).
jsonFilter :: (Pandoc -> Pandoc) -> String -> StringSource
Deprecated: Use toJsonFilter instead
Converts a transformation on the Pandoc AST into a function that reads and writes a JSON-encoded string. This is useful for writing small scripts.
class ToJsonFilter a whereSource
toJsonFilter
convert a function into a filter that reads pandoc's json output
from stdin, transforms it by walking the AST and applying the specified
function, and writes the result as json to stdout. Usage example:
-- capitalize.hs -- compile with: ghc --make capitalize -- run with: pandoc -t json | ./capitalize | pandoc -f json import Text.Pandoc import Data.Char (toUpper) main :: IO () main = toJsonFilter capitalizeStrings capitalizeStrings :: Inline -> Inline capitalizeStrings (Str s) = Str $ map toUpper s capitalizeStrings x = x
The function can be any type (a -> a)
, (a -> IO a)
, (a -> [a])
,
or (a -> IO [a])
, where a
is an instance of Data
.
So, for example, a
can be Pandoc
, Inline
, Block
, [Inline
],
[Block
], Meta
, ListNumberStyle
, Alignment
, ListNumberDelim
,
QuoteType
, etc. See Definition
.
toJsonFilter :: a -> IO ()Source
Data a => ToJsonFilter (a -> IO [a]) | |
Data a => ToJsonFilter (a -> [a]) | |
Data a => ToJsonFilter (a -> IO a) | |
Data a => ToJsonFilter (a -> a) |