]> gitweb.michael.orlitzky.com - hath.git/blob - src/Octet.hs
ceeb4b8ff2ddd9e3c047ab78924f7f7b206d6ef8
[hath.git] / src / Octet.hs
1 module Octet where
2
3 import Test.HUnit
4 import Test.QuickCheck
5
6 import Bit as B
7 import Maskable
8 import Maskbits
9
10 -- An Octet consists of eight bits. For our purposes, the most
11 -- significant bit will come "first." That is, b1 is in the 2^7
12 -- place while b8 is in the 2^0 place.
13 data Octet = None | Octet { b1 :: Bit,
14 b2 :: Bit,
15 b3 :: Bit,
16 b4 :: Bit,
17 b5 :: Bit,
18 b6 :: Bit,
19 b7 :: Bit,
20 b8 :: Bit }
21 deriving (Eq)
22
23
24 instance Show Octet where
25 show Octet.None = "None"
26 show oct = show (octet_to_int oct)
27
28
29 instance Arbitrary Octet where
30 arbitrary = do
31 a1 <- arbitrary :: Gen Bit
32 a2 <- arbitrary :: Gen Bit
33 a3 <- arbitrary :: Gen Bit
34 a4 <- arbitrary :: Gen Bit
35 a5 <- arbitrary :: Gen Bit
36 a6 <- arbitrary :: Gen Bit
37 a7 <- arbitrary :: Gen Bit
38 a8 <- arbitrary :: Gen Bit
39 return (Octet a1 a2 a3 a4 a5 a6 a7 a8)
40
41 coarbitrary _ = variant 0
42
43
44 instance Maskable Octet where
45 apply_mask _ Maskbits.None = Octet.None
46 apply_mask Octet.None _ = Octet.None
47 apply_mask oct mask
48 | mask == Eight = oct
49 | mask == Seven = oct { b8 = B.Zero }
50 | mask == Six = oct { b8 = B.Zero, b7 = B.Zero }
51 | mask == Five = oct { b8 = B.Zero, b7 = B.Zero, b6 = B.Zero }
52 | mask == Four = oct { b8 = B.Zero, b7 = B.Zero, b6 = B.Zero, b5 = B.Zero }
53 | mask == Three = oct { b8 = B.Zero, b7 = B.Zero, b6 = B.Zero, b5 = B.Zero, b4 = B.Zero }
54 | mask == Two = oct { b8 = B.Zero, b7 = B.Zero, b6 = B.Zero, b5 = B.Zero, b4 = B.Zero, b3 = B.Zero }
55 | mask == Maskbits.One = oct { b8 = B.Zero, b7 = B.Zero, b6 = B.Zero, b5 = B.Zero, b4 = B.Zero, b3 = B.Zero, b2 = B.Zero }
56 | mask == Maskbits.Zero = min_octet
57 | otherwise = Octet.None
58
59
60 -- Convert each bit to its integer value, and multiply by the
61 -- appropriate power of two. Sum them up, and we should get an integer
62 -- between 0 and 255.
63 octet_to_int :: Octet -> Int
64 octet_to_int x =
65 128 * (bit_to_int (b1 x)) +
66 64 * (bit_to_int (b2 x)) +
67 32 * (bit_to_int (b3 x)) +
68 16 * (bit_to_int (b4 x)) +
69 8 * (bit_to_int (b5 x)) +
70 4 * (bit_to_int (b6 x)) +
71 2 * (bit_to_int (b7 x)) +
72 1 * (bit_to_int (b8 x))
73
74
75
76 octet_from_int :: Int -> Octet
77 octet_from_int x
78 | (x < 0) || (x > 255) = Octet.None
79 | otherwise = (Octet a1 a2 a3 a4 a5 a6 a7 a8)
80 where
81 a1 = if (x >= 128) then B.One else B.Zero
82 a2 = if ((x `mod` 128) >= 64) then B.One else B.Zero
83 a3 = if ((x `mod` 64) >= 32) then B.One else B.Zero
84 a4 = if ((x `mod` 32) >= 16) then B.One else B.Zero
85 a5 = if ((x `mod` 16) >= 8) then B.One else B.Zero
86 a6 = if ((x `mod` 8) >= 4) then B.One else B.Zero
87 a7 = if ((x `mod` 4) >= 2) then B.One else B.Zero
88 a8 = if ((x `mod` 2) == 1) then B.One else B.Zero
89
90
91 octet_from_string :: String -> Octet
92 octet_from_string s =
93 case (reads s :: [(Int, String)]) of
94 [] -> Octet.None
95 x:_ -> octet_from_int (fst x)
96
97
98 -- The octet with the least possible value.
99 min_octet :: Octet
100 min_octet = Octet B.Zero B.Zero B.Zero B.Zero B.Zero B.Zero B.Zero B.Zero
101
102
103 -- The octet with the greatest possible value.
104 max_octet :: Octet
105 max_octet = Octet B.One B.One B.One B.One B.One B.One B.One B.One
106
107
108
109 -- HUnit Tests
110 test_octet_from_int1 :: Test
111 test_octet_from_int1 =
112 TestCase $ assertEqual "octet_from_int 128 should parse as 10000000" oct1 (octet_from_int 128)
113 where
114 oct1 = Octet B.One B.Zero B.Zero B.Zero B.Zero B.Zero B.Zero B.Zero
115
116
117 test_octet_mask1 :: Test
118 test_octet_mask1 =
119 TestCase $ assertEqual "The network bits of 255/4 should equal 240" oct2 (apply_mask oct1 Four)
120 where
121 oct1 = octet_from_int 255
122 oct2 = octet_from_int 240
123
124
125 test_octet_mask2 :: Test
126 test_octet_mask2 =
127 TestCase $ assertEqual "The network bits of 255/1 should equal 128" oct2 (apply_mask oct1 Maskbits.One)
128 where
129 oct1 = octet_from_int 255
130 oct2 = octet_from_int 128
131
132
133 octet_tests :: [Test]
134 octet_tests = [ test_octet_from_int1,
135 test_octet_mask1,
136 test_octet_mask2 ]