]> gitweb.michael.orlitzky.com - hath.git/blobdiff - src/IPv4Address.hs
Switch from test-framework to tasty.
[hath.git] / src / IPv4Address.hs
index 6cfed3a7e9ecf54845254620c6b810d9ccc04a5f..d262a5c0537ea47092d0255ab417b6516d1cdab8 100644 (file)
-module IPv4Address where
+module IPv4Address(
+  IPv4Address(..),
+  ipv4address_properties,
+  ipv4address_tests,
+  most_sig_bit_different )
+where
 
-import Bit
-import Octet
 
-type Maskbits = Int
+import Test.QuickCheck ( Gen ) -- Not re-exported by tasty
+import Test.Tasty ( TestTree, testGroup )
+import Test.Tasty.HUnit ( (@?=), testCase )
+import Test.Tasty.QuickCheck (
+  Arbitrary(..),
+  Property,
+  (==>),
+  testProperty )
 
-data IPv4Address = IPv4Address { octet1 :: Octet,
-                                 octet2 :: Octet,
-                                 octet3 :: Octet,
-                                 octet4 :: Octet }
-                 deriving (Eq, Show)
+import Maskable (Maskable(..))
+import Maskbits (Maskbits(..))
+import Octet (Octet(..))
 
+data IPv4Address =
+  IPv4Address { octet1 :: Octet,
+                octet2 :: Octet,
+                octet3 :: Octet,
+                octet4 :: Octet }
+    deriving (Eq)
 
-default_ipv4address :: IPv4Address
-default_ipv4address = IPv4Address (min_octet) (min_octet) (min_octet) (min_octet)
 
+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)
 
