pandoc-3.1: Conversion between markup formats
CopyrightCopyright (C) 2006-2023 John MacFarlane
LicenseGNU GPL, version 2 or above
MaintainerJohn MacFarlane <jgm@berkeley.edu>
Stabilityalpha
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Pandoc

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
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
Synopsis

Definitions

Generics

Options

Logging

Typeclass

Internal data files

Error handling

Readers: converting to Pandoc format

Writers: converting from Pandoc format

Rendering templates and default templates

Localization

setTranslations :: PandocMonad m => Lang -> m () Source #

Select the language to use with translateTerm. Note that this does not read a translation file; that is only done the first time translateTerm is used.

translateTerm :: PandocMonad m => Term -> m Text Source #

Get a translation from the current term map. Issue a warning if the term is not defined.

Version information

pandocVersion :: Version Source #

Version number of pandoc library.

pandocVersionText :: Text Source #

Text representation of the library's version number.