]> gitweb.michael.orlitzky.com - dead/halcyon.git/blobdiff - src/Main.hs
Fix a few hlint suggestions.
[dead/halcyon.git] / src / Main.hs
index bf99fe853fd2e947a5e1508cb8eeb9ddf92d835f..14539c11a737defc430d35e8aed0491c9d3cb397 100644 (file)
@@ -2,11 +2,11 @@ module Main
 where
 
 import Control.Concurrent (forkIO, threadDelay)
-import Control.Monad (forever, when)
+import Control.Monad (forever, unless, when)
 import Data.Aeson (decode)
 import Data.List ((\\))
 import Data.Time.LocalTime (TimeZone, getCurrentTimeZone)
-import System.Exit (ExitCode(..), exitWith)
+import System.Exit (ExitCode(..), exitSuccess, exitWith)
 import System.IO (hPutStrLn, stderr)
 
 import CommandLine
@@ -85,13 +85,13 @@ filter_statuses cfg ss =
   replies  = filter reply ss
   retweets = filter retweeted ss
 
-  good_statuses' = case (ignore_replies cfg) of
-                         True  -> ss \\ replies
-                         False -> ss
+  good_statuses' = if (ignore_replies cfg)
+                   then ss \\ replies
+                   else ss
 
-  good_statuses = case (ignore_retweets cfg) of
-                    True  -> good_statuses' \\ retweets
-                    False -> good_statuses'
+  good_statuses = if (ignore_retweets cfg)
+                  then good_statuses' \\ retweets
+                  else good_statuses'
 
 
 
@@ -104,7 +104,7 @@ filter_statuses cfg ss =
 recurse :: Cfg -> String -> Integer -> (Maybe Message) -> IO ()
 recurse cfg username latest_status_id maybe_message = do
   thread_sleep (heartbeat cfg)
-  timeline <- get_user_new_statuses username latest_status_id
+  timeline <- get_user_new_statuses cfg username latest_status_id
 
   -- FIXME
   let Just new_statuses = decode timeline :: Maybe Timeline
@@ -137,9 +137,10 @@ recurse cfg username latest_status_id maybe_message = do
 
 -- | Try continually to download username's timeline, and determine the
 --   latest status id to be posted once we have done so.
-get_latest_status_id :: Int -> String -> IO Integer
-get_latest_status_id delay username = do
-  timeline <- get_user_timeline username
+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
@@ -147,7 +148,7 @@ get_latest_status_id delay username = 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 delay username
+      get_latest_status_id cfg username
     _ -> return (get_max_status_id initial_timeline)
 
 
@@ -159,7 +160,7 @@ get_latest_status_id delay username = do
 --   should be emailed.
 run_twat :: Cfg -> Maybe Message -> String -> IO ()
 run_twat cfg msg username = do
-  latest_status_id <- get_latest_status_id (heartbeat cfg) username
+  latest_status_id <- get_latest_status_id cfg username
   recurse cfg username latest_status_id msg
   return ()
 
@@ -188,7 +189,7 @@ main = do
 
   -- If there  were errors parsing the command-line options,
   -- print them and exit.
-  when (not (null errors)) $ do
+  unless (null errors) $ do
       hPutStrLn stderr (concat errors)
       putStrLn help_text
       exitWith (ExitFailure exit_args_parse_failed)
@@ -198,14 +199,14 @@ main = do
   help <- help_set
   when (help) $ do
     putStrLn help_text
-    exitWith ExitSuccess
+    exitSuccess
 
   -- Get the list of usernames.
   usernames <- parse_usernames
 
   -- And a Cfg object.
   cfg <- get_cfg
-  
+
   -- If we have both a "To" and "From" address, we'll create a
   -- message object to be passed to all of our threads.
   let message = construct_message cfg
@@ -214,7 +215,7 @@ main = do
   let run_twat_curried = run_twat cfg message
   _ <- mapM (forkIO . run_twat_curried) usernames
 
-  _ <- forever $ do
+  _ <- forever $
     -- This thread (the one executing main) doesn't do anything,
     -- but when it terminates, so do all the threads we forked.
     -- As a result, we need to keep this thread on life support.