module IPv4Address( IPv4Address(..), ipv4address_properties, ipv4address_tests, most_sig_bit_different ) where import Data.Int ( Int32, Int64 ) import Data.Word ( Word32 ) import Test.Tasty ( TestTree, testGroup ) import Test.Tasty.HUnit ( (@?=), testCase ) import Test.Tasty.QuickCheck ( Arbitrary( arbitrary ), Gen, Large, Property, Small, (==>), testProperty ) import Maskable ( Maskable( apply_mask) ) import Maskbits ( Maskbits( 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 ) ) import Octet ( Octet( b1, b2, b3, b4, b5, b6, b7, b8) ) data IPv4Address = IPv4Address { octet1 :: Octet, octet2 :: Octet, octet3 :: Octet, octet4 :: Octet } deriving (Eq, Ord) instance Show IPv4Address where show addr = concat [(show oct1) ++ ".", (show oct2) ++ ".", (show oct3) ++ ".", (show oct4)] where oct1 = (octet1 addr) oct2 = (octet2 addr) oct3 = (octet3 addr) 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) instance Maskable IPv4Address where apply_mask addr mask bit = apply_mask' mask where oct1 = octet1 addr oct2 = octet2 addr oct3 = octet3 addr oct4 = octet4 addr -- A copy of 'addr' with the fourth octet zeroed (or oned). new_addr1 = addr { octet4 = (apply_mask oct4 Zero bit) } -- Likewise for new_addr1's third octet. new_addr2 = new_addr1 { octet3 = (apply_mask oct3 Zero bit) } -- And new_addr2's second octet. new_addr3 = new_addr2 { octet2 = (apply_mask oct2 Zero bit) } -- This helper function allows us to pattern-match cleanly. apply_mask' :: Maskbits -> IPv4Address apply_mask' ThirtyTwo = addr apply_mask' ThirtyOne = addr { octet4 = (apply_mask oct4 Seven bit) } apply_mask' Thirty = addr { octet4 = (apply_mask oct4 Six bit) } apply_mask' TwentyNine = addr { octet4 = (apply_mask oct4 Five bit) } apply_mask' TwentyEight = addr { octet4 = (apply_mask oct4 Four bit) } apply_mask' TwentySeven = addr { octet4 = (apply_mask oct4 Three bit) } apply_mask' TwentySix = addr { octet4 = (apply_mask oct4 Two bit) } apply_mask' TwentyFive = addr { octet4 = (apply_mask oct4 One bit) } apply_mask' TwentyFour = new_addr1 apply_mask' TwentyThree = new_addr1 { octet3 = (apply_mask oct3 Seven bit) } apply_mask' TwentyTwo = new_addr1 { octet3 = (apply_mask oct3 Six bit) } apply_mask' TwentyOne = new_addr1 { octet3 = (apply_mask oct3 Five bit) } apply_mask' Twenty = new_addr1 { octet3 = (apply_mask oct3 Four bit) } apply_mask' Nineteen = new_addr1 { octet3 = (apply_mask oct3 Three bit) } apply_mask' Eighteen = new_addr1 { octet3 = (apply_mask oct3 Two bit) } apply_mask' Seventeen = new_addr1 { octet3 = (apply_mask oct3 One bit) } apply_mask' Sixteen = new_addr2 apply_mask' Fifteen = new_addr2 { octet2 = (apply_mask oct2 Seven bit) } apply_mask' Fourteen = new_addr2 { octet2 = (apply_mask oct2 Six bit) } apply_mask' Thirteen = new_addr2 { octet2 = (apply_mask oct2 Five bit) } apply_mask' Twelve = new_addr2 { octet2 = (apply_mask oct2 Four bit) } apply_mask' Eleven = new_addr2 { octet2 = (apply_mask oct2 Three bit) } apply_mask' Ten = new_addr2 { octet2 = (apply_mask oct2 Two bit) } apply_mask' Nine = new_addr2 { octet2 = (apply_mask oct2 One bit) } apply_mask' Eight = new_addr3 { octet2 = (apply_mask oct2 Zero bit) } apply_mask' Seven = new_addr3 { octet1 = (apply_mask oct1 Seven bit) } apply_mask' Six = new_addr3 { octet1 = (apply_mask oct1 Six bit) } apply_mask' Five = new_addr3 { octet1 = (apply_mask oct1 Five bit) } apply_mask' Four = new_addr3 { octet1 = (apply_mask oct1 Four bit) } apply_mask' Three = new_addr3 { octet1 = (apply_mask oct1 Three bit) } apply_mask' Two = new_addr3 { octet1 = (apply_mask oct1 Two bit) } apply_mask' One = new_addr3 { octet1 = (apply_mask oct1 One bit) } apply_mask' Zero = new_addr3 { octet1 = (apply_mask oct1 Zero bit) } instance Bounded IPv4Address where -- | The minimum possible IPv4 address, 0.0.0.0. minBound = IPv4Address minBound minBound minBound minBound -- | The maximum possible IPv4 address, 255.255.255.255. maxBound = IPv4Address maxBound maxBound maxBound maxBound instance Enum IPv4Address where -- | Convert an 'Int' @x@ to an 'IPv4Address'. Each octet of @x@ is -- right-shifted by the appropriate number of bits, and the fractional -- part is dropped. toEnum signed_x = IPv4Address oct1 oct2 oct3 oct4 where -- Convert the input Int to a Word32 before we proceed. On x86, -- the Int that we get could be negative (half of all IP -- addresses correspond to negative numbers), and then the magic -- below doesn't work. The Word32 type is unsigned, so we do the -- math on that and then convert everything back to Int later on -- once we have four much-smaller non-negative numbers. x = fromIntegral signed_x :: Word32 -- Chop off the higher octets. x1 = x `mod` 2^32, would be -- redundant. x2 = x `mod` (2 ^ (24 :: Integer)) x3 = x `mod` (2 ^ (16 :: Integer)) x4 = (fromIntegral $ x `mod` (2 ^ (8 :: Integer))) :: Int -- Perform right-shifts. x4 doesn't need a shift. shifted_x1 = (fromIntegral $ x `quot` (2 ^ (24 :: Integer))) :: Int shifted_x2 = (fromIntegral $ x2 `quot` (2 ^ (16 :: Integer))) :: Int shifted_x3 = (fromIntegral $ x3 `quot` (2 ^ (8 :: Integer))) :: Int oct1 = toEnum shifted_x1 :: Octet oct2 = toEnum shifted_x2 :: Octet oct3 = toEnum shifted_x3 :: Octet oct4 = toEnum x4 :: Octet -- | Convert @addr@ to an 'Int' by converting each octet to an 'Int' -- and shifting the result to the left by 0,8.16, or 24 bits. fromEnum addr = (shifted_oct1) + (shifted_oct2) + (shifted_oct3) + oct4 where oct1 = fromEnum (octet1 addr) oct2 = fromEnum (octet2 addr) oct3 = fromEnum (octet3 addr) oct4 = fromEnum (octet4 addr) shifted_oct1 = oct1 * (2 ^ (24 :: Integer)) shifted_oct2 = oct2 * (2 ^ (16 :: Integer)) shifted_oct3 = oct3 * (2 ^ (8 :: Integer)) -- | Given two addresses, find the number of the most significant bit -- where they differ. If the addresses are the same, return -- Maskbits.Zero. most_sig_bit_different :: IPv4Address -> IPv4Address -> Maskbits most_sig_bit_different addr1 addr2 | addr1 == addr2 = Maskbits.Zero | m1 /= n1 = Maskbits.One | m2 /= n2 = Two | m3 /= n3 = Three | m4 /= n4 = Four | m5 /= n5 = Five | m6 /= n6 = Six | m7 /= n7 = Seven | m8 /= n8 = Eight | m9 /= n9 = Nine | m10 /= n10 = Ten | m11 /= n11 = Eleven | m12 /= n12 = Twelve | m13 /= n13 = Thirteen | m14 /= n14 = Fourteen | m15 /= n15 = Fifteen | m16 /= n16 = Sixteen | m17 /= n17 = Seventeen | m18 /= n18 = Eighteen | m19 /= n19 = Nineteen | m20 /= n20 = Twenty | m21 /= n21 = TwentyOne | m22 /= n22 = TwentyTwo | m23 /= n23 = TwentyThree | m24 /= n24 = TwentyFour | m25 /= n25 = TwentyFive | m26 /= n26 = TwentySix | m27 /= n27 = TwentySeven | m28 /= n28 = TwentyEight | m29 /= n29 = TwentyNine | m30 /= n30 = Thirty | m31 /= n31 = ThirtyOne | m32 /= n32 = ThirtyTwo | otherwise = Maskbits.Zero where m1 = (b1 oct1a) m2 = (b2 oct1a) m3 = (b3 oct1a) m4 = (b4 oct1a) m5 = (b5 oct1a) m6 = (b6 oct1a) m7 = (b7 oct1a) m8 = (b8 oct1a) m9 = (b1 oct2a) m10 = (b2 oct2a) m11 = (b3 oct2a) m12 = (b4 oct2a) m13 = (b5 oct2a) m14 = (b6 oct2a) m15 = (b7 oct2a) m16 = (b8 oct2a) m17 = (b1 oct3a) m18 = (b2 oct3a) m19 = (b3 oct3a) m20 = (b4 oct3a) m21 = (b5 oct3a) m22 = (b6 oct3a) m23 = (b7 oct3a) m24 = (b8 oct3a) m25 = (b1 oct4a) m26 = (b2 oct4a) m27 = (b3 oct4a) m28 = (b4 oct4a) m29 = (b5 oct4a) m30 = (b6 oct4a) m31 = (b7 oct4a) m32 = (b8 oct4a) oct1a = (octet1 addr1) oct2a = (octet2 addr1) oct3a = (octet3 addr1) oct4a = (octet4 addr1) n1 = (b1 oct1b) n2 = (b2 oct1b) n3 = (b3 oct1b) n4 = (b4 oct1b) n5 = (b5 oct1b) n6 = (b6 oct1b) n7 = (b7 oct1b) n8 = (b8 oct1b) n9 = (b1 oct2b) n10 = (b2 oct2b) n11 = (b3 oct2b) n12 = (b4 oct2b) n13 = (b5 oct2b) n14 = (b6 oct2b) n15 = (b7 oct2b) n16 = (b8 oct2b) n17 = (b1 oct3b) n18 = (b2 oct3b) n19 = (b3 oct3b) n20 = (b4 oct3b) n21 = (b5 oct3b) n22 = (b6 oct3b) n23 = (b7 oct3b) n24 = (b8 oct3b) n25 = (b1 oct4b) n26 = (b2 oct4b) n27 = (b3 oct4b) n28 = (b4 oct4b) n29 = (b5 oct4b) n30 = (b6 oct4b) n31 = (b7 oct4b) n32 = (b8 oct4b) oct1b = (octet1 addr2) oct2b = (octet2 addr2) oct3b = (octet3 addr2) oct4b = (octet4 addr2) -- Test lists. ipv4address_tests :: TestTree ipv4address_tests = testGroup "IPv4 Address Tests" [ test_enum, test_maxBound, test_minBound, test_most_sig_bit_different1, test_most_sig_bit_different2, test_ord_instance1, test_ord_instance2, test_ord_instance3, test_ord_instance4, test_to_enum ] ipv4address_properties :: TestTree ipv4address_properties = testGroup "IPv4 Address Properties " [ prop_from_enum_to_enum_inverses_x32, prop_from_enum_to_enum_inverses_x64 ] -- QuickCheck properties -- -- We have two different tests to show that toEnum and fromEnum are -- inverses of one another. This part of the code isn't really -- type-safe, because the stupid Enum class insists that we use a -- machine 'Int' for our representation. Since IPv4 addresses can -- correspond to very large 32-bit integers, there's a possibility -- that our math is wrong in 32- but not 64-bits, and vice-versa. -- -- tl;dr we want to ensure that this test passes when the 'Int' type -- is both 32-bit and 64-bit. -- Generate "Small" 64-bit numbers, because almost all 64-bit integers are -- too large to satisfy our predicate (i.e. also be 32-bit integers). prop_from_enum_to_enum_inverses_x64 :: TestTree prop_from_enum_to_enum_inverses_x64 = testProperty "fromEnum and toEnum are inverses (x64)" prop where prop :: (Small Int64) -> Property prop x = 0 <= x && x <= (2 ^ (32 :: Integer)) - 1 ==> fromIntegral (fromEnum (toEnum (fromIntegral x) :: IPv4Address)) == x -- According to the QuickCheck documentation, we need the "Large" -- modifier to ensure that the test cases are drawn from the entire -- range of Int32 values. prop_from_enum_to_enum_inverses_x32 :: TestTree prop_from_enum_to_enum_inverses_x32 = testProperty "fromEnum and toEnum are inverses (x32)" prop where prop :: (Large Int32) -> Bool prop x = fromIntegral (fromEnum (toEnum (fromIntegral x) :: IPv4Address)) == x -- HUnit Tests mk_testaddr :: Int -> Int -> Int -> Int -> IPv4Address mk_testaddr a b c d = IPv4Address oct1 oct2 oct3 oct4 where oct1 = toEnum a :: Octet oct2 = toEnum b :: Octet oct3 = toEnum c :: Octet oct4 = toEnum d :: Octet test_minBound :: TestTree test_minBound = testCase desc $ actual @?= expected where desc = "minBound should be 0.0.0.0" expected = mk_testaddr 0 0 0 0 actual = minBound :: IPv4Address test_maxBound :: TestTree test_maxBound = testCase desc $ actual @?= expected where desc = "maxBound should be 255.255.255.255" expected = mk_testaddr 255 255 255 255 actual = maxBound :: IPv4Address test_enum :: TestTree test_enum = testCase desc $ actual @?= expected where desc = "enumerating a /24 gives the correct addresses" expected = ["192.168.0." ++ (show x) | x <- [0..255::Int] ] lb = mk_testaddr 192 168 0 0 ub = mk_testaddr 192 168 0 255 actual = map show [lb..ub] test_most_sig_bit_different1 :: TestTree test_most_sig_bit_different1 = testCase desc $ actual @?= expected where desc = "10.1.1.0 and 10.1.0.0 differ in bit 24" addr1 = mk_testaddr 10 1 1 0 addr2 = (mk_testaddr 10 1 0 0) expected = TwentyFour actual = most_sig_bit_different addr1 addr2 test_most_sig_bit_different2 :: TestTree test_most_sig_bit_different2 = testCase desc $ actual @?= expected where desc = "10.1.2.0 and 10.1.1.0 differ in bit 23" addr1 = mk_testaddr 10 1 2 0 addr2 = mk_testaddr 10 1 1 0 expected = TwentyThree actual = most_sig_bit_different addr1 addr2 test_to_enum :: TestTree test_to_enum = testCase desc $ actual @?= expected where desc = "192.168.0.0 in base-10 is 3232235520" expected = mk_testaddr 192 168 0 0 -- We declare the big number as Word32 because otherwise, on x86, -- we get a warning that it's too big to fit in a 32-bit integer. -- Ultimately we convert it to a (negative) Int on those systems -- anyway, but the gymnastics declare our intent to the compiler. actual = toEnum (fromIntegral (3232235520 :: Word32)) :: IPv4Address test_ord_instance1 :: TestTree test_ord_instance1 = testCase desc $ actual @?= expected where desc = "127.0.0.0 is less than 127.0.0.1" addr1 = mk_testaddr 127 0 0 0 addr2 = mk_testaddr 127 0 0 1 expected = True actual = addr1 <= addr2 test_ord_instance2 :: TestTree test_ord_instance2 = testCase desc $ actual @?= expected where desc = "127.0.0.0 is less than 127.0.1.0" addr1 = mk_testaddr 127 0 0 0 addr2 = mk_testaddr 127 0 1 0 expected = True actual = addr1 <= addr2 test_ord_instance3 :: TestTree test_ord_instance3 = testCase desc $ actual @?= expected where desc = "127.0.0.0 is less than 127.1.0.0" addr1 = mk_testaddr 127 0 0 0 addr2 = mk_testaddr 127 1 0 0 expected = True actual = addr1 <= addr2 test_ord_instance4 :: TestTree test_ord_instance4 = testCase desc $ actual @?= expected where desc = "127.0.0.0 is less than 128.0.0.0" addr1 = mk_testaddr 127 0 0 0 addr2 = mk_testaddr 128 0 0 0 expected = True actual = addr1 <= addr2