]> gitweb.michael.orlitzky.com - email-validator.git/blob - src/Main.hs
Add length tests and fix zero-length domain bug.
[email-validator.git] / src / Main.hs
1 {-# LANGUAGE DoAndIfThenElse #-}
2 {-# LANGUAGE RecordWildCards #-}
3
4 module Main
5 where
6
7 import Control.Concurrent.ParallelIO.Global (parallel, stopGlobalPool)
8 import Control.Monad (unless)
9 import qualified Data.ByteString as BS
10 import qualified Data.ByteString.UTF8 as BSU
11 import Network.DNS (
12 Domain,
13 Resolver,
14 ResolvConf(..),
15 defaultResolvConf,
16 makeResolvSeed,
17 withResolver)
18 import Network.DNS.Lookup (lookupMX)
19 import System.Directory (doesFileExist)
20 import System.Exit (exitWith, ExitCode(..))
21 import System.IO (
22 Handle,
23 IOMode( WriteMode ),
24 hClose,
25 hFlush,
26 openFile,
27 stdin,
28 stdout)
29
30
31 import CommandLine (Args(..), apply_args)
32 import EmailAddress
33 import ExitCodes (exit_input_file_doesnt_exist)
34
35
36 -- | Resolver parameters. We increase the default timeout from 3 to 5
37 -- seconds.
38 resolv_conf :: ResolvConf
39 resolv_conf = defaultResolvConf { resolvTimeout = 5 * 1000 * 1000 }
40
41 -- | A list of common domains, there's no need to waste MX lookups
42 -- on these.
43 common_domains :: [Domain]
44 common_domains = map BSU.fromString [ "aol.com",
45 "comcast.net",
46 "gmail.com",
47 "msn.com",
48 "yahoo.com",
49 "verizon.net" ]
50
51
52 -- | Check whether the given domain has a valid MX record.
53 validate_mx :: Resolver -> Domain -> IO Bool
54 validate_mx resolver domain
55 | domain `elem` common_domains = return True
56 | otherwise = do
57 result <- lookupMX resolver domain
58 case result of
59 Nothing -> return False
60 _ -> return True
61
62
63
64 -- | Validate an email address by doing some simple syntax checks and
65 -- (if those fail) an MX lookup. We don't count an A record as a mail
66 -- exchanger.
67 validate :: Resolver -> Address -> IO (Address, Bool)
68 validate resolver address = do
69 let valid_syntax = validate_syntax address
70 if valid_syntax then do
71 let (_,domain) = parts address
72 mx_result <- validate_mx resolver domain
73 return (address, mx_result)
74 else
75 return (address, False)
76
77
78 -- | Append a ByteString to a file Handle, followed by a newline.
79 append_handle_with_newline :: Handle -> BS.ByteString -> IO ()
80 append_handle_with_newline h bs = do
81 BS.hPutStr h bs
82 BS.hPutStr h newline
83 where
84 newline = BSU.fromString "\n"
85
86
87 main :: IO ()
88 main = do
89 Args{..} <- apply_args
90
91 -- Get the input from either stdin, or the file given on the command
92 -- line.
93 input <- case input_file of
94 Nothing -> BS.hGetContents stdin
95 Just path -> do
96 is_file <- doesFileExist path
97 unless is_file $
98 exitWith (ExitFailure exit_input_file_doesnt_exist)
99 BS.readFile path
100
101 -- Do the same for the output handle and stdout.
102 output_handle <- case output_file of
103 Nothing -> return stdout
104 Just path -> openFile path WriteMode
105
106 -- Split the input into lines.
107 let addresses = BSU.lines input
108
109 -- And remove the empty ones.
110 let nonempty_addresses = filter (not . BS.null) addresses
111
112 rs <- makeResolvSeed resolv_conf
113 withResolver rs $ \resolver -> do
114 -- Construst a list of [IO (Address, Bool)]
115 let actions = map (validate resolver) nonempty_addresses
116 -- And compute them in parallel.
117 results <- parallel actions
118 stopGlobalPool
119 -- Find the pairs with a True in the second position.
120 let good_pairs = filter snd results
121 -- And output the results.
122 mapM_ ((append_handle_with_newline output_handle) . fst) good_pairs
123
124 -- Clean up. It's safe to try to close stdout.
125 hFlush output_handle
126 hClose output_handle