aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2012-01-24 09:06:19 -0800
committerJohn MacFarlane <fiddlosopher@gmail.com>2012-01-24 09:06:19 -0800
commit2e62ec096f0336dd00ec3c2da598a3e6fd2c2b03 (patch)
tree1cfe37dfba32184509ed19184980229e306f8e51 /src/Text/Pandoc.hs
parent0fd0dc23449165280add5d145a13c39422874432 (diff)
downloadpandoc-2e62ec096f0336dd00ec3c2da598a3e6fd2c2b03.tar.gz
Added ToJsonFilter class, deprecated old jsonFilter function.
Diffstat (limited to 'src/Text/Pandoc.hs')
-rw-r--r--src/Text/Pandoc.hs37
1 files changed, 37 insertions, 0 deletions
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index 187fb98d7..ba05589cd 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>
@@ -111,6 +112,7 @@ module Text.Pandoc
-- * Miscellaneous
, rtfEmbedImage
, jsonFilter
+ , ToJsonFilter(..)
) where
import Text.Pandoc.Definition
@@ -205,8 +207,43 @@ writers = [("native" , writeNative)
,("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, and writes it 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)@ 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