]> gitweb.michael.orlitzky.com - hath.git/blobdiff - src/Octet.hs
Bump the version number to 0.0.4 in hath.cabal.
[hath.git] / src / Octet.hs
index 2e372fd4a489c14963508328253e466903d0e333..531d4d071f051e0124e57fa3417e167e8cb70542 100644 (file)
@@ -2,8 +2,12 @@ module Octet
 where
 
 import Data.Maybe (fromJust)
-import Test.HUnit
-import Test.QuickCheck
+
+import Test.HUnit (assertEqual)
+import Test.Framework (Test, testGroup)
+import Test.Framework.Providers.HUnit (testCase)
+
+import Test.QuickCheck (Arbitrary(..), Gen)
 
 import Bit as B
 import Maskable
@@ -74,6 +78,36 @@ instance Maskable Octet where
   apply_mask oct _ _ = oct
 
 
+instance Ord Octet where
+  (Octet x1 x2 x3 x4 x5 x6 x7 x8) <= (Octet y1 y2 y3 y4 y5 y6 y7 y8)
+    | x1 > y1 = False
+    | x2 > y2 = False
+    | x3 > y3 = False
+    | x4 > y4 = False
+    | x5 > y5 = False
+    | x6 > y6 = False
+    | x7 > y7 = False
+    | x8 > y8 = False
+    | otherwise = True
+
+
+instance Bounded Octet where
+  -- | The octet with the least possible value.
+  minBound =
+    Octet B.Zero B.Zero B.Zero B.Zero B.Zero B.Zero B.Zero B.Zero
+
+  -- | The octet with the greatest possible value.
+  maxBound =
+    Octet B.One B.One B.One B.One B.One B.One B.One B.One
+
+
+instance Enum Octet 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 . octet_from_int
+  fromEnum = octet_to_int
+
 -- | 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.
@@ -112,53 +146,39 @@ octet_from_string s =
     x:_ -> octet_from_int (fst x)
 
 
--- | The octet with the least possible value.
-min_octet :: Octet
-min_octet =
-  Octet B.Zero B.Zero B.Zero B.Zero B.Zero B.Zero B.Zero B.Zero
-
-
--- | The octet with the greatest possible value.
-max_octet :: Octet
-max_octet =
-  Octet B.One B.One B.One B.One B.One B.One B.One B.One
-
-
 
 -- HUnit Tests
 test_octet_from_int1 :: Test
 test_octet_from_int1 =
-  TestCase $ assertEqual "octet_from_int 128 should parse as 10000000" oct1 oct2
+  testCase desc $ assertEqual desc oct1 oct2
   where
+    desc = "octet_from_int 128 should parse as 10000000"
     oct1 = Octet B.One B.Zero B.Zero B.Zero B.Zero B.Zero B.Zero B.Zero
     oct2 = fromJust $ octet_from_int 128
 
 test_octet_mask1 :: Test
 test_octet_mask1 =
-  TestCase $
-    assertEqual
-    "The network bits of 255/4 should equal 240"
-    oct2
-    (apply_mask oct1 Four B.Zero)
+  testCase desc $
+    assertEqual desc oct2 (apply_mask oct1 Four B.Zero)
   where
+    desc = "The network bits of 255/4 should equal 240"
     oct1 = fromJust $ octet_from_int 255
     oct2 = fromJust $ octet_from_int 240
 
 
 test_octet_mask2 :: Test
 test_octet_mask2 =
-  TestCase $
-    assertEqual
-    "The network bits of 255/1 should equal 128"
-    oct2
-    (apply_mask oct1 Maskbits.One B.Zero)
+  testCase desc $
+    assertEqual desc oct2 (apply_mask oct1 Maskbits.One B.Zero)
   where
+    desc = "The network bits of 255/1 should equal 128"
     oct1 = fromJust $ octet_from_int 255
     oct2 = fromJust $ octet_from_int 128
 
 
-octet_tests :: [Test]
+octet_tests :: Test
 octet_tests =
-  [ test_octet_from_int1,
+  testGroup "Octet Tests" [
+    test_octet_from_int1,
     test_octet_mask1,
     test_octet_mask2 ]