File: bench.hs

package info (click to toggle)
haskell-string-interpolate 0.3.4.0-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 200 kB
  • sloc: haskell: 1,452; makefile: 6
file content (230 lines) | stat: -rw-r--r-- 7,719 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
{-# LANGUAGE CPP               #-}
{-# LANGUAGE ConstraintKinds   #-}
{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE GADTs             #-}
{-# LANGUAGE KindSignatures    #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PackageImports    #-}
{-# LANGUAGE QuasiQuotes       #-}
{-# LANGUAGE RankNTypes        #-}
{-# LANGUAGE TypeApplications  #-}
{-# LANGUAGE TypeOperators     #-}

import Criterion      ( Benchmark, bench, bgroup, env, nf )
import Criterion.Main ( defaultMain )

import qualified Data.ByteString      as B
import qualified Data.ByteString.Lazy as LB
import qualified Data.String          as S
import qualified Data.Text            as T
import qualified Data.Text.Lazy       as LT

import qualified "string-interpolate" Data.String.Interpolate            as SI
import qualified "string-interpolate" Data.String.Interpolate.Conversion as SI
import qualified "interpolate" Data.String.Interpolate.IsString          as I
import           "formatting" Formatting                                 ( (%) )
import qualified "formatting" Formatting                                 as F
import qualified "formatting" Formatting.ShortFormatters                 as F
import qualified "neat-interpolation" NeatInterpolation                  as NI

import Control.DeepSeq

import Test.QuickCheck

#ifdef EXTENDED_BENCHMARKS
import "Interpolation" Data.String.Interpolation                as N
import "interpolatedstring-perl6" Text.InterpolatedString.Perl6 as P
#endif

type SIInterpolatable str flag =
  ( SI.IsCustomSink str ~ flag
  , SI.InterpSink flag str
  , SI.Interpolatable flag str str
  , SI.Interpolatable flag Int str
  , SI.Interpolatable flag Bool str
  )

type AllInterpolatable str flag =
  ( SIInterpolatable str flag
  , Show str
  , S.IsString str
  , Monoid str
  )

--------------------
-- string-interpolate
--------------------

singleInterpSI :: SIInterpolatable str flag => str -> str
singleInterpSI str = [SI.i|A fine day to die, #{str}.|]

multiInterpSI :: SIInterpolatable str flag => (Int, str, Bool) -> str
multiInterpSI (x, y, z) = [SI.i| foo #{x} bar #{y} baz #{z} quux |]

--------------------
-- interpolate
--------------------

singleInterpI :: (Show str, S.IsString str) => str -> str
singleInterpI str = [I.i|A fine day to die, #{str}.|]

multiInterpI :: (Show str, S.IsString str) => (Int, str, Bool) -> str
multiInterpI (x, y, z) = [I.i| foo #{x} bar #{y} baz #{z} quux |]

--------------------
-- formatting
--------------------

stringF :: String -> String
stringF = F.formatToString ("A fine day to die, " % F.s % ".")

multiStringF :: (Int, String, Bool) -> String
multiStringF (x, y, z) =
  F.formatToString (" foo " % F.d % " bar " % F.s % " baz " % F.sh % " quux ") x y z

textF :: T.Text -> T.Text
textF = F.sformat ("A fine day to die, " % F.st % ".")

multiTextF :: (Int, T.Text, Bool) -> T.Text
multiTextF (x, y, z) =
  F.sformat (" foo " % F.d % " bar " % F.st % " baz " % F.sh % " quux ") x y z

lazyTextF :: LT.Text -> LT.Text
lazyTextF = F.format ("A find day to die, " % F.t % ".")

multiLazyTextF :: (Int, LT.Text, Bool) -> LT.Text
multiLazyTextF (x, y, z) =
  F.format (" foo " % F.d % " bar " % F.t % " baz " % F.sh % " quux ") x y z

--------------------
-- neat-interpolation
--------------------

textNI :: T.Text -> T.Text
textNI t = [NI.text|A fine day to die, $t.|]

multiTextNI :: (Int, T.Text, Bool) -> T.Text
multiTextNI (x, y, z) =
  let x' = T.pack $ show x
      z' = T.pack $ show z
  in [NI.text| foo $x' bar $y baz $z' quux |]

#ifdef EXTENDED_BENCHMARKS

--------------------
-- Interpolation
--------------------

singleInterpN :: (Monoid str, S.IsString str) => str -> str
singleInterpN t = [str|A fine day to die, $t$.|]

multiInterpN ::(Monoid str, S.IsString str) => (Int, str, Bool) -> str
multiInterpN (x, y, z) = [str| foo $:x$ bar $y$ baz $:z$ quux |]

--------------------
-- interpolatedstring-perl6
--------------------

singleInterpP :: (Monoid str, S.IsString str) => str -> str
singleInterpP t = [qc|A fine day to die, {t}.|]

multiInterpP :: (Monoid str, S.IsString str) => (Int, str, Bool) -> str
multiInterpP (x, y, z) = [qc| foo {x} bar {y} baz {z} quux |]

#endif

--------------------
-- BENCHMARK GROUPS
--------------------

singleInterpBenches :: AllInterpolatable str flag
                    => [(String, (str -> str))]
singleInterpBenches =
  [ ("string-interpolate"      , singleInterpSI)
  , ("interpolate"             , singleInterpI)
#ifdef EXTENDED_BENCHMARKS
  , ("interpolatedstring-perl6", singleInterpP)
  , ("Interpolation"           , singleInterpN)
#endif
  ]

multiInterpBenches :: AllInterpolatable str flag
                   => [(String, ((Int, str, Bool) -> str))]
multiInterpBenches =
  [ ("string-interpolate"      , multiInterpSI)
  , ("interpolate"             , multiInterpI)
#ifdef EXTENDED_BENCHMARKS
  , ("interpolatedstring-perl6", multiInterpP)
  , ("Interpolation"           , multiInterpN)
#endif
  ]

main :: IO ()
main = defaultMain $
  [ benches @String "Small Strings Bench" "William" $
      singleInterpBenches ++
        [ ("formatting", stringF) ]
  , benches @T.Text "Small Text Bench" "William" $
      singleInterpBenches ++
        [ ("formatting"        , textF)
        , ("neat-interpolation", textNI)
        ]
  , benches @LT.Text "Small Lazy Text Bench" "William" $
      singleInterpBenches ++
        [ ("formatting", lazyTextF) ]
  , benches @B.ByteString "Small ByteStrings Bench" "William" $
      singleInterpBenches
  , benches @LB.ByteString "Small Lazy ByteStrings Bench" "William" $
      singleInterpBenches
  , benches @String "Multiple Interpolations String Bench" (42, "CATALLAXY", True) $
      multiInterpBenches ++
        [ ("formatting", multiStringF) ]
  , benches @T.Text "Multiple Interpolations Text Bench" (42, "CATALLAXY", True) $
      multiInterpBenches ++
        [ ("formatting"        , multiTextF)
        , ("neat-interpolation", multiTextNI)
        ]
  , benches @LT.Text "Multiple Interpolations Lazy Text Bench" (42, "CATALLAXY", True) $
      multiInterpBenches ++
        [ ("formatting", multiLazyTextF) ]
  , benches @B.ByteString "Multiple Interpolations ByteString Bench" (42, "CATALLAXY", True) $
      multiInterpBenches
  , benches @LB.ByteString "Multiple Interpolations Lazy ByteString Bench" (42, "CATALLAXY", True) $
      multiInterpBenches
  , env largeishText $ \ ~t -> benches @T.Text "Largeish Text Bench" t $
      singleInterpBenches ++
        [ ("formatting"        , textF)
        , ("neat-interpolation", textNI)
        ]
  , env largeishLazyText $ \ ~lt -> benches @LT.Text "Largeish Lazy Text Bench" lt $
      singleInterpBenches ++
        [ ("formatting", lazyTextF) ]
  , env largeishByteString $ \ ~bs -> benches @B.ByteString "Largeish ByteString Bench" bs $
      singleInterpBenches
  , env largeishLazyByteString $ \ ~lbs -> benches @LB.ByteString "Largeish Lazy ByteString Bench" lbs $
      singleInterpBenches
  ]

largeishText :: IO T.Text
largeishText =
  generate $ T.pack <$> Prelude.take 100000 <$> infiniteListOf arbitrary

largeishLazyText :: IO LT.Text
largeishLazyText =
  generate $ LT.pack <$> Prelude.take 100000 <$> infiniteListOf arbitrary

largeishByteString :: IO B.ByteString
largeishByteString =
  generate $ B.pack <$> Prelude.take 100000 <$> infiniteListOf arbitrary

largeishLazyByteString :: IO LB.ByteString
largeishLazyByteString =
  generate $ LB.pack <$> Prelude.take 100000 <$> infiniteListOf arbitrary

--------------------
-- BENCHMARK UTIL
--------------------

benches :: forall b a. NFData b => String -> a -> [(String, a -> b)] -> Benchmark
benches groupname arg fs = bgroup groupname (fmap benchF fs)
  where benchF (bname, f) = bench bname $ nf f arg