]> gitweb.michael.orlitzky.com - email-validator.git/blobdiff - src/Main.hs
Add length tests and fix zero-length domain bug.
[email-validator.git] / src / Main.hs
index 3e99d0d006ccdcf8ee8e7e105ae4a74636187a95..9b22f5cfa20afe00ac3b82160a743781061ae754 100644 (file)
@@ -1,10 +1,13 @@
 {-# LANGUAGE DoAndIfThenElse #-}
+{-# LANGUAGE RecordWildCards #-}
 
 module Main
 where
 
-import Control.Monad (filterM)
-import qualified Data.ByteString.UTF8 as BS
+import Control.Concurrent.ParallelIO.Global (parallel, stopGlobalPool)
+import Control.Monad (unless)
+import qualified Data.ByteString as BS
+import qualified Data.ByteString.UTF8 as BSU
 import Network.DNS (
   Domain,
   Resolver,
@@ -13,50 +16,111 @@ 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)
 
 
-type Address = BS.ByteString
+import CommandLine (Args(..), apply_args)
+import EmailAddress
+import ExitCodes (exit_input_file_doesnt_exist)
 
+
+-- | Resolver parameters. We increase the default timeout from 3 to 5
+--   seconds.
 resolv_conf ::  ResolvConf
 resolv_conf = defaultResolvConf { resolvTimeout = 5 * 1000 * 1000 }
 
+-- | A list of common domains, there's no need to waste MX lookups
+--   on these.
+common_domains :: [Domain]
+common_domains = map BSU.fromString [ "aol.com",
+                                      "comcast.net",
+                                      "gmail.com",
+                                      "msn.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 = do
-  result <- lookupMX resolver domain
-  case result of
-      Nothing -> return False
-      _       -> return True
+validate_mx resolver domain
+  | domain `elem` common_domains = return True
+  | otherwise = do
+      result <- lookupMX resolver domain
+      case result of
+        Nothing -> return False
+        _       -> return True
 
-validate_syntax :: Address -> IO Bool
-validate_syntax address = do
-  return True
 
-utf8_split = undefined
 
-validate :: Resolver -> Address -> IO Bool
+-- | Validate an email address by doing some simple syntax checks and
+--   (if those fail) an MX lookup. We don't count an A record as a mail
+--   exchanger.
+validate :: Resolver -> Address -> IO (Address, Bool)
 validate resolver address = do
-  valid_syntax <- validate_syntax address
+  let valid_syntax = validate_syntax address
   if valid_syntax then do
-    let domain = utf8_split address (BS.fromString "@")
-    validate_mx resolver domain
-  else do
-    return False
+    let (_,domain) = parts address
+    mx_result <- validate_mx resolver domain
+    return (address, mx_result)
+  else
+    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"
 
-empty_string :: BS.ByteString
-empty_string = BS.fromString ""
 
 main :: IO ()
 main = do
-  input <- hGetContents stdin
+  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
+               unless is_file $
+                 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
 
-  let addresses = BS.lines $ BS.fromString input
-  let nonempty_addresses = filter (/= empty_string) addresses
+  -- And remove the empty ones.
+  let nonempty_addresses = filter (not . BS.null) addresses
 
   rs <- makeResolvSeed resolv_conf
   withResolver rs $ \resolver -> do
-    good_addresses <- filterM (validate resolver) nonempty_addresses
-    let good_address_strings = map BS.toString good_addresses
-    mapM_ (hPutStrLn stdout) good_address_strings
+    -- 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
+    -- And output the results.
+    mapM_ ((append_handle_with_newline output_handle) . fst) good_pairs
 
-  hFlush stdout
+  -- Clean up. It's safe to try to close stdout.
+  hFlush output_handle
+  hClose output_handle