{-# LANGUAGE CPP #-}
#if (defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
module Network.Email.Sendmail
where
#else
module Network.Email.Sendmail(sendmail)
where
import System.Cmd.Utils ( PipeMode(WriteToPipe), pOpen )
import System.Directory
( doesFileExist, getPermissions, Permissions(executable) )
import System.IO ( hPutStr )
import System.IO.Error ()
import qualified Control.Exception(try, IOException)
sendmails :: [String]
sendmails :: [String]
sendmails = [String
"/usr/sbin/sendmail",
String
"/usr/local/sbin/sendmail",
String
"/usr/local/bin/sendmail",
String
"/usr/bin/sendmail",
String
"/etc/sendmail",
String
"/usr/etc/sendmail"]
findsendmail :: IO String
findsendmail :: IO String
findsendmail =
let worker :: [String] -> IO String
worker [] = String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
"sendmail"
worker (String
this:[String]
next) =
do
e <- String -> IO Bool
doesFileExist String
this
if e then
do
p <- getPermissions this
if executable p then
return this
else worker next
else worker next
in
[String] -> IO String
worker [String]
sendmails
sendmail :: Maybe String
-> [String]
-> String
-> IO ()
sendmail :: Maybe String -> [String] -> String -> IO ()
sendmail Maybe String
_ [] String
_ = String -> IO ()
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"sendmail: no recipients specified"
sendmail Maybe String
Nothing [String]
recipients String
msg = [String] -> String -> IO ()
sendmail_worker [String]
recipients String
msg
sendmail (Just String
from) [String]
recipients String
msg =
[String] -> String -> IO ()
sendmail_worker ((String
"-f" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
from) String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
recipients) String
msg
sendmail_worker :: [String] -> String -> IO ()
sendmail_worker :: [String] -> String -> IO ()
sendmail_worker [String]
args String
msg =
let func :: Handle -> IO ()
func Handle
h = Handle -> String -> IO ()
hPutStr Handle
h String
msg
in
do
rv <- IO () -> IO (Either IOException ())
forall e a. Exception e => IO a -> IO (Either e a)
Control.Exception.try (PipeMode -> String -> [String] -> (Handle -> IO ()) -> IO ()
forall a.
PipeMode -> String -> [String] -> (Handle -> IO a) -> IO a
pOpen PipeMode
WriteToPipe String
"sendmail" [String]
args Handle -> IO ()
func)
case rv of
Right ()
x -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
x
Left (IOException
_ :: Control.Exception.IOException) -> do
sn <- IO String
findsendmail
r <- pOpen WriteToPipe sn args func
return $! r
#endif