module EmailAddress
where
-import qualified Data.ByteString as BS
-import qualified Data.ByteString.UTF8 as BSU
+import qualified Data.ByteString.Char8 as BS (
+ ByteString,
+ break,
+ empty,
+ length,
+ pack,
+ tail)
import Text.Email.Validate (isValid)
import Test.HUnit (assertEqual)
import Test.Framework (Test, testGroup)
utf8
)
-type Address = BSU.ByteString
-type LocalPart = BSU.ByteString
-type DomainPart = BSU.ByteString
+type Address = BS.ByteString
+type LocalPart = BS.ByteString
+type DomainPart = BS.ByteString
(before, after)
where
break_func = (== '@')
- (before, rest) = BSU.break break_func address
+ (before, rest) = BS.break break_func address
after =
if rest == BS.empty
then BS.empty
-- | Check that the lengths of the local/domain parts are within spec.
validate_length :: Address -> Bool
validate_length address =
- (BSU.length localpart <= 64) && (BSU.length domain <= 255)
+ (BS.length localpart <= 64) && (BS.length domain <= 255)
where
(localpart, domain) = parts address
_ -> True
where
regex_str = "(\\w+)([\\w\\-\\.]*)@(([a-z0-9\\-]+\\.)+)[a-z]{2,4}$"
- regex_bs = BSU.fromString regex_str
+ regex_bs = BS.pack regex_str
regex = compile regex_bs [anchored, caseless, dollar_endonly, utf8]
matches = match regex address []
-- HUnit tests
good_addresses :: [Address]
good_addresses =
- map BSU.fromString [
+ map BS.pack [
"phil@hotmail.com",
"philq23562@hotmail.com",
"gsdfg22-2_22@hot-mail.com",
bad_addresses :: [Address]
bad_addresses =
- map BSU.fromString [
--- Bad, but not caught by email-validate-1.0.0.
--- "badunderscore@dom_ain.com",
+ map BS.pack [
+ -- Bad, but not caught by email-validate-0.0.1.
+ -- "badunderscore@dom_ain.com",
"(fail)@domain.com",
"no spaces@domain.com",
".beginswith@a-dot.com",
unsupported_addresses :: [Address]
unsupported_addresses =
- map BSU.fromString [
+ map BS.pack [
"ok!char@domain.com",
"ok#char@domain.com",
"ok$char@domain.com",
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,
import System.Directory (doesFileExist)
import System.Exit (exitWith, ExitCode(..))
import System.IO (
- Handle,
IOMode( WriteMode ),
hClose,
hFlush,
-- | 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.
| 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.
| 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
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
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