]> gitweb.michael.orlitzky.com - dead/halcyon.git/blobdiff - src/Mail.hs
Accept a sendmail_path on the command line.
[dead/halcyon.git] / src / Mail.hs
index ba605f977673ae3a76694888131767bfd383e255..2e86a204e003ceda90bfb32994fe4e83f386ad48 100644 (file)
@@ -4,12 +4,14 @@ module Mail
 where
 
 import Control.Concurrent
-import Control.Concurrent.MVar
 import Control.Exception (evaluate)
 import Data.List (intercalate)
+import Data.Time (formatTime, getZonedTime)
 import System.Exit
+import System.Locale (defaultTimeLocale, rfc822DateFormat)
 import System.Process
-import System.IO
+import System.IO (hClose, hGetContents, hPutStr)
+
 
 type Header = String
 
@@ -21,10 +23,18 @@ data Message = Message { headers :: [Header],
                          to      :: String }
              deriving (Eq)
 
+-- |The default headers attached to each message.
+-- The MIME junk is needed for UTF-8 to work properly.
+-- Note that your mail server should support the 8BITMIME extension.
+default_headers :: [Header]
+default_headers = ["MIME-Version: 1.0",
+                   "Content-Type: text/plain; charset=UTF-8",
+                   "Content-Transfer-Encoding: 8bit"]
+
 -- |Showing a message will print it in roughly RFC-compliant
 -- form. This form is sufficient for handing the message off to
--- sendmail.
-instance Show Message where    
+-- sendmail (or compatible).
+instance Show Message where
     show m =
         concat [ if (length (headers m) == 0) then "" else (intercalate "\n" (headers m)) ++ "\n",
                  "Subject: " ++ (subject m) ++ "\n",
@@ -34,15 +44,35 @@ instance Show Message where
                  (body m) ]
 
 
+
+-- |Pad a string on the left with zeros until the entire string has
+-- length n.
+pad_left :: String -> Int -> String
+pad_left str n
+         | n < (length str) = str
+         | otherwise = (replicate num_zeros '0') ++ str
+    where num_zeros = n - (length str)
+
+
+
+-- | Constructs a 'String' in RFC822 date format for the current
+--   date/time.
+rfc822_now :: IO String
+rfc822_now = do
+  date <- getZonedTime
+  return $ formatTime defaultTimeLocale rfc822DateFormat date
+
+
+
 -- |Takes a message as an argument, and passes it to the system's
--- sendmail binary.
-sendmail :: Message -> IO (String, String, ExitCode)
-sendmail message = do
+-- sendmail (or compatible) binary.
+sendmail :: FilePath -> Message -> IO (String, String, ExitCode)
+sendmail sendmail_path message = do
   let sendmail_args = ["-f",
                        (from message)]
 
   (inh, outh, errh, ph) <-
-      runInteractiveProcess "/usr/bin/sendmail" sendmail_args Nothing Nothing
+      runInteractiveProcess sendmail_path sendmail_args Nothing Nothing
 
   outm <- newEmptyMVar
   outs <- hGetContents outh
@@ -50,9 +80,9 @@ sendmail message = do
   errm <- newEmptyMVar
   errs <- hGetContents errh
 
-  forkIO $ hPutStr inh (show message) >> hClose inh
-  forkIO $ evaluate (length outs) >> putMVar outm ()
-  forkIO $ evaluate (length errs) >> putMVar errm ()
+  _ <- forkIO $ hPutStr inh (show message) >> hClose inh
+  _ <- forkIO $ evaluate (length outs) >> putMVar outm ()
+  _ <- forkIO $ evaluate (length errs) >> putMVar errm ()
 
   readMVar outm
   readMVar errm