]> gitweb.michael.orlitzky.com - hath.git/blobdiff - src/Main.hs
Switch from test-framework to tasty.
[hath.git] / src / Main.hs
index 53365373d9c4230b12760a5ea9a2e51f9e70866f..2bb586980f5a06bf2de39a54dfdab580c3cda21d 100644 (file)
-import Data.Char (digitToInt, intToDigit)
-import qualified Data.List as DL
-import qualified Numeric as N
-import System.Exit (exitFailure)
-import Text.Regex.Posix
-
-import ListUtils
-
--- Takes an IP address in CIDR notation, and returns a list of its
--- octets (converted to Int).
-octets :: String -> [Int]
-octets cidr = map read (take 4 (splitWith (`elem` "./") cidr))
-
-
--- Returns the mask portion of a CIDR address. That is, everything
--- after the trailing slash.
-maskbits :: String -> Int
-maskbits cidr = read ((splitWith (`elem` "/") cidr) !! 1)
-
-
--- Takes an Int, and returns its base-two representation as a String.
-base_two :: Int -> String
-base_two n = N.showIntAtBase 2 intToDigit n ""
-
-
--- Takes a set of octets, and converts them to base-two
--- individually. The results are then zero-padded on the left to 8
--- characters, and concatenated together.
-octets_base_two :: [Int] -> String
-octets_base_two octet_list =
-    DL.concatMap ((pad_left_to 8 '0') .base_two) octet_list
-
-
--- Returns the minimum address (as a base-two string) satisfying the
--- given CIDR string.
-min_base_two_address :: String -> String
-min_base_two_address cidr =
-    pad_right_to 32 '0' netpart
-    where
-      netpart = take (maskbits cidr) (octets_base_two (octets cidr))
-
-
--- Returns the maximum address (as a base-two string) satisfying the
--- given CIDR string.
-max_base_two_address :: String -> String
-max_base_two_address cidr =
-    pad_right_to 32 '1' netpart
-    where
-      netpart = take (maskbits cidr) (octets_base_two (octets cidr))
-
-
--- The octet components of min_base_two_address, as a base-two String.
-min_base_two_octets :: String -> [String]
-min_base_two_octets cidr =
-    [octet1, octet2, octet3, octet4]
-    where
-      addr   = min_base_two_address cidr
-      octet1 = fst (DL.splitAt 8 addr)
-      octet2 = fst (DL.splitAt 8 (snd (DL.splitAt 8 addr)))
-      octet3 = fst (DL.splitAt 8 (snd (DL.splitAt 16 addr)))
-      octet4 = snd (DL.splitAt 24 addr)
-
-
--- The octet components of max_base_two_address, as a base-two String.
-max_base_two_octets :: String -> [String]
-max_base_two_octets cidr =
-    [octet1, octet2, octet3, octet4]
-    where
-      addr   = max_base_two_address cidr
-      octet1 = fst (DL.splitAt 8 addr)
-      octet2 = fst (DL.splitAt 8 (snd (DL.splitAt 8 addr)))
-      octet3 = fst (DL.splitAt 8 (snd (DL.splitAt 16 addr)))
-      octet4 = snd (DL.splitAt 24 addr)
-
-
--- The octet components of min_base_two_address, as Ints.
-min_octets :: String -> [Int]
-min_octets cidr =
-    map base_two_to_base_ten (min_base_two_octets cidr)
-
-
--- The octet components of max_base_two_address, as Ints.
-max_octets :: String -> [Int]
-max_octets cidr =
-    map base_two_to_base_ten (max_base_two_octets cidr)
-
-
--- The base_two_to_base_ten function requires a way to determine
--- whether or not the character it's currently parsing is valid. This
--- should do it.
-is_binary_digit :: Char -> Bool
-is_binary_digit c =
-    if c `elem` ['0','1'] then
-        True
-    else
-        False
-
-
--- Convert a base-two String to an Int.
-base_two_to_base_ten :: String -> Int
-base_two_to_base_ten s =
-    if (length parsed) == 0 then
-        0
-    else
-        fst (parsed !! 0)
-    where
-      parsed = N.readInt 2 is_binary_digit digitToInt s
-
-
--- A regular expression that matches a non-address character.
+module Main
+where
+
+import Control.Concurrent.ParallelIO.Global ( stopGlobalPool )
+import Control.Monad (when)
+import qualified Data.ByteString.Char8 as BS (intercalate, pack, unpack)
+import Data.List ((\\), intercalate)
+import Data.Maybe (catMaybes, isNothing)
+import Data.String.Utils (splitWs)
+import Network.DNS.Types ( DNSError (NameError) )
+import System.Exit (ExitCode(..), exitWith)
+import System.IO (stderr, hPutStrLn)
+import Text.Read (readMaybe)
+
+import Cidr (
+  Cidr(..),
+  combine_all,
+  enumerate,
+  max_octet1,
+  max_octet2,
+  max_octet3,
+  max_octet4,
+  min_octet1,
+  min_octet2,
+  min_octet3,
+  min_octet4 )
+import CommandLine (Args(..), get_args)
+import DNS (Domain, PTRResult, lookup_ptrs)
+import ExitCodes ( exit_invalid_cidr )
+import Octet ()
+
+
+-- | A regular expression that matches a non-address character.
 non_addr_char :: String
 non_addr_char = "[^\\.0-9]"
 
 
--- Add non_addr_chars on either side of the given String. This
--- prevents (for example) the regex '127.0.0.1' from matching
--- '127.0.0.100'.
-addr_barrier :: String -> String
-addr_barrier x = non_addr_char ++ x ++ non_addr_char
+-- Add non_addr_chars on either side of the given String. This
+--   prevents (for example) the regex '127.0.0.1' from matching
+--   '127.0.0.100'.
+add_barriers :: String -> String
+add_barriers x = non_addr_char ++ x ++ non_addr_char
 
 
--- The magic happens here. We take a CIDR String as an argument, and
--- return the equivalent regular expression. We do this as follows:
+-- The magic happens here. We take a CIDR String as an argument, and
+--   return the equivalent regular expression. We do this as follows:
 --
--- 1. Compute the minimum possible value of each octet.
--- 2. Compute the maximum possible value of each octet.
--- 3. Generate a regex matching every value between those min and
---    max values.
--- 4. Join the regexes from step 3 with regexes matching periods.
--- 5. Stick an address boundary on either side of the result.
-cidr_to_regex :: String -> String
-cidr_to_regex cidr =
-    addr_barrier (DL.intercalate "\\." [range1, range2, range3, range4])
+--   1. Compute the minimum possible value of each octet.
+--   2. Compute the maximum possible value of each octet.
+--   3. Generate a regex matching every value between those min and
+--      max values.
+--   4. Join the regexes from step 3 with regexes matching periods.
+--   5. Stick an address boundary on either side of the result if
+--      use_barriers is True.
+--
+cidr_to_regex :: Bool -> Cidr.Cidr -> String
+cidr_to_regex use_barriers cidr =
+    let f = if use_barriers then add_barriers else id in
+      f (intercalate "\\." [range1, range2, range3, range4])
     where
       range1 = numeric_range min1 max1
       range2 = numeric_range min2 max2
       range3 = numeric_range min3 max3
       range4 = numeric_range min4 max4
-      min1   = (min_octets cidr) !! 0
-      min2   = (min_octets cidr) !! 1
-      min3   = (min_octets cidr) !! 2
-      min4   = (min_octets cidr) !! 3
-      max1   = (max_octets cidr) !! 0
-      max2   = (max_octets cidr) !! 1
-      max3   = (max_octets cidr) !! 2
-      max4   = (max_octets cidr) !! 3
-
+      min1   = fromEnum (min_octet1 cidr)
+      min2   = fromEnum (min_octet2 cidr)
+      min3   = fromEnum (min_octet3 cidr)
+      min4   = fromEnum (min_octet4 cidr)
+      max1   = fromEnum (max_octet1 cidr)
+      max2   = fromEnum (max_octet2 cidr)
+      max3   = fromEnum (max_octet3 cidr)
+      max4   = fromEnum (max_octet4 cidr)
 
--- Will return True if the passed String is in CIDR notation, False
--- otherwise.
-is_valid_cidr :: String -> Bool
-is_valid_cidr cidr = cidr =~ "([0-9]{1,3}\\.){3}[0-9]{1,3}/[0-9]{1,2}"
 
 
--- Take a list of Strings, and return a regular expression matching
--- any of them.
+-- Take a list of Strings, and return a regular expression matching
+--   any of them.
 alternate :: [String] -> String
-alternate terms = "(" ++ (concat (DL.intersperse "|" terms)) ++ ")"
+alternate terms = "(" ++ (intercalate "|" terms) ++ ")"
 
 
--- Take two Ints as parameters, and return a regex matching any
--- integer between them (inclusive).
+-- | Take two Ints as parameters, and return a regex matching any
+--   integer between them (inclusive).
+--
+--   IMPORTANT: we match from max to min so that if e.g. the last
+--   octet is '255', we want '255' to match before '2' in the regex
+--   (255|254|...|3|2|1) which does not happen if we use
+--   (1|2|3|...|254|255).
+--
 numeric_range :: Int -> Int -> String
 numeric_range x y =
-    alternate (map show [lower..upper])
+    alternate (map show $ reverse [lower..upper])
      where
        lower = minimum [x,y]
        upper = maximum [x,y]
 
 
--- Take a CIDR String, and exitFailure if it's invalid.
-validate_or_die :: String -> IO ()
-validate_or_die cidr = do
-  if (is_valid_cidr cidr)
-    then do
-      return ()
-    else do
-        putStrLn "Error: not valid CIDR notation."
-        exitFailure
-
-
 main :: IO ()
 main = do
+  args <- get_args
+
+  -- This reads stdin.
   input <- getContents
-  let cidrs = lines input
-  mapM validate_or_die cidrs
-  let regexes = map cidr_to_regex cidrs
-  putStrLn $ alternate regexes
 
+  let cidr_strings = splitWs input
+  let cidrs = map readMaybe cidr_strings
+
+  when (any isNothing cidrs) $ do
+    hPutStrLn stderr "ERROR: not valid CIDR notation:"
+
+    -- Output the bad lines, safely.
+    let pairs = zip cidr_strings cidrs
+    let print_pair (x, Nothing) = hPutStrLn stderr ("  * " ++ x)
+        print_pair (_, _) = return ()
+
+    mapM_ print_pair pairs
+    exitWith (ExitFailure exit_invalid_cidr)
+
+  -- Filter out only the valid ones.
+  let valid_cidrs = catMaybes cidrs
+
+  case args of
+    Regexed{} -> do
+      let cidrs' = combine_all valid_cidrs
+      let regexes = map (cidr_to_regex (barriers args)) cidrs'
+      putStrLn $ alternate regexes
+    Reduced{} ->
+      mapM_ print (combine_all valid_cidrs)
+    Duped{} ->
+       mapM_ print dupes
+       where
+         dupes = valid_cidrs \\ (combine_all valid_cidrs)
+    Diffed{} -> do
+       mapM_ putStrLn deletions
+       mapM_ putStrLn additions
+       where
+         dupes = valid_cidrs \\ (combine_all valid_cidrs)
+         deletions = map (\s -> '-' : (show s)) dupes
+         newcidrs = (combine_all valid_cidrs) \\ valid_cidrs
+         additions = map (\s -> '+' : (show s)) newcidrs
+    Listed{} -> do
+      let combined_cidrs = combine_all valid_cidrs
+      let addrs = concatMap enumerate combined_cidrs
+      mapM_ print addrs
+    Reversed{} -> do
+      let combined_cidrs = combine_all valid_cidrs
+      let addrs = concatMap enumerate combined_cidrs
+      let addr_bytestrings = map (BS.pack . show) addrs
+      ptrs <- lookup_ptrs addr_bytestrings
+      let pairs = zip addr_bytestrings ptrs
+      mapM_ (putStrLn . show_pair) pairs
+
+  stopGlobalPool
+
+  where
+    show_pair :: (Domain, PTRResult) -> String
+    show_pair (s, eds) =
+      (BS.unpack s) ++ ": " ++ results
+      where
+        space = BS.pack " "
+        results =
+          case eds of
+            -- NameError simply means "not found" so we output nothing.
+            Left NameError -> ""
+            Left err -> "ERROR (" ++ (show err) ++ ")"
+            Right ds -> BS.unpack $ BS.intercalate space ds