X-Git-Url: http://gitweb.michael.orlitzky.com/?p=dead%2Fhalcyon.git;a=blobdiff_plain;f=src%2FMain.hs;h=14539c11a737defc430d35e8aed0491c9d3cb397;hp=bd749f8ca47115b89e7f57c38301ad3f7f7f11e7;hb=dd6cea3dc5e830691b1da442fcf91602e4cf94aa;hpb=86efdb6afac4a7a165babba90a0a25e0e1185e5b diff --git a/src/Main.hs b/src/Main.hs index bd749f8..14539c1 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -2,9 +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 System.Exit (ExitCode(..), exitWith) +import Data.Time.LocalTime (TimeZone, getCurrentTimeZone) +import System.Exit (ExitCode(..), exitSuccess, exitWith) import System.IO (hPutStrLn, stderr) import CommandLine @@ -16,44 +18,43 @@ import Twitter.Status import Twitter.User --- |A wrapper around threadDelay which takes seconds instead of --- microseconds as its argument. +-- | A wrapper around threadDelay which takes seconds instead of +-- microseconds as its argument. thread_sleep :: Int -> IO () thread_sleep seconds = do let microseconds = seconds * (10 ^ (6 :: Int)) threadDelay microseconds --- |Given a 'Message', 'Status', and default date, update that --- message's body and subject with the information contained in the --- status. Adds a /Date: / header, and returns the updated message. -message_from_status :: Message -> String -> Status -> Message -message_from_status message default_date status = +-- | Given a 'Message', 'Status', and date, update that message's body +-- and subject with the information contained in the status. Adds a +-- /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)), - body = (pretty_print status), + body = (pretty_print mtz status), headers = ((headers message) ++ ["Date: " ++ date])} where - -- Use the Status' created_at date if it can be coerced into - -- RFC822 format. - date = case (created_at_to_rfc822 $ created_at status) of - Nothing -> default_date - Just c -> c + date = + case created_at status of + Nothing -> default_date + Just c -> utc_time_to_rfc822 mtz c -- | If the given Message is not Nothing, send a copy of it for every -- Status in the list. -send_messages :: Maybe Message -> [Status] -> IO () -send_messages maybe_message statuses = +send_messages :: Cfg -> Maybe TimeZone -> Maybe Message -> [Status] -> IO () +send_messages cfg mtz maybe_message statuses = case maybe_message of Nothing -> return () Just message -> do default_date <- rfc822_now - let mfs = message_from_status message (default_date) + let mfs = message_from_status mtz message default_date let messages = map mfs statuses - sendmail_results <- mapM sendmail messages + sendmail_results <- mapM sendmail' messages _ <- mapM print_sendmail_result sendmail_results return () - - + where + sendmail' = sendmail (sendmail_path cfg) -- | Display the number of skipped replies if ignore_replies is true -- and verbose is enabled. @@ -69,7 +70,7 @@ mention_replies cfg ss = do -- and verbose is enabled. mention_retweets :: Cfg -> [Status] -> IO () mention_retweets cfg ss = do - let retweets = filter retweet ss + let retweets = filter retweeted ss when ((ignore_retweets cfg) && (verbose cfg)) $ do let countstr = show $ length retweets putStrLn $ "Ignoring " ++ countstr ++ " retweets." @@ -82,15 +83,15 @@ filter_statuses cfg ss = good_statuses where replies = filter reply ss - retweets = filter retweet 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' @@ -103,13 +104,10 @@ filter_statuses cfg ss = recurse :: Cfg -> String -> Integer -> (Maybe Message) -> IO () recurse cfg username latest_status_id maybe_message = do thread_sleep (heartbeat cfg) - xmldata <- get_user_new_statuses username latest_status_id + timeline <- get_user_new_statuses cfg username latest_status_id - -- Parsing an empty result can blow up. Just pretend there are - -- no new statuses in that case. - let new_statuses = case xmldata of - Just xml -> parse_statuses xml - Nothing -> [] + -- FIXME + let Just new_statuses = decode timeline :: Maybe Timeline case (length new_statuses) of 0 -> @@ -121,9 +119,11 @@ recurse cfg username latest_status_id maybe_message = do let good_statuses = filter_statuses cfg new_statuses - _ <- mapM (putStrLn . pretty_print) good_statuses + tz <- getCurrentTimeZone + let mtz = Just tz + mapM_ (putStrLn . (pretty_print mtz)) good_statuses - send_messages maybe_message good_statuses + send_messages cfg mtz maybe_message good_statuses let new_latest_status_id = get_max_status_id new_statuses do_recurse new_latest_status_id @@ -137,21 +137,19 @@ 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 - xmldata <- get_user_timeline username - - let initial_statuses = case xmldata of - Just xml -> parse_statuses xml - Nothing -> [] +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_statuses) of + case (length initial_timeline) of 0 -> 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 - _ -> return (get_max_status_id initial_statuses) + get_latest_status_id cfg username + _ -> return (get_max_status_id initial_timeline) @@ -162,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 () @@ -191,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) @@ -201,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 @@ -217,41 +215,10 @@ 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. thread_sleep (heartbeat cfg) return () - - --- | A debugging tool that will parse, print, and email a single --- status (given by its id). -twat_single_status :: Integer -> (Maybe Message) -> IO () -twat_single_status the_status_id maybe_message = do - xmldata <- get_status the_status_id - - -- Parsing an empty result can blow up. Just pretend there are - -- no new statuses in that case. - let statuses = case xmldata of - Just xml -> parse_status xml - Nothing -> [] - - case (length statuses) of - 0 -> do - putStrLn "No statuses returned." - return () - _ -> do - _ <- mapM (putStrLn . pretty_print) statuses - - case maybe_message of - Nothing -> do - putStrLn "No message object given." - return () - Just message -> do - default_date <- rfc822_now - let messages = map (message_from_status message (default_date)) statuses - sendmail_results <- mapM sendmail messages - _ <- mapM print_sendmail_result sendmail_results - return ()