[commit: packages/time] format-widths, improve-leapseconds, master, posix-perf, tasty, wip/travis: haddock comments for formatTime and others (8573895)

git at git.haskell.org git at git.haskell.org
Mon Feb 20 21:10:13 UTC 2017


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

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

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

commit 85738953ad2b075730cf79de9c557dc42f095504
Author: Ashley Yakeley <ashley at semantic.org>
Date:   Sat Dec 17 14:10:53 2005 -0800

    haddock comments for formatTime and others
    
    darcs-hash:20051217221053-ac6dd-21a6dfbffaf15cc895532249c0b8a9cd451a97ca


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

85738953ad2b075730cf79de9c557dc42f095504
 Data/Time/Calendar/OrdinalDate.hs |  7 +--
 Data/Time/Calendar/WeekDate.hs    |  7 +--
 Data/Time/LocalTime/Format.hs     | 95 ++++++++++++++++++++++++++++++++++++++-
 3 files changed, 102 insertions(+), 7 deletions(-)

diff --git a/Data/Time/Calendar/OrdinalDate.hs b/Data/Time/Calendar/OrdinalDate.hs
index 94a1bfa..7c2099a 100644
--- a/Data/Time/Calendar/OrdinalDate.hs
+++ b/Data/Time/Calendar/OrdinalDate.hs
@@ -1,11 +1,12 @@
 {-# OPTIONS -Wall -Werror #-}
 
+-- | ISO 8601 Ordinal Date format
 module Data.Time.Calendar.OrdinalDate where
 
 import Data.Time.Calendar.Days
 import Data.Time.Calendar.Private
 
--- | convert to ISO 8601 Ordinal Day format. First element of result is year (proleptic Gregoran calendar),
+-- | convert to ISO 8601 Ordinal Date format. First element of result is year (proleptic Gregoran calendar),
 -- second is the day of the year, with 1 for Jan 1, and 365 (or 366 in leap years) for Dec 31.
 toOrdinalDate :: Day -> (Integer,Int)
 toOrdinalDate (ModifiedJulianDay mjd) = (year,yd) where
@@ -20,14 +21,14 @@ toOrdinalDate (ModifiedJulianDay mjd) = (year,yd) where
 	yd = fromInteger (d - (y * 365) + 1)
 	year = quadcent * 400 + cent * 100 + quad * 4 + y + 1
 
--- | convert from ISO 8601 Ordinal Day format.
+-- | convert from ISO 8601 Ordinal Date format.
 -- Invalid day numbers will be clipped to the correct range (1 to 365 or 366).
 fromOrdinalDate :: Integer -> Int -> Day
 fromOrdinalDate year day = ModifiedJulianDay mjd where
 	y = year - 1
 	mjd = (fromIntegral (clip 1 (if isLeapYear year then 366 else 365) day)) + (365 * y) + (div y 4) - (div y 100) + (div y 400) - 678576
 
--- | show in ISO 8601 Ordinal Day format (yyyy-ddd)
+-- | show in ISO 8601 Ordinal Date format (yyyy-ddd)
 showOrdinalDate :: Day -> String
 showOrdinalDate date = (show4 y) ++ "-" ++ (show3 d) where
 	(y,d) = toOrdinalDate date
diff --git a/Data/Time/Calendar/WeekDate.hs b/Data/Time/Calendar/WeekDate.hs
index 1d4ebe5..a186ca9 100644
--- a/Data/Time/Calendar/WeekDate.hs
+++ b/Data/Time/Calendar/WeekDate.hs
@@ -1,12 +1,13 @@
 {-# OPTIONS -Wall -Werror #-}
 
+-- | ISO 8601 Week Date format
 module Data.Time.Calendar.WeekDate where
 
 import Data.Time.Calendar.OrdinalDate
 import Data.Time.Calendar.Days
 import Data.Time.Calendar.Private
 
--- | convert to ISO 8601 Week format. First element of result is year, second week number (1-53), third day of week (1 for Monday to 7 for Sunday).
+-- | convert to ISO 8601 Week Date format. First element of result is year, second week number (1-53), third day of week (1 for Monday to 7 for Sunday).
 -- Note that \"Week\" years are not quite the same as Gregorian years, as the first day of the year is always a Monday.
 -- The first week of a year is the first week to contain at least four days in the corresponding Gregorian year.
 toWeekDate :: Day -> (Integer,Int,Int)
@@ -25,7 +26,7 @@ toWeekDate date@(ModifiedJulianDay mjd) = (y1,fromInteger (w1 + 1),fromInteger (
 			else (y0,w0)
 		else (y0,w0)
 
--- | convert from ISO 8601 Week format. First argument is year, second week number (1-52 or 53), third day of week (1 for Monday to 7 for Sunday).
+-- | convert from ISO 8601 Week Date format. First argument is year, second week number (1-52 or 53), third day of week (1 for Monday to 7 for Sunday).
 -- Invalid week and day values will be clipped to the correct range.
 fromWeekDate :: Integer -> Int -> Int -> Day
 fromWeekDate y w d = ModifiedJulianDay (k - (mod k 7) + (toInteger (((clip 1 (if longYear then 53 else 52) w) * 7) + (clip 1 7 d))) - 10) where
@@ -34,7 +35,7 @@ fromWeekDate y w d = ModifiedJulianDay (k - (mod k 7) + (toInteger (((clip 1 (if
 			(_,53,_) -> True
 			_ -> False
 
--- | show in ISO 8601 Week format as yyyy-Www-dd (e.g. 
+-- | show in ISO 8601 Week Date format as yyyy-Www-dd (e.g. 
 showWeekDate :: Day -> String
 showWeekDate date = (show4 y) ++ "-W" ++ (show2 w) ++ "-" ++ (show d) where
 	(y,w,d) = toWeekDate date
diff --git a/Data/Time/LocalTime/Format.hs b/Data/Time/LocalTime/Format.hs
index 4f36f33..9564868 100644
--- a/Data/Time/LocalTime/Format.hs
+++ b/Data/Time/LocalTime/Format.hs
@@ -25,6 +25,99 @@ import Data.Char
 class FormatTime t where
 	formatCharacter :: Char -> Maybe (TimeLocale -> t -> String)
 
+-- | Substitute various time-related information for each %-code in the string, as per 'formatCharacter'.
+--
+-- For all types (note these three are done here, not by 'formatCharacter'):
+--
+-- [@%%@] @%@
+--
+-- [@%t@] tab
+--
+-- [@%n@] newline
+--
+-- For TimeZone (and ZonedTime and UTCTime):
+--
+-- [@%z@] timezone offset
+--
+-- [@%Z@] timezone name
+--
+-- For LocalTime (and ZonedTime and UTCTime):
+--
+-- [@%c@] as 'dateTimeFmt' @locale@ (e.g. @%a %b %e %H:%M:%S %Z %Y@)
+--
+-- For TimeOfDay (and LocalTime and ZonedTime and UTCTime):
+--
+-- [@%R@] same as @%H:%M@
+--
+-- [@%T@] same as @%H:%M:%S@
+--
+-- [@%X@] as 'timeFmt' @locale@ (e.g. @%H:%M:%S@)
+--
+-- [@%r@] as 'time12Fmt' @locale@ (e.g. @%I:%M:%S %p@)
+--
+-- [@%P@] day half from ('amPm' @locale@), converted to lowercase, @am@, @pm@
+--
+-- [@%p@] day half from ('amPm' @locale@), @AM@, @PM@
+--
+-- [@%H@] hour, 24-hour, leading 0 as needed, @00@ - @23@
+--
+-- [@%I@] hour, 12-hour, leading 0 as needed, @01@ - @12@
+--
+-- [@%k@] hour, 24-hour, leading space as needed, @ 0@ - @23@
+--
+-- [@%l@] hour, 12-hour, leading space as needed, @ 1@ - @12@
+--
+-- [@%M@] minute, @00@ - @59@
+--
+-- [@%S@] second with decimal part if not an integer, @00@ - @60.999999999999@
+--
+-- For UTCTime and ZonedTime:
+--
+-- [@%s@] number of seconds since the Unix epoch
+--
+-- For Day (and LocalTime and ZonedTime and UTCTime):
+--
+-- [@%D@] same as @%m\/%d\/%y@
+--
+-- [@%F@] same as @%Y-%m-%d@
+--
+-- [@%x@] as 'dateFmt' @locale@ (e.g. @%m\/%d\/%y@)
+--
+-- [@%Y@] year
+--
+-- [@%y@] last two digits of year, @00@ - @99@
+--
+-- [@%C@] century (being the first two digits of the year), @00@ - @99@
+--
+-- [@%B@] month name, long form ('fst' from 'months' @locale@), @January@ - @December@
+--
+-- [@%b@, @%h@] month name, short form ('snd' from 'months' @locale@), @Jan@ - @Dec@
+--
+-- [@%m@] month of year, leading 0 as needed, @01@ - @12@
+--
+-- [@%d@] day of month, leading 0 as needed, @01@ - @31@
+--
+-- [@%e@] day of month, leading space as needed,  @ 1@ - @31@
+--
+-- [@%j@] day of year for Ordinal Date format, @001@ - @366@
+--
+-- [@%G@] year for Week Date format
+--
+-- [@%g@] last 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@
+--
+-- [@%a@] day of week, short form ('snd' from 'wDays' @locale@), @Sun@ - @Sat@
+--
+-- [@%A@] day of week, long form ('fst' from 'wDays' @locale@), @Sunday@ - @Saturday@
+--
+-- [@%U@] week number of year, where weeks start on Sunday (as 'sundayStartWeek'), @01@ - @53@
+--
+-- [@%w@] day of week number, @0@ (= Sunday) - @6@ (= Saturday)
+--
+-- [@%W@] week number of year, where weeks start on Monday (as 'mondayStartWeek'), @01@ - @53@
 formatTime :: (FormatTime t) => TimeLocale -> String -> t -> String
 formatTime _ [] _ = ""
 formatTime locale ('%':c:cs) t = (formatChar c) ++ (formatTime locale cs t) where
@@ -100,7 +193,7 @@ instance FormatTime Day where
 	-- Day of Year
 	formatCharacter 'j' = Just (\_ -> show3 . snd . toOrdinalDate)
 
-	-- ISOWeekDay
+	-- ISO 8601 Week Date
 	formatCharacter 'G' = Just (\_ -> show . (\(y,_,_) -> y) . toWeekDate)
 	formatCharacter 'g' = Just (\_ -> show2 . mod100 . (\(y,_,_) -> y) . toWeekDate)
 	formatCharacter 'V' = Just (\_ -> show2 . (\(_,w,_) -> w) . toWeekDate)



More information about the ghc-commits mailing list