Skip to content

Commit b07c916

Browse files
committed
init
0 parents  commit b07c916

File tree

5 files changed

+197
-0
lines changed

5 files changed

+197
-0
lines changed

.gitignore

+3
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
dist
2+
.cabal-sandbox/
3+
cabal.sandbox.config

LICENSE

Whitespace-only changes.

Setup.hs

+2
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
import Distribution.Simple
2+
main = defaultMain

serialization-bench.cabal

+30
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,30 @@
1+
name: serialization-bench
2+
version: 0.1.0.0
3+
-- synopsis:
4+
-- description:
5+
-- license:
6+
license-file: LICENSE
7+
author: Ömer Sinan Ağacan
8+
maintainer: [email protected]
9+
-- copyright:
10+
-- category:
11+
build-type: Simple
12+
-- extra-source-files:
13+
cabal-version: >=1.10
14+
15+
executable serialization-bench
16+
main-is: Main.hs
17+
-- other-modules:
18+
-- other-extensions:
19+
build-depends: base >=4.7 && <4.8,
20+
binary >=0.7.1 && <0.7.3,
21+
bytestring,
22+
cereal >=0.4.1 && <0.4.2,
23+
criterion,
24+
deepseq,
25+
packman,
26+
QuickCheck,
27+
random
28+
hs-source-dirs: src
29+
default-language: Haskell2010
30+
ghc-options: -Wall

src/Main.hs

+162
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,162 @@
1+
{-# LANGUAGE DeriveDataTypeable, FlexibleContexts, FlexibleInstances,
2+
MultiParamTypeClasses #-}
3+
4+
module Main where
5+
6+
import Control.Applicative
7+
import Control.DeepSeq
8+
import qualified Data.ByteString as BS
9+
import qualified Data.ByteString.Lazy as LBS
10+
import Data.Typeable
11+
import Data.Word
12+
import System.IO
13+
import System.Random
14+
15+
-- Serialization libs
16+
import qualified Data.Binary as B
17+
import qualified Data.Serialize as C
18+
import qualified GHC.Packing as P
19+
20+
-- Testing and random data generation
21+
import Test.QuickCheck
22+
import Test.QuickCheck.Arbitrary
23+
import Test.QuickCheck.Gen
24+
25+
-- Benchmarks
26+
import Criterion.Main
27+
import Criterion.Types
28+
29+
data BinTree a = Tree (BinTree a) (BinTree a) | Leaf a
30+
deriving (Show, Eq, Typeable)
31+
32+
instance NFData a => NFData (BinTree a) where
33+
rnf (Leaf a) = rnf a `seq` ()
34+
rnf (Tree left right) = rnf left `seq` rnf right `seq` ()
35+
36+
instance Arbitrary a => Arbitrary (BinTree a) where
37+
arbitrary = oneof [Leaf <$> arbitrary, Tree <$> arbitrary <*> arbitrary]
38+
39+
shrink Leaf{} = []
40+
shrink (Tree left right) = [left, right] ++ shrink left ++ shrink right
41+
42+
instance B.Binary a => B.Binary (BinTree a) where
43+
put (Leaf a) = do
44+
B.put (0 :: Word8)
45+
B.put a
46+
47+
put (Tree left right) = do
48+
B.put (1 :: Word8)
49+
B.put left
50+
B.put right
51+
52+
get = do
53+
t <- B.get :: B.Get Word8
54+
case t of
55+
0 -> Leaf <$> B.get
56+
1 -> Tree <$> B.get <*> B.get
57+
58+
instance C.Serialize a => C.Serialize (BinTree a) where
59+
put (Leaf a) = do
60+
C.put (0 :: Word8)
61+
C.put a
62+
63+
put (Tree left right) = do
64+
C.put (1 :: Word8)
65+
C.put left
66+
C.put right
67+
68+
get = do
69+
t <- C.get :: C.Get Word8
70+
case t of
71+
0 -> Leaf <$> C.get
72+
1 -> Tree <$> C.get <*> C.get
73+
74+
data Binary = Binary
75+
data Cereal = Cereal
76+
data Packman = Packman
77+
78+
class Serialize lib a where
79+
serialize :: lib -> a -> IO BS.ByteString
80+
deserialize :: lib -> BS.ByteString -> IO a
81+
82+
instance (B.Binary a, NFData a) => Serialize Binary a where
83+
serialize _ = return . force . LBS.toStrict . B.encode
84+
deserialize _ = return . force . B.decode . LBS.fromStrict
85+
86+
instance (C.Serialize a, NFData a) => Serialize Cereal a where
87+
serialize _ = return . force . C.encode
88+
deserialize _ = either error (return . force) . C.decode
89+
90+
instance (NFData a, Typeable a) => Serialize Packman a where
91+
serialize _ = fmap (force . LBS.toStrict . B.encode) . P.trySerialize
92+
deserialize _ = either error (fmap force . P.deserialize) . B.decode . LBS.fromStrict
93+
94+
prop :: Serialize lib (BinTree Int) => lib -> Property
95+
prop lib = forAll arbitrary (ioProperty . test)
96+
where
97+
test :: BinTree Int -> IO Bool
98+
test t = do
99+
s <- serialize lib t
100+
d <- deserialize lib s
101+
return $ d == t
102+
103+
runQC :: Serialize lib (BinTree Int) => lib -> IO ()
104+
runQC = quickCheckWith stdArgs{maxSuccess=1000} . prop
105+
106+
bug :: IO ()
107+
bug = do
108+
let ex = Tree (Leaf 10) (Leaf 20) :: BinTree Int
109+
-- this works
110+
-- P.encodeToFile "test" ex
111+
-- tree <- P.decodeFromFile "test" :: IO (BinTree Int)
112+
-- print tree
113+
114+
-- this works
115+
-- s <- P.trySerialize ex
116+
-- d <- P.deserialize s
117+
-- print d
118+
119+
-- this doesn't work
120+
s <- fmap B.encode . P.trySerialize $ (1 :: Int)
121+
print (LBS.unpack s)
122+
d <- (either error P.deserialize . B.decode $ s) :: IO Int
123+
print d
124+
125+
-- this doesn't work
126+
-- b <- serialize Packman ex
127+
-- b' <- deserialize Packman b :: IO (BinTree Int)
128+
-- print b'
129+
130+
generateBalancedTree :: Word32 -> IO (BinTree Int)
131+
generateBalancedTree 0 = Leaf <$> randomIO
132+
generateBalancedTree n = Tree <$> generateBalancedTree (n-1) <*> generateBalancedTree (n-1)
133+
134+
runBench :: IO ()
135+
runBench = do
136+
putStr "Generating tree... "
137+
hFlush stdout
138+
tree <- force <$> generateBalancedTree 22
139+
putStrLn "Done."
140+
defaultMainWith defaultConfig{forceGC=True, verbosity=Verbose}
141+
[ bgroup "binary"
142+
[ bench "serialize" $ nfIO $ serialize Binary tree
143+
, bench "serialize + deserialize" $
144+
nfIO (serialize Binary tree >>= deserialize Binary :: IO (BinTree Int))
145+
]
146+
, bgroup "cereal"
147+
[ bench "serialize" $ nfIO $ serialize Cereal tree
148+
, bench "serialize + deserialize" $ nfIO
149+
(serialize Cereal tree >>= deserialize Cereal :: IO (BinTree Int))
150+
]
151+
, bgroup "packman" []
152+
]
153+
154+
main :: IO ()
155+
main = do
156+
-- runQC Binary
157+
-- runQC Cereal
158+
-- runQC Packman
159+
160+
-- bug
161+
162+
runBench

0 commit comments

Comments
 (0)