]> gitweb.michael.orlitzky.com - dead/halcyon.git/blobdiff - src/Twitter/Status.hs
Bump all dependencies and switch from test-framework to tasty for tests.
[dead/halcyon.git] / src / Twitter / Status.hs
index ef4e1037b9ca54b212f5666d60271ff832468301..506a2c0bbe26ff67a561e7eee6b2e73d0629fb9f 100644 (file)
@@ -1,24 +1,34 @@
+{-# LANGUAGE NoMonomorphismRestriction #-}
+
 -- | Functions and data for working with Twitter statuses.
-module Twitter.Status
+module Twitter.Status (
+  Status(..),
+  Timeline,
+  get_max_status_id,
+  pretty_print,
+  status_tests,
+  utc_time_to_rfc822 )
 where
 
-import Control.Applicative ((<$>), (<*>))
-import Control.Monad (liftM)
-import Data.Aeson ((.:), FromJSON(..), Value(Object))
-import Data.Maybe (catMaybes, isJust)
-import Data.Monoid (mempty)
-import Data.String.Utils (join, splitWs)
-import Data.Text (pack)
-import Data.Time (formatTime)
-import Data.Time.Clock (UTCTime)
-import Data.Time.Format (parseTime)
-import Data.Time.LocalTime (TimeZone, utcToZonedTime)
-import System.Locale (defaultTimeLocale, rfc822DateFormat)
-import Test.HUnit
-import Text.Regex (matchRegex, mkRegex)
-
-import StringUtils (listify)
-import Twitter.User
+import Control.Applicative ( (<$>), (<*>) )
+import Control.Monad ( liftM )
+import Data.Aeson ( (.:), FromJSON(..), Value(Object) )
+import Data.Maybe ( mapMaybe, isJust )
+import Data.Monoid ( mempty )
+import Data.String.Utils ( join, splitWs )
+import Data.Text ( pack )
+import Data.Time ( formatTime )
+import Data.Time.Clock ( UTCTime )
+import Data.Time.Format ( parseTime )
+import Data.Time.LocalTime ( TimeZone, utcToZonedTime )
+import System.Locale ( defaultTimeLocale, rfc822DateFormat )
+import Test.Tasty ( TestTree, testGroup )
+import Test.Tasty.HUnit ( (@?=), testCase )
+import Text.Regex ( matchRegex, mkRegex )
+
+import Html ( replace_entities )
+import StringUtils ( listify )
+import Twitter.User ( User(..), screen_name_to_timeline_url )
 
 data Status = Status {
   created_at :: Maybe UTCTime,
@@ -38,7 +48,7 @@ instance FromJSON Status where
       (t .: id_field) <*>
       liftM isJustInt (t .: in_reply_to_status_id_field) <*>
       (t .: retweeted_field) <*>
-      (t .: text_field) <*>
+      liftM replace_entities (t .: text_field) <*>
       (t .: user_field)
     where
       -- The typechecker flips out without this.
@@ -74,10 +84,11 @@ utc_time_to_rfc822 mtz utc =
 
 show_created_at :: Maybe TimeZone -> Status -> String
 show_created_at mtz =
-  (maybe "" id) . (fmap $ utc_time_to_rfc822 mtz) . created_at
+  (maybe "" (utc_time_to_rfc822 mtz)) . created_at
 
 -- | Returns a nicely-formatted String representing the given 'Status'
 --   object.
+--
 pretty_print :: Maybe TimeZone -> Status -> String
 pretty_print mtz status =
   concat [ name,
@@ -99,6 +110,7 @@ pretty_print mtz status =
 
 -- | Given a list of statuses, returns the greatest status_id
 --   belonging to one of the statuses in the list.
+--
 get_max_status_id :: Timeline -> Integer
 get_max_status_id statuses =
   maximum status_ids
@@ -107,6 +119,7 @@ get_max_status_id statuses =
 
 
 -- | Parse one username from a word.
+--
 parse_username :: String -> Maybe String
 parse_username word =
   case matches of
@@ -119,13 +132,16 @@ parse_username word =
 
 
 -- | Parse all usernames of the form \@username from a status.
+--
 parse_usernames_from_status :: Status -> [String]
 parse_usernames_from_status status =
-  catMaybes (map parse_username status_words)
+  mapMaybe parse_username status_words
   where
     status_words = splitWs (text status)
 
+
 -- | Get all referenced users' timeline URLs.
+--
 make_user_timeline_urls :: Status -> [String]
 make_user_timeline_urls status =
   map screen_name_to_timeline_url usernames
@@ -133,26 +149,27 @@ make_user_timeline_urls status =
     usernames = parse_usernames_from_status status
 
 
-status_tests :: [Test]
-status_tests = [ test_parse_usernames ]
+status_tests :: TestTree
+status_tests =
+  testGroup "Status Tests" [ test_parse_usernames ]
 
 
-test_parse_usernames :: Test
+test_parse_usernames :: TestTree
 test_parse_usernames =
-    TestCase $
-      assertEqual
-      "All usernames are parsed."
-      expected_usernames
-      actual_usernames
-    where
-      dummy_user = User { screen_name = "nobody" }
-      dummy_status = Status { status_id = 1,
-                              created_at = Nothing,
-                              text = "Hypothesis: @donsbot and @bonus500 are two personalities belonging to the same person.",
-                              user = dummy_user,
-                              reply = False,
-                              retweeted = False
-                            }
-
-      actual_usernames = parse_usernames_from_status dummy_status
-      expected_usernames = ["donsbot", "bonus500"]
+  testCase description $ actual @?= expected
+  where
+    description = "all usernames are parsed"
+
+    dummy_user = User { screen_name = "nobody" }
+    dummy_text = "Hypothesis: @donsbot and @bonus500 are two " ++
+                 "personalities belonging to the same person."
+    dummy_status = Status { status_id = 1,
+                            created_at = Nothing,
+                            text = dummy_text,
+                            user = dummy_user,
+                            reply = False,
+                            retweeted = False
+                          }
+
+    actual = parse_usernames_from_status dummy_status
+    expected = ["donsbot", "bonus500"]