1
1
{-# LANGUAGE FlexibleContexts #-}
2
- {-# LANGUAGE OverloadedStrings #-}
3
2
{-# LANGUAGE PackageImports #-}
4
3
{-# LANGUAGE RankNTypes #-}
5
4
@@ -15,9 +14,8 @@ import Criterion.Main
15
14
import Data.Hashable
16
15
import Data.Proxy (Proxy (.. ))
17
16
import Data.Tagged (Tagged (.. ))
18
- import qualified "aeson" Data.Aeson as A
19
- import qualified "aeson-benchmarks" Data.Aeson as B
20
- import qualified "aeson-benchmarks" Data.Aeson.Types as B (fromJSONKeyCoerce )
17
+ import Data.Aeson
18
+ import Data.Aeson.Types (fromJSONKeyCoerce )
21
19
import qualified Data.ByteString.Lazy as LBS
22
20
import qualified Data.HashMap.Strict as HM
23
21
import qualified Data.Map as M
@@ -47,10 +45,10 @@ instance NFData T1 where
47
45
instance Hashable T1 where
48
46
hashWithSalt salt (T1 t) = hashWithSalt salt t
49
47
50
- instance B. FromJSON T1 where
51
- parseJSON = B. withText " T1" $ pure . T1
52
- instance B. FromJSONKey T1 where
53
- fromJSONKey = B. FromJSONKeyText T1
48
+ instance FromJSON T1 where
49
+ parseJSON = withText " T1" $ pure . T1
50
+ instance FromJSONKey T1 where
51
+ fromJSONKey = FromJSONKeyText T1
54
52
55
53
-------------------------------------------------------------------------------
56
54
-- Coerce
@@ -64,10 +62,10 @@ instance NFData T2 where
64
62
instance Hashable T2 where
65
63
hashWithSalt salt (T2 t) = hashWithSalt salt t
66
64
67
- instance B. FromJSON T2 where
68
- parseJSON = B. withText " T2" $ pure . T2
69
- instance B. FromJSONKey T2 where
70
- fromJSONKey = B. fromJSONKeyCoerce
65
+ instance FromJSON T2 where
66
+ parseJSON = withText " T2" $ pure . T2
67
+ instance FromJSONKey T2 where
68
+ fromJSONKey = fromJSONKeyCoerce
71
69
72
70
-------------------------------------------------------------------------------
73
71
-- TextParser
@@ -81,10 +79,10 @@ instance NFData T3 where
81
79
instance Hashable T3 where
82
80
hashWithSalt salt (T3 t) = hashWithSalt salt t
83
81
84
- instance B. FromJSON T3 where
85
- parseJSON = B. withText " T3" $ pure . T3
86
- instance B. FromJSONKey T3 where
87
- fromJSONKey = B. FromJSONKeyTextParser (pure . T3 )
82
+ instance FromJSON T3 where
83
+ parseJSON = withText " T3" $ pure . T3
84
+ instance FromJSONKey T3 where
85
+ fromJSONKey = FromJSONKeyTextParser (pure . T3 )
88
86
89
87
-------------------------------------------------------------------------------
90
88
-- Values
@@ -97,40 +95,30 @@ value1000 = value 1000
97
95
value10000 = value 10000
98
96
99
97
encodedValue10 :: LBS. ByteString
100
- encodedValue10 = B. encode value10
98
+ encodedValue10 = encode value10
101
99
102
100
encodedValue100 :: LBS. ByteString
103
- encodedValue100 = B. encode value100
101
+ encodedValue100 = encode value100
104
102
105
103
encodedValue1000 :: LBS. ByteString
106
- encodedValue1000 = B. encode value1000
104
+ encodedValue1000 = encode value1000
107
105
108
106
encodedValue10000 :: LBS. ByteString
109
- encodedValue10000 = B. encode value10000
107
+ encodedValue10000 = encode value10000
110
108
111
109
-------------------------------------------------------------------------------
112
110
-- Helpers
113
111
-------------------------------------------------------------------------------
114
112
115
- decodeHMB
116
- :: (B. FromJSONKey k , Eq k , Hashable k )
113
+ decodeHM
114
+ :: (FromJSON ( HM. HashMap k T. Text ) , Eq k , Hashable k )
117
115
=> Proxy k -> LBS. ByteString -> Maybe (HM. HashMap k T. Text )
118
- decodeHMB _ = B. decode
116
+ decodeHM _ = decode
119
117
120
- decodeHMA
121
- :: (A. FromJSON (HM. HashMap k T. Text ), Eq k , Hashable k )
122
- => Proxy k -> LBS. ByteString -> Maybe (HM. HashMap k T. Text )
123
- decodeHMA _ = A. decode
124
-
125
- decodeMapB
126
- :: (B. FromJSONKey k , Ord k )
127
- => Proxy k -> LBS. ByteString -> Maybe (M. Map k T. Text )
128
- decodeMapB _ = B. decode
129
-
130
- decodeMapA
131
- :: (A. FromJSON (M. Map k T. Text ), Ord k )
118
+ decodeMap
119
+ :: (FromJSON (M. Map k T. Text ), Ord k )
132
120
=> Proxy k -> LBS. ByteString -> Maybe (M. Map k T. Text )
133
- decodeMapA _ = A. decode
121
+ decodeMap _ = decode
134
122
135
123
proxyText :: Proxy T. Text
136
124
proxyText = Proxy
@@ -156,45 +144,41 @@ benchDecodeHM
156
144
-> LBS. ByteString
157
145
-> Benchmark
158
146
benchDecodeHM name val = bgroup name
159
- [ bench " Text" $ nf (decodeHMB proxyText) val
160
- , bench " Identity" $ nf (decodeHMB proxyT1) val
161
- , bench " Coerce" $ nf (decodeHMB proxyT2) val
162
- , bench " Parser" $ nf (decodeHMB proxyT3) val
163
- , bench " aeson-hackage" $ nf (decodeHMA proxyText) val
164
- , bench " Tagged Text" $ nf (decodeHMB $ proxyTagged proxyText) val
165
- , bench " Tagged Identity" $ nf (decodeHMB $ proxyTagged proxyT1) val
166
- , bench " Tagged Coerce" $ nf (decodeHMB $ proxyTagged proxyT2) val
167
- , bench " Tagged Parser" $ nf (decodeHMB $ proxyTagged proxyT3) val
147
+ [ bench " Text" $ nf (decodeHM proxyText) val
148
+ , bench " Identity" $ nf (decodeHM proxyT1) val
149
+ , bench " Coerce" $ nf (decodeHM proxyT2) val
150
+ , bench " Parser" $ nf (decodeHM proxyT3) val
151
+ , bench " Tagged Text" $ nf (decodeHM $ proxyTagged proxyText) val
152
+ , bench " Tagged Identity" $ nf (decodeHM $ proxyTagged proxyT1) val
153
+ , bench " Tagged Coerce" $ nf (decodeHM $ proxyTagged proxyT2) val
154
+ , bench " Tagged Parser" $ nf (decodeHM $ proxyTagged proxyT3) val
168
155
]
169
156
170
157
benchDecodeMap
171
158
:: String
172
159
-> LBS. ByteString
173
160
-> Benchmark
174
161
benchDecodeMap name val = bgroup name
175
- [ bench " Text" $ nf (decodeMapB proxyText) val
176
- , bench " Identity" $ nf (decodeMapB proxyT1) val
177
- , bench " Coerce" $ nf (decodeMapB proxyT2) val
178
- , bench " Parser" $ nf (decodeMapB proxyT3) val
179
- , bench " aeson-hackage" $ nf (decodeMapA proxyText) val
162
+ [ bench " Text" $ nf (decodeMap proxyText) val
163
+ , bench " Identity" $ nf (decodeMap proxyT1) val
164
+ , bench " Coerce" $ nf (decodeMap proxyT2) val
165
+ , bench " Parser" $ nf (decodeMap proxyT3) val
180
166
]
181
167
182
168
benchEncodeHM
183
169
:: String
184
170
-> HM. HashMap T. Text T. Text
185
171
-> Benchmark
186
172
benchEncodeHM name val = bgroup name
187
- [ bench " Text" $ nf B. encode val
188
- , bench " aeson-0.11" $ nf A. encode val
173
+ [ bench " Text" $ nf encode val
189
174
]
190
175
191
176
benchEncodeMap
192
177
:: String
193
178
-> HM. HashMap T. Text T. Text
194
179
-> Benchmark
195
180
benchEncodeMap name val = bgroup name
196
- [ bench " Text" $ nf B. encode val'
197
- , bench " aeson-0.11" $ nf A. encode val'
181
+ [ bench " Text" $ nf encode val'
198
182
]
199
183
where
200
184
val' :: M. Map T. Text T. Text
0 commit comments