[commit: packages/time] format-widths, ghc, improve-leapseconds, master, posix-perf, tasty, wip/travis: Changed %Z to produce the time zone offset if the time zone name is "". (4d14562)

git at git.haskell.org git at git.haskell.org
Fri Apr 21 16:48:28 UTC 2017


Repository : ssh://git@git.haskell.org/time

On branches: format-widths,ghc,improve-leapseconds,master,posix-perf,tasty,wip/travis
Link       : http://git.haskell.org/packages/time.git/commitdiff/4d14562fbd5ba0118216365198b3298eb6265648

>---------------------------------------------------------------

commit 4d14562fbd5ba0118216365198b3298eb6265648
Author: bjorn <bjorn at bringert.net>
Date:   Sun Feb 11 10:11:09 2007 -0800

    Changed %Z to produce the time zone offset if the time zone name is "".
    
    Rationale: Without this, if you format a ZonedTime which contains an
    unnamed timezone, %Z produces the empty string. This is invalid in
    many formats. It is better to output the offset when there
    is no timezone name.
    
    darcs-hash:20070211181109-6cdb2-bde288cdfb6400ef08b24b26aa2f59d7f25807e4


>---------------------------------------------------------------

4d14562fbd5ba0118216365198b3298eb6265648
 Data/Time/LocalTime/Format.hs |  4 +++-
 Data/Time/LocalTime/Parse.hs  | 17 ++++++++++-------
 2 files changed, 13 insertions(+), 8 deletions(-)

diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs
index ff9ca67..61a4e90 100644
--- a/Data/Time/LocalTime/Format.hs
+++ b/Data/Time/LocalTime/Format.hs
@@ -183,7 +183,9 @@ instance FormatTime ZonedTime where
 
 instance FormatTime TimeZone where
 	formatCharacter 'z' = Just (\_ -> timeZoneOffsetString)
-	formatCharacter 'Z' = Just (\_ -> timeZoneName)
+	formatCharacter 'Z' = 
+            Just (\_ z -> let n = timeZoneName z
+                           in if null n then timeZoneOffsetString z else n)
 	formatCharacter _ = Nothing
 
 instance FormatTime Day where
diff --git a/Data/Time/LocalTime/Parse.hs b/Data/Time/LocalTime/Parse.hs
index fa71a8a..605eee9 100644
--- a/Data/Time/LocalTime/Parse.hs
+++ b/Data/Time/LocalTime/Parse.hs
@@ -114,7 +114,9 @@ parseValue :: TimeLocale -> Char -> ReadP String
 parseValue l c = 
     case c of
       'z' -> liftM2 (:) (choice [char '+', char '-']) (digits 4)
-      'Z' -> munch isUpper
+      'Z' -> munch1 isUpper <++
+             liftM2 (:) (choice [char '+', char '-']) (digits 4) <++
+             return "" -- produced by %Z for LocalTime
       'P' -> oneOf (let (am,pm) = amPm l 
                      in [map toLower am, map toLower pm])
       'p' -> oneOf (let (am,pm) = amPm l in [am, pm])
@@ -271,13 +273,16 @@ instance ParseTime TimeZone where
       where 
         f t@(TimeZone offset dst name) (c,x) = 
             case c of
-              'z' -> TimeZone (sign * (60 * h + m)) dst name
+              'z' -> zone
+              'Z' | null x           -> t
+                  | isUpper (head x) -> TimeZone offset dst x -- FIXME: figure out timezone offset?
+                  | otherwise        -> zone
+              _   -> t
+          where zone = TimeZone (sign * (60 * h + m)) dst name
                   where (s:h1:h2:m1:m2:[]) = x
                         sign = if s == '-' then -1 else 1
                         h = read [h1,h2]
                         m = read [m1,m2] 
-              'Z' -> TimeZone offset dst x -- FIXME: figure out timezone offset?
-              _   -> t
 
 instance ParseTime ZonedTime where
     buildTime l xs = foldl f (ZonedTime (buildTime l xs) (buildTime l xs)) xs
@@ -305,9 +310,7 @@ instance Read LocalTime where
     readsPrec _ = readParen False $ readsTime defaultTimeLocale "%Y-%m-%d %H:%M:%S%Q"
 
 instance Read TimeZone where
-    readsPrec _ = readParen False $ \s ->
-                      readsTime defaultTimeLocale "%z" s
-                       ++ readsTime defaultTimeLocale "%Z" s
+    readsPrec _ = readParen False $ readsTime defaultTimeLocale "%Z"
 
 instance Read ZonedTime where
     readsPrec n = readParen False $ \s ->



More information about the ghc-commits mailing list