From 2e62ec096f0336dd00ec3c2da598a3e6fd2c2b03 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 24 Jan 2012 09:06:19 -0800 Subject: Added ToJsonFilter class, deprecated old jsonFilter function. --- src/Text/Pandoc.hs | 37 +++++++++++++++++++++++++++++++++++++ 1 file changed, 37 insertions(+) (limited to 'src/Text/Pandoc.hs') 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 @@ -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 -- cgit v1.2.3