-ipv4address_from_string :: String -> IPv4Address
-ipv4address_from_string s
-    | length s < 32 = default_ipv4address
-    | otherwise = IPv4Address (Octet a1 a2 a3 a4 a5 a6 a7 a8) (Octet a9 a10 a11 a12 a13 a14 a15 a16)(Octet a17 a18 a19 a20 a21 a22 a23 a24) (Octet a25 a26 a27 a28 a29 a30 a31 a32)
-    where
-      a1  = bit_from_char (s !! 0)
-      a2  = bit_from_char (s !! 1)
-      a3  = bit_from_char (s !! 2)
-      a4  = bit_from_char (s !! 3)
-      a5  = bit_from_char (s !! 4)
-      a6  = bit_from_char (s !! 5)
-      a7  = bit_from_char (s !! 6)
-      a8  = bit_from_char (s !! 7)
-      a9  = bit_from_char (s !! 8)
-      a10 = bit_from_char (s !! 9)
-      a11 = bit_from_char (s !! 10)
-      a12 = bit_from_char (s !! 11)
-      a13 = bit_from_char (s !! 12)
-      a14 = bit_from_char (s !! 13)
-      a15 = bit_from_char (s !! 14)
-      a16 = bit_from_char (s !! 15)
-      a17 = bit_from_char (s !! 16)
-      a18 = bit_from_char (s !! 17)
-      a19 = bit_from_char (s !! 18)
-      a20 = bit_from_char (s !! 19)
-      a21 = bit_from_char (s !! 20)
-      a22 = bit_from_char (s !! 21)
-      a23 = bit_from_char (s !! 22)
-      a24 = bit_from_char (s !! 23)
-      a25 = bit_from_char (s !! 24)
-      a26 = bit_from_char (s !! 25)
-      a27 = bit_from_char (s !! 26)
-      a28 = bit_from_char (s !! 27)
-      a29 = bit_from_char (s !! 28)
-      a30 = bit_from_char (s !! 29)
-      a31 = bit_from_char (s !! 30)
-      a32 = bit_from_char (s !! 31)
-
-
-min_address :: IPv4Address -> Maskbits -> IPv4Address
-min_address addr mask
-    | mask == 32 = IPv4Address oct1 oct2 oct3 oct4
-    | mask == 31 = IPv4Address oct1 oct2 oct3 (Octet a25 a26 a27 a28 a29 a30 a31 Zero)
-    | mask == 30 = IPv4Address oct1 oct2 oct3 (Octet a25 a26 a27 a28 a29 a30 Zero Zero)
-    | mask == 29 = IPv4Address oct1 oct2 oct3 (Octet a25 a26 a27 a28 a29 Zero Zero Zero)
-    | mask == 28 = IPv4Address oct1 oct2 oct3 (Octet a25 a26 a27 a28 Zero Zero Zero Zero)
-    | mask == 27 = IPv4Address oct1 oct2 oct3 (Octet a25 a26 a27 Zero Zero Zero Zero Zero)
-    | mask == 26 = IPv4Address oct1 oct2 oct3 (Octet a25 a26 Zero Zero Zero Zero Zero Zero)
-    | mask == 25 = IPv4Address oct1 oct2 oct3 (Octet a25 Zero Zero Zero Zero Zero Zero Zero)
-    | mask == 24 = IPv4Address oct1 oct2 oct3 (min_octet)
-    | mask == 23 = IPv4Address oct1 oct2 (Octet a17 a18 a19 a20 a21 a22 a23 Zero) (min_octet)
-    | mask == 22 = IPv4Address oct1 oct2 (Octet a17 a18 a19 a20 a21 a22 Zero Zero) (min_octet)
-    | mask == 21 = IPv4Address oct1 oct2 (Octet a17 a18 a19 a20 a21 Zero Zero Zero) (min_octet)
-    | mask == 20 = IPv4Address oct1 oct2 (Octet a17 a18 a19 a20 Zero Zero Zero Zero) (min_octet)
-    | mask == 19 = IPv4Address oct1 oct2 (Octet a17 a18 a19 Zero Zero Zero Zero Zero) (min_octet)
-    | mask == 18 = IPv4Address oct1 oct2 (Octet a17 a18 Zero Zero Zero Zero Zero Zero) (min_octet)
-    | mask == 17 = IPv4Address oct1 oct2 (Octet a17 Zero Zero Zero Zero Zero Zero Zero) (min_octet)
-    | mask == 16 = IPv4Address oct1 oct2 (min_octet) (min_octet)
-    | mask == 15 = IPv4Address oct1 (Octet a9 a10 a11 a12 a13 a14 a15 Zero) (min_octet) (min_octet)
-    | mask == 14 = IPv4Address oct1 (Octet a9 a10 a11 a12 a13 a14 Zero Zero) (min_octet) (min_octet)
-    | mask == 13 = IPv4Address oct1 (Octet a9 a10 a11 a12 a13 Zero Zero Zero) (min_octet) (min_octet)
-    | mask == 12 = IPv4Address oct1 (Octet a9 a10 a11 a12 Zero Zero Zero Zero) (min_octet) (min_octet)
-    | mask == 11 = IPv4Address oct1 (Octet a9 a10 a11 Zero Zero Zero Zero Zero) (min_octet) (min_octet)
-    | mask == 10 = IPv4Address oct1 (Octet a9 a10 Zero Zero Zero Zero Zero Zero) (min_octet) (min_octet)
-    | mask == 9 = IPv4Address oct1 (Octet a9 Zero Zero Zero Zero Zero Zero Zero) (min_octet) (min_octet)
-    | mask == 8 = IPv4Address oct1 (min_octet) (min_octet) (min_octet)
-    | mask == 7 = IPv4Address (Octet a1 a2 a3 a4 a5 a6 a7 Zero) (min_octet) (min_octet) (min_octet)
-    | mask == 6 = IPv4Address (Octet a1 a2 a3 a4 a5 a6 Zero Zero) (min_octet) (min_octet) (min_octet)
-    | mask == 5 = IPv4Address (Octet a1 a2 a3 a4 a5 Zero Zero Zero) (min_octet) (min_octet) (min_octet)
-    | mask == 4 = IPv4Address (Octet a1 a2 a3 a4 Zero Zero Zero Zero) (min_octet) (min_octet) (min_octet)
-    | mask == 3 = IPv4Address (Octet a1 a2 a3 Zero Zero Zero Zero Zero) (min_octet) (min_octet) (min_octet)
-    | mask == 2 = IPv4Address (Octet a1 a2 Zero Zero Zero Zero Zero Zero) (min_octet) (min_octet) (min_octet)
-    | mask == 1 = IPv4Address (Octet a1 Zero Zero Zero Zero Zero Zero Zero) (min_octet) (min_octet) (min_octet)
-    | mask == 0 = IPv4Address (min_octet) (min_octet) (min_octet) (min_octet)
-    | otherwise = 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 x =
+    IPv4Address oct1 oct2 oct3 oct4
     where
