X-Git-Url: http://gitweb.michael.orlitzky.com/?p=haeredes.git;a=blobdiff_plain;f=src%2FMain.hs;h=70fa2f57c842ebb34c96e2e268070065b2488530;hp=142ace670cf62d4a83796c431185d5af2eeb891f;hb=e862342c38e41176a7ab300b6d7ed03cf0ffd6b2;hpb=825753e2731b8491d93d9f2d66b457fe31b1c763 diff --git a/src/Main.hs b/src/Main.hs index 142ace6..70fa2f5 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -1,68 +1,129 @@ module Main where -import qualified Data.ByteString.Char8 as BS (pack) +import Control.Concurrent.ParallelIO.Global ( + parallelInterleaved, + stopGlobalPool ) +import Control.Monad (unless) +import qualified Data.ByteString.Char8 as BS ( + getContents, + pack, + words ) import Data.List ((\\)) -import Data.String.Utils (join, splitWs) - +import Data.String.Utils (join) import Network.DNS ( Domain, FileOrNumericHost(RCHostName), - ResolvConf(resolvInfo), + ResolvConf(resolvInfo, resolvTimeout), defaultResolvConf, - lookupNS, makeResolvSeed, - withResolver - ) + normalize, + normalizeCase, + withResolver ) +import System.Exit (ExitCode(..), exitWith) +import System.IO (hPutStrLn, stderr) + + +import CommandLine (Args(..), get_args) +import DNS ( + LookupResult, + lookupMX', + lookupNS', + resolve_address ) +import ExitCodes (exit_bad_server) +import Timeout (Timeout(..)) + -import System.IO (hGetContents, stdin) +-- | 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 () -import CommandLine (Args(..), Delegates(..), get_args) +-- If the lookup resulted in a DNS error, we just ignore the whole +-- thing. +report _ (_, Left _) = return () -report :: (Domain, Maybe [Domain]) -> IO () -report (d, Nothing) = +-- 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 :: Delegates -> (Domain, Maybe [Domain]) -> (Domain, Maybe [Domain]) -clean _ p@(_, Nothing) = p -clean (Delegates ds') (d, Just targets) = - (d, Just $ targets \\ ds) - where - ds = map BS.pack 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 () main = do cfg <- get_args - print cfg - input <- hGetContents stdin + + -- This reads stdin. + input <- BS.getContents -- Split the input on any whitespace characters. - let domains' = splitWs input + let raw_domains = BS.words input + + -- Convert these to ByteStrings. + let raw_delegates = map BS.pack (delegates cfg) - -- Convert those Strings to ByteStrings - let domains = map BS.pack domains' + let normalize_function = + if (no_append_root cfg) + then normalizeCase + else normalize - let rc = case (server cfg) of - Nothing -> defaultResolvConf - Just s -> defaultResolvConf { resolvInfo = RCHostName s } + -- Normalize the given names and 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 - withResolver rs $ \resolver -> do - -- This function keeps the domain matches with its NS records. - let lookupNS' = \d -> (lookupNS resolver d) >>= (return . ((,) d)) - domains_ns <- mapM lookupNS' domains - let cdns = map (clean (delegates cfg)) domains_ns - - case cfg of - (NS _ _) -> - -- We're only checking NS records, so report what we found. - mapM_ report cdns - (MX _ _) -> - print "Hello, world." + + let lookup_function = case cfg of + NS{} -> lookupNS' + MX{} -> lookupMX' + + 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