]> gitweb.michael.orlitzky.com - hath.git/blobdiff - src/IPv4Address.hs
hath.cabal: drop a word and a period from the synopsis
[hath.git] / src / IPv4Address.hs
index 7c4436781099b5be4ae98434b0455772145e9ab8..f9fd8c24e435ac9f2c5ba51d9665aa5243b94d47 100644 (file)
@@ -1,27 +1,40 @@
 module IPv4Address(
+  IPv4Address(..),
   ipv4address_properties,
   ipv4address_tests,
-  IPv4Address(..),
-  most_sig_bit_different,
-) where
-
-import Data.Maybe (fromJust)
-import Test.HUnit (assertEqual)
-import Test.Framework (Test, testGroup)
-import Test.Framework.Providers.HUnit (testCase)
-import Test.Framework.Providers.QuickCheck2 (testProperty)
-import Test.QuickCheck (Arbitrary(..), Gen, Property, (==>))
-
-import Maskable
-import Maskbits
-import Octet
+  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)
+    deriving (Eq, Ord)
 
 
 instance Show IPv4Address where
@@ -174,55 +187,48 @@ instance Bounded IPv4Address where
 
 
 
--- | 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.
-ipv4address_to_int :: IPv4Address -> Int
-ipv4address_to_int addr =
-  (shifted_oct1) + (shifted_oct2) + (shifted_oct3) + oct4
-  where
-    oct1 = octet_to_int (octet1 addr)
-    oct2 = octet_to_int (octet2 addr)
-    oct3 = octet_to_int (octet3 addr)
-    oct4 = octet_to_int (octet4 addr)
-
-    shifted_oct1 = oct1 * 2^(24 :: Integer)
-    shifted_oct2 = oct2 * 2^(16 :: Integer)
-    shifted_oct3 = oct3 * 2^(8 :: Integer)
-
-
-
--- | 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.
-ipv4address_from_int :: Int -> Maybe IPv4Address
-ipv4address_from_int x
-  | (x < 0) || (x > 2^(32 :: Integer) - 1) = Nothing
-  | otherwise = do
-      -- If the algebra is right, none of these octet_from_int calls
-      -- below can fail since 0 <= x <= 2^32 - 1.
-      oct1 <- octet_from_int shifted_x1
-      oct2 <- octet_from_int shifted_x2
-      oct3 <- octet_from_int shifted_x3
-      oct4 <- octet_from_int x4
-      return $ IPv4Address oct1 oct2 oct3 oct4
-      where
-        -- 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 = x `mod` 2^(8  :: Integer)
-        -- Perform right-shifts. x4 doesn't need a shift.
-        shifted_x1 = x `quot` 2^(24 :: Integer)
-        shifted_x2 = x2 `quot` 2^(16 :: Integer)
-        shifted_x3 = x3 `quot` 2^(8 :: Integer)
-
 
 instance Enum IPv4Address where
-  -- We're supposed to throw a runtime error if you call (succ
-  -- maxBound), so the fromJust here doesn't introduce any additional
-  -- badness.
-  toEnum   = fromJust . ipv4address_from_int
-  fromEnum = ipv4address_to_int
+  -- | 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
@@ -339,58 +345,93 @@ most_sig_bit_different addr1 addr2
 
 
 -- Test lists.
-ipv4address_tests :: Test
+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 ]
-
-ipv4address_properties :: Test
+    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 "
-    [ testProperty
-        "fromEnum/toEnum are inverses"
-        prop_from_enum_to_enum_inverses ]
+    [ prop_from_enum_to_enum_inverses_x32,
+      prop_from_enum_to_enum_inverses_x64 ]
 
 -- QuickCheck properties
-prop_from_enum_to_enum_inverses :: Int -> Property
-prop_from_enum_to_enum_inverses x =
-  (0 <= x) && (x <= 2^(32 :: Integer) - 1) ==>
-    fromEnum (toEnum x :: IPv4Address) == x
+--
+-- 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 = fromJust $ octet_from_int a
-    oct2 = fromJust $ octet_from_int b
-    oct3 = fromJust $ octet_from_int c
-    oct4 = fromJust $ octet_from_int d
+    oct1 = toEnum a :: Octet
+    oct2 = toEnum b :: Octet
+    oct3 = toEnum c :: Octet
+    oct4 = toEnum d :: Octet
+
 
-test_minBound :: Test
+test_minBound :: TestTree
 test_minBound =
-  testCase desc $ assertEqual desc expected actual
+  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 :: Test
+
+test_maxBound :: TestTree
 test_maxBound =
-  testCase desc $ assertEqual desc expected actual
+  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 :: Test
+
+test_enum :: TestTree
 test_enum =
-  testCase desc $ assertEqual desc expected actual
+  testCase desc $ actual @?= expected
   where
     desc = "enumerating a /24 gives the correct addresses"
     expected = ["192.168.0." ++ (show x) | x <- [0..255::Int] ]
@@ -398,28 +439,80 @@ test_enum =
     ub = mk_testaddr 192 168 0 255
     actual = map show [lb..ub]
 
-test_most_sig_bit_different1 :: Test
+
+test_most_sig_bit_different1 :: TestTree
 test_most_sig_bit_different1 =
-  testCase desc $ assertEqual desc
-             TwentyFour
-             bit
+  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)
-    bit = most_sig_bit_different addr1 addr2
+    expected = TwentyFour
+    actual = most_sig_bit_different addr1 addr2
 
 
 
-test_most_sig_bit_different2 :: Test
+test_most_sig_bit_different2 :: TestTree
 test_most_sig_bit_different2 =
-  testCase desc $ assertEqual desc
-               TwentyThree
-               bit
+  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
-    bit = most_sig_bit_different addr1 addr2
+    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