]> gitweb.michael.orlitzky.com - hath.git/blobdiff - src/Cidr.hs
Add a bunch of tests for our weird CIDR order.
[hath.git] / src / Cidr.hs
index 6e759660486a1dffc5e1967c147ac7ff1b4d464d..9ed146ab92a08c1c889a610b23e69e5314a3efa8 100644 (file)
@@ -16,27 +16,31 @@ module Cidr
   min_octet2,
   min_octet3,
   min_octet4,
+  normalize
 ) where
 
-import Data.List (nubBy)
+import Data.List (nub)
 import Data.List.Split (splitOneOf)
 import Data.Maybe (catMaybes, mapMaybe)
 
-import Test.QuickCheck ( Gen ) -- Not re-exported by tasty
-import Test.Tasty ( TestTree, testGroup )
+import Test.Tasty ( TestTree, localOption, testGroup )
 import Test.Tasty.HUnit ( (@?=), testCase )
 import Test.Tasty.QuickCheck (
-  Arbitrary(..),
+  Arbitrary( arbitrary ),
+  Gen,
   Property,
+  QuickCheckTests( QuickCheckTests ),
   (==>),
   testProperty )
 import Text.Read (readMaybe)
 
 import qualified Bit as B (Bit(..))
-import IPv4Address (IPv4Address(..), most_sig_bit_different)
-import Maskable (Maskable(..))
-import Maskbits (Maskbits(..))
-import Octet (Octet(..))
+import IPv4Address (
+  IPv4Address( IPv4Address, octet1, octet2, octet3, octet4 ),
+  most_sig_bit_different )
+import Maskable (Maskable(apply_mask))
+import Maskbits ( Maskbits(Zero) )
+import Octet (Octet())
 
 
 data Cidr = Cidr { ipv4address :: IPv4Address,
@@ -55,14 +59,29 @@ instance Arbitrary Cidr where
 
 
 instance Eq Cidr where
-  cidr1 == cidr2 = (cidr1 `equivalent` cidr2)
-
-
--- | Two CIDR ranges are equivalent if they have the same network bits
---   and the masks are the same.
-equivalent :: Cidr -> Cidr -> Bool
-equivalent (Cidr addr1 mbits1) (Cidr addr2 mbits2) =
-    (mbits1 == mbits2) && ((apply_mask addr1 mbits1 B.Zero) == (apply_mask addr2 mbits2 B.Zero))
+  -- | Two CIDRs are equal if they have the same network bits and if
+  --   their masks are the same. In other words, if they are the same
+  --   after normalization.
+  cidr1 == cidr2 = (cidr1 <= cidr2) && (cidr2 <= cidr1)
+
+instance Ord Cidr where
+  -- | The CIDR order is simply numeric, with the IPv4Address being
+  --   considered first, before the mask. There was an arbitrary
+  --   choice that had to be made here: which CIDR is smaller,
+  --   127.0.0.1/8, or 127.0.0.1/32?
+  --
+  --   The arguments for 127.0.0.1/8 <= 127.0.0.1/32 are that it
+  --   agrees with the numeric sort order on masks, and that it's
+  --   generally nicer to see the big networks before the small ones.
+  --
+  --   On the other hand, this order disagrees with the containment
+  --   partial order, since 127.0.0.1/32 is contained properly in
+  --   127.0.0.1/8.
+  --
+  cidr1 <= cidr2 = if addr1 == addr2 then mask1 <= mask2 else addr1 <= addr2
+    where
+      Cidr addr1 mask1 = normalize cidr1
+      Cidr addr2 mask2 = normalize cidr2
 
 -- | Returns the mask portion of a CIDR address. That is, everything
 --   after the trailing slash.
@@ -217,7 +236,7 @@ combine_all cidrs
   | cidrs == (combine_contained unique_cidrs) = cidrs
   | otherwise = combine_all (combine_contained unique_cidrs)
     where
-      unique_cidrs = nubBy equivalent cidr_combinations
+      unique_cidrs = nub cidr_combinations
       cidr_combinations =
         cidrs ++ (catMaybes [ (combine_adjacent x y) | x <- cidrs, y <- cidrs ])
 
@@ -259,6 +278,14 @@ adjacent cidr1 cidr2
 enumerate :: Cidr -> [IPv4Address]
 enumerate cidr = [(min_host cidr)..(max_host cidr)]
 
+
+-- | Replace any masked bits in this CIDR's IPv4Address with zeros.
+normalize :: Cidr -> Cidr
+normalize (Cidr addr mask) =
+  Cidr nrml_addr mask
+  where
+    nrml_addr = apply_mask addr mask B.Zero
+
 -- Test lists.
 cidr_tests :: TestTree
 cidr_tests =
@@ -279,13 +306,27 @@ cidr_tests =
     test_combine_contained2,
     test_combine_all1,
     test_combine_all2,
-    test_combine_all3 ]
+    test_combine_all3,
+    test_normalize1,
+    test_normalize2,
+    test_normalize3,
+    test_big_networks_come_first ]
 
 cidr_properties :: TestTree
 cidr_properties =
   testGroup "CIDR Properties" [
       prop_all_cidrs_contain_themselves,
-      prop_contains_proper_antisymmetric ]
+      prop_contains_proper_antisymmetric,
+      prop_normalize_idempotent,
+      prop_normalize_preserves_equality,
+      prop_ord_instance_antisymmetric,
+      prop_ord_instance_reflexive,
+      prop_ord_instance_transitive,
+      prop_ord_uses_addr_when_masks_equal,
+      prop_ord_uses_mask_when_addrs_equal,
+      prop_ord_and_contains_disagree,
+      prop_ord_minimum,
+      prop_ord_maximum ]
 
 
 -- HUnit Tests
