module Bit where
+import Test.QuickCheck
+
+
data Bit = None | Zero | One
deriving (Eq)
show Zero = "0"
show One = "1"
-
+
+instance Arbitrary Bit where
+ arbitrary = elements [ Zero, One ]
+ coarbitrary _ = variant 0
+
+
bit_to_int :: Bit -> Int
bit_to_int None = -1
bit_to_int Zero = 0
import Data.List (nubBy)
import Test.HUnit
+import Test.QuickCheck
import IPv4Address
import ListUtils
show cidr = (show (ipv4address cidr)) ++ "/" ++ (show (maskbits cidr))
+instance Arbitrary Cidr where
+ arbitrary = do
+ ipv4 <- arbitrary :: Gen IPv4Address
+ mask <- arbitrary :: Gen Maskbits
+ return (Cidr ipv4 mask)
+
+ coarbitrary _ = variant 0
+
+
-- Two CIDR ranges are equivalent if they have the same network bits
-- and the masks are the same.
equivalent :: Cidr -> Cidr -> Bool
) where
import Test.HUnit
+import Test.QuickCheck
import qualified Bit as B
import Maskbits
oct4 = (octet4 addr)
+instance Arbitrary IPv4Address where
+ arbitrary = do
+ oct1 <- arbitrary :: Gen Octet
+ oct2 <- arbitrary :: Gen Octet
+ oct3 <- arbitrary :: Gen Octet
+ oct4 <- arbitrary :: Gen Octet
+ return (IPv4Address oct1 oct2 oct3 oct4)
+
+ coarbitrary _ = variant 0
+
+
+
-- We don't export our constructor so this function is the only
-- way to construct an address from octets. As a result, we can
-- return IPv4Address.None in response to being passed one of more
maskbits_from_string
) where
+import Test.QuickCheck
+
-- A type representing the number of bits in a CIDR netmask.
data Maskbits = None
| Zero
show ThirtyTwo = "32"
+instance Arbitrary Maskbits where
+ arbitrary = elements [ Zero,
+ One,
+ Two,
+ Three,
+ Four,
+ Five,
+ Six,
+ Seven,
+ Eight,
+ Nine,
+ Ten,
+ Eleven,
+ Twelve,
+ Thirteen,
+ Fourteen,
+ Fifteen,
+ Sixteen,
+ Seventeen,
+ Eighteen,
+ Nineteen,
+ Twenty,
+ TwentyOne,
+ TwentyTwo,
+ TwentyThree,
+ TwentyFour,
+ TwentyFive,
+ TwentySix,
+ TwentySeven,
+ TwentyEight,
+ TwentyNine,
+ Thirty,
+ ThirtyOne,
+ ThirtyTwo ]
+
+ coarbitrary _ = variant 0
+
+
-- There are only 32 bits in an IPv4 address, so there
-- can't be more bits than that in the mask.
module Octet where
import Test.HUnit
+import Test.QuickCheck
import Bit
show oct = show (octet_to_int oct)
+instance Arbitrary Octet where
+ arbitrary = do
+ a1 <- arbitrary :: Gen Bit
+ a2 <- arbitrary :: Gen Bit
+ a3 <- arbitrary :: Gen Bit
+ a4 <- arbitrary :: Gen Bit
+ a5 <- arbitrary :: Gen Bit
+ a6 <- arbitrary :: Gen Bit
+ a7 <- arbitrary :: Gen Bit
+ a8 <- arbitrary :: Gen Bit
+ return (Octet a1 a2 a3 a4 a5 a6 a7 a8)
+
+ coarbitrary _ = variant 0
+
+
-- Convert each bit to its integer value, and multiply by the
-- appropriate power of two. Sum them up, and we should get an integer
-- between 0 and 255.