aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2010-12-09 10:40:31 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2010-12-09 10:40:31 -0800
commit167eeef6cb68d7cf4b5bd94f6543f84543df8c8c (patch)
treea90560029d94da2de57228f4dce82df51e8fc575 /src
parentbb609a85e3db8a25fbfac30858c8637eb6664fd6 (diff)
downloadpandoc-167eeef6cb68d7cf4b5bd94f6543f84543df8c8c.tar.gz
Added json format for reading and writing.
This is faster to parse than native.
Diffstat (limited to 'src')
-rw-r--r--src/pandoc.hs11
1 files changed, 11 insertions, 0 deletions
diff --git a/src/pandoc.hs b/src/pandoc.hs
index 3aa9a4ba8..e8220de34 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -29,6 +29,7 @@ Parses command-line options and calls the appropriate readers and
writers.
-}
module Main where
+import Text.JSON.Generic (encodeJSON, decodeJSON)
import Text.Pandoc
import Text.Pandoc.S5 (s5HeaderIncludes)
import Text.Pandoc.Shared ( tabFilter, ObfuscationMethod (..), readDataFile,
@@ -83,6 +84,7 @@ wrapWords c = wrap' c c where
-- | Association list of formats and readers.
readers :: [(String, ParserState -> String -> Pandoc)]
readers = [("native" , readPandoc)
+ ,("json" , readJSON)
,("markdown" , readMarkdown)
,("markdown+lhs" , readMarkdown)
,("rst" , readRST)
@@ -97,9 +99,18 @@ readers = [("native" , readPandoc)
readPandoc :: ParserState -> String -> Pandoc
readPandoc _ = read
+-- | Reader for JSON version of Pandoc AST.
+readJSON :: ParserState -> String -> Pandoc
+readJSON _ = decodeJSON
+
+-- | Writer for JSON version of Pandoc AST.
+writeJSON :: WriterOptions -> Pandoc -> String
+writeJSON _ = encodeJSON
+
-- | Association list of formats and writers.
writers :: [ ( String, WriterOptions -> Pandoc -> String ) ]
writers = [("native" , writeNative)
+ ,("json" , writeJSON)
,("html" , writeHtmlString)
,("html+lhs" , writeHtmlString)
,("s5" , writeHtmlString)