]> gitweb.michael.orlitzky.com - email-validator.git/blobdiff - src/Main.hs
Remove the "--input" and "--output" command-line flags.
[email-validator.git] / src / Main.hs
index 551dae752ae3343446716b520f0d13bb5274ed74..1cc4c73aa47d963e56f30a7188f05781f010b76c 100644 (file)
@@ -1,42 +1,39 @@
 {-# LANGUAGE DoAndIfThenElse #-}
 {-# LANGUAGE RecordWildCards #-}
 
-module Main
+module Main (main)
 where
 
 import Control.Concurrent.ParallelIO.Global (
    parallelInterleaved,
-   stopGlobalPool)
-import Control.Monad (unless)
+   stopGlobalPool )
 import qualified Data.ByteString.Char8 as BS (
   hGetContents,
   hPutStrLn,
   lines,
   null,
-  pack,
-  readFile)
+  pack )
 import Network.DNS (
   Domain,
   Resolver,
-  ResolvConf(..),
+  ResolvConf( resolvTimeout ),
   defaultResolvConf,
   makeResolvSeed,
-  withResolver)
-import Network.DNS.Lookup (lookupA, lookupMX)
-import System.Directory (doesFileExist)
-import System.Exit (exitWith, ExitCode(..))
+  withResolver )
+import Network.DNS.Lookup ( lookupA, lookupMX )
 import System.IO (
-  IOMode( WriteMode ),
-  hClose,
   hFlush,
-  openFile,
   stdin,
-  stdout)
+  stdout )
 
 
-import CommandLine (Args(..), get_args)
-import EmailAddress
-import ExitCodes (exit_input_file_doesnt_exist)
+import CommandLine (
+  Args( Args, accept_a, rfc5322 ),
+  get_args )
+import EmailAddress(
+  Address,
+  parts,
+  validate_syntax )
 
 
 -- | Resolver parameters. We increase the default timeout from 3 to 10
@@ -105,22 +102,8 @@ main :: IO ()
 main = do
   Args{..} <- get_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.
+  -- Split stdin into lines, which should result in a list of addresses.
+  input <- BS.hGetContents stdin
   let addresses = BS.lines input
 
   -- And remove the empty ones.
@@ -142,10 +125,7 @@ main = do
 
   -- Output the results.
   let valid_addresses = map fst valid_results
-  _ <- mapM (BS.hPutStrLn output_handle) valid_addresses
+  mapM_ (BS.hPutStrLn stdout) valid_addresses
 
   stopGlobalPool
-
-  -- Clean up. It's safe to try to close stdout.
-  hFlush output_handle
-  hClose output_handle
+  hFlush stdout