instance Arbitrary Bit where
arbitrary = elements [ Zero, One ]
- coarbitrary _ = variant 0
bit_to_int :: Bit -> Int
mask <- arbitrary :: Gen Maskbits
return (Cidr ipv4 mask)
- coarbitrary _ = variant 0
instance Eq Cidr where
cidr1 == cidr2 = (cidr1 `equivalent` cidr2)
oct4 <- arbitrary :: Gen Octet
return (IPv4Address oct1 oct2 oct3 oct4)
- coarbitrary _ = variant 0
-
instance Maskable IPv4Address where
ThirtyOne,
ThirtyTwo ]
- coarbitrary _ = variant 0
-
-- There are only 32 bits in an IPv4 address, so there
a8 <- arbitrary :: Gen Bit
return (Octet a1 a2 a3 a4 a5 a6 a7 a8)
- coarbitrary _ = variant 0
-
instance Maskable Octet where
apply_mask _ Maskbits.None _ = Octet.None
+{-# LANGUAGE NoMonomorphismRestriction #-}
import Test.HUnit
-import Test.QuickCheck.Batch
+import Test.QuickCheck (Args(..), quickCheckWith, stdArgs)
import Cidr (cidr_tests,
prop_all_cidrs_contain_themselves,
ipv4address_tests,
octet_tests])
--- QuickCheck options
-options = TestOptions { no_of_tests = 1000,
- length_of_tests = 0, -- No time limit on tests.
- debug_tests = False }
-
main :: IO ()
main = do
putStrLn "HUnit"
putStrLn "QuickCheck"
putStrLn "----------"
- runTests "Cidr" options [ run prop_all_cidrs_contain_themselves,
- run prop_contains_proper_intransitive]
+ qc prop_all_cidrs_contain_themselves
+ qc prop_contains_proper_intransitive
+ where
+ args :: Args
+ args = stdArgs { maxDiscard = 5000 }
+ qc = quickCheckWith args