File: ReadNumbers.hs

package info (click to toggle)
ghc 9.6.6-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, trixie
  • size: 158,216 kB
  • sloc: haskell: 648,228; ansic: 81,656; cpp: 11,808; javascript: 8,444; sh: 5,831; fortran: 3,527; python: 3,277; asm: 2,523; makefile: 2,298; yacc: 1,570; lisp: 532; xml: 196; perl: 145; csh: 2
file content (69 lines) | stat: -rw-r--r-- 2,078 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
-- | Read numbers from a file with a just a number on each line, find the
-- minimum of those numbers. The file contains different kinds of numbers:
--
-- * Decimals
--
-- * Hexadecimals
--
-- * Floating point numbers
--
-- * Floating point numbers in scientific notation
--
-- The different benchmarks will only take into account the values they can
-- parse.
--
-- Tested in this benchmark:
--
-- * Lexing/parsing of different numerical types
--
module Benchmarks.ReadNumbers
    ( initEnv
    , benchmark
    ) where

import Test.Tasty.Bench (Benchmark, bgroup, bench, whnf)
import Data.List (foldl')
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.IO as TL
import qualified Data.Text.Lazy.Read as TL
import qualified Data.Text.Read as T

type Env = ([T.Text], [TL.Text])

initEnv :: FilePath -> IO Env
initEnv fp = do
    t <- T.lines `fmap` T.readFile fp
    tl <- TL.lines `fmap` TL.readFile fp
    return (t, tl)

benchmark :: Env -> Benchmark
benchmark ~(t, tl) =
    bgroup "ReadNumbers"
        [ bench "DecimalText"     $ whnf (int . text (T.signed T.decimal)) t
        , bench "HexadecimalText" $ whnf (int . text (T.signed T.hexadecimal)) t
        , bench "DoubleText"      $ whnf (double . text T.double) t
        , bench "RationalText"    $ whnf (double . text T.rational) t

        , bench "DecimalLazyText" $
            whnf (int . text (TL.signed TL.decimal)) tl
        , bench "HexadecimalLazyText" $
            whnf (int . text (TL.signed TL.hexadecimal)) tl
        , bench "DoubleLazyText" $
            whnf (double . text TL.double) tl
        , bench "RationalLazyText" $
            whnf (double . text TL.rational) tl
        ]
  where
    -- Used for fixing types
    int :: Int -> Int
    int = id
    double :: Double -> Double
    double = id

text :: (Ord a, Num a) => (t -> Either String (a,t)) -> [t] -> a
text reader = foldl' go 1000000
  where
    go z t = case reader t of Left _       -> z
                              Right (n, _) -> min n z