-      a1  = (b1 oct1)
-      a2  = (b2 oct1)
-      a3  = (b3 oct1)
-      a4  = (b4 oct1)
-      a5  = (b5 oct1)
-      a6  = (b6 oct1)
-      a7  = (b7 oct1)
-      a9  = (b1 oct2)
-      a10 = (b2 oct2)
-      a11 = (b3 oct2)
-      a12 = (b4 oct2)
-      a13 = (b5 oct2)
-      a14 = (b6 oct2)
-      a15 = (b7 oct2)
-      a17 = (b1 oct3)
-      a18 = (b2 oct3)
-      a19 = (b3 oct3)
-      a20 = (b4 oct3)
-      a21 = (b5 oct3)
-      a22 = (b6 oct3)
-      a23 = (b7 oct3)
-      a25 = (b1 oct4)
-      a26 = (b2 oct4)
-      a27 = (b3 oct4)
-      a28 = (b4 oct4)
-      a29 = (b5 oct4)
-      a30 = (b6 oct4)
-      a31 = (b7 oct4)
-      oct1 = (octet1 addr)
-      oct2 = (octet2 addr)
-      oct3 = (octet3 addr)
-      oct4 = (octet4 addr)
-
-
-
-max_address :: IPv4Address -> Maskbits -> IPv4Address
-max_address addr mask
-    | mask == 32 = IPv4Address oct1 oct2 oct3 oct4
-    | mask == 31 = IPv4Address oct1 oct2 oct3 (Octet a25 a26 a27 a28 a29 a30 a31 One)
-    | mask == 30 = IPv4Address oct1 oct2 oct3 (Octet a25 a26 a27 a28 a29 a30 One One)
-    | mask == 29 = IPv4Address oct1 oct2 oct3 (Octet a25 a26 a27 a28 a29 One One One)
-    | mask == 28 = IPv4Address oct1 oct2 oct3 (Octet a25 a26 a27 a28 One One One One)
-    | mask == 27 = IPv4Address oct1 oct2 oct3 (Octet a25 a26 a27 One One One One One)
-    | mask == 26 = IPv4Address oct1 oct2 oct3 (Octet a25 a26 One One One One One One)
-    | mask == 25 = IPv4Address oct1 oct2 oct3 (Octet a25 One One One One One One One)
-    | mask == 24 = IPv4Address oct1 oct2 oct3 (max_octet)
-    | mask == 23 = IPv4Address oct1 oct2 (Octet a17 a18 a19 a20 a21 a22 a23 One) (max_octet)
-    | mask == 22 = IPv4Address oct1 oct2 (Octet a17 a18 a19 a20 a21 a22 One One) (max_octet)
-    | mask == 21 = IPv4Address oct1 oct2 (Octet a17 a18 a19 a20 a21 One One One) (max_octet)
-    | mask == 20 = IPv4Address oct1 oct2 (Octet a17 a18 a19 a20 One One One One) (max_octet)
-    | mask == 19 = IPv4Address oct1 oct2 (Octet a17 a18 a19 One One One One One) (max_octet)
-    | mask == 18 = IPv4Address oct1 oct2 (Octet a17 a18 One One One One One One) (max_octet)
-    | mask == 17 = IPv4Address oct1 oct2 (Octet a17 One One One One One One One) (max_octet)
-    | mask == 16 = IPv4Address oct1 oct2 (max_octet) (max_octet)
-    | mask == 15 = IPv4Address oct1 (Octet a9 a10 a11 a12 a13 a14 a15 One) (max_octet) (max_octet)
-    | mask == 14 = IPv4Address oct1 (Octet a9 a10 a11 a12 a13 a14 One One) (max_octet) (max_octet)
-    | mask == 13 = IPv4Address oct1 (Octet a9 a10 a11 a12 a13 One One One) (max_octet) (max_octet)
-    | mask == 12 = IPv4Address oct1 (Octet a9 a10 a11 a12 One One One One) (max_octet) (max_octet)
-    | mask == 11 = IPv4Address oct1 (Octet a9 a10 a11 One One One One One) (max_octet) (max_octet)
-    | mask == 10 = IPv4Address oct1 (Octet a9 a10 One One One One One One) (max_octet) (max_octet)
-    | mask == 9 = IPv4Address oct1 (Octet a9 One One One One One One One) (max_octet) (max_octet)
-    | mask == 8 = IPv4Address oct1 (max_octet) (max_octet) (max_octet)
-    | mask == 7 = IPv4Address (Octet a1 a2 a3 a4 a5 a6 a7 One) (max_octet) (max_octet) (max_octet)
-    | mask == 6 = IPv4Address (Octet a1 a2 a3 a4 a5 a6 One One) (max_octet) (max_octet) (max_octet)
-    | mask == 5 = IPv4Address (Octet a1 a2 a3 a4 a5 One One One) (max_octet) (max_octet) (max_octet)
-    | mask == 4 = IPv4Address (Octet a1 a2 a3 a4 One One One One) (max_octet) (max_octet) (max_octet)
-    | mask == 3 = IPv4Address (Octet a1 a2 a3 One One One One One) (max_octet) (max_octet) (max_octet)
-    | mask == 2 = IPv4Address (Octet a1 a2 One One One One One One) (max_octet) (max_octet) (max_octet)
-    | mask == 1 = IPv4Address (Octet a1 One One One One One One One) (max_octet) (max_octet) (max_octet)
-    | mask == 0 = IPv4Address (max_octet) (max_octet) (max_octet) (max_octet)
-    | otherwise = addr
+      -- 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)
+      oct1 = toEnum shifted_x1
+      oct2 = toEnum shifted_x2
+      oct3 = toEnum shifted_x3
+      oct4 = toEnum x4
+
+  -- | 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
-      a1  = (b1 oct1)
-      a2  = (b2 oct1)
-      a3  = (b3 oct1)
-      a4  = (b4 oct1)
-      a5  = (b5 oct1)
-      a6  = (b6 oct1)
-      a7  = (b7 oct1)
-      a9  = (b1 oct2)
-      a10 = (b2 oct2)
-      a11 = (b3 oct2)
-      a12 = (b4 oct2)
-      a13 = (b5 oct2)
-      a14 = (b6 oct2)
-      a15 = (b7 oct2)
-      a17 = (b1 oct3)
-      a18 = (b2 oct3)
-      a19 = (b3 oct3)
-      a20 = (b4 oct3)
-      a21 = (b5 oct3)
-      a22 = (b6 oct3)
-      a23 = (b7 oct3)
-      a25 = (b1 oct4)
-      a26 = (b2 oct4)
-      a27 = (b3 oct4)
-      a28 = (b4 oct4)
-      a29 = (b5 oct4)
-      a30 = (b6 oct4)
-      a31 = (b7 oct4)
-      oct1 = (octet1 addr)
-      oct2 = (octet2 addr)
-      oct3 = (octet3 addr)
-      oct4 = (octet4 addr)
-
-
-
-min_octet1 :: IPv4Address -> Maskbits -> Octet
-min_octet1 addr mask = octet1 (min_address addr mask)
-
-min_octet2 :: IPv4Address -> Maskbits -> Octet
-min_octet2 addr mask = octet2 (min_address addr mask)
-
-min_octet3 :: IPv4Address -> Maskbits -> Octet
-min_octet3 addr mask = octet3 (min_address addr mask)
-
-min_octet4 :: IPv4Address -> Maskbits -> Octet
-min_octet4 addr mask = octet4 (min_address addr mask)
-
-max_octet1 :: IPv4Address -> Maskbits -> Octet
-max_octet1 addr mask = octet1 (max_address addr mask)
-
-max_octet2 :: IPv4Address -> Maskbits -> Octet
-max_octet2 addr mask = octet2 (max_address addr mask)
-
-max_octet3 :: IPv4Address -> Maskbits -> Octet
-max_octet3 addr mask = octet3 (max_address addr mask)
-
-max_octet4 :: IPv4Address -> Maskbits -> Octet
-max_octet4 addr mask = octet4 (max_address addr mask)
+      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_to_enum ]
+
+ipv4address_properties :: TestTree
+ipv4address_properties =
+  testGroup
+    "IPv4 Address Properties "
+    [ prop_from_enum_to_enum_inverses ]
+
+-- QuickCheck properties
+prop_from_enum_to_enum_inverses :: TestTree
+prop_from_enum_to_enum_inverses =
+  testProperty "fromEnum and toEnum are inverses" prop
+  where
+    prop :: Int -> Property
+    prop x =
+      (0 <= x) && (x <= 2^(32 :: Integer) - 1) ==>
+        fromEnum (toEnum 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
+    oct2 = toEnum b
+    oct3 = toEnum c
+    oct4 = toEnum d
+
+
+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
+    actual   = toEnum 3232235520