Added ToJsonFilter class, deprecated old jsonFilter function.
This commit is contained in:
parent
0fd0dc2344
commit
2e62ec096f
1 changed files with 37 additions and 0 deletions
|
@ -1,3 +1,4 @@
|
||||||
|
{-# LANGUAGE ScopedTypeVariables, FlexibleInstances #-}
|
||||||
{-
|
{-
|
||||||
Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu>
|
Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu>
|
||||||
|
|
||||||
|
@ -111,6 +112,7 @@ module Text.Pandoc
|
||||||
-- * Miscellaneous
|
-- * Miscellaneous
|
||||||
, rtfEmbedImage
|
, rtfEmbedImage
|
||||||
, jsonFilter
|
, jsonFilter
|
||||||
|
, ToJsonFilter(..)
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Text.Pandoc.Definition
|
import Text.Pandoc.Definition
|
||||||
|
@ -205,8 +207,43 @@ writers = [("native" , writeNative)
|
||||||
,("asciidoc" , writeAsciiDoc)
|
,("asciidoc" , writeAsciiDoc)
|
||||||
]
|
]
|
||||||
|
|
||||||
|
{-# DEPRECATED jsonFilter "Use toJsonFilter instead" #-}
|
||||||
-- | Converts a transformation on the Pandoc AST into a function
|
-- | Converts a transformation on the Pandoc AST into a function
|
||||||
-- that reads and writes a JSON-encoded string. This is useful
|
-- that reads and writes a JSON-encoded string. This is useful
|
||||||
-- for writing small scripts.
|
-- for writing small scripts.
|
||||||
jsonFilter :: (Pandoc -> Pandoc) -> String -> String
|
jsonFilter :: (Pandoc -> Pandoc) -> String -> String
|
||||||
jsonFilter f = encodeJSON . f . decodeJSON
|
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
|
||||||
|
|
Loading…
Add table
Reference in a new issue