File: bench.hs

package info (click to toggle)
haskell-generic-data 1.1.0.1-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 304 kB
  • sloc: haskell: 2,577; makefile: 6
file content (68 lines) | stat: -rw-r--r-- 1,508 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
{-# LANGUAGE
    DeriveAnyClass,
    DeriveGeneric,
    DerivingVia,
    DerivingStrategies,
    FlexibleInstances,
    ScopedTypeVariables,
    StandaloneDeriving,
    TypeApplications
  #-}

import Data.Semigroup (Sum(..))
import Text.Show (showParen, showString)

import Control.DeepSeq
import Test.Tasty.Bench

import Generic.Data
import Generic.Data.Microsurgery

data H  -- handwritten
data G  -- generic
data S  -- surgery

data T x = C { _a :: Sum Int, _b :: [Int] }
  deriving stock Generic

deriving via (Surgery Derecordify (T S)) instance Show (T S)

instance Show (T H) where
  showsPrec n (C a b) =
    showParen (n > 10)
      (showString "C "
        . showsPrec 11 a
        . showString " "
        . showsPrec 11 b)

deriving via (Generically (T G)) instance Semigroup (T G)
instance Semigroup (T H) where
  C a1 b1 <> C a2 b2 = C (a1 <> a2) (b1 <> b2)

deriving anyclass instance NFData (T G)

instance NFData (T H) where
  rnf (C a b) = rnf a `seq` rnf b `seq` ()

u :: forall x. T x
u = C 33 [99]

v :: forall x. T x
v = C 13 [14]

main :: IO ()
main = defaultMain
  [ bgroup "Show"
      [ bench "handwri" (nf show (u @H))
      , bench "surgery" (nf show (u @S))
      ]
  , bgroup "NFData"
      [ bench "handwri" (nf id (u @H))
      , bench "generic" (nf id (u @G))
      ]
  , bgroup "Semigroup"
      [ bench "baselin" (nf (uncurry (++)) ([99], [14 :: Int]))
      , bench "handwri" (nf (uncurry (<>)) (u @H, v))
      , bench "generic" (nf (uncurry (<>)) (u @G, v))
      ]
  ]