@@ -294,23 +335,23 @@ test_enumerate =
   testCase desc $ actual @?= expected
   where
     desc = "192.168.0.240/30 is enumerated correctly"
-    oct1 = toEnum 192
-    oct2 = toEnum 168
-    oct3 = minBound
+    oct1 = toEnum 192 :: Octet
+    oct2 = toEnum 168 :: Octet
+    oct3 = minBound :: Octet
     mk_ip = IPv4Address oct1 oct2 oct3
     addr1 = mk_ip $ toEnum 240
     addr2 = mk_ip $ toEnum 241
     addr3 = mk_ip $ toEnum 242
     addr4 = mk_ip $ toEnum 243
     expected = [addr1, addr2, addr3, addr4]
-    actual = enumerate $ read "192.168.0.240/30"
+    actual = enumerate (read "192.168.0.240/30" :: Cidr)
 
 test_min_host1 :: TestTree
 test_min_host1 =
   testCase desc $ actual @?= expected
   where
     desc = "The minimum host in 10.0.0.0/24 is 10.0.0.0"
-    actual = show $ min_host (read "10.0.0.0/24")
+    actual = show $ min_host (read "10.0.0.0/24" :: Cidr)
     expected = "10.0.0.0"
 
 
@@ -319,7 +360,7 @@ test_max_host1 =
   testCase desc $ actual @?= expected
   where
     desc = "The maximum host in 10.0.0.0/24 is 10.0.0.255"
-    actual = show $ max_host (read "10.0.0.0/24")
+    actual = show $ max_host (read "10.0.0.0/24" :: Cidr)
     expected = "10.0.0.255"
 
 
@@ -337,8 +378,8 @@ test_contains1 =
   testCase desc $ actual @?= expected
   where
     desc = "10.1.1.0/23 contains 10.1.1.0/24"
-    cidr1 = read "10.1.1.0/23"
-    cidr2 = read "10.1.1.0/24"
+    cidr1 = read "10.1.1.0/23" :: Cidr
+    cidr2 = read "10.1.1.0/24" :: Cidr
     expected = True
     actual = cidr1 `contains` cidr2
 
@@ -348,7 +389,7 @@ test_contains2 =
   testCase desc $ actual @?= expected
   where
     desc = "10.1.1.0/23 contains itself"
-    cidr1 = read "10.1.1.0/23"
+    cidr1 = read "10.1.1.0/23" :: Cidr
     expected = True
     actual = cidr1 `contains` cidr1
 
@@ -358,8 +399,8 @@ test_contains_proper1 =
   testCase desc $ actual @?= expected
   where
     desc = "10.1.1.0/23 contains 10.1.1.0/24 properly"
-    cidr1 = read "10.1.1.0/23"
-    cidr2 = read "10.1.1.0/24"
+    cidr1 = read "10.1.1.0/23" :: Cidr
+    cidr2 = read "10.1.1.0/24" :: Cidr
     expected = True
     actual = cidr1 `contains_proper` cidr2
 
@@ -369,7 +410,7 @@ test_contains_proper2 =
   testCase desc $ actual @?= expected
   where
     desc = "10.1.1.0/23 does not contain itself properly"
-    cidr1 = read "10.1.1.0/23"
+    cidr1 = read "10.1.1.0/23" :: Cidr
     expected = False
     actual = cidr1 `contains_proper` cidr1
 
@@ -379,8 +420,8 @@ test_adjacent1 =
   testCase desc $ actual @?= expected
   where
     desc = "10.1.0.0/24 is adjacent to 10.1.1.0/24"
-    cidr1 = read "10.1.0.0/24"
-    cidr2 = read "10.1.1.0/24"
+    cidr1 = read "10.1.0.0/24" :: Cidr
+    cidr2 = read "10.1.1.0/24" :: Cidr
     expected = True
     actual = cidr1 `adjacent` cidr2
 
@@ -390,8 +431,8 @@ test_adjacent2 =
   testCase desc $ actual @?= expected
   where
     desc = "10.1.0.0/23 is not adjacent to 10.1.0.0/24"
-    cidr1 = read "10.1.0.0/23"
-    cidr2 = read "10.1.0.0/24"
+    cidr1 = read "10.1.0.0/23" :: Cidr
+    cidr2 = read "10.1.0.0/24" :: Cidr
     expected = False
     actual = cidr1 `adjacent` cidr2
 
@@ -401,8 +442,8 @@ test_adjacent3 =
   testCase desc $ actual @?= expected
   where
     desc = "10.1.0.0/24 is not adjacent to 10.2.5.0/24"
-    cidr1 = read "10.1.0.0/24"
-    cidr2 = read "10.2.5.0/24"
+    cidr1 = read "10.1.0.0/24" :: Cidr
+    cidr2 = read "10.2.5.0/24" :: Cidr
     expected = False
     actual = cidr1 `adjacent` cidr2
 
@@ -412,8 +453,8 @@ test_adjacent4 =
   testCase desc $ actual @?= expected
   where
     desc = "10.1.1.0/24 is not adjacent to 10.1.2.0/24"
-    cidr1 = read "10.1.1.0/24"
-    cidr2 = read "10.1.2.0/24"
+    cidr1 = read "10.1.1.0/24" :: Cidr
+    cidr2 = read "10.1.2.0/24" :: Cidr
     expected = False
     actual = cidr1 `adjacent` cidr2
 
@@ -422,9 +463,9 @@ test_combine_contained1 =
   testCase desc $ actual @?= expected
   where
     desc = "10.0.0.0/8, 10.1.0.0/16, and 10.1.1.0/24 combine to 10.0.0.0/8"
-    cidr1 = read "10.0.0.0/8"
-    cidr2 = read "10.1.0.0/16"
-    cidr3 = read "10.1.1.0/24"
+    cidr1 = read "10.0.0.0/8" :: Cidr
+    cidr2 = read "10.1.0.0/16" :: Cidr
+    cidr3 = read "10.1.1.0/24" :: Cidr
     test_cidrs = [cidr1, cidr2, cidr3]
     expected = [cidr1]
     actual = combine_contained test_cidrs
@@ -434,8 +475,8 @@ test_combine_contained2 =
   testCase desc $ actual @?= expected
   where
     desc = "192.168.3.0/23 does not contain 192.168.1.0/24"
-    cidr1 = read "192.168.3.0/23"
-    cidr2 = read "192.168.1.0/24"
+    cidr1 = read "192.168.3.0/23" :: Cidr
+    cidr2 = read "192.168.1.0/24" :: Cidr
     expected = [cidr1, cidr2]
     actual = combine_contained [cidr1, cidr2]
 
@@ -446,13 +487,13 @@ test_combine_all1 =
   where
     desc = "10.0.0.0/24 is adjacent to 10.0.1.0/24 "
            ++ "and 10.0.3.0/23 contains 10.0.2.0/24"
-    cidr1 = read "10.0.0.0/24"
-    cidr2 = read "10.0.1.0/24"
-    cidr3 = read "10.0.2.0/24"
-    cidr4 = read "10.0.3.0/23"
-    cidr5 = read "10.0.0.0/23"
+    cidr1 = read "10.0.0.0/24" :: Cidr
+    cidr2 = read "10.0.1.0/24" :: Cidr
+    cidr3 = read "10.0.2.0/24" :: Cidr
+    cidr4 = read "10.0.3.0/23" :: Cidr
+    cidr5 = read "10.0.0.0/23" :: Cidr
     test_cidrs = [cidr1, cidr2, cidr3, cidr4, cidr5]
-    expected = [read "10.0.0.0/22"]
+    expected = [read "10.0.0.0/22" :: Cidr]
     actual = combine_all test_cidrs
 
 
@@ -461,7 +502,7 @@ test_combine_all2 =
   testCase desc $ actual @?= expected
   where
     desc = "127.0.0.1/32 combines with itself recursively"
-    cidr1 = read "127.0.0.1/32"
+    cidr1 = read "127.0.0.1/32" :: Cidr
     test_cidrs = [cidr1, cidr1, cidr1, cidr1, cidr1]
     expected = [cidr1]
     actual = combine_all test_cidrs
@@ -473,14 +514,51 @@ test_combine_all3 =
   where
     desc = "10.0.0.16, 10.0.0.17, 10.0.0.18, and "
            ++ "10.0.0.19 get combined into 10.0.0.16/30"
-    cidr1 = read "10.0.0.16/32"
-    cidr2 = read "10.0.0.17/32"
-    cidr3 = read "10.0.0.18/32"
-    cidr4 = read "10.0.0.19/32"
+    cidr1 = read "10.0.0.16/32" :: Cidr
+    cidr2 = read "10.0.0.17/32" :: Cidr
+    cidr3 = read "10.0.0.18/32" :: Cidr
+    cidr4 = read "10.0.0.19/32" :: Cidr
     test_cidrs = [cidr1, cidr2, cidr3, cidr4]
-    expected = [read "10.0.0.16/30"]
+    expected = [read "10.0.0.16/30" :: Cidr]
     actual = combine_all test_cidrs
 
+test_normalize1 :: TestTree
+test_normalize1 =
+  testCase desc $ actual @?= expected
+  where
+    desc = "127.0.0.1/8 normalized is 127.0.0.0/8"
+    expected = read "127.0.0.0/8" :: Cidr
+    actual = normalize (read "127.0.0.1/8" :: Cidr)
+
+
+test_normalize2 :: TestTree
+test_normalize2 =
+  testCase desc $ actual @?= expected
+  where
+    desc = "192.168.1.101/24 normalized is 192.168.1.0/24"
+    expected = read "192.168.1.0/24" :: Cidr
+    actual = normalize (read "192.168.1.101/24" :: Cidr)
+
+test_normalize3 :: TestTree
+test_normalize3 =
+  testCase desc $ actual @?= expected
+  where
+    desc = "10.10.10.10/22 normalized is 10.10.8.0/22"
+    expected = read "10.10.8.0/22" :: Cidr
+    actual = normalize (read "10.10.10.10/22" :: Cidr)
+
+-- | Test a stated property of the Ord instance, namely that the big
+--   network 127.0.0.1/8 comes before the small network 127.0.0.1/32.
+test_big_networks_come_first :: TestTree
+test_big_networks_come_first =
+  testCase desc $ actual @?= expected
+  where
+    desc = "127.0.0.1/8 comes before 127.0.0.1/32"
+    big = read "127.0.0.1/8" :: Cidr
+    small = read "127.0.0.1/32" :: Cidr
+    expected = True
+    actual = big <= small -- not a typo
+
 -- QuickCheck Tests
 prop_all_cidrs_contain_themselves :: TestTree
 prop_all_cidrs_contain_themselves =
@@ -500,3 +578,109 @@ prop_contains_proper_antisymmetric =
     prop cidr1 cidr2 =
       (cidr1 `contains_proper` cidr2) ==>
         (not (cidr2 `contains_proper` cidr1))
+
+
+-- Running "normalize" a second time shouldn't do anything.
+prop_normalize_idempotent :: TestTree
+prop_normalize_idempotent =
+  testProperty "The CIDR \"normalize\" function is idempotent" prop
+  where
+    prop :: Cidr -> Bool
+    prop cidr = (normalize cidr) == (normalize (normalize cidr))
+
+-- Normalization should not affect equality of two CIDRs.
+prop_normalize_preserves_equality :: TestTree
+prop_normalize_preserves_equality =
+  testProperty "The CIDR \"normalize\" function preserves equality" prop
+  where
+    prop :: Cidr -> Cidr -> Bool
+    prop cidr1 cidr2 = (cidr1 == cidr2) == (normalize cidr1 == normalize cidr2)
+
+
+prop_ord_instance_reflexive :: TestTree
+prop_ord_instance_reflexive =
+  testProperty "The CIDR order is reflexive" prop
+  where
+    prop :: Cidr -> Bool
+    prop cidr = cidr <= cidr
+
+
+prop_ord_instance_transitive :: TestTree
+prop_ord_instance_transitive =
+  testProperty "The CIDR order is transitive" prop
+  where
+    prop :: Cidr -> Cidr -> Cidr -> Property
+    prop cidr1 cidr2 cidr3 =
+      (cidr1 <= cidr2 && cidr2 <= cidr3) ==> cidr1 <= cidr3
+
+-- This is how Eq is currently implemented, but it is useful to have
+-- around in case that changes. Try fewer instances of this than usual
+-- because it's a rare condition.
+prop_ord_instance_antisymmetric :: TestTree
+prop_ord_instance_antisymmetric =
+  localOption (QuickCheckTests 500) $
+    testProperty "The CIDR order is antisymmetric" prop
+  where
+    prop :: Cidr -> Cidr -> Property
+    prop cidr1 cidr2 =
+      (cidr1 <= cidr2 && cidr2 <= cidr1) ==> cidr1 == cidr2
+
+
+-- When comparing two CIDRs with the same mask, the comparison
+-- should be numeric (i.e. whatever the IPv4Address does).
+-- Of course, we have to normalize first.
+prop_ord_uses_addr_when_masks_equal :: TestTree
+prop_ord_uses_addr_when_masks_equal =
+  testProperty "The CIDR order is the IPv4Address order for equal masks" prop
+  where
+    prop :: Cidr -> Cidr -> Property
+    prop cidr1 cidr2 =
+      (mask1 == mask2) ==> (cidr1 <= cidr2) == (addr1 <= addr2)
+      where
+        (Cidr addr1 mask1) = normalize cidr1
+        (Cidr addr2 mask2) = normalize cidr2
+
+
+-- If we have two CIDRs whose normalized addresses agree, then we want
+-- to use the mask order, i.e. that big networks come before small
+-- networks. This disagrees with containment order.
+prop_ord_uses_mask_when_addrs_equal :: TestTree
+prop_ord_uses_mask_when_addrs_equal =
+  localOption (QuickCheckTests 500) $
+    testProperty "The CIDR order is by mask when the addresses agree" prop
+  where
+    prop :: Cidr -> Cidr -> Property
+    prop cidr1 cidr2 =
+      (addr1 == addr2) ==> (cidr1 <= cidr2) == (mask1 <= mask2)
+      where
+        (Cidr addr1 mask1) = normalize cidr1
+        (Cidr addr2 mask2) = normalize cidr2
+
+
+-- Big networks come first.
+prop_ord_and_contains_disagree :: TestTree
+prop_ord_and_contains_disagree =
+  testProperty "The CIDR order disagrees with containment" prop
+  where
+    prop :: Cidr -> Cidr -> Property
+    prop cidr1 cidr2 = (cidr1 `contains` cidr2) ==> (cidr1 <= cidr2)
+
+
+-- The biggest network always comes first.
+prop_ord_minimum :: TestTree
+prop_ord_minimum =
+  testProperty "The CIDR order has 0.0.0.0/0 as a minimum" prop
+  where
+    min_cidr = read "0.0.0.0/0" :: Cidr
+    prop :: Cidr -> Bool
+    prop cidr = min_cidr <= cidr
+
+
+-- The CIDR order also has a maximum.
+prop_ord_maximum :: TestTree
+prop_ord_maximum =
+  testProperty "The CIDR order has 255.255.255.255/32 as a maximum" prop
+  where
+    max_cidr = read "255.255.255.255/32" :: Cidr
+    prop :: Cidr -> Bool
+    prop cidr = max_cidr >= cidr