X-Git-Url: http://gitweb.michael.orlitzky.com/?p=haeredes.git;a=blobdiff_plain;f=src%2FMain.hs;h=f513ec67ff62149c5ec1409940cedbdab1bae7e2;hp=a5dc79466067f0dc70fc529169f55d111ae13b96;hb=a555c07f5692995bdda0ac03cec1cb0cd5a68225;hpb=689bda2499ec821772b456cb7982527d6740649f diff --git a/src/Main.hs b/src/Main.hs index a5dc794..f513ec6 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -2,14 +2,14 @@ module Main where import Control.Concurrent.ParallelIO.Global ( - parallel, + parallelInterleaved, stopGlobalPool ) import Control.Monad (unless) import qualified Data.ByteString.Char8 as BS ( getContents, pack, words ) -import Data.List ((\\)) +import Data.List ( (\\) ) import Data.String.Utils (join) import Network.DNS ( Domain, @@ -17,6 +17,8 @@ import Network.DNS ( ResolvConf(resolvInfo, resolvTimeout), defaultResolvConf, makeResolvSeed, + normalize, + normalizeCase, withResolver ) import System.Exit (ExitCode(..), exitWith) import System.IO (hPutStrLn, stderr) @@ -27,38 +29,43 @@ 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. +-- '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. -- +-- Before processing, all names are normalized using the supplied +-- function @normalize_function@. Ideally this should be the same +-- function applied to the user-input names. +-- report :: [Domain] -- ^ The list of @delgts@ + -> (Domain -> Domain) -- ^ Domain name normalization function, + -- @normalize_function@. -> LookupResult -> IO () -- If the lookup resulted in a DNS error, we just ignore the whole -- thing. -report _ (_, Left _) = return () +report _ _ (_, Left _) = return () -- If the lookup succeeded but there were no results, report that the -- domain is not delegated. -report _ (d, Right []) = +report _ _ (d, Right []) = putStrLn $ "Domain " ++ (show d) ++ " not delegated." -- Otherwise, subtract our delegates from the list of results and -- report the leftovers. -report delgts (d, Right hosts) = do - let leftovers = hosts \\ delgts +report delgts normalize_function (d, Right raw_hosts) = do + let nrml_hosts = map normalize_function raw_hosts + let leftovers = nrml_hosts \\ delgts unless (null leftovers) $ putStrLn $ "Domain " ++ (show d) ++ @@ -81,7 +88,7 @@ main = do let normalize_function = if (no_append_root cfg) - then normalize_case + then normalizeCase else normalize -- Normalize the given names and delegates @@ -106,17 +113,25 @@ main = do -- 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 a_million = 1000 * 1000 :: Int + let rc = rc' { resolvTimeout = a_million * 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 - parallel (map (report nrml_delegates) 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 normalize_function) results stopGlobalPool