]> gitweb.michael.orlitzky.com - haeredes.git/blobdiff - src/Main.hs
Update code and doctests to support the new version of the dns library.
[haeredes.git] / src / Main.hs
index d425734c275404e24310edb650ac33c9b4fe0b67..a5dc79466067f0dc70fc529169f55d111ae13b96 100644 (file)
@@ -4,42 +4,66 @@ where
 import Control.Concurrent.ParallelIO.Global (
   parallel,
   stopGlobalPool )
+import Control.Monad (unless)
 import qualified Data.ByteString.Char8 as BS (
   getContents,
   pack,
   words )
 import Data.List ((\\))
 import Data.String.Utils (join)
-
 import Network.DNS (
   Domain,
   FileOrNumericHost(RCHostName),
-  ResolvConf(resolvInfo),
+  ResolvConf(resolvInfo, resolvTimeout),
   defaultResolvConf,
-  lookupNS,
   makeResolvSeed,
   withResolver )
+import System.Exit (ExitCode(..), exitWith)
+import System.IO (hPutStrLn, stderr)
 
-import CommandLine (Args(..), get_args)
-import DNS (normalize)
 
-report :: (Domain, Maybe [Domain]) -> IO ()
-report (d, Nothing) =
+import CommandLine (Args(..), get_args)
+import DNS (
+  LookupResult,
+  lookupMX',
+  lookupNS',
+  normalize,
+  normalize_case,
+  resolve_address )
+import ExitCodes (exit_bad_server)
+import Timeout (Timeout(..))
+
+
+-- | Given a list of delegates, report results for this
+--   LookupResult.
+--
+--   If there's an empty list in the second component, there were no
+--   query results, so we report that the domain was not delegated. If
+--   there were some results and there are leftovers (after removing
+--   the delegates), we report those as well.
+--
+report :: [Domain] -- ^ The list of @delgts@
+       -> LookupResult
+       -> IO ()
+
+-- If the lookup resulted in a DNS error, we just ignore the whole
+-- thing.
+report _ (_, Left _) = return ()
+
+-- If the lookup succeeded but there were no results, report that the
+-- domain is not delegated.
+report _ (d, Right []) =
   putStrLn $ "Domain " ++ (show d) ++ " not delegated."
-report (d, Just leftovers) =
-  if null leftovers
-  then return ()
-  else putStrLn $ "Domain " ++
-                  (show d) ++
-                  " delegates somewhere else: " ++
-                  (join " " (map show leftovers))
-
-clean :: [Domain] -- ^ List of delegates, @ds@
-      -> (Domain, Maybe [Domain]) -- ^ Pairs of (domain name, lookup result)
-      -> (Domain, Maybe [Domain])
-clean _ p@(_, Nothing) = p
-clean ds (d, Just targets) =
-  (d, Just $ targets \\ ds)
+
+-- Otherwise, subtract our delegates from the list of results and
+-- report the leftovers.
+report delgts (d, Right hosts) = do
+  let leftovers = hosts \\ delgts
+  unless (null leftovers) $
+    putStrLn $ "Domain " ++
+               (show d) ++
+               " delegates somewhere else: " ++
+               (join " " (map show leftovers))
 
 
 main :: IO ()
@@ -55,29 +79,44 @@ main = do
   -- Convert these to ByteStrings.
   let raw_delegates = map BS.pack (delegates cfg)
 
+  let normalize_function =
+        if (no_append_root cfg)
+        then normalize_case
+        else normalize
+
   -- Normalize the given names and delegates
-  let nrml_domains   = map normalize raw_domains
-  let nrml_delegates = map normalize raw_delegates
+  let nrml_domains   = map normalize_function raw_domains
+  let nrml_delegates = map normalize_function raw_delegates
+
+  rc' <- case (server cfg) of
+           Nothing -> return defaultResolvConf
+           Just s -> do
+             s' <- resolve_address s
+             case s' of
+               Left err -> do
+                 let errmsg = show err
+                 hPutStrLn stderr ("Bad DNS server or lookup error: " ++ errmsg)
+                 exitWith (ExitFailure exit_bad_server)
+               Right []  -> do
+                 hPutStrLn stderr ("Hostname " ++ s ++ " has no 'A' records.")
+                 exitWith (ExitFailure exit_bad_server)
+               Right (srv:_) ->
+                 return $ defaultResolvConf { resolvInfo =
+                                                RCHostName (show srv) }
+
+  -- Set the timeout from the command line. The resolvTimeout field is
+  -- in microseconds, so we multiply by one million.
+  let rc = rc' { resolvTimeout = 1000 * 1000 * seconds (timeout cfg) }
+  rs <- makeResolvSeed rc
 
-  let rc = case (server cfg) of
-             Nothing -> defaultResolvConf
-             Just s -> defaultResolvConf { resolvInfo = RCHostName s }
+  let lookup_function = case cfg of
+                          NS{} -> lookupNS'
+                          MX{} -> lookupMX'
 
-  rs <- makeResolvSeed rc
-  withResolver rs $ \resolver -> do
-    -- This function keeps the domain matches with its NS records.
-    let lookupNS' = \d -> (lookupNS resolver d) >>= (return . ((,) d))
-
-    -- Bad stuff happens if we try to run these lookups in parallel
-    -- instead of the reports.
-    domains_ns <- mapM lookupNS' nrml_domains
-    let cdns = map (clean nrml_delegates) domains_ns
-
-    _ <- case cfg of
-           (NS _ _) ->
-             -- We're only checking NS records, so report what we found.
-             parallel (map report cdns)
-           (MX _ _) ->
-             return [()]
-
-    stopGlobalPool
+  _ <- withResolver rs $ \resolver -> do
+         -- Bad stuff happens if we try to run these lookups in parallel
+         -- instead of the reports.
+         records <- mapM (lookup_function resolver) nrml_domains
+         parallel (map (report nrml_delegates) records)
+
+  stopGlobalPool