Use aeson for json.

Benchmarked:  about twice as slow as json!
This commit is contained in:
John MacFarlane 2013-05-09 10:38:11 -07:00
parent a578a490ee
commit 5f4a32e465
3 changed files with 27 additions and 24 deletions

View file

@ -1,8 +1,6 @@
import Text.Pandoc
import Text.Pandoc.Shared (normalize)
import Criterion.Main
import Criterion.Config
import Text.JSON.Generic
import System.Environment (getArgs)
import Data.Monoid
@ -26,11 +24,6 @@ writerBench :: Pandoc
writerBench doc (name, writer) = bench (name ++ " writer") $ nf
(writer def{ writerWrapText = True }) doc
normalizeBench :: Pandoc -> [Benchmark]
normalizeBench doc = [ bench "normalize - with" $ nf (encodeJSON . normalize) doc
, bench "normalize - without" $ nf encodeJSON doc
]
main :: IO ()
main = do
args <- getArgs
@ -42,5 +35,5 @@ main = do
let readerBs = map (readerBench doc) readers
let writers' = [(n,w) | (n, PureStringWriter w) <- writers]
defaultMainWith conf (return ()) $
map (writerBench doc) writers' ++ readerBs ++ normalizeBench doc
map (writerBench doc) writers' ++ readerBs

View file

@ -247,7 +247,7 @@ Library
extensible-exceptions >= 0.1 && < 0.2,
citeproc-hs >= 0.3.7 && < 0.4,
pandoc-types >= 1.10 && < 1.11,
json >= 0.4 && < 0.8,
aeson >= 0.6 && < 0.7,
tagsoup >= 0.12.5 && < 0.13,
base64-bytestring >= 0.1 && < 1.1,
zlib >= 0.5 && < 0.6,
@ -438,8 +438,7 @@ benchmark benchmark-pandoc
Build-Depends: pandoc,
base >= 4.2 && < 5,
syb >= 0.1 && < 0.5,
criterion >= 0.5 && < 0.9,
json >= 0.4 && < 0.8
criterion >= 0.5 && < 0.9
if impl(ghc >= 7.0.1)
Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind
else

View file

@ -145,13 +145,16 @@ import Text.Pandoc.Templates
import Text.Pandoc.Options
import Text.Pandoc.Shared (safeRead, warn)
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy as BL
import Data.List (intercalate, isSuffixOf)
import Data.Version (showVersion)
import Text.JSON.Generic
import Data.Aeson.Generic
import Data.Set (Set)
import Data.Data
import qualified Data.Set as Set
import Text.Parsec
import Text.Parsec.Error
import qualified Text.Pandoc.UTF8 as UTF8
import Paths_pandoc (version)
-- | Version number of pandoc library.
@ -188,7 +191,8 @@ markdown o s = do
-- | Association list of formats and readers.
readers :: [(String, ReaderOptions -> String -> IO Pandoc)]
readers = [("native" , \_ s -> return $ readNative s)
,("json" , \_ s -> return $ decodeJSON s)
,("json" , \_ s -> return $ checkJSON
$ decode $ UTF8.fromStringLazy s)
,("markdown" , markdown)
,("markdown_strict" , markdown)
,("markdown_phpextra" , markdown)
@ -212,7 +216,7 @@ data Writer = PureStringWriter (WriterOptions -> Pandoc -> String)
writers :: [ ( String, Writer ) ]
writers = [
("native" , PureStringWriter writeNative)
,("json" , PureStringWriter $ \_ -> encodeJSON)
,("json" , PureStringWriter $ \_ -> UTF8.toStringLazy . encode)
,("docx" , IOByteStringWriter writeDocx)
,("odt" , IOByteStringWriter writeODT)
,("epub" , IOByteStringWriter $ \o ->
@ -304,7 +308,7 @@ getWriter s =
-- 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
jsonFilter f = UTF8.toStringLazy . encode . f . checkJSON . decode . UTF8.fromStringLazy
-- | '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
@ -333,18 +337,25 @@ class ToJsonFilter a where
toJsonFilter :: a -> IO ()
instance (Data a) => ToJsonFilter (a -> a) where
toJsonFilter f = getContents
>>= putStr . encodeJSON . (bottomUp f :: Pandoc -> Pandoc) . decodeJSON
toJsonFilter f = BL.getContents >>=
BL.putStr . encode . (bottomUp f :: Pandoc -> Pandoc) . checkJSON . decode
instance (Data a) => ToJsonFilter (a -> IO a) where
toJsonFilter f = getContents >>= (bottomUpM f :: Pandoc -> IO Pandoc) . decodeJSON
>>= putStr . encodeJSON
toJsonFilter f = BL.getContents >>=
(bottomUpM f :: Pandoc -> IO Pandoc) . checkJSON . decode >>=
BL.putStr . encode
instance (Data a) => ToJsonFilter (a -> [a]) where
toJsonFilter f = getContents
>>= putStr . encodeJSON . (bottomUp (concatMap f) :: Pandoc -> Pandoc) . decodeJSON
toJsonFilter f = BL.getContents >>=
BL.putStr . encode . (bottomUp (concatMap f) :: Pandoc -> Pandoc) .
checkJSON . decode
instance (Data a) => ToJsonFilter (a -> IO [a]) where
toJsonFilter f = getContents
>>= (bottomUpM (fmap concat . mapM f) :: Pandoc -> IO Pandoc) . decodeJSON
>>= putStr . encodeJSON
toJsonFilter f = BL.getContents >>=
(bottomUpM (fmap concat . mapM f) :: Pandoc -> IO Pandoc)
. checkJSON . decode >>=
BL.putStr . encode
checkJSON :: Maybe a -> a
checkJSON Nothing = error "Error parsing JSON"
checkJSON (Just r) = r