]> gitweb.michael.orlitzky.com - hath.git/blobdiff - src/Main.hs
Add a --sort flag to hath and document/test why it was needed after all.
[hath.git] / src / Main.hs
index deb902297c45d3fac0990854f7a471c80f09a9b2..4774c8778e5904a42378e53e2673ef112f3cdef7 100644 (file)
@@ -1,18 +1,16 @@
 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 qualified Data.List as List (sort)
 import Data.Maybe (catMaybes, isNothing)
-import Data.String.Utils (splitWs)
-import System.Exit (ExitCode(..), exitWith)
+import System.Exit (ExitCode( ExitFailure ), exitWith)
 import System.IO (stderr, hPutStrLn)
 import Text.Read (readMaybe)
 
 import Cidr (
-  Cidr(..),
+  Cidr(),
   combine_all,
   enumerate,
   max_octet1,
@@ -23,13 +21,16 @@ import Cidr (
   min_octet2,
   min_octet3,
   min_octet4 )
-import CommandLine (Args(..), get_args)
-import DNS (Domain, PTRResult, lookup_ptrs)
+import qualified Cidr ( normalize )
+import CommandLine(
+  Args( Regexed, Reduced, Duped, Diffed, Listed, barriers, normalize, sort ),
+  get_args )
 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]"
 
@@ -37,6 +38,7 @@ 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'.
+--
 add_barriers :: String -> String
 add_barriers x = non_addr_char ++ x ++ non_addr_char
 
@@ -52,7 +54,7 @@ add_barriers x = non_addr_char ++ x ++ non_addr_char
 --   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 :: Bool -> 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])
@@ -74,6 +76,7 @@ cidr_to_regex use_barriers cidr =
 
 -- | Take a list of Strings, and return a regular expression matching
 --   any of them.
+--
 alternate :: [String] -> String
 alternate terms = "(" ++ (intercalate "|" terms) ++ ")"
 
@@ -101,15 +104,17 @@ main = do
   -- This reads stdin.
   input <- getContents
 
-  let cidr_strings = splitWs input
-  let cidrs = map readMaybe cidr_strings
+  let cidr_strings = words input
+  let cidrs = map readMaybe cidr_strings :: [Maybe Cidr]
 
   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)
+
+    let print_pair :: (String, Maybe Cidr) -> IO ()
+        print_pair (x, Nothing) = hPutStrLn stderr ("  * " ++ x)
         print_pair (_, _) = return ()
 
     mapM_ print_pair pairs
@@ -123,8 +128,11 @@ main = 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)
+    Reduced{} -> do
+      -- Pre-normalize all CIDRs if the user asked for it.
+      let nrml_func = if (normalize args) then Cidr.normalize else id
+      let sort_func = if (sort args) then List.sort else id :: [Cidr] -> [Cidr]
+      mapM_ (print . nrml_func) (sort_func $ combine_all valid_cidrs)
     Duped{} ->
        mapM_ print dupes
        where
@@ -141,23 +149,3 @@ main = 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
-            Left err -> "ERROR (" ++ (show err) ++ ")"
-            Right ds -> BS.unpack $ BS.intercalate space ds