Portability | portable |
---|---|
Stability | alpha |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
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 defaultWriterOptions {writerReferenceLinks = True}) . readMarkdown defaultParserState 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
- readMarkdown :: ParserState -> String -> Pandoc
- readRST :: ParserState -> String -> Pandoc
- readLaTeX :: ParserState -> String -> Pandoc
- readHtml :: ParserState -> String -> Pandoc
- data ParserState = ParserState {
- stateParseRaw :: Bool
- stateParserContext :: ParserContext
- stateQuoteContext :: QuoteContext
- stateSanitizeHTML :: Bool
- stateKeys :: KeyTable
- stateNotes :: NoteTable
- stateTabStop :: Int
- stateStandalone :: Bool
- stateTitle :: [Inline]
- stateAuthors :: [[Inline]]
- stateDate :: [Inline]
- stateStrict :: Bool
- stateSmart :: Bool
- stateLiterateHaskell :: Bool
- stateColumns :: Int
- stateHeaderTable :: [HeaderType]
- stateIndentedCodeClasses :: [String]
- defaultParserState :: ParserState
- data ParserContext
- data QuoteContext
- type KeyTable = [([Inline], Target)]
- type NoteTable = [(String, String)]
- data HeaderType
- 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
- writeS5 :: WriterOptions -> Pandoc -> Html
- writeS5String :: WriterOptions -> Pandoc -> String
- writeDocbook :: WriterOptions -> Pandoc -> String
- writeOpenDocument :: WriterOptions -> Pandoc -> String
- writeMan :: WriterOptions -> Pandoc -> String
- writeMediaWiki :: WriterOptions -> Pandoc -> String
- writeRTF :: WriterOptions -> Pandoc -> String
- prettyPandoc :: Pandoc -> String
- data WriterOptions = WriterOptions {
- writerStandalone :: Bool
- writerTemplate :: String
- writerVariables :: [(String, String)]
- writerIncludeBefore :: String
- writerIncludeAfter :: String
- writerTabStop :: Int
- writerTableOfContents :: Bool
- writerS5 :: Bool
- writerXeTeX :: Bool
- writerHTMLMathMethod :: HTMLMathMethod
- writerIgnoreNotes :: Bool
- writerIncremental :: Bool
- writerNumberSections :: Bool
- writerStrictMarkdown :: Bool
- writerReferenceLinks :: Bool
- writerWrapText :: Bool
- writerLiterateHaskell :: Bool
- writerEmailObfuscation :: ObfuscationMethod
- writerIdentifierPrefix :: String
- data HTMLMathMethod
- defaultWriterOptions :: WriterOptions
- module Text.Pandoc.Templates
- pandocVersion :: String
Definitions
module Text.Pandoc.Definition
Readers: converting to Pandoc format
:: ParserState | Parser state, including options for parser |
-> String | String to parse (assuming |
-> Pandoc |
Read markdown from an input string and return a Pandoc document.
:: ParserState | Parser state, including options for parser |
-> String | String to parse (assuming |
-> Pandoc |
Parse reStructuredText string and return Pandoc document.
:: ParserState | Parser state, including options for parser |
-> String | String to parse (assumes |
-> Pandoc |
Parse LaTeX from string and return Pandoc
document.
:: ParserState | Parser state |
-> String | String to parse (assumes |
-> Pandoc |
Convert HTML-formatted string to Pandoc
document.
Parser state used in readers
data ParserState Source
Parsing options.
ParserState | |
|
data ParserContext Source
ListItemState | Used when running parser on list item contents |
NullState | Default state |
data QuoteContext Source
InSingleQuote | Used when parsing inside single quotes |
InDoubleQuote | Used when parsing inside double quotes |
NoQuote | Used when not parsing inside quotes |
data HeaderType Source
SingleHeader Char | Single line of characters underneath |
DoubleHeader Char | Lines of characters above and below |
Writers: converting from Pandoc format
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.
writeS5 :: WriterOptions -> Pandoc -> HtmlSource
Converts Pandoc document to an S5 HTML presentation (Html structure).
writeS5String :: WriterOptions -> Pandoc -> StringSource
Converts Pandoc document to an S5 HTML presentation (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.
writeRTF :: WriterOptions -> Pandoc -> StringSource
Convert Pandoc to a string in rich text format.
prettyPandoc :: Pandoc -> StringSource
Prettyprint Pandoc document.
Writer options used in writers
data WriterOptions Source
Options for writers
WriterOptions | |
|
data HTMLMathMethod Source
defaultWriterOptions :: WriterOptionsSource
Default writer options.
Rendering templates and default templates
module Text.Pandoc.Templates
Version
Version number of pandoc library.