summaryrefslogtreecommitdiff
path: root/src/Text/Pandoc.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc.hs')
-rw-r--r--src/Text/Pandoc.hs61
1 files changed, 60 insertions, 1 deletions
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index ef8560284..878f0e0dd 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE ScopedTypeVariables, FlexibleInstances #-}
{-
Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu>
@@ -94,8 +95,10 @@ module Text.Pandoc
, writeTextile
, writeRTF
, writeODT
+ , writeDocx
, writeEPUB
, writeOrg
+ , writeAsciiDoc
-- * Writer options used in writers
, WriterOptions (..)
, HTMLSlideVariant (..)
@@ -109,6 +112,7 @@ module Text.Pandoc
-- * Miscellaneous
, rtfEmbedImage
, jsonFilter
+ , ToJsonFilter(..)
) where
import Text.Pandoc.Definition
@@ -127,6 +131,7 @@ import Text.Pandoc.Writers.ConTeXt
import Text.Pandoc.Writers.Texinfo
import Text.Pandoc.Writers.HTML
import Text.Pandoc.Writers.ODT
+import Text.Pandoc.Writers.Docx
import Text.Pandoc.Writers.EPUB
import Text.Pandoc.Writers.Docbook
import Text.Pandoc.Writers.OpenDocument
@@ -135,6 +140,7 @@ import Text.Pandoc.Writers.RTF
import Text.Pandoc.Writers.MediaWiki
import Text.Pandoc.Writers.Textile
import Text.Pandoc.Writers.Org
+import Text.Pandoc.Writers.AsciiDoc
import Text.Pandoc.Templates
import Text.Pandoc.Parsing
import Text.Pandoc.Shared
@@ -164,20 +170,28 @@ readers = [("native" , \_ -> readNative)
]
-- | Association list of formats and writers (omitting the
--- binary writers, odt and epub).
+-- binary writers, odt, docx, and epub).
writers :: [ ( String, WriterOptions -> Pandoc -> String ) ]
writers = [("native" , writeNative)
,("json" , \_ -> encodeJSON)
,("html" , writeHtmlString)
+ ,("html5" , \o ->
+ writeHtmlString o{ writerHtml5 = True })
,("html+lhs" , \o ->
writeHtmlString o{ writerLiterateHaskell = True })
+ ,("html5+lhs" , \o ->
+ writeHtmlString o{ writerLiterateHaskell = True,
+ writerHtml5 = True })
,("s5" , writeHtmlString)
,("slidy" , writeHtmlString)
+ ,("dzslides" , writeHtmlString)
,("docbook" , writeDocbook)
,("opendocument" , writeOpenDocument)
,("latex" , writeLaTeX)
,("latex+lhs" , \o ->
writeLaTeX o{ writerLiterateHaskell = True })
+ ,("beamer" , \o ->
+ writeLaTeX o{ writerBeamer = True })
,("context" , writeConTeXt)
,("texinfo" , writeTexinfo)
,("man" , writeMan)
@@ -192,10 +206,55 @@ writers = [("native" , writeNative)
,("textile" , writeTextile)
,("rtf" , writeRTF)
,("org" , writeOrg)
+ ,("asciidoc" , writeAsciiDoc)
]
+{-# 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
-- for writing small scripts.
jsonFilter :: (Pandoc -> Pandoc) -> String -> String
jsonFilter f = encodeJSON . f . decodeJSON
+
+-- | '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 'Text.Pandoc.Definition'.
+class ToJsonFilter a where
+ toJsonFilter :: a -> IO ()
+
+instance (Data a) => ToJsonFilter (a -> a) where
+ toJsonFilter f = getContents
+ >>= putStr . encodeJSON . (bottomUp f :: Pandoc -> Pandoc) . decodeJSON
+
+instance (Data a) => ToJsonFilter (a -> IO a) where
+ toJsonFilter f = getContents >>= (bottomUpM f :: Pandoc -> IO Pandoc) . decodeJSON
+ >>= putStr . encodeJSON
+
+instance (Data a) => ToJsonFilter (a -> [a]) where
+ toJsonFilter f = getContents
+ >>= putStr . encodeJSON . (bottomUp (concatMap f) :: Pandoc -> Pandoc) . decodeJSON
+
+instance (Data a) => ToJsonFilter (a -> IO [a]) where
+ toJsonFilter f = getContents
+ >>= (bottomUpM (fmap concat . mapM f) :: Pandoc -> IO Pandoc) . decodeJSON
+ >>= putStr . encodeJSON