]> gitweb.michael.orlitzky.com - haeredes.git/blobdiff - src/Main.hs
Fix parallelization and bump to v0.3.0.
[haeredes.git] / src / Main.hs
index 4e0da6b6dc0296e730025f5295219eeaae254fe1..679a1ac1fe1d0dc3cf684420596676dde91e10e5 100644 (file)
@@ -2,7 +2,7 @@ module Main
 where
 
 import Control.Concurrent.ParallelIO.Global (
-  parallel,
+  parallelInterleaved,
   stopGlobalPool )
 import Control.Monad (unless)
 import qualified Data.ByteString.Char8 as BS (
@@ -34,14 +34,31 @@ import ExitCodes (exit_bad_server)
 import Timeout (Timeout(..))
 
 
--- | Report results for this LookupResult. If there's a Nothing 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 "cleaning"), we report those as well.
-report :: LookupResult -> IO ()
-report (d, Nothing) =
+-- | 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) =
+
+-- 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) ++
@@ -49,19 +66,6 @@ report (d, Just leftovers) =
                (join " " (map show leftovers))
 
 
--- | "Clean" a lookup result by subtracting out the list of delegates.
---   There shouldn't be anything left over. If there were no lookup
---   results, we leave the Nothing in place so that 'report' can
---   pattern match on it.
-clean :: [Domain] -- ^ List of delegates, @ds@
-      -> LookupResult
-      -> LookupResult
-clean _ p@(_, Nothing) = p
-clean delgts (d, Just targets) =
-  (d, Just $ targets \\ delgts)
-
-
-
 main :: IO ()
 main = do
   cfg <- get_args
@@ -89,27 +93,37 @@ main = do
            Just s -> do
              s' <- resolve_address s
              case s' of
-               Nothing -> do
-                 hPutStrLn stderr ("Bad DNS server or lookup error: " ++ s)
+               Left err -> do
+                 let errmsg = show err
+                 hPutStrLn stderr ("Bad DNS server or lookup error: " ++ errmsg)
                  exitWith (ExitFailure exit_bad_server)
-               Just s'' ->
+               Right []  -> do
+                 hPutStrLn stderr ("Hostname " ++ s ++ " has no 'A' records.")
+                 exitWith (ExitFailure exit_bad_server)
+               Right (srv:_) ->
                  return $ defaultResolvConf { resolvInfo =
-                                                RCHostName (show s'') }
+                                                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) }
+  let rc = rc' { resolvTimeout = 1000 * 1000 * seconds (timeout cfg) }
   rs <- makeResolvSeed rc
 
   let lookup_function = case cfg of
                           NS{} -> lookupNS'
                           MX{} -> lookupMX'
 
-  _ <- 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
-         let cleaned_records = map (clean nrml_delegates) records
-         parallel (map report cleaned_records)
+  let lookup' d = withResolver rs $ \resolver ->
+                    lookup_function resolver d
+
+  -- Construct a list of [IO whatever]. The withResolver calls
+  -- are the ones that should be run in parallel.
+  let actions = map lookup' nrml_domains
+
+  -- Run the lookup actions in parallel.
+  results <- parallelInterleaved actions
+
+  -- Output the results.
+  _ <- mapM (report nrml_delegates) results
 
   stopGlobalPool