X-Git-Url: http://gitweb.michael.orlitzky.com/?a=blobdiff_plain;f=src%2FMain.hs;h=293f953ac8b82a5952d759ee85c1a07dab13ca61;hb=8096b134a33ace33ea23368353c011e9f68549c7;hp=bd3cc45f5ff741e936243c9de0cf5baa84f0e1ce;hpb=c9c873eead8a45dd7df8e8ef1f5861a5aa741d9e;p=email-validator.git diff --git a/src/Main.hs b/src/Main.hs index bd3cc45..293f953 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -1,9 +1,11 @@ {-# LANGUAGE DoAndIfThenElse #-} +{-# LANGUAGE RecordWildCards #-} module Main where import Control.Concurrent.ParallelIO.Global (parallel, stopGlobalPool) +import Control.Monad (when) import qualified Data.ByteString as BS import qualified Data.ByteString.UTF8 as BSU import Network.DNS ( @@ -14,9 +16,21 @@ import Network.DNS ( makeResolvSeed, withResolver) import Network.DNS.Lookup (lookupMX) -import System.IO (hGetContents, hFlush, hPutStrLn, stdin, stdout) +import System.Directory (doesFileExist) +import System.Exit (exitWith, ExitCode(..)) +import System.IO ( + Handle, + IOMode( WriteMode ), + hClose, + hFlush, + openFile, + stdin, + stdout) import Text.Regex.PCRE.Light (compile, match, utf8) +import CommandLine (Args(..), apply_args) +import ExitCodes (exit_input_file_doesnt_exist) + type Address = BSU.ByteString -- | Resolver parameters. We increase the default timeout from 3 to 5 @@ -34,6 +48,8 @@ common_domains = map BSU.fromString [ "aol.com", "yahoo.com", "verizon.net" ] + +-- | Check whether the given domain has a valid MX record. validate_mx :: Resolver -> Domain -> IO Bool validate_mx resolver domain | domain `elem` common_domains = return True @@ -96,19 +112,53 @@ validate resolver address = do else do return (address, False) + +-- | Append a ByteString to a file Handle, followed by a newline. +append_handle_with_newline :: Handle -> BS.ByteString -> IO () +append_handle_with_newline h bs = do + BS.hPutStr h bs + BS.hPutStr h newline + where + newline = BSU.fromString "\n" + + main :: IO () main = do - input <- hGetContents stdin - - let addresses = BSU.lines $ BSU.fromString input + Args{..} <- apply_args + + -- Get the input from either stdin, or the file given on the command + -- line. + input <- case input_file of + Nothing -> BS.hGetContents stdin + Just path -> do + is_file <- doesFileExist path + when (not is_file) $ do + exitWith (ExitFailure exit_input_file_doesnt_exist) + BS.readFile path + + -- Do the same for the output handle and stdout. + output_handle <- case output_file of + Nothing -> return stdout + Just path -> openFile path WriteMode + + -- Split the input into lines. + let addresses = BSU.lines input + + -- And remove the empty ones. let nonempty_addresses = filter (not . BS.null) addresses rs <- makeResolvSeed resolv_conf withResolver rs $ \resolver -> do + -- Construst a list of [IO (Address, Bool)] let actions = map (validate resolver) nonempty_addresses + -- And compute them in parallel. results <- parallel actions + stopGlobalPool + -- Find the pairs with a True in the second position. let good_pairs = filter snd results - mapM_ ((hPutStrLn stdout) . BSU.toString . fst) good_pairs + -- And output the results. + mapM_ ((append_handle_with_newline output_handle) . fst) good_pairs - stopGlobalPool - hFlush stdout + -- Clean up. It's safe to try to close stdout. + hFlush output_handle + hClose output_handle