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