aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc.hs')
-rw-r--r--src/Text/Pandoc.hs34
1 files changed, 26 insertions, 8 deletions
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index 878f0e0dd..0a2c613b1 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -20,10 +20,10 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Text.Pandoc
Copyright : Copyright (C) 2006-2010 John MacFarlane
- License : GNU GPL, version 2 or above
+ License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
- Stability : alpha
+ Stability : alpha
Portability : portable
This helper module exports the main writers, readers, and data
@@ -45,7 +45,7 @@ inline links:
> markdownToRST =
> (writeRST defaultWriterOptions {writerReferenceLinks = True}) .
> readMarkdown defaultParserState
->
+>
> main = getContents >>= putStrLn . markdownToRST
Note: all of the readers assume that the input text has @'\n'@
@@ -55,7 +55,7 @@ you should remove @'\r'@ characters using @filter (/='\r')@.
-}
module Text.Pandoc
- (
+ (
-- * Definitions
module Text.Pandoc.Definition
-- * Generics
@@ -63,12 +63,14 @@ module Text.Pandoc
-- * Lists of readers and writers
, readers
, writers
+ , iowriters
-- * Readers: converting /to/ Pandoc format
, readMarkdown
, readRST
, readLaTeX
, readHtml
, readTextile
+ , readDocBook
, readNative
-- * Parser state used in readers
, ParserState (..)
@@ -97,9 +99,10 @@ module Text.Pandoc
, writeODT
, writeDocx
, writeEPUB
+ , writeFB2
, writeOrg
, writeAsciiDoc
- -- * Writer options used in writers
+ -- * Writer options used in writers
, WriterOptions (..)
, HTMLSlideVariant (..)
, HTMLMathMethod (..)
@@ -113,19 +116,22 @@ module Text.Pandoc
, rtfEmbedImage
, jsonFilter
, ToJsonFilter(..)
+ -- * From Data.Default
+ , def
) where
import Text.Pandoc.Definition
import Text.Pandoc.Generic
import Text.Pandoc.Readers.Markdown
import Text.Pandoc.Readers.RST
+import Text.Pandoc.Readers.DocBook
import Text.Pandoc.Readers.LaTeX
import Text.Pandoc.Readers.HTML
import Text.Pandoc.Readers.Textile
import Text.Pandoc.Readers.Native
import Text.Pandoc.Writers.Native
import Text.Pandoc.Writers.Markdown
-import Text.Pandoc.Writers.RST
+import Text.Pandoc.Writers.RST
import Text.Pandoc.Writers.LaTeX
import Text.Pandoc.Writers.ConTeXt
import Text.Pandoc.Writers.Texinfo
@@ -133,10 +139,11 @@ import Text.Pandoc.Writers.HTML
import Text.Pandoc.Writers.ODT
import Text.Pandoc.Writers.Docx
import Text.Pandoc.Writers.EPUB
+import Text.Pandoc.Writers.FB2
import Text.Pandoc.Writers.Docbook
import Text.Pandoc.Writers.OpenDocument
import Text.Pandoc.Writers.Man
-import Text.Pandoc.Writers.RTF
+import Text.Pandoc.Writers.RTF
import Text.Pandoc.Writers.MediaWiki
import Text.Pandoc.Writers.Textile
import Text.Pandoc.Writers.Org
@@ -147,6 +154,7 @@ import Text.Pandoc.Shared
import Data.Version (showVersion)
import Text.JSON.Generic
import Paths_pandoc (version)
+import Data.Default
-- | Version number of pandoc library.
pandocVersion :: String
@@ -162,7 +170,8 @@ readers = [("native" , \_ -> readNative)
,("rst" , readRST)
,("rst+lhs" , \st ->
readRST st{ stateLiterateHaskell = True})
- ,("textile" , readTextile) -- TODO : textile+lhs
+ ,("docbook" , readDocBook)
+ ,("textile" , readTextile) -- TODO : textile+lhs
,("html" , readHtml)
,("latex" , readLaTeX)
,("latex+lhs" , \st ->
@@ -184,6 +193,7 @@ writers = [("native" , writeNative)
writerHtml5 = True })
,("s5" , writeHtmlString)
,("slidy" , writeHtmlString)
+ ,("slideous" , writeHtmlString)
,("dzslides" , writeHtmlString)
,("docbook" , writeDocbook)
,("opendocument" , writeOpenDocument)
@@ -192,6 +202,8 @@ writers = [("native" , writeNative)
writeLaTeX o{ writerLiterateHaskell = True })
,("beamer" , \o ->
writeLaTeX o{ writerBeamer = True })
+ ,("beamer+lhs" , \o ->
+ writeLaTeX o{ writerBeamer = True, writerLiterateHaskell = True })
,("context" , writeConTeXt)
,("texinfo" , writeTexinfo)
,("man" , writeMan)
@@ -209,6 +221,12 @@ writers = [("native" , writeNative)
,("asciidoc" , writeAsciiDoc)
]
+-- | Association list of formats and writers which require IO to work.
+-- These writers produce text output as well as thoses in 'writers'.
+iowriters :: [ (String, WriterOptions -> Pandoc -> IO String) ]
+iowriters = [ ("fb2" , writeFB2)
+ ]
+
{-# DEPRECATED jsonFilter "Use toJsonFilter instead" #-}
-- | Converts a transformation on the Pandoc AST into a function
-- that reads and writes a JSON-encoded string. This is useful