]> gitweb.michael.orlitzky.com - dead/htsn-import.git/blobdiff - src/TSN/Picklers.hs
Add the 'xp_attr_option' pickler and use it to fix tests broken by HXT.
[dead/htsn-import.git] / src / TSN / Picklers.hs
index a8b0567819c89a1c03297a086ac4165a6f77c7e7..3135d6ae194d483f3704755d46063cc513393808 100644 (file)
@@ -1,13 +1,18 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+
 -- | (Un)picklers for data types present in The Sports Network XML
 --   feed.
 --
 module TSN.Picklers (
   pickler_tests,
   xp_ambiguous_time,
+  xp_attr_option,
   xp_date,
   xp_date_padded,
   xp_datetime,
+  xp_early_line_date,
   xp_earnings,
+  xp_fracpart_only_double,
   xp_gamedate,
   xp_tba_time,
   xp_time,
@@ -16,15 +21,18 @@ module TSN.Picklers (
 where
 
 -- System imports.
+import Data.Char ( toUpper )
 import Data.List ( intercalate )
 import Data.List.Split ( chunksOf )
+import Data.Maybe ( catMaybes, listToMaybe )
 import Data.String.Utils ( replace )
-import Data.Time.Clock ( NominalDiffTime, UTCTime, addUTCTime )
+import Data.Time.Clock ( UTCTime )
 import Data.Time.Format ( formatTime, parseTime )
 import Data.Tree.NTree.TypeDefs ( NTree(..) )
-import System.Locale ( defaultTimeLocale )
+import System.Locale ( TimeLocale( wDays, months ), defaultTimeLocale )
 import Test.Tasty ( TestTree, testGroup )
 import Test.Tasty.HUnit ( (@?=), testCase )
+import Text.Read ( readMaybe )
 import Text.XML.HXT.Arrow.Pickle (
   xpText,
   xpWrap,
@@ -69,6 +77,21 @@ date_format_padded = "%0m/%0d/%Y"
 
 -- | (Un)pickle a UTCTime without the time portion.
 --
+--   /Examples/:
+--
+--   This should parse:
+--
+--   >>> let tn = text_node "2/15/1983"
+--   >>> unpickleDoc xp_date tn
+--   Just 1983-02-15 00:00:00 UTC
+--
+--   But for some reason, it can also parse a leading zero in the
+--   month. Whatever. This isn't required behavior.
+--
+--   >>> let tn = text_node "02/15/1983"
+--   >>> unpickleDoc xp_date tn
+--   Just 1983-02-15 00:00:00 UTC
+--
 xp_date :: PU UTCTime
 xp_date =
   (to_date, from_date) `xpWrapMaybe` xpText
@@ -83,6 +106,16 @@ xp_date =
 -- | (Un)pickle a UTCTime without the time portion. The day/month are
 --   padded to two characters with zeros.
 --
+--   Examples:
+--
+--   >>> let tn = text_node "02/15/1983"
+--   >>> unpickleDoc xp_date_padded tn
+--   Just 1983-02-15 00:00:00 UTC
+--
+--   >>> let tn = text_node "06/07/2014"
+--   >>> unpickleDoc xp_date_padded tn
+--   Just 2014-06-07 00:00:00 UTC
+--
 xp_date_padded :: PU UTCTime
 xp_date_padded =
   (to_date, from_date) `xpWrapMaybe` xpText
@@ -119,6 +152,8 @@ format_commas :: Int -> String
 format_commas x =
   reverse (intercalate "," $ chunksOf 3 $ reverse $ show x)
 
+
+
 -- | Parse \<Earnings\> from an 'AutoRaceResultsListing'. These are
 --   essentially 'Int's, but they look like,
 --
@@ -128,6 +163,16 @@ format_commas x =
 --
 --   * \<Earnings\>TBA\</Earnings\>
 --
+--   Examples:
+--
+--   >>> let tn = text_node "1,000,191"
+--   >>> unpickleDoc xp_earnings tn
+--   Just (Just 1000191)
+--
+--   >>> let tn = text_node "TBA"
+--   >>> unpickleDoc xp_earnings tn
+--   Just Nothing
+--
 xp_earnings :: PU (Maybe Int)
 xp_earnings =
   (to_earnings, from_earnings) `xpWrap` xpText
@@ -145,14 +190,65 @@ xp_earnings =
     from_earnings (Just i) = format_commas i
 
 
+
+-- | Pickle a 'Double' that can be missing its leading zero (for
+--   values less than one). For example, we've seen,
+--
+--   <TrackLength KPH=".805">0.5</TrackLength>
+--
+--   Which 'xpPrim' can't handle without the leading
+--   zero. Unfortunately there's no way pickle/unpickle can be
+--   inverses of each other here, since \"0.5\" and \".5\" should
+--   unpickle to the same 'Double'.
+--
+--   Examples:
+--
+--   >>> let tn = text_node "0.5"
+--   >>> unpickleDoc xp_fracpart_only_double tn
+--   Just 0.5
+--
+--   >>> let tn = text_node ".5"
+--   >>> unpickleDoc xp_fracpart_only_double tn
+--   Just 0.5
+--
+--   >>> let tn = text_node "foo"
+--   >>> unpickleDoc xp_fracpart_only_double tn
+--   Nothing
+--
+xp_fracpart_only_double :: PU Double
+xp_fracpart_only_double =
+  (to_double, from_double) `xpWrapMaybe` xpText
+  where
+    -- | Convert a 'String' to a 'Double', maybe. We always prepend a
+    -- zero, since it will fix the fraction-only values, and not hurt
+    -- the ones that already have a leading integer.
+    to_double :: String -> Maybe Double
+    to_double s = readMaybe ("0" ++ s)
+
+    from_double :: Double -> String
+    from_double = show
+
+
+
 -- | (Un)pickle an unpadded 'UTCTime'. Used for example on the
 --   \<RaceDate\> elements in an 'AutoRaceResults' message.
 --
 --   Examples:
 --
---   * \<RaceDate\>6/1/2014 1:00:00 PM\</RaceDate\>
+--   >>> let tn = text_node "6/1/2014 1:00:00 PM"
+--   >>> unpickleDoc xp_datetime tn
+--   Just 2014-06-01 13:00:00 UTC
+--
+--   >>> let tn = text_node "5/24/2014 2:45:00 PM"
+--   >>> unpickleDoc xp_datetime tn
+--   Just 2014-05-24 14:45:00 UTC
+--
+--   Padded! For some reason it works with only one zero in front. I
+--   dunno man. NOT required (or even desired?) behavior.
 --
---   * \<RaceDate\>5/24/2014 2:45:00 PM\</RaceDate\>
+--   >>> let tn = text_node "05/24/2014 2:45:00 PM"
+--   >>> unpickleDoc xp_datetime tn
+--   Just 2014-05-24 14:45:00 UTC
 --
 xp_datetime :: PU UTCTime
 xp_datetime =
@@ -167,15 +263,53 @@ xp_datetime =
     from_datetime = formatTime defaultTimeLocale format
 
 
+
+-- | Takes a 'UTCTime', and returns the English suffix that would be
+--   appropriate after the day of the month. For example, if we have a
+--   UTCTime representing Christmas, this would return \"th\" because
+--   \"th\" is the right suffix of \"December 25th\".
+--
+--   Examples:
+--
+--   >>> import Data.Maybe ( fromJust )
+--   >>> :{
+--         let parse_date :: String -> Maybe UTCTime
+--             parse_date = parseTime defaultTimeLocale date_format
+--       :}
+--
+--   >>> let dates = [ "1/" ++ (d : "/1970") | d <- ['1'..'9'] ]
+--   >>> let suffixes = map (date_suffix . fromJust . parse_date) dates
+--   >>> suffixes
+--   ["st","nd","rd","th","th","th","th","th","th"]
+--
+date_suffix :: UTCTime -> String
+date_suffix t =
+  case (reverse daystr) of
+    []       -> []
+    ('1':_) -> "st"
+    ('2':_) -> "nd"
+    ('3':_) -> "rd"
+    _        -> "th"
+  where
+    daystr = formatTime defaultTimeLocale "%d" t
+
+
 -- | (Un)pickle a UTCTime from a weather forecast's gamedate. Example
 --   input looks like,
 --
---   \<forecast gamedate=\"Monday, December 30th\"\>
---
 --   When unpickling we get rid of the suffixes \"st\", \"nd\", \"rd\", and
 --   \"th\". During pickling, we add them back based on the last digit
 --   of the date.
 --
+--   Examples:
+--
+--   >>> let tn = text_node "Monday, December 30th"
+--   >>> let (Just gd) = unpickleDoc xp_gamedate tn
+--   >>> gd
+--   1970-12-30 00:00:00 UTC
+--   >>> pickleDoc xp_gamedate gd
+--   NTree (XTag "/" []) [NTree (XText "Wednesday, December 30th") []]
+--
 xp_gamedate :: PU UTCTime
 xp_gamedate =
   (to_gamedate, from_gamedate) `xpWrapMaybe` xpText
@@ -189,36 +323,41 @@ xp_gamedate =
         s' = case (reverse s) of
                (c2:c1:cs) -> let suffix = [c1,c2]
                              in
-                               case suffix of
-                                 "st" -> reverse cs
-                                 "nd" -> reverse cs
-                                 "rd" -> reverse cs
-                                 "th" -> reverse cs
-                                 _    -> s -- Unknown suffix, leave it alone.
+                               if suffix `elem` ["st","nd","rd","th"]
+                               then reverse cs
+                               else s -- Unknown suffix, leave it alone.
+
                _ -> s -- The String is less than two characters long,
                       -- leave it alone.
 
 
     from_gamedate :: UTCTime -> String
-    from_gamedate d = s ++ (suffix s)
+    from_gamedate d = s ++ (date_suffix d)
       where
         s = formatTime defaultTimeLocale format d
 
-        suffix :: String -> String
-        suffix cs =
-          case (reverse cs) of
-            []       -> []
-            ('1':_) -> "st"
-            ('2':_) -> "nd"
-            ('3':_) -> "rd"
-            _        -> "th"
 
 
 
 
 
 
--- | (Un)pickle a UTCTime without the date portion.
+-- | (Un)pickle a UTCTime without the date portion. Doesn't work if
+--   the fields aren't zero-padded to two characters.
+--
+--   /Examples/:
+--
+--   Padded, should work:
+--
+--   >>> let tn = text_node "04:35 PM"
+--   >>> unpickleDoc xp_time tn
+--   Just 1970-01-01 16:35:00 UTC
+--
+--   Unpadded, should fail:
+--
+--   >>> let tn = text_node "4:35 PM"
+--   >>> unpickleDoc xp_time tn
+--   Nothing
 --
 xp_time :: PU UTCTime
 xp_time =
@@ -235,9 +374,22 @@ xp_time =
 --   'xp_time' in that it uses periods in the AM/PM part, i.e. \"A.M.\"
 --   and \"P.M.\" It also doesn't use padding for the \"hours\" part.
 --
---   Examples:
+--   /Examples/:
+--
+--   A standard example of the correct form:
+--
+--   >>> let tn = text_node "11:30 A.M."
+--   >>> let (Just result) = unpickleDoc xp_time_dots tn
+--   >>> result
+--   1970-01-01 11:30:00 UTC
+--   >>> pickleDoc xp_time_dots result
+--   NTree (XTag "/" []) [NTree (XText "11:30 A.M.") []]
+--
+--   Another miracle, it still parses with a leading zero!
 --
---   * \<CurrentTimeStamp\>11:30 A.M.\</CurrentTimeStamp\>
+--   >>> let tn = text_node "01:30 A.M."
+--   >>> unpickleDoc xp_time_dots tn
+--   Just 1970-01-01 01:30:00 UTC
 --
 xp_time_dots :: PU UTCTime
 xp_time_dots =
@@ -305,29 +457,33 @@ xp_tba_time =
 --
 --   \<time_stamp\> January 6, 2014, at 10:11 PM ET \</time_stamp\>
 --
---   TSN doesn't provide a proper time zone name, so we assume that
---   it's always Eastern Standard Time. EST is UTC-5, so we
---   add/subtract 5 hours to convert to/from UTC.
+--   TSN doesn't provide a proper time zone name, only \"ET\" for
+--   \"Eastern Time\". But \"Eastern Time\" changes throughout the
+--   year, depending on one's location, for daylight-savings
+--   time. It's really not any more useful to be off by one hour than
+--   it is to be off by 5 hours, so rather than guess at EDT/EST, we
+--   just store the timestamp as UTC.
 --
 --   Examples:
 --
 --   >>> let tn = text_node " January 6, 2014, at 10:11 PM ET "
---   >>> unpickleDoc xp_time_stamp tn
---   Just 2014-01-07 03:11:00 UTC
+--   >>> let (Just tstamp) = unpickleDoc xp_time_stamp tn
+--   >>> tstamp
+--   2014-01-06 22:11:00 UTC
+--   >>> pickleDoc xp_time_stamp tstamp
+--   NTree (XTag "/" []) [NTree (XText " January 6, 2014, at 10:11 PM ET ") []]
 --
 xp_time_stamp :: PU UTCTime
 xp_time_stamp =
   (parse_time_stamp, from_time_stamp) `xpWrapMaybe` xpText
   where
-    five_hours :: NominalDiffTime
-    five_hours = 5 * 60 * 60
-
-    subtract_five :: UTCTime -> UTCTime
-    subtract_five = addUTCTime (-1 * five_hours)
-
+    -- | We have to re-pad the time_stamp_format with a leading and
+    --   trailing space; see the documentation of 'time_stamp_format'
+    --   for more information.
     from_time_stamp :: UTCTime -> String
     from_time_stamp =
-      formatTime defaultTimeLocale time_stamp_format . subtract_five
+      formatTime defaultTimeLocale (" " ++ time_stamp_format ++ " ")
+
 
 
 -- | (Un)pickle an ambiguous 12-hour AM/PM time, which is ambiguous
@@ -354,6 +510,86 @@ xp_ambiguous_time =
       formatTime defaultTimeLocale ambiguous_time_format
 
 
+-- | Pickle a date value from a \<date\> element as they appear in the
+--   early lines. This is a particularly wacky format, but then so is
+--   the associated time (see 'xp_ambiguous_time').
+--
+--   Examples:
+--
+--   >>> let tn = text_node "SUNDAY, MAY 25TH (05/25/2014)"
+--   >>> let (Just result) = unpickleDoc xp_early_line_date tn
+--   >>> result
+--   2014-05-25 00:00:00 UTC
+--   >>> pickleDoc xp_early_line_date result
+--   NTree (XTag "/" []) [NTree (XText "SUNDAY, MAY 25TH (05/25/2014)") []]
+--
+--   >>> let tn = text_node "SATURDAY, JUNE 7TH (06/07/2014)"
+--   >>> let (Just result) = unpickleDoc xp_early_line_date tn
+--   >>> result
+--   2014-06-07 00:00:00 UTC
+--   >>> pickleDoc xp_early_line_date result
+--   NTree (XTag "/" []) [NTree (XText "SATURDAY, JUNE 7TH (06/07/2014)") []]
+--
+xp_early_line_date :: PU UTCTime
+xp_early_line_date =
+  (to_time, from_time) `xpWrapMaybe` xpText
+  where
+    -- | We need to create our own time locale that talks IN ALL CAPS.
+    --   Actually, 'parseTime' doesn't seem to care about the
+    --   case. But when we spit it back out again ('formatTime'),
+    --   we'll want it to be in all caps.
+    --
+    caps_time_locale :: TimeLocale
+    caps_time_locale =
+      defaultTimeLocale { wDays = caps_days, months = caps_months }
+
+    caps_days :: [(String,String)]
+    caps_days = map both_to_upper (wDays defaultTimeLocale)
+
+    caps_months :: [(String,String)]
+    caps_months = map both_to_upper (months defaultTimeLocale)
+
+    both_to_upper :: (String,String) -> (String,String)
+    both_to_upper (s1,s2) = (map toUpper s1, map toUpper s2)
+
+    wacko_date_formats :: [String]
+    wacko_date_formats =
+      ["%A, %B %-d" ++ suffix ++ " (" ++ date_format_padded ++ ")" |
+         suffix <- ["ST", "ND", "RD","TH"] ]
+
+    to_time :: String -> Maybe UTCTime
+    to_time s =
+      listToMaybe $ catMaybes possible_parses
+      where
+        possible_parses = [ parseTime caps_time_locale fmt s |
+                              fmt <- wacko_date_formats ]
+
+    from_time :: UTCTime -> String
+    from_time t =
+      formatTime caps_time_locale fmt t
+      where
+        upper_suffix = map toUpper (date_suffix t)
+        fmt = "%A, %B %-d" ++ upper_suffix ++ " (" ++ date_format_padded ++ ")"
+
+
+-- | This is a replacement for @xpOption xpFoo@ within an 'xpAttr'.
+--   There's a bug <https://github.com/UweSchmidt/hxt/issues/39> in
+--   newer versions of HXT that prevents us from using the usual
+--   'xpOption' solution, so this is our stopgap. It should work on
+--   any type that can be unpickled with a plain read/show.
+--
+xp_attr_option ::  forall a. (Read a, Show a) => PU (Maybe a)
+xp_attr_option =
+  (to_a, from_a) `xpWrap` xpText
+  where
+    to_a :: String -> Maybe a
+    to_a = readMaybe
+
+    from_a :: Maybe a -> String
+    from_a Nothing  = ""
+    from_a (Just x) = show x
+
+
 -- | Create an 'XmlTree' containing only the given text. This is
 --   useful for testing (un)picklers, where we don't want to have to
 --   bother to create a dummy XML document.