]> gitweb.michael.orlitzky.com - email-validator.git/blobdiff - src/Main.hs
Bump the version to 0.0.2.
[email-validator.git] / src / Main.hs
index ac72ad513919bc932866bed73608268935ec8062..0e7c30fa03bd5d93e23a5f61acf716d55ff549a9 100644 (file)
@@ -4,10 +4,17 @@
 module Main
 where
 
-import Control.Concurrent.ParallelIO.Global (parallel, stopGlobalPool)
+import Control.Concurrent.ParallelIO.Global (
+   parallelInterleaved,
+   stopGlobalPool)
 import Control.Monad (unless)
-import qualified Data.ByteString as BS
-import qualified Data.ByteString.UTF8 as BSU
+import qualified Data.ByteString.Char8 as BS (
+  hGetContents,
+  hPutStrLn,
+  lines,
+  null,
+  pack,
+  readFile)
 import Network.DNS (
   Domain,
   Resolver,
@@ -19,7 +26,6 @@ import Network.DNS.Lookup (lookupA, lookupMX)
 import System.Directory (doesFileExist)
 import System.Exit (exitWith, ExitCode(..))
 import System.IO (
-  Handle,
   IOMode( WriteMode ),
   hClose,
   hFlush,
@@ -41,12 +47,12 @@ resolv_conf = defaultResolvConf { resolvTimeout = 10 * 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" ]
+common_domains = map BS.pack [ "aol.com",
+                               "comcast.net",
+                               "gmail.com",
+                               "msn.com",
+                               "yahoo.com",
+                               "verizon.net" ]
 
 
 -- | Check whether the given domain has a valid MX record.
@@ -56,8 +62,9 @@ validate_mx resolver domain
   | otherwise = do
       result <- lookupMX resolver domain
       case result of
-        Nothing -> return False
-        _       -> return True
+        -- A list of one or more elements?
+        Right (_:_) -> return True
+        _           -> return False
 
 
 -- | Check whether the given domain has a valid A record.
@@ -67,8 +74,8 @@ validate_a resolver domain
   | otherwise = do
       result <- lookupA resolver domain
       case result of
-        Nothing -> return False
-        _       -> return True
+        Right (_:_) -> return True
+        _           -> return False
 
 
 -- | Validate an email address by doing some simple syntax checks and
@@ -93,14 +100,6 @@ validate resolver accept_a rfc5322 address = 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
@@ -122,23 +121,30 @@ main = do
                      Just path -> openFile path WriteMode
 
   -- Split the input into lines.
-  let addresses = BSU.lines input
+  let addresses = BS.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 validate' = validate resolver accept_a rfc5322
-    let actions = map validate' 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
+  let validate' addr = withResolver rs $ \resolver ->
+                         validate resolver accept_a rfc5322 addr
+
+  -- Construct a list of [IO (Address, Bool)]. The withResolver calls
+  -- are the ones that should be run in parallel.
+  let actions = map validate' nonempty_addresses
+
+  -- Run the lookup actions in parallel.
+  results <- parallelInterleaved actions
+
+  -- Filter the bad ones.
+  let valid_results = filter snd results
+
+  -- Output the results.
+  let valid_addresses = map fst valid_results
+  _ <- mapM (BS.hPutStrLn output_handle) valid_addresses
+
+  stopGlobalPool
 
   -- Clean up. It's safe to try to close stdout.
   hFlush output_handle