File: SaySpec.hs

package info (click to toggle)
haskell-say 0.1.0.1-6
  • links: PTS
  • area: main
  • in suites: sid, trixie
  • size: 100 kB
  • sloc: haskell: 263; makefile: 6
file content (71 lines) | stat: -rw-r--r-- 2,013 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
71
{-# LANGUAGE CPP #-}
module SaySpec (spec) where

import Test.Hspec
import Test.Hspec.QuickCheck
import Say
import Control.Monad (forM_)
import Data.Text (pack)
import qualified Data.Text.IO as T
import System.IO
import UnliftIO.Temporary (withSystemTempFile)
import qualified Data.ByteString as S
import Data.List (nub)

encodings :: [TextEncoding]
encodings = [utf8, utf16le, utf32be
#if MIN_VERSION_base(4, 4, 0)
    , char8
#endif
    ]

newlines :: [NewlineMode]
newlines = nub
    [ noNewlineTranslation
    , universalNewlineMode
    , nativeNewlineMode
    , NewlineMode CRLF CRLF
    ]

bufferings :: [BufferMode]
bufferings =
    [ NoBuffering
    , LineBuffering
    , BlockBuffering Nothing
    , BlockBuffering $ Just 10
    , BlockBuffering $ Just 2048
    , BlockBuffering $ Just 30000
    ]

alts :: [(String, Handle -> String -> IO ())]
alts =
    [ ("String", hPutStrLn)
    , ("Text", \h -> T.hPutStrLn h . pack)
    ]

spec :: Spec
spec = do
  forM_ encodings $ \encoding -> describe ("Encoding: " ++ show encoding) $
    forM_ newlines $ \newline -> describe ("Newline: " ++ show newline) $
    forM_ bufferings $ \buffering -> describe ("Buffering: " ++ show buffering) $
    forM_ alts $ \(altName, altFunc) -> describe ("Versus: " ++ altName) $ do
      let prepHandle h = do
            hSetEncoding h encoding
            hSetNewlineMode h newline
            hSetBuffering h buffering

          test str =
            withSystemTempFile "say" $ \fpSay handleSay ->
            withSystemTempFile "alt" $ \fpAlt handleAlt -> do
              forM_ [(handleSay, \h -> hSay h . pack), (handleAlt, altFunc)] $ \(h, f) -> do
                  prepHandle h
                  f h str
                  hClose h
              bsSay <- S.readFile fpSay
              bsAlt <- S.readFile fpAlt
              bsSay `shouldBe` bsAlt

      prop "matches" test

      forM_ [10, 20, 100, 1000, 2047, 2048, 2049, 10000] $ \size -> do
          it ("size: " ++ show size) $ test $ replicate size 'A'