Copyright | Copyright (C) 2006-2016 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} . 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')
.
- module Text.Pandoc.Definition
- module Text.Pandoc.Generic
- module Text.Pandoc.Options
- module Text.Pandoc.Error
- readers :: [(String, Reader)]
- writers :: [(String, Writer)]
- data Reader
- = StringReader (ReaderOptions -> String -> IO (Either PandocError Pandoc))
- | ByteStringReader (ReaderOptions -> ByteString -> IO (Either PandocError (Pandoc, MediaBag)))
- mkStringReader :: (ReaderOptions -> String -> Either PandocError Pandoc) -> Reader
- readDocx :: ReaderOptions -> ByteString -> Either PandocError (Pandoc, MediaBag)
- readOdt :: ReaderOptions -> ByteString -> Either PandocError (Pandoc, MediaBag)
- readMarkdown :: ReaderOptions -> String -> Either PandocError Pandoc
- readCommonMark :: ReaderOptions -> String -> Either PandocError Pandoc
- readMediaWiki :: ReaderOptions -> String -> Either PandocError Pandoc
- readRST :: ReaderOptions -> String -> Either PandocError Pandoc
- readOrg :: ReaderOptions -> String -> Either PandocError Pandoc
- readLaTeX :: ReaderOptions -> String -> Either PandocError Pandoc
- readHtml :: ReaderOptions -> String -> Either PandocError Pandoc
- readTextile :: ReaderOptions -> String -> Either PandocError Pandoc
- readDocBook :: ReaderOptions -> String -> Either PandocError Pandoc
- readOPML :: ReaderOptions -> String -> Either PandocError Pandoc
- readHaddock :: ReaderOptions -> String -> Either PandocError Pandoc
- readNative :: String -> Either PandocError Pandoc
- readJSON :: ReaderOptions -> String -> Either PandocError Pandoc
- readTWiki :: ReaderOptions -> String -> Either PandocError Pandoc
- readTxt2Tags :: T2TMeta -> ReaderOptions -> String -> Either PandocError Pandoc
- readTxt2TagsNoMacros :: ReaderOptions -> String -> Either PandocError Pandoc
- readEPUB :: ReaderOptions -> ByteString -> Either PandocError (Pandoc, MediaBag)
- 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 -> IO String
- writeDocbook :: WriterOptions -> Pandoc -> String
- writeOPML :: WriterOptions -> Pandoc -> String
- writeOpenDocument :: WriterOptions -> Pandoc -> String
- writeMan :: WriterOptions -> Pandoc -> String
- writeMediaWiki :: WriterOptions -> Pandoc -> String
- writeDokuWiki :: WriterOptions -> Pandoc -> String
- writeZimWiki :: 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
- writeHaddock :: WriterOptions -> Pandoc -> String
- writeCommonMark :: WriterOptions -> Pandoc -> String
- writeCustom :: FilePath -> WriterOptions -> Pandoc -> IO String
- writeTEI :: WriterOptions -> Pandoc -> String
- module Text.Pandoc.Templates
- getReader :: String -> Either String Reader
- getWriter :: String -> Either String Writer
- getDefaultExtensions :: String -> Set Extension
- class ToJSONFilter a => ToJsonFilter a where
- pandocVersion :: String
Definitions
module Text.Pandoc.Definition
Generics
module Text.Pandoc.Generic
Options
module Text.Pandoc.Options
Error handling
module Text.Pandoc.Error
Lists of readers and writers
Readers: converting to Pandoc format
StringReader (ReaderOptions -> String -> IO (Either PandocError Pandoc)) | |
ByteStringReader (ReaderOptions -> ByteString -> IO (Either PandocError (Pandoc, MediaBag))) |
mkStringReader :: (ReaderOptions -> String -> Either PandocError Pandoc) -> Reader Source #
readDocx :: ReaderOptions -> ByteString -> Either PandocError (Pandoc, MediaBag) Source #
readOdt :: ReaderOptions -> ByteString -> Either PandocError (Pandoc, MediaBag) Source #
:: ReaderOptions | Reader options |
-> String | String to parse (assuming |
-> 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.
:: ReaderOptions | Reader options |
-> String | String to parse (assuming |
-> Either PandocError Pandoc |
Read mediawiki from an input string and return a Pandoc document.
:: ReaderOptions | Reader options |
-> String | String to parse (assuming |
-> Either PandocError Pandoc |
Parse reStructuredText string and return Pandoc document.
:: ReaderOptions | Reader options |
-> String | String to parse (assuming |
-> Either PandocError Pandoc |
Parse org-mode string and return a Pandoc document.
:: ReaderOptions | Reader options |
-> String | String to parse (assumes |
-> Either PandocError Pandoc |
Parse LaTeX from string and return Pandoc
document.
:: ReaderOptions | Reader options |
-> String | String to parse (assumes |
-> Either PandocError Pandoc |
Convert HTML-formatted string to Pandoc
document.
:: ReaderOptions | Reader options |
-> String | String to parse (assuming |
-> Either PandocError Pandoc |
Parse a Textile text and return a Pandoc document.
readDocBook :: ReaderOptions -> String -> Either PandocError Pandoc Source #
readOPML :: ReaderOptions -> String -> Either PandocError Pandoc Source #
:: ReaderOptions | Reader options |
-> String | String to parse |
-> Either PandocError Pandoc |
Parse Haddock markup and return a Pandoc
document.
:: String | String to parse (assuming |
-> 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"]]
readJSON :: ReaderOptions -> String -> Either PandocError Pandoc Source #
:: ReaderOptions | Reader options |
-> String | String to parse (assuming |
-> 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
readEPUB :: ReaderOptions -> ByteString -> Either PandocError (Pandoc, MediaBag) Source #
Writers: converting from Pandoc format
PureStringWriter (WriterOptions -> Pandoc -> String) | |
IOStringWriter (WriterOptions -> Pandoc -> IO String) | |
IOByteStringWriter (WriterOptions -> Pandoc -> IO ByteString) |
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).
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.
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.
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.
:: 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.
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
module Text.Pandoc.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.
toJsonFilter :: a -> IO () Source #
Deprecated: Use toJSONFilter
from JSON
instead
pandocVersion :: String Source #
Version number of pandoc library.