File: IntegralSpec.hs

package info (click to toggle)
haskell-text-show 3.10.5-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 1,148 kB
  • sloc: haskell: 8,817; ansic: 23; makefile: 6
file content (79 lines) | stat: -rw-r--r-- 2,434 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
{-# LANGUAGE CPP #-}

{-|
Module:      Spec.Data.IntegralSpec
Copyright:   (C) 2014-2017 Ryan Scott
License:     BSD-style (see the file LICENSE)
Maintainer:  Ryan Scott
Stability:   Provisional
Portability: GHC

@hspec@ tests for integral data types.
-}
module Spec.Data.IntegralSpec (main, spec) where

import Data.Int (Int8, Int16, Int32, Int64)
import Data.Proxy.Compat (Proxy(..))
import Data.Word (Word8, Word16, Word32, Word64)

import Prelude ()
import Prelude.Compat

import Spec.Utils (matchesTextShowSpec)

import Test.Hspec (Spec, describe, hspec, parallel)

#if !defined(mingw32_HOST_OS) && MIN_VERSION_text(1,0,0)
import Data.Char (intToDigit)

import Numeric (showIntAtBase)

import Test.QuickCheck (Gen, arbitrary, getNonNegative, suchThat)
import Test.Hspec (Expectation, shouldBe)
import Test.Hspec.QuickCheck (prop)

import TextShow (fromString)
import TextShow.Data.Integral (showbIntAtBase)
#endif

main :: IO ()
main = hspec spec

spec :: Spec
spec = parallel $ do
    describe "Int" $
        matchesTextShowSpec (Proxy :: Proxy Int)
    describe "Int8" $
        matchesTextShowSpec (Proxy :: Proxy Int8)
    describe "Int16" $
        matchesTextShowSpec (Proxy :: Proxy Int16)
    describe "Int32" $
        matchesTextShowSpec (Proxy :: Proxy Int32)
    describe "Int64" $
        matchesTextShowSpec (Proxy :: Proxy Int64)
    describe "Integer" $
        matchesTextShowSpec (Proxy :: Proxy Integer)
    describe "Word" $
        matchesTextShowSpec (Proxy :: Proxy Word)
    describe "Word8" $
        matchesTextShowSpec (Proxy :: Proxy Word8)
    describe "Word16" $
        matchesTextShowSpec (Proxy :: Proxy Word16)
    describe "Word32" $
        matchesTextShowSpec (Proxy :: Proxy Word32)
    describe "Word64" $
        matchesTextShowSpec (Proxy :: Proxy Word64)
#if !defined(mingw32_HOST_OS) && MIN_VERSION_text(1,0,0)
-- TODO: Figure out why this diverges on Windows
    describe "showbIntAtBase" $
        prop "has the same output as showIntAtBase" prop_showIntAtBase
#endif

-- | Verifies 'showIntAtBase' and 'showbIntAtBase' generate the same output.
#if !defined(mingw32_HOST_OS) && MIN_VERSION_text(1,0,0)
prop_showIntAtBase :: Gen Expectation
prop_showIntAtBase = do
    base <- arbitrary `suchThat` \b -> 1 < b && b <= 16
    i    <- getNonNegative <$> arbitrary :: Gen Int
    pure $ fromString (showIntAtBase base intToDigit i "") `shouldBe` showbIntAtBase base intToDigit i
#endif