Pandoc

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
import Data.Text (Text)
import qualified Data.Text.IO as T

mdToRST :: Text -> IO Text
mdToRST txt = runIOorExplode $
readMarkdown def txt
>>= writeRST def{ writerReferenceLinks = True }

main :: IO ()
main = do
T.getContents >>= mdToRST >>= T.putStrLn
Module exporting convenient pandoc bindings
Functions for writing a parsed formula as a list of Pandoc Inlines.
This module defines a CiteprocOutput instance for pandoc Inlines.
Marshaling/unmarshaling functions of Pandoc values.
Conversion between markup formats Pandoc is a Haskell library for converting from one markup format to another. The formats it can handle include
  • light markup formats (many variants of Markdown, reStructuredText, AsciiDoc, Org-mode, Muse, Textile, txt2tags, djot)
  • HTML formats (HTML 4 and 5)
  • Ebook formats (EPUB v2 and v3, FB2)
  • Documentation formats (GNU TexInfo, Haddock)
  • Roff formats (man, ms)
  • TeX formats (LaTeX, ConTeXt)
  • Typst
  • XML formats (DocBook 4 and 5, JATS, TEI Simple, OpenDocument)
  • Outline formats (OPML)
  • Bibliography formats (BibTeX, BibLaTeX, CSL JSON, CSL YAML, RIS)
  • Word processor formats (Docx, RTF, ODT)
  • Interactive notebook formats (Jupyter notebook ipynb)
  • Page layout formats (InDesign ICML)
  • Wiki markup formats (MediaWiki, DokuWiki, TikiWiki, TWiki, Vimwiki, XWiki, ZimWiki, Jira wiki, Creole)
  • Slide show formats (LaTeX Beamer, PowerPoint, Slidy, reveal.js, Slideous, S5, DZSlides)
  • Data formats (CSV and TSV tables)
  • PDF (via external programs such as pdflatex or wkhtmltopdf)
Pandoc can convert mathematical content in documents between TeX, MathML, Word equations, roff eqn, typst, and plain text. It includes a powerful system for automatic citations and bibliographies, and it can be customized extensively using templates, filters, and custom readers and writers written in Lua. For the pandoc command-line program, see the pandoc-cli package.
The PandocMonad typeclass contains all the potentially IO-related functions used in pandoc's readers and writers. Instances of this typeclass may implement these functions in IO (as in PandocIO) or using an internal state that represents a file system, time, and so on (as in PandocPure).