]> gitweb.michael.orlitzky.com - dead/halcyon.git/blobdiff - src/Main.hs
Clean up imports.
[dead/halcyon.git] / src / Main.hs
index 40703d7ea9170c10110efe3787ce070c47786256..b7d7f716a32722431b6d27eee617e9aaa69b31a1 100644 (file)
@@ -1,30 +1,35 @@
 module Main
 where
 
-import Control.Concurrent (forkIO, threadDelay)
-import Control.Monad (forever, when)
-import Data.Aeson (decode)
-import Data.List ((\\))
-import Data.Monoid ((<>))
-import Data.Time.LocalTime (TimeZone, getCurrentTimeZone)
-import System.Exit (ExitCode(..), exitWith)
-import System.IO (hPutStrLn, stderr)
-
-import CommandLine
-import Configuration (Cfg(..), default_config, merge_optional)
-import ExitCodes (exit_no_usernames)
-import qualified OptionalConfiguration as OC
+import Control.Concurrent ( forkIO, threadDelay )
+import Control.Monad ( forever, when )
+import Data.Aeson ( decode )
+import Data.List ( (\\) )
+import Data.Maybe ( fromMaybe, isNothing )
+import Data.Monoid ( (<>) )
+import Data.Time.LocalTime ( TimeZone, getCurrentTimeZone )
+import System.Exit ( ExitCode(..), exitWith )
+import System.IO ( hPutStrLn, stderr )
+
+import CommandLine ( get_args, show_help )
+import Configuration ( Cfg(..), default_config, merge_optional )
+import ExitCodes ( exit_no_usernames )
+import qualified OptionalConfiguration as OC ( from_rc )
 import Mail (
   Message(..),
   default_headers,
   print_sendmail_result,
   rfc822_now,
-  sendmail
-  )
-import Twitter.Http
-import Twitter.Status
-import Twitter.User
-
+  sendmail )
+import Twitter.Http ( get_user_new_statuses, get_user_timeline )
+import Twitter.Status (
+  Status(..),
+  Timeline,
+  get_max_status_id,
+  pretty_print,
+  utc_time_to_rfc822 )
+import Twitter.User ( User(..) )
+import Usernames ( Usernames(..) )
 
 -- | A wrapper around threadDelay which takes seconds instead of
 --   microseconds as its argument.
@@ -39,7 +44,7 @@ thread_sleep seconds = do
 -- /Date: / header, and returns the updated message.
 message_from_status :: Maybe TimeZone -> Message -> String -> Status -> Message
 message_from_status mtz message default_date status =
-  message { subject = "Twat: " ++ (screen_name (user status)),
+  message { subject = "Halcyon: " ++ (screen_name (user status)),
             body    = (pretty_print mtz status),
             headers = ((headers message) ++ ["Date: " ++ date])}
   where
@@ -114,14 +119,19 @@ recurse cfg username latest_status_id maybe_message = do
   thread_sleep (heartbeat cfg)
   timeline <- get_user_new_statuses cfg username latest_status_id
 
-  -- FIXME
-  let Just new_statuses = decode timeline :: Maybe Timeline
+  let decoded_timeline = decode timeline :: Maybe Timeline
+
+  when (isNothing decoded_timeline) $
+    hPutStrLn stderr $
+      "Couldn't retrieve "
+      ++ username
+      ++ "'s timeline. Skipping..."
 
-  case (length new_statuses) of
-    0 ->
-      do_recurse latest_status_id
-    _ -> do
+  let new_statuses = fromMaybe [] decoded_timeline
 
+  case new_statuses of
+    [] -> do_recurse latest_status_id
+    _  -> do
       mention_replies cfg new_statuses
       mention_retweets cfg new_statuses
 
@@ -129,7 +139,7 @@ recurse cfg username latest_status_id maybe_message = do
 
       tz <- getCurrentTimeZone
       let mtz = Just tz
-      mapM_ (putStrLn . (pretty_print mtz)) good_statuses
+      mapM_ (putStr . (pretty_print mtz)) good_statuses
 
       send_messages cfg mtz maybe_message good_statuses
 
@@ -149,15 +159,24 @@ get_latest_status_id :: Cfg -> String -> IO Integer
 get_latest_status_id cfg username = do
   let delay = heartbeat cfg
   timeline <- get_user_timeline cfg username
-  let Just initial_timeline = decode timeline :: Maybe Timeline
 
-  case (length initial_timeline) of
-    0 -> do
+  let decoded_timeline = decode timeline :: Maybe Timeline
+
+  when (isNothing decoded_timeline) $
+    hPutStrLn stderr $
+      "Couldn't retrieve "
+      ++ username
+      ++ "'s timeline. Skipping..."
+
+  let initial_timeline = fromMaybe [] decoded_timeline
+
+  case initial_timeline of
+    [] -> do
       -- If the HTTP part barfs, try again after a while.
-      putStrLn ("Couldn't retrieve " ++ username ++ "'s timeline. Retrying...")
       thread_sleep delay
       get_latest_status_id cfg username
-    _ -> return (get_max_status_id initial_timeline)
+    _  ->
+      return (get_max_status_id initial_timeline)
 
 
 
@@ -166,8 +185,8 @@ get_latest_status_id cfg username = do
 --   recursive loop that checks for updates forever. The message
 --   argument is optional and is passed to recurse in case the updates
 --   should be emailed.
-run_twat :: Cfg -> Maybe Message -> String -> IO ()
-run_twat cfg msg username = do
+run :: Cfg -> Maybe Message -> String -> IO ()
+run cfg msg username = do
   latest_status_id <- get_latest_status_id cfg username
   recurse cfg username latest_status_id msg
   return ()
@@ -189,13 +208,13 @@ construct_message cfg = do
                              from = f }
 
 -- |The main function just parses the command-line arguments and then
--- forks off calls to 'run_twat' for each supplied username. After
+-- forks off calls to 'run' for each supplied username. After
 -- forking, main loops forever.
 main :: IO ()
 main = do
   -- And a Cfg object.
   rc_cfg  <- OC.from_rc
-  cmd_cfg <- apply_args
+  cmd_cfg <- get_args
 
   -- Merge the config file options with the command-line ones,
   -- prefering the command-line ones.
@@ -205,7 +224,7 @@ main = do
   -- set in either the config file or on the command-line.
   let cfg = merge_optional default_config opt_config
 
-  when (null $ usernames cfg) $ do
+  when (null $ get_usernames (usernames cfg)) $ do
     hPutStrLn stderr "ERROR: no usernames supplied."
     _ <- show_help
     exitWith (ExitFailure exit_no_usernames)
@@ -214,9 +233,9 @@ main = do
   -- message object to be passed to all of our threads.
   let message = construct_message cfg
 
-  -- Execute run_twat on each username in a new thread.
-  let run_twat_curried = run_twat cfg message
-  _ <- mapM (forkIO . run_twat_curried) (usernames cfg)
+  -- Execute run on each username in a new thread.
+  let run_curried = run cfg message
+  _ <- mapM (forkIO . run_curried) (get_usernames (usernames cfg))
 
   _ <- forever $
     -- This thread (the one executing main) doesn't do anything,