{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}

{- arch-tag: Sendmail utility
Copyright (c) 2004-2011 John Goerzen <jgoerzen@complete.org>

All rights reserved.

For license and copyright information, see the file LICENSE
-}

{- |
   Module     : Network.Email.Sendmail
   Copyright  : Copyright (C) 2004-2011 John Goerzen
   SPDX-License-Identifier: BSD-3-Clause

   Stability  : stable
   Portability: portable

This Haskell module provides an interface to transmitting a mail message.

This is not compatible with Windows at this time.

Written by John Goerzen, jgoerzen\@complete.org
-}

#if (defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
module Network.Email.Sendmail
where
#else
module Network.Email.Sendmail(sendmail)
where

import safe System.Cmd.Utils ( PipeMode(WriteToPipe), pOpen )
import safe System.Directory
    ( doesFileExist, getPermissions, Permissions(executable) )
import safe System.IO ( hPutStr )
import safe 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 (m :: * -> *) a. Monad m => a -> m a
return String
"sendmail"
        worker (String
this:[String]
next) =
            do
            Bool
e <- String -> IO Bool
doesFileExist String
this
            if Bool
e then
               do
               Permissions
p <- String -> IO Permissions
getPermissions String
this
               if Permissions -> Bool
executable Permissions
p then
                  String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
this
                  else [String] -> IO String
worker [String]
next
               else [String] -> IO String
worker [String]
next
        in
        [String] -> IO String
worker [String]
sendmails

{- | Transmits an e-mail message using the system's mail transport agent.

This function takes a message, a list of recipients, and an optional sender,
and transmits it using the system's MTA, sendmail.

If @sendmail@ is on the @PATH@, it will be used; otherwise, a list of system
default locations will be searched.

A failure will be logged, since this function uses 'System.Cmd.Utils.safeSystem'
internally.

This function will first try @sendmail@.  If it does not exist, an error is
logged under @System.Cmd.Utils.pOpen3@ and various default @sendmail@ locations
are tried.  If that still fails, an error is logged and an exception raised.

 -}
sendmail :: Maybe String                -- ^ The envelope from address.  If not specified, takes the system's default, which is usually based on the effective userid of the current process.  This is not necessarily what you want, so I recommend specifying it.
         -> [String]                    -- ^ A list of recipients for your message.  An empty list is an error.
         -> String                      -- ^ The message itself.
         -> IO ()
sendmail :: Maybe String -> [String] -> String -> IO ()
sendmail Maybe String
_ [] String
_ = String -> IO ()
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
        --pOpen WriteToPipe "/usr/sbin/sendmail" args func
        Either IOException ()
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 Either IOException ()
rv of
            Right ()
x -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
x
            Left (IOException
_ :: Control.Exception.IOException) -> do
                      String
sn <- IO String
findsendmail
                      ()
r <- PipeMode -> String -> [String] -> (Handle -> IO ()) -> IO ()
forall a.
PipeMode -> String -> [String] -> (Handle -> IO a) -> IO a
pOpen PipeMode
WriteToPipe String
sn [String]
args Handle -> IO ()
func
                      () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$! ()
r

#endif