File: Cut.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 (70 lines) | stat: -rw-r--r-- 2,139 bytes parent folder | download | duplicates (4)
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
-- | Cut into a file, selecting certain columns (e.g. columns 10 to 40)
--
-- Tested in this benchmark:
--
-- * Reading the file
--
-- * Splitting into lines
--
-- * Taking a number of characters from the lines
--
-- * Joining the lines
--
-- * Writing back to a handle
--
module Benchmarks.Programs.Cut
    ( benchmark
    ) where

import Test.Tasty.Bench (Benchmark, bgroup, bench, whnfIO)
import System.IO (Handle)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import qualified Data.Text.Lazy.IO as TL

benchmark :: FilePath -> Handle -> Int -> Int -> Benchmark
benchmark p sink from to = bgroup "Cut"
    [ bench' "Text" text
    , bench' "LazyText" lazyText
    , bench' "TextByteString" textByteString
    , bench' "LazyTextByteString" lazyTextByteString
    ]
  where
    bench' n s = bench n $ whnfIO (s p sink from to)

text :: FilePath -> Handle -> Int -> Int -> IO ()
text fp sink from to = do
    t <- T.readFile fp
    T.hPutStr sink $ cut t
  where
    cut = T.unlines . map (T.take (to - from) . T.drop from) . T.lines

lazyText :: FilePath -> Handle -> Int -> Int -> IO ()
lazyText fp sink from to = do
    t <- TL.readFile fp
    TL.hPutStr sink $ cut t
  where
    cut = TL.unlines . map (TL.take (to' - from') . TL.drop from') . TL.lines
    from' = fromIntegral from
    to' = fromIntegral to

textByteString :: FilePath -> Handle -> Int -> Int -> IO ()
textByteString fp sink from to = do
    t <- T.decodeUtf8 `fmap` B.readFile fp
    B.hPutStr sink $ T.encodeUtf8 $ cut t
  where
    cut = T.unlines . map (T.take (to - from) . T.drop from) . T.lines

lazyTextByteString :: FilePath -> Handle -> Int -> Int -> IO ()
lazyTextByteString fp sink from to = do
    t <- TL.decodeUtf8 `fmap` BL.readFile fp
    BL.hPutStr sink $ TL.encodeUtf8 $ cut t
  where
    cut = TL.unlines . map (TL.take (to' - from') . TL.drop from') . TL.lines
    from' = fromIntegral from
    to' = fromIntegral to