A ton more code cleanup.
-- | The Bit module contains the Bit data type, which is essentially a
-- renamed Boolean, and some convenience functions.
-module Bit
+module Bit (
+ Bit(..)
+ )
where
import Test.QuickCheck (
instance Bounded Bit where
minBound = Zero
maxBound = One
-
-
--- | Convert a Bit to an Int.
-bit_to_int :: Bit -> Int
-bit_to_int Zero = 0
-bit_to_int One = 1
-
--- | If we are passed a '0' or '1', convert it
--- appropriately. Otherwise, return Nothing.
-bit_from_char :: Char -> Maybe Bit
-bit_from_char '0' = Just Zero
-bit_from_char '1' = Just One
-bit_from_char _ = Nothing
import Test.QuickCheck (Arbitrary(..), Gen, Property, (==>))
import Text.Read (readMaybe)
-import qualified Bit as B
-import IPv4Address
-import Maskable
-import Maskbits
-import Octet
+import qualified Bit as B (Bit(..))
+import IPv4Address (IPv4Address(..), most_sig_bit_different)
+import Maskable (Maskable(..))
+import Maskbits (Maskbits(..))
+import Octet (Octet(..))
data Cidr = Cidr { ipv4address :: IPv4Address,
-- after the trailing slash.
maskbits_from_cidr_string :: String -> Maybe Maskbits
maskbits_from_cidr_string s
- | length partlist == 2 = maskbits_from_string (partlist !! 1)
+ | length partlist == 2 = readMaybe (partlist !! 1)
| otherwise = Nothing
where
partlist = splitOneOf "/" s
combine_adjacent cidr1 cidr2
| not (adjacent cidr1 cidr2) = Nothing
| (maskbits cidr1 == Zero) = Nothing
- | otherwise = Just $ cidr1 { maskbits = decrement (maskbits cidr1) }
+ | otherwise = Just $ cidr1 { maskbits = pred (maskbits cidr1) }
enumerate :: Cidr -> [IPv4Address]
enumerate cidr = [(min_host cidr)..(max_host cidr)]
+-- Test lists.
+cidr_tests :: Test
+cidr_tests =
+ testGroup "CIDR Tests" [
+ test_enumerate,
+ test_min_host1,
+ test_max_host1,
+ test_equality1,
+ test_contains1,
+ test_contains2,
+ test_contains_proper1,
+ test_contains_proper2,
+ test_adjacent1,
+ test_adjacent2,
+ test_adjacent3,
+ test_adjacent4,
+ test_combine_contained1,
+ test_combine_contained2,
+ test_combine_all1,
+ test_combine_all2,
+ test_combine_all3 ]
+
+cidr_properties :: Test
+cidr_properties =
+ testGroup "CIDR Properties" [
+ testProperty
+ "All CIDRs contain themselves"
+ prop_all_cidrs_contain_themselves,
+
+ testProperty
+ "contains_proper is intransitive"
+ prop_contains_proper_intransitive
+ ]
+
-- HUnit Tests
+test_enumerate :: Test
+test_enumerate =
+ testCase desc $ assertEqual desc expected actual
+ where
+ desc = "192.168.0.240/30 is enumerated correctly"
+ oct1 = toEnum 192
+ oct2 = toEnum 168
+ oct3 = minBound
+ 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 $ fromJust $ cidr_from_string "192.168.0.240/30"
test_min_host1 :: Test
test_min_host1 =
test_cidrs = [cidr1, cidr2, cidr3, cidr4]
-cidr_tests :: Test
-cidr_tests =
- testGroup "CIDR Tests" [
- test_min_host1,
- test_max_host1,
- test_equality1,
- test_contains1,
- test_contains2,
- test_contains_proper1,
- test_contains_proper2,
- test_adjacent1,
- test_adjacent2,
- test_adjacent3,
- test_adjacent4,
- test_combine_contained1,
- test_combine_contained2,
- test_combine_all1,
- test_combine_all2,
- test_combine_all3 ]
-
-
-- QuickCheck Tests
prop_all_cidrs_contain_themselves :: Cidr -> Bool
prop_all_cidrs_contain_themselves cidr1 = cidr1 `contains` cidr1
prop_contains_proper_intransitive cidr1 cidr2 =
(cidr1 `contains_proper` cidr2) ==>
(not (cidr2 `contains_proper` cidr1))
-
-cidr_properties :: Test
-cidr_properties =
- testGroup "CIDR Properties" [
- testProperty
- "All CIDRs contain themselves"
- prop_all_cidrs_contain_themselves,
-
- testProperty
- "contains_proper is intransitive"
- prop_contains_proper_intransitive
- ]
--- The CommandLine module handles parsing of the command-line options.
--- It should more or less be a black box, providing Main with only the
--- information it requires.
-
+-- | The CommandLine module handles parsing of the command-line
+-- options. It should more or less be a black box, providing Main
+-- with only the information it requires.
module CommandLine
( help_set,
help_text,
input_function,
Mode(..),
parse_errors,
- parse_mode
-) where
-
-import Data.Char(toLower)
-import System.Console.GetOpt
+ parse_mode)
+where
+
+import Data.Char (toLower)
+import System.Console.GetOpt (
+ ArgDescr(NoArg, ReqArg),
+ ArgOrder(Permute),
+ OptDescr(..),
+ getOpt,
+ usageInfo )
import System.Environment (getArgs)
module IPv4Address(
+ IPv4Address(..),
ipv4address_properties,
ipv4address_tests,
- IPv4Address(..),
- most_sig_bit_different,
-) where
+ most_sig_bit_different )
+where
-import Data.Maybe (fromJust)
import Test.HUnit (assertEqual)
import Test.Framework (Test, testGroup)
import Test.Framework.Providers.HUnit (testCase)
import Test.Framework.Providers.QuickCheck2 (testProperty)
import Test.QuickCheck (Arbitrary(..), Gen, Property, (==>))
-import Maskable
-import Maskbits
-import Octet
+import Maskable (Maskable(..))
+import Maskbits (Maskbits(..))
+import Octet (Octet(..))
data IPv4Address =
IPv4Address { octet1 :: Octet,
--- | Convert @addr@ to an 'Int' by converting each octet to an 'Int'
--- and shifting the result to the left by 0,8.16, or 24 bits.
-ipv4address_to_int :: IPv4Address -> Int
-ipv4address_to_int addr =
- (shifted_oct1) + (shifted_oct2) + (shifted_oct3) + oct4
- where
- oct1 = fromEnum (octet1 addr)
- oct2 = fromEnum (octet2 addr)
- oct3 = fromEnum (octet3 addr)
- oct4 = fromEnum (octet4 addr)
-
- shifted_oct1 = oct1 * 2^(24 :: Integer)
- shifted_oct2 = oct2 * 2^(16 :: Integer)
- shifted_oct3 = oct3 * 2^(8 :: Integer)
-
-
-
--- | Convert an 'Int' @x@ to an 'IPv4Address'. Each octet of @x@ is
--- right-shifted by the appropriate number of bits, and the fractional
--- part is dropped.
-ipv4address_from_int :: Int -> Maybe IPv4Address
-ipv4address_from_int x
- | (x < 0) || (x > 2^(32 :: Integer) - 1) = Nothing
- | otherwise = do
- -- If the algebra is right, none of these octet_from_int calls
- -- below can fail since 0 <= x <= 2^32 - 1.
- oct1 <- octet_from_int shifted_x1
- oct2 <- octet_from_int shifted_x2
- oct3 <- octet_from_int shifted_x3
- oct4 <- octet_from_int x4
- return $ IPv4Address oct1 oct2 oct3 oct4
- where
- -- Chop off the higher octets. x1 = x `mod` 2^32, would be
- -- redundant.
- x2 = x `mod` 2^(24 :: Integer)
- x3 = x `mod` 2^(16 :: Integer)
- x4 = x `mod` 2^(8 :: Integer)
- -- Perform right-shifts. x4 doesn't need a shift.
- shifted_x1 = x `quot` 2^(24 :: Integer)
- shifted_x2 = x2 `quot` 2^(16 :: Integer)
- shifted_x3 = x3 `quot` 2^(8 :: Integer)
-
instance Enum IPv4Address 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 . ipv4address_from_int
- fromEnum = ipv4address_to_int
+ -- | Convert an 'Int' @x@ to an 'IPv4Address'. Each octet of @x@ is
+ -- right-shifted by the appropriate number of bits, and the fractional
+ -- part is dropped.
+ toEnum x =
+ IPv4Address oct1 oct2 oct3 oct4
+ where
+ -- Chop off the higher octets. x1 = x `mod` 2^32, would be
+ -- redundant.
+ x2 = x `mod` 2^(24 :: Integer)
+ x3 = x `mod` 2^(16 :: Integer)
+ x4 = x `mod` 2^(8 :: Integer)
+ -- Perform right-shifts. x4 doesn't need a shift.
+ shifted_x1 = x `quot` 2^(24 :: Integer)
+ shifted_x2 = x2 `quot` 2^(16 :: Integer)
+ shifted_x3 = x3 `quot` 2^(8 :: Integer)
+ oct1 = toEnum shifted_x1
+ oct2 = toEnum shifted_x2
+ oct3 = toEnum shifted_x3
+ oct4 = toEnum x4
+
+ -- | Convert @addr@ to an 'Int' by converting each octet to an 'Int'
+ -- and shifting the result to the left by 0,8.16, or 24 bits.
+ fromEnum addr =
+ (shifted_oct1) + (shifted_oct2) + (shifted_oct3) + oct4
+ where
+ oct1 = fromEnum (octet1 addr)
+ oct2 = fromEnum (octet2 addr)
+ oct3 = fromEnum (octet3 addr)
+ oct4 = fromEnum (octet4 addr)
+ shifted_oct1 = oct1 * 2^(24 :: Integer)
+ shifted_oct2 = oct2 * 2^(16 :: Integer)
+ shifted_oct3 = oct3 * 2^(8 :: Integer)
-- | Given two addresses, find the number of the most significant bit
-- where they differ. If the addresses are the same, return
mk_testaddr a b c d =
IPv4Address oct1 oct2 oct3 oct4
where
- oct1 = fromJust $ octet_from_int a
- oct2 = fromJust $ octet_from_int b
- oct3 = fromJust $ octet_from_int c
- oct4 = fromJust $ octet_from_int d
+ oct1 = toEnum a
+ oct2 = toEnum b
+ oct3 = toEnum c
+ oct4 = toEnum d
test_minBound :: Test
test_minBound =
+module Main
+where
+
import Control.Concurrent.ParallelIO.Global (
parallel,
stopGlobalPool )
import System.Exit (ExitCode(..), exitSuccess, exitWith)
import System.IO (stderr, hPutStrLn)
-import Cidr (Cidr(..),
- cidr_from_string,
- combine_all,
- enumerate,
- max_octet1,
- max_octet2,
- max_octet3,
- max_octet4,
- min_octet1,
- min_octet2,
- min_octet3,
- min_octet4 )
-
-import CommandLine (help_set,
- help_text,
- input_function,
- Mode(..),
- parse_errors,
- parse_mode)
-
+import Cidr (
+ Cidr(..),
+ cidr_from_string,
+ combine_all,
+ enumerate,
+ max_octet1,
+ max_octet2,
+ max_octet3,
+ max_octet4,
+ min_octet1,
+ min_octet2,
+ min_octet3,
+ min_octet4 )
+import CommandLine (
+ help_set,
+ help_text,
+ input_function,
+ Mode(..),
+ parse_errors,
+ parse_mode )
import DNS (Domain, lookup_ptrs)
import ExitCodes ( exit_args_parse_failed, exit_invalid_cidr )
import Octet ()
-module Maskable where
+module Maskable (
+ Maskable(..) )
+where
-import Bit
-import Maskbits
+import Bit (Bit)
+import Maskbits (Maskbits)
-- | Any string of bits should be maskable by some number of netmask
-- bits. The convention of the Maskable typeclass follows CIDR
-module Maskbits
-( Maskbits(..),
- decrement,
- maskbits_from_string
-) where
+module Maskbits(
+ Maskbits(..),
+ )
+where
+
+import Test.QuickCheck (Arbitrary(..), elements)
-import Test.QuickCheck
-- | A type representing the number of bits in a CIDR netmask.
data Maskbits =
| Thirty
| ThirtyOne
| ThirtyTwo
- deriving (Eq, Ord)
+ deriving (Enum, Eq, Ord)
instance Show Maskbits where
ThirtyTwo ]
-
--- | There are only 32 bits in an IPv4 address, so there
--- can't be more bits than that in the mask.
-maskbits_from_int :: Int -> Maybe Maskbits
-maskbits_from_int 0 = Just Zero
-maskbits_from_int 1 = Just One
-maskbits_from_int 2 = Just Two
-maskbits_from_int 3 = Just Three
-maskbits_from_int 4 = Just Four
-maskbits_from_int 5 = Just Five
-maskbits_from_int 6 = Just Six
-maskbits_from_int 7 = Just Seven
-maskbits_from_int 8 = Just Eight
-maskbits_from_int 9 = Just Nine
-maskbits_from_int 10 = Just Ten
-maskbits_from_int 11 = Just Eleven
-maskbits_from_int 12 = Just Twelve
-maskbits_from_int 13 = Just Thirteen
-maskbits_from_int 14 = Just Fourteen
-maskbits_from_int 15 = Just Fifteen
-maskbits_from_int 16 = Just Sixteen
-maskbits_from_int 17 = Just Seventeen
-maskbits_from_int 18 = Just Eighteen
-maskbits_from_int 19 = Just Nineteen
-maskbits_from_int 20 = Just Twenty
-maskbits_from_int 21 = Just TwentyOne
-maskbits_from_int 22 = Just TwentyTwo
-maskbits_from_int 23 = Just TwentyThree
-maskbits_from_int 24 = Just TwentyFour
-maskbits_from_int 25 = Just TwentyFive
-maskbits_from_int 26 = Just TwentySix
-maskbits_from_int 27 = Just TwentySeven
-maskbits_from_int 28 = Just TwentyEight
-maskbits_from_int 29 = Just TwentyNine
-maskbits_from_int 30 = Just Thirty
-maskbits_from_int 31 = Just ThirtyOne
-maskbits_from_int 32 = Just ThirtyTwo
-maskbits_from_int _ = Nothing
-
-
--- | Convert a String to Maskbits, if possible.
-maskbits_from_string :: String -> Maybe Maskbits
-maskbits_from_string s =
- case (reads s :: [(Int, String)]) of
- [] -> Nothing
- x:_ -> maskbits_from_int (fst x)
-
-
-
--- | Maskbits are just natural numbers, this returns the previous one.
-decrement :: Maskbits -> Maskbits
-decrement Zero = Zero
-decrement One = Zero
-decrement Two = One
-decrement Three = Two
-decrement Four = Three
-decrement Five = Four
-decrement Six = Five
-decrement Seven = Six
-decrement Eight = Seven
-decrement Nine = Eight
-decrement Ten = Nine
-decrement Eleven = Ten
-decrement Twelve = Eleven
-decrement Thirteen = Twelve
-decrement Fourteen = Thirteen
-decrement Fifteen = Fourteen
-decrement Sixteen = Fifteen
-decrement Seventeen = Sixteen
-decrement Eighteen = Seventeen
-decrement Nineteen = Eighteen
-decrement Twenty = Nineteen
-decrement TwentyOne = Twenty
-decrement TwentyTwo = TwentyOne
-decrement TwentyThree = TwentyTwo
-decrement TwentyFour = TwentyThree
-decrement TwentyFive = TwentyFour
-decrement TwentySix = TwentyFive
-decrement TwentySeven = TwentySix
-decrement TwentyEight = TwentySeven
-decrement TwentyNine = TwentyEight
-decrement Thirty = TwentyNine
-decrement ThirtyOne = Thirty
-decrement ThirtyTwo = ThirtyOne
+instance Read Maskbits where
+ readsPrec _ = \s ->
+ case (reads s :: [(Int, String)]) of
+ [] -> []
+ (x,leftover):_ -> go x leftover
+ where
+ go :: Int -> String -> [(Maskbits, String)]
+ go y s
+ | y < minBound || y > maxBound = []
+ | otherwise = [(toEnum y, s)]
module Octet (
Octet(..),
- octet_from_int,
octet_properties,
octet_tests,
)
where
-import Data.Maybe (fromJust)
import Test.HUnit (assertEqual)
import Test.Framework (Test, testGroup)
import Test.Framework.Providers.HUnit (testCase)
import Test.Framework.Providers.QuickCheck2 (testProperty)
import Test.QuickCheck (Arbitrary(..), Gen, Property, (==>))
-import Bit as B
-import Maskable
-import Maskbits
+import Bit as B (Bit(..))
+import Maskable (Maskable(..))
+import Maskbits (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
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
+
+ -- | Create an 'Octet' from an 'Int'. The docs for Enum say we
+ -- should throw a runtime error on out-of-bounds, so we do.
+ toEnum x
+ | x < minBound || x > maxBound = error "octet out of bounds"
+ | otherwise = 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
-- | 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.
fromEnum 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))
-
+ 128 * (fromEnum (b1 x)) +
+ 64 * (fromEnum (b2 x)) +
+ 32 * (fromEnum (b3 x)) +
+ 16 * (fromEnum (b4 x)) +
+ 8 * (fromEnum (b5 x)) +
+ 4 * (fromEnum (b6 x)) +
+ 2 * (fromEnum (b7 x)) +
+ 1 * (fromEnum (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
-
instance Read Octet where
readsPrec _ = \s ->
case (reads s :: [(Int, String)]) of
[] -> []
- (x,leftover):_ -> case (octet_from_int x) of
- Nothing -> []
- Just oct -> [(oct, leftover)]
+ (x,leftover):_ -> go x leftover
+ where
+ go :: Int -> String -> [(Octet, String)]
+ go y s
+ | y < minBound || y > maxBound = []
+ | otherwise = [(toEnum y, s)]
-- Test lists.
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
+ oct2 = toEnum 128
test_octet_mask1 :: Test
test_octet_mask1 =
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
+ oct1 = toEnum 255
+ oct2 = toEnum 240 :: Octet
test_octet_mask2 :: Test
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
+ oct1 = toEnum 255
+ oct2 = toEnum 128 :: Octet