File: TestNum.hs

package info (click to toggle)
haskell-convertible 1.1.1.0-8
  • links: PTS, VCS
  • area: main
  • in suites: buster
  • size: 216 kB
  • sloc: haskell: 2,230; makefile: 26
file content (104 lines) | stat: -rw-r--r-- 4,309 bytes parent folder | download | duplicates (5)
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
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
{-
Copyright (C) 2009-2011 John Goerzen <jgoerzen@complete.org>

All rights reserved.

For license and copyright information, see the file LICENSE
-}

module TestNum where
import TestInfrastructure
import Data.Convertible
import Test.QuickCheck
import Test.QuickCheck.Tools
import qualified Test.QuickCheck.Property as P
import Data.Word

prop_int_to_integer :: Int -> P.Result
prop_int_to_integer x =
    safeConvert x @?= Right ((fromIntegral x)::Integer)

prop_integer_to_int_pass :: Integer -> Property
prop_integer_to_int_pass x =
    (x <= fromIntegral (maxBound :: Int)) &&
    (x >= fromIntegral (minBound :: Int)) ==> 
                                          safeConvert x @?= Right ((fromIntegral x)::Int)

prop_integer_to_word8 :: Integer -> P.Result
prop_integer_to_word8 x =
    safeConvert x @?= if x >= fromIntegral (minBound :: Word8) &&
                         x <= fromIntegral (maxBound :: Word8)
                      then Right ((fromIntegral x)::Word8)
                      else Left $ ConvertError (show x) "Integer" "Word8" "Input value outside of bounds: (0,255)"

prop_integer_to_word8_safe :: Integer -> Property
prop_integer_to_word8_safe x =
    x <= fromIntegral (maxBound :: Word8) &&
    x >= fromIntegral (minBound :: Word8) ==>
      safeConvert x @?= Right ((fromIntegral x)::Word8)

prop_integer_to_word8_unsafe :: Integer -> Property
prop_integer_to_word8_unsafe x =
    x < fromIntegral (minBound :: Word8) ||
    x > fromIntegral (maxBound :: Word8) ==>
      ((safeConvert x)::ConvertResult Word8) @?= (Left $ ConvertError (show x) "Integer" "Word8" "Input value outside of bounds: (0,255)")

prop_double_to_word8 :: Double -> P.Result
prop_double_to_word8 x =
    safeConvert x @?= if truncate x >= toInteger (minBound :: Word8) &&
                         truncate x <= toInteger (maxBound :: Word8)
                      then Right ((truncate x)::Word8)
                      else Left $ ConvertError (show x) "Double" "Word8" "Input value outside of bounds: (0,255)"

prop_double_to_word8_safe :: Double -> Property
prop_double_to_word8_safe x =
    x <= fromIntegral (maxBound :: Word8) &&
    x >= fromIntegral (minBound :: Word8) ==>
      safeConvert x @?= Right ((truncate x)::Word8)

prop_double_to_word8_unsafe :: Double -> Property
prop_double_to_word8_unsafe x =
    truncate x < toInteger (minBound :: Word8) ||
    truncate x > toInteger (maxBound :: Word8) ==>
      ((safeConvert x)::ConvertResult Word8) @?= (Left $ ConvertError (show x) "Double" "Word8" "Input value outside of bounds: (0,255)")

propIntDouble :: Int -> P.Result
propIntDouble x =
    safeConvert x @?= Right ((fromIntegral x)::Double)

propIntChar :: Int -> P.Result
propIntChar x =
    safeConvert x @?= if x >= fromEnum (minBound :: Char) &&
                         x <= fromEnum (maxBound :: Char)
                      then Right ((toEnum x)::Char)
                      else Left $ ConvertError (show x) "Int" "Char" "Input value outside of bounds: ('\\NUL','\\1114111')"

propCharInt :: Char -> P.Result
propCharInt c =
    safeConvert c @?= Right ((fromEnum c)::Int)
    where x = fromEnum c

propIntIntegerInt :: Int -> P.Result
propIntIntegerInt x =
    Right x @=? do r1 <- ((safeConvert x)::ConvertResult Integer)
                   ((safeConvert r1)::ConvertResult Int)
    
propDoubleRationalDouble :: Double -> P.Result
propDoubleRationalDouble x =
    Right x @=? do r1 <- ((safeConvert x)::ConvertResult Rational)
                   ((safeConvert r1)::ConvertResult Double)

allt = [q "Int -> Integer" prop_int_to_integer,
        q "Integer -> Int (safe bounds)" prop_integer_to_int_pass,
        q "Integer -> Word8 (general)" prop_integer_to_word8,
        q "Integer -> Word8 (safe bounds)" prop_integer_to_word8_safe,
        q "Integer -> Word8 (unsafe bounds)" prop_integer_to_word8_unsafe,
        q "Double -> Word8 (general)" prop_double_to_word8,
        q "Double -> Word8 (safe bounds)" prop_double_to_word8_safe,
        q "Double -> Word8 (unsafe bounds)" prop_double_to_word8_unsafe,
        q "Int -> Double" propIntDouble,
        q "Int -> Char" propIntChar,
        q "Char -> Int" propCharInt,
        q "identity Int -> Integer -> Int" propIntIntegerInt,
        q "identity Double -> Rational -> Double" propDoubleRationalDouble
       ]