[commit: packages/time] format-widths, ghc, improve-leapseconds, master, posix-perf, tasty, wip/travis: Added %f: The century part of the week date year. (5ac1884)

git at git.haskell.org git at git.haskell.org
Fri Apr 21 16:48:26 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/5ac1884daa4866c151c1955cca0b0a308e95412d

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

commit 5ac1884daa4866c151c1955cca0b0a308e95412d
Author: bjorn <bjorn at bringert.net>
Date:   Sun Feb 11 08:26:07 2007 -0800

    Added %f: The century part of the week date year.
    
    Fixes part of http://hackage.haskell.org/trac/ghc/ticket/1007
    Rationale: There is a %g specifier for the last two digits of the
    week date year, but no specifier for the century. %C cannot be used,
    since the normal century and the week date century can differ:
    
    > formatTime defaultTimeLocale "%Y %G" (fromGregorian 2000 1 1)
    "2000 1999"
    
    darcs-hash:20070211162607-6cdb2-605a7f26b21c0a063f2308683845e727688a35bd


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

5ac1884daa4866c151c1955cca0b0a308e95412d
 Data/Time/LocalTime/Format.hs | 4 ++++
 Data/Time/LocalTime/Parse.hs  | 3 +++
 test/TestParseTime.hs         | 2 ++
 3 files changed, 9 insertions(+)

diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs
index fc26327..ff9ca67 100644
--- a/Data/Time/LocalTime/Format.hs
+++ b/Data/Time/LocalTime/Format.hs
@@ -114,6 +114,8 @@ class FormatTime t where
 --
 -- [@%g@] last two digits of year for Week Date format, @00@ - @99@
 --
+-- [@%f@] century (first two digits of year) for Week Date format, @00@ - @99@
+--
 -- [@%V@] week for Week Date format, @01@ - @53@
 --
 -- [@%u@] day for Week Date format, @1@ - @7@
@@ -208,6 +210,8 @@ instance FormatTime Day where
 	-- ISO 8601 Week Date
 	formatCharacter 'G' = Just (\_ -> show . (\(y,_,_) -> y) . toWeekDate)
 	formatCharacter 'g' = Just (\_ -> show2 . mod100 . (\(y,_,_) -> y) . toWeekDate)
+	formatCharacter 'f' = Just (\_ -> show2 . div100 . (\(y,_,_) -> y) . toWeekDate)
+
 	formatCharacter 'V' = Just (\_ -> show2 . (\(_,w,_) -> w) . toWeekDate)
 	formatCharacter 'u' = Just (\_ -> show . (\(_,_,d) -> d) . toWeekDate)
 
diff --git a/Data/Time/LocalTime/Parse.hs b/Data/Time/LocalTime/Parse.hs
index b6ae350..fa71a8a 100644
--- a/Data/Time/LocalTime/Parse.hs
+++ b/Data/Time/LocalTime/Parse.hs
@@ -139,6 +139,7 @@ parseValue l c =
       'j' -> digits 3
       'G' -> digits 4
       'g' -> digits 2
+      'f' -> digits 2
       'V' -> digits 2
       'u' -> oneOf $ map (:[]) ['1'..'7']
       'a' -> oneOf (map snd (wDays l))
@@ -198,6 +199,8 @@ instance ParseTime Day where
           'G' -> let y = read x in [Century (y `div` 100), Year (y `mod` 100)]
           -- %g: last two digits of year for Week Date format, 00 - 99
           'g' -> [Year (read x)]
+          -- %f century (first two digits of year) for Week Date format, 00 - 99
+          'f' -> [Century (read x)]
           -- %V: week for Week Date format, 01 - 53
           'V' -> [Week ISOWeek (read x)]
           -- %u: day for Week Date format, 1 - 7
diff --git a/test/TestParseTime.hs b/test/TestParseTime.hs
index 8b8b334..876c227 100644
--- a/test/TestParseTime.hs
+++ b/test/TestParseTime.hs
@@ -236,6 +236,8 @@ dayFormats = map FormatString
      -- ISO week dates
      "%G-%V-%u","%G-%V-%a","%G-%V-%A","%G-%V-%w", "%A week %V, %G", "day %V, week %A, %G",
      "%G-W%V-%u",
+     "%f%g-%V-%u","%f%g-%V-%a","%f%g-%V-%A","%f%g-%V-%w", "%A week %V, %f%g", "day %V, week %A, %f%g",
+     "%f%g-W%V-%u",
      -- monday and sunday week dates
      "%Y-w%U-%A", "%Y-w%W-%A", "%Y-%A-w%U", "%Y-%A-w%W", "%A week %U, %Y", "%A week %W, %Y"
     ]



More information about the ghc-commits mailing list