Portability | portable |
---|---|
Stability | alpha |
Maintainer | John MacFarlane <jgm@berkeley.edu> |
Safe Haskell | Safe-Infered |
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
- module Text.Pandoc.Generic
- readers :: [(String, ParserState -> String -> Pandoc)]
- writers :: [(String, WriterOptions -> Pandoc -> String)]
- readMarkdown :: ParserState -> String -> Pandoc
- readRST :: ParserState -> String -> Pandoc
- readLaTeX :: ParserState -> String -> Pandoc
- readHtml :: ParserState -> String -> Pandoc
- readTextile :: ParserState -> String -> Pandoc
- readDocBook :: ParserState -> String -> Pandoc
- readNative :: String -> Pandoc
- data ParserState = ParserState {
- stateParseRaw :: Bool
- stateParserContext :: ParserContext
- stateQuoteContext :: QuoteContext
- stateMaxNestingLevel :: Int
- stateLastStrPos :: Maybe SourcePos
- stateKeys :: KeyTable
- stateCitations :: [String]
- stateNotes :: NoteTable
- stateTabStop :: Int
- stateStandalone :: Bool
- stateTitle :: [Inline]
- stateAuthors :: [[Inline]]
- stateDate :: [Inline]
- stateStrict :: Bool
- stateSmart :: Bool
- stateOldDashes :: Bool
- stateLiterateHaskell :: Bool
- stateColumns :: Int
- stateHeaderTable :: [HeaderType]
- stateIndentedCodeClasses :: [String]
- stateNextExample :: Int
- stateExamples :: Map String Int
- stateHasChapters :: Bool
- stateApplyMacros :: Bool
- stateMacros :: [Macro]
- stateRstDefaultRole :: String
- defaultParserState :: ParserState
- data ParserContext
- data QuoteContext
- type KeyTable = Map Key Target
- type NoteTable = [(String, String)]
- data HeaderType
- 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 :: Maybe FilePath -> WriterOptions -> Pandoc -> IO ByteString
- writeDocx :: Maybe FilePath -> WriterOptions -> Pandoc -> IO ByteString
- writeEPUB :: Maybe String -> [FilePath] -> WriterOptions -> Pandoc -> IO ByteString
- writeOrg :: WriterOptions -> Pandoc -> String
- writeAsciiDoc :: WriterOptions -> Pandoc -> String
- data WriterOptions = WriterOptions {
- writerStandalone :: Bool
- writerTemplate :: String
- writerVariables :: [(String, String)]
- writerEPUBMetadata :: String
- writerTabStop :: Int
- writerTableOfContents :: Bool
- writerSlideVariant :: HTMLSlideVariant
- writerIncremental :: Bool
- writerXeTeX :: Bool
- writerHTMLMathMethod :: HTMLMathMethod
- writerIgnoreNotes :: Bool
- writerNumberSections :: Bool
- writerSectionDivs :: Bool
- writerStrictMarkdown :: Bool
- writerReferenceLinks :: Bool
- writerWrapText :: Bool
- writerColumns :: Int
- writerLiterateHaskell :: Bool
- writerEmailObfuscation :: ObfuscationMethod
- writerIdentifierPrefix :: String
- writerSourceDirectory :: FilePath
- writerUserDataDir :: Maybe FilePath
- writerCiteMethod :: CiteMethod
- writerBiblioFiles :: [FilePath]
- writerHtml5 :: Bool
- writerBeamer :: Bool
- writerSlideLevel :: Maybe Int
- writerChapters :: Bool
- writerListings :: Bool
- writerHighlight :: Bool
- writerHighlightStyle :: Style
- writerSetextHeaders :: Bool
- writerTeXLigatures :: Bool
- data HTMLSlideVariant
- = S5Slides
- | SlidySlides
- | SlideousSlides
- | DZSlides
- | NoSlides
- data HTMLMathMethod
- data CiteMethod
- defaultWriterOptions :: WriterOptions
- module Text.Pandoc.Templates
- pandocVersion :: String
- rtfEmbedImage :: Inline -> IO Inline
- jsonFilter :: (Pandoc -> Pandoc) -> String -> String
- class ToJsonFilter a where
- toJsonFilter :: a -> IO ()
Definitions
module Text.Pandoc.Definition
Generics
module Text.Pandoc.Generic
Lists of readers and writers
readers :: [(String, ParserState -> String -> Pandoc)]Source
Association list of formats and readers.
writers :: [(String, WriterOptions -> Pandoc -> String)]Source
Association list of formats and writers (omitting the binary writers, odt, docx, and epub).
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.
:: ParserState | Parser state, including options for parser |
-> String | String to parse (assuming |
-> Pandoc |
Parse a Textile text and return a Pandoc document.
readDocBook :: ParserState -> 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"]]
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
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.
:: Maybe FilePath | Path specified by --reference-odt |
-> WriterOptions | Writer options |
-> Pandoc | Document to convert |
-> IO ByteString |
Produce an ODT file from a Pandoc document.
:: Maybe FilePath | Path specified by --reference-docx |
-> WriterOptions | Writer options |
-> Pandoc | Document to convert |
-> IO ByteString |
Produce an Docx file from a Pandoc document.
:: Maybe String | EPUB stylesheet specified at command line |
-> [FilePath] | Paths to fonts to embed |
-> WriterOptions | Writer options |
-> Pandoc | Document to convert |
-> IO ByteString |
Produce an EPUB file from a Pandoc document.
writeOrg :: WriterOptions -> Pandoc -> StringSource
Convert Pandoc to Org.
writeAsciiDoc :: WriterOptions -> Pandoc -> StringSource
Convert Pandoc to AsciiDoc.
Writer options used in writers
data WriterOptions Source
Options for writers
WriterOptions | |
|
data HTMLSlideVariant Source
Varieties of HTML slide shows.
data HTMLMathMethod Source
defaultWriterOptions :: WriterOptionsSource
Default writer options.
Rendering templates and default templates
module Text.Pandoc.Templates
Version
Version number of pandoc library.
Miscellaneous
rtfEmbedImage :: Inline -> IO InlineSource
Convert Image inlines into a raw RTF embedded image, read from a file. If file not found or filetype not jpeg or png, leave the inline unchanged.
jsonFilter :: (Pandoc -> Pandoc) -> String -> StringSource
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) |