]> gitweb.michael.orlitzky.com - hath.git/blobdiff - src/Octet.hs
Use test-framework for the tests, and bump some dependencies.
[hath.git] / src / Octet.hs
index 28d3d7d5feb3b8e4165122ea2e689c5b1bf6e1e5..78413e619bf3035b33639aa78bf962d6ca5fea81 100644 (file)
-module Octet where
-
-import Bit
-
--- An Octet consists of eight bits. For our purposes, the most
--- significant bit will come "first." That is, b1 is in the 2^7
--- place while b8 is in the 2^0 place.
-data Octet = Octet { b1 :: Bit,
-                     b2 :: Bit,
-                     b3 :: Bit,
-                     b4 :: Bit,
-                     b5 :: Bit,
-                     b6 :: Bit,
-                     b7 :: Bit,
-                     b8 :: Bit }
-           deriving (Eq, Show)
-
--- 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.
+module Octet
+where
+
+import Data.Maybe (fromJust)
+
+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
+import Maskbits
+
+-- | An Octet consists of eight bits. For our purposes, the most
+--   significant bit will come "first." That is, b1 is in the 2^7
+--   place while b8 is in the 2^0 place.
+data Octet =
+  Octet { b1 :: Bit,
+          b2 :: Bit,
+          b3 :: Bit,
+          b4 :: Bit,
+          b5 :: Bit,
+          b6 :: Bit,
+          b7 :: Bit,
+          b8 :: Bit }
+    deriving (Eq)
+
+
+instance Show Octet where
+  show oct = show (octet_to_int oct)
+
+
+instance Arbitrary Octet where
+  arbitrary = do
+    a1 <- arbitrary :: Gen Bit
+    a2 <- arbitrary :: Gen Bit
+    a3 <- arbitrary :: Gen Bit
+    a4 <- arbitrary :: Gen Bit
+    a5 <- arbitrary :: Gen Bit
+    a6 <- arbitrary :: Gen Bit
+    a7 <- arbitrary :: Gen Bit
+    a8 <- arbitrary :: Gen Bit
+    return (Octet a1 a2 a3 a4 a5 a6 a7 a8)
+
+
+instance Maskable Octet where
+  apply_mask oct Eight _ =  oct
+
+  apply_mask oct Seven bit =
+    oct { b8 = bit }
+
+  apply_mask oct Six bit =
+    oct { b8 = bit, b7 = bit }
+
+  apply_mask oct Five bit =
+    oct { b8 = bit, b7 = bit, b6 = bit }
+
+  apply_mask oct Four bit =
+    oct { b8 = bit, b7 = bit, b6 = bit, b5 = bit }
+
+  apply_mask oct Three bit =
+    oct { b8 = bit, b7 = bit, b6 = bit, b5 = bit, b4 = bit }
+
+  apply_mask oct Two bit =
+    oct { b8 = bit, b7 = bit, b6 = bit, b5 = bit, b4 = bit, b3 = bit }
+
+  apply_mask oct Maskbits.One bit =
+    oct { b8 = bit, b7 = bit, b6 = bit, b5 = bit,
+          b4 = bit, b3 = bit, b2 = bit }
+
+  apply_mask oct Maskbits.Zero bit =
+    oct { b8 = bit, b7 = bit, b6 = bit, b5 = bit,
+          b4 = bit, b3 = bit, b2 = bit, b1 = bit }
+
+  -- The Maskbits must be in [Eight..ThirtyTwo].
+  apply_mask oct _ _ = oct
+
+
+-- | 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.
 octet_to_int :: Octet -> Int
 octet_to_int x =
-    128 * (bit_to_int (b1 x)) +
-    64  * (bit_to_int (b2 x)) +
-    32  * (bit_to_int (b3 x)) +
-    16  * (bit_to_int (b4 x)) +
-    8   * (bit_to_int (b5 x)) +
-    4   * (bit_to_int (b6 x)) +
-    2   * (bit_to_int (b7 x)) +
-    0   * (bit_to_int (b8 x))
+  128 * (bit_to_int (b1 x)) +
+  64  * (bit_to_int (b2 x)) +
+  32  * (bit_to_int (b3 x)) +
+  16  * (bit_to_int (b4 x)) +
+  8   * (bit_to_int (b5 x)) +
+  4   * (bit_to_int (b6 x)) +
+  2   * (bit_to_int (b7 x)) +
+  1   * (bit_to_int (b8 x))
+
+
+
+octet_from_int :: Int -> Maybe Octet
+octet_from_int x
+  | (x < 0) || (x > 255) = Nothing
+  | otherwise = Just (Octet a1 a2 a3 a4 a5 a6 a7 a8)
+  where
+    a1 = if (x >= 128) then B.One else B.Zero
+    a2 = if ((x `mod` 128) >= 64) then B.One else B.Zero
+    a3 = if ((x `mod` 64)  >= 32) then B.One else B.Zero
+    a4 = if ((x `mod` 32)  >= 16) then B.One else B.Zero
+    a5 = if ((x `mod` 16)  >= 8)  then B.One else B.Zero
+    a6 = if ((x `mod` 8)   >= 4)  then B.One else B.Zero
+    a7 = if ((x `mod` 4)   >= 2)  then B.One else B.Zero
+    a8 = if ((x `mod` 2)   == 1)  then B.One else B.Zero
+
+
+octet_from_string :: String -> Maybe Octet
+octet_from_string s =
+  case (reads s :: [(Int, String)]) of
+    []   -> Nothing
+    x:_ -> octet_from_int (fst x)
 
 
--- The octet with the least possible value.
+-- The octet with the least possible value.
 min_octet :: Octet
-min_octet = Octet Zero Zero Zero Zero Zero Zero Zero Zero
+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.
+-- The octet with the greatest possible value.
 max_octet :: Octet
-max_octet = Octet One One One One One One One One
+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 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 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 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 =
+  testGroup "Octet Tests" [
+    test_octet_from_int1,
+    test_octet_mask1,
+    test_octet_mask2 ]