45d8583bc3b8da59bdd925bfb65b29c05d7b95ee
[ghc-hetmet.git] / ghc / lib / std / Time.hsc
1
2 -- -----------------------------------------------------------------------------
3 -- $Id: Time.hsc,v 1.20 2001/08/14 13:40:08 sewardj Exp $
4 --
5 -- (c) The University of Glasgow, 1995-2001
6 --
7
8 {-
9 Haskell 98 Time of Day Library
10 ------------------------------
11
12 The Time library provides standard functionality for clock times,
13 including timezone information (i.e, the functionality of "time.h",
14 adapted to the Haskell environment), It follows RFC 1129 in its use of
15 Coordinated Universal Time (UTC).
16
17 2000/06/17 <michael.weber@post.rwth-aachen.de>:
18 RESTRICTIONS:
19   * min./max. time diff currently is restricted to
20     [minBound::Int, maxBound::Int]
21
22   * surely other restrictions wrt. min/max bounds
23
24
25 NOTES:
26   * printing times
27
28     `showTime' (used in `instance Show ClockTime') always prints time
29     converted to the local timezone (even if it is taken from
30     `(toClockTime . toUTCTime)'), whereas `calendarTimeToString'
31     honors the tzone & tz fields and prints UTC or whatever timezone
32     is stored inside CalendarTime.
33
34     Maybe `showTime' should be changed to use UTC, since it would
35     better correspond to the actual representation of `ClockTime'
36     (can be done by replacing localtime(3) by gmtime(3)).
37
38
39 BUGS:
40   * add proper handling of microsecs, currently, they're mostly
41     ignored
42
43   * `formatFOO' case of `%s' is currently broken...
44
45
46 TODO:
47   * check for unusual date cases, like 1970/1/1 00:00h, and conversions
48     between different timezone's etc.
49
50   * check, what needs to be in the IO monad, the current situation
51     seems to be a bit inconsistent to me
52
53   * check whether `isDst = -1' works as expected on other arch's
54     (Solaris anyone?)
55
56   * add functions to parse strings to `CalendarTime' (some day...)
57
58   * implement padding capabilities ("%_", "%-") in `formatFOO'
59
60   * add rfc822 timezone (+0200 is CEST) representation ("%z") in `formatFOO'
61 -}
62
63 module Time 
64      (
65         Month(..)
66      ,  Day(..)
67
68      ,  ClockTime(..) -- non-standard, lib. report gives this as abstract
69         -- instance Eq, Ord
70         -- instance Show (non-standard)
71
72      ,  getClockTime
73
74      ,  TimeDiff(..)
75      ,  noTimeDiff      -- non-standard (but useful when constructing TimeDiff vals.)
76      ,  diffClockTimes
77      ,  addToClockTime
78
79      ,  normalizeTimeDiff -- non-standard
80      ,  timeDiffToString  -- non-standard
81      ,  formatTimeDiff    -- non-standard
82
83      ,  CalendarTime(..)
84      ,  toCalendarTime
85      ,  toUTCTime
86      ,  toClockTime
87      ,  calendarTimeToString
88      ,  formatCalendarTime
89
90      ) where
91
92 #include "HsStd.h"
93
94 import Ix
95 import Locale
96         
97 import PrelMarshalAlloc
98 import PrelMarshalUtils
99 import PrelMarshalError
100 import PrelStorable
101 import PrelCString
102 import PrelCTypesISO
103 import PrelCTypes
104 import PrelCError
105 import PrelInt
106 import PrelPtr
107 import PrelIOBase
108 import PrelShow
109 import PrelNum
110 import PrelBase
111
112 -- One way to partition and give name to chunks of a year and a week:
113
114 data Month
115  = January   | February | March    | April
116  | May       | June     | July     | August
117  | September | October  | November | December
118  deriving (Eq, Ord, Enum, Bounded, Ix, Read, Show)
119
120 data Day 
121  = Sunday   | Monday | Tuesday | Wednesday
122  | Thursday | Friday | Saturday
123  deriving (Eq, Ord, Enum, Bounded, Ix, Read, Show)
124
125 -- @ClockTime@ is an abstract type, used for the internal clock time.
126 -- Clock times may be compared, converted to strings, or converted to an
127 -- external calendar time @CalendarTime@.
128
129 data ClockTime = TOD Integer            -- Seconds since 00:00:00 on 1 Jan 1970
130                      Integer            -- Picoseconds with the specified second
131                deriving (Eq, Ord)
132
133 -- When a ClockTime is shown, it is converted to a CalendarTime in the current
134 -- timezone and then printed.  FIXME: This is arguably wrong, since we can't
135 -- get the current timezone without being in the IO monad.
136
137 instance Show ClockTime where
138     showsPrec _ t = showString (calendarTimeToString 
139                                  (unsafePerformIO (toCalendarTime t)))
140     showList = showList__ (showsPrec 0)
141
142 {-
143 @CalendarTime@ is a user-readable and manipulable
144 representation of the internal $ClockTime$ type.  The
145 numeric fields have the following ranges.
146
147 \begin{verbatim}
148 Value         Range             Comments
149 -----         -----             --------
150
151 year    -maxInt .. maxInt       [Pre-Gregorian dates are inaccurate]
152 mon           0 .. 11           [Jan = 0, Dec = 11]
153 day           1 .. 31
154 hour          0 .. 23
155 min           0 .. 59
156 sec           0 .. 61           [Allows for two leap seconds]
157 picosec       0 .. (10^12)-1    [This could be over-precise?]
158 wday          0 .. 6            [Sunday = 0, Saturday = 6]
159 yday          0 .. 365          [364 in non-Leap years]
160 tz       -43200 .. 43200        [Variation from UTC in seconds]
161 \end{verbatim}
162
163 The {\em tzname} field is the name of the time zone.  The {\em isdst}
164 field indicates whether Daylight Savings Time would be in effect.
165 -}
166
167 data CalendarTime 
168  = CalendarTime  {
169      ctYear    :: Int,
170      ctMonth   :: Month,
171      ctDay     :: Int,
172      ctHour    :: Int,
173      ctMin     :: Int,
174      ctSec     :: Int,
175      ctPicosec :: Integer,
176      ctWDay    :: Day,
177      ctYDay    :: Int,
178      ctTZName  :: String,
179      ctTZ      :: Int,
180      ctIsDST   :: Bool
181  }
182  deriving (Eq,Ord,Read,Show)
183
184 -- The @TimeDiff@ type records the difference between two clock times in
185 -- a user-readable way.
186
187 data TimeDiff
188  = TimeDiff {
189      tdYear    :: Int,
190      tdMonth   :: Int,
191      tdDay     :: Int,
192      tdHour    :: Int,
193      tdMin     :: Int,
194      tdSec     :: Int,
195      tdPicosec :: Integer -- not standard
196    }
197    deriving (Eq,Ord,Read,Show)
198
199 noTimeDiff :: TimeDiff
200 noTimeDiff = TimeDiff 0 0 0 0 0 0 0
201
202 -- -----------------------------------------------------------------------------
203 -- getClockTime returns the current time in its internal representation.
204
205 #if HAVE_GETTIMEOFDAY
206 getClockTime = do
207   allocaBytes (#const sizeof(struct timeval)) $ \ p_timeval -> do
208     throwErrnoIfMinus1_ "getClockTime" $ gettimeofday p_timeval nullPtr
209     sec  <- (#peek struct timeval,tv_sec)  p_timeval :: IO Int32
210     usec <- (#peek struct timeval,tv_usec) p_timeval :: IO Int32
211     return (TOD (fromIntegral sec) ((fromIntegral usec) * 1000))
212  
213 #elif HAVE_FTIME
214 getClockTime = do
215   allocaBytes (#const sizeof(struct timeb)) $ \ p_timeb -> do
216   ftime p_timeb
217   sec  <- (#peek struct timeb,time) p_timeb :: IO CTime
218   msec <- (#peek struct timeb,millitm) p_timeb :: IO CUShort
219   return (TOD (fromIntegral sec) (fromIntegral msec * 1000{-ToDo: correct???-}))
220
221 #else /* use POSIX time() */
222 getClockTime = do
223     secs <- time nullPtr -- can't fail, according to POSIX
224     return (TOD (fromIntegral secs) 0)
225
226 #endif
227
228 -- -----------------------------------------------------------------------------
229 -- addToClockTime d t adds a time difference d and a
230 -- clock time t to yield a new clock time.  The difference d
231 -- may be either positive or negative.  diffClockTimes t1 t2 returns 
232 -- the difference between two clock times t1 and t2 as a TimeDiff.
233
234 addToClockTime  :: TimeDiff  -> ClockTime -> ClockTime
235 addToClockTime (TimeDiff year mon day hour min sec psec) 
236                (TOD c_sec c_psec) = 
237         let
238           sec_diff = toInteger sec +
239                      60 * toInteger min +
240                      3600 * toInteger hour +
241                      24 * 3600 * toInteger day
242           cal      = toUTCTime (TOD (c_sec + sec_diff) (c_psec + psec))
243                                                        -- FIXME! ^^^^
244           new_mon  = fromEnum (ctMonth cal) + r_mon 
245           (month', yr_diff)
246             | new_mon < 0  = (toEnum (12 + new_mon), (-1))
247             | new_mon > 11 = (toEnum (new_mon `mod` 12), 1)
248             | otherwise    = (toEnum new_mon, 0)
249             
250           (r_yr, r_mon) = mon `quotRem` 12
251
252           year' = ctYear cal + year + r_yr + yr_diff
253         in
254         toClockTime cal{ctMonth=month', ctYear=year'}
255
256 diffClockTimes  :: ClockTime -> ClockTime -> TimeDiff
257 -- diffClockTimes is meant to be the dual to `addToClockTime'.
258 -- If you want to have the TimeDiff properly splitted, use
259 -- `normalizeTimeDiff' on this function's result
260 --
261 -- CAVEAT: see comment of normalizeTimeDiff
262 diffClockTimes (TOD sa pa) (TOD sb pb) =
263     noTimeDiff{ tdSec     = fromIntegral (sa - sb) 
264                 -- FIXME: can handle just 68 years...
265               , tdPicosec = pa - pb
266               }
267
268
269 normalizeTimeDiff :: TimeDiff -> TimeDiff
270 -- FIXME: handle psecs properly
271 -- FIXME: ?should be called by formatTimeDiff automagically?
272 --
273 -- when applied to something coming out of `diffClockTimes', you loose
274 -- the duality to `addToClockTime', since a year does not always have
275 -- 365 days, etc.
276 --
277 -- apply this function as late as possible to prevent those "rounding"
278 -- errors
279 normalizeTimeDiff td =
280   let
281       rest0 = tdSec td 
282                + 60 * (tdMin td 
283                     + 60 * (tdHour td 
284                          + 24 * (tdDay td 
285                               + 30 * (tdMonth td 
286                                    + 365 * tdYear td))))
287
288       (diffYears,  rest1)    = rest0 `quotRem` (365 * 24 * 3600)
289       (diffMonths, rest2)    = rest1 `quotRem` (30 * 24 * 3600)
290       (diffDays,   rest3)    = rest2 `quotRem` (24 * 3600)
291       (diffHours,  rest4)    = rest3 `quotRem` 3600
292       (diffMins,   diffSecs) = rest4 `quotRem` 60
293   in
294       td{ tdYear = diffYears
295         , tdMonth = diffMonths
296         , tdDay   = diffDays
297         , tdHour  = diffHours
298         , tdMin   = diffMins
299         , tdSec   = diffSecs
300         }
301
302 -- -----------------------------------------------------------------------------
303 -- How do we deal with timezones on this architecture?
304
305 -- The POSIX way to do it is through the global variable tzname[].
306 -- But that's crap, so we do it The BSD Way if we can: namely use the
307 -- tm_zone and tm_gmtoff fields of struct tm, if they're available.
308
309 zone   :: Ptr CTm -> IO (Ptr CChar)
310 gmtoff :: Ptr CTm -> IO CLong
311 #if HAVE_TM_ZONE
312 zone x      = (#peek struct tm,tm_zone) x
313 gmtoff x    = (#peek struct tm,tm_gmtoff) x
314
315 #else /* ! HAVE_TM_ZONE */
316 # if HAVE_TZNAME || defined(_WIN32)
317 #  if cygwin32_TARGET_OS
318 #   define tzname _tzname
319 #  endif
320 #  ifndef mingw32_TARGET_OS
321 foreign label tzname :: Ptr (Ptr CChar)
322 #  else
323 foreign import "ghcTimezone" unsafe timezone :: Ptr CLong
324 foreign import "ghcTzname" unsafe tzname :: Ptr (Ptr CChar)
325 #   def inline long  *ghcTimezone(void) { return &_timezone; }
326 #   def inline char **ghcTzname(void) { return _tzname; }
327 #  endif
328 zone x = do 
329   dst <- (#peek struct tm,tm_isdst) x
330   if dst then peekElemOff tzname 1 else peekElemOff tzname 0
331 # else /* ! HAVE_TZNAME */
332 -- We're in trouble. If you should end up here, please report this as a bug.
333 #  error "Don't know how to get at timezone name on your OS."
334 # endif /* ! HAVE_TZNAME */
335
336 -- Get the offset in secs from UTC, if (struct tm) doesn't supply it. */
337 #if defined(mingw32_TARGET_OS) || defined(cygwin32_TARGET_OS)
338 #define timezone _timezone
339 #endif
340
341 # if HAVE_ALTZONE
342 foreign label altzone  :: Ptr CTime
343 foreign label timezone :: Ptr CTime
344 gmtoff x = do 
345   dst <- (#peek struct tm,tm_isdst) x
346   tz <- if dst then peek altzone else peek timezone
347   return (fromIntegral tz)
348 #  define GMTOFF(x)      (((struct tm *)x)->tm_isdst ? altzone : timezone )
349 # else /* ! HAVE_ALTZONE */
350 -- Assume that DST offset is 1 hour ...
351 gmtoff x = do 
352   dst <- (#peek struct tm,tm_isdst) x
353   tz  <- peek timezone
354   if dst then return (fromIntegral tz - 3600) else return tz
355 # endif /* ! HAVE_ALTZONE */
356 #endif  /* ! HAVE_TM_ZONE */
357
358 -- -----------------------------------------------------------------------------
359 -- toCalendarTime t converts t to a local time, modified by
360 -- the current timezone and daylight savings time settings.  toUTCTime
361 -- t converts t into UTC time.  toClockTime l converts l into the 
362 -- corresponding internal ClockTime.  The wday, yday, tzname, and isdst fields
363 -- are ignored.
364
365
366 toCalendarTime :: ClockTime -> IO CalendarTime
367 #if HAVE_LOCALTIME_R
368 toCalendarTime =  clockToCalendarTime_reentrant (throwAwayReturnPointer localtime_r) False
369 #else
370 toCalendarTime =  clockToCalendarTime_static localtime False
371 #endif
372
373 toUTCTime      :: ClockTime -> CalendarTime
374 #if HAVE_GMTIME_R
375 toUTCTime      =  unsafePerformIO . clockToCalendarTime_reentrant (throwAwayReturnPointer gmtime_r) True
376 #else
377 toUTCTime      =  unsafePerformIO . clockToCalendarTime_static gmtime True
378 #endif
379
380 throwAwayReturnPointer :: (Ptr CTime -> Ptr CTm -> IO (Ptr CTm))
381                        -> (Ptr CTime -> Ptr CTm -> IO (       ))
382 throwAwayReturnPointer fun x y = fun x y >> return ()
383
384 clockToCalendarTime_static :: (Ptr CTime -> IO (Ptr CTm)) -> Bool -> ClockTime
385          -> IO CalendarTime
386 clockToCalendarTime_static fun is_utc (TOD secs psec) = do
387   withObject (fromIntegral secs :: CTime)  $ \ p_timer -> do
388     p_tm <- fun p_timer         -- can't fail, according to POSIX
389     clockToCalendarTime_aux is_utc p_tm psec
390
391 clockToCalendarTime_reentrant :: (Ptr CTime -> Ptr CTm -> IO ()) -> Bool -> ClockTime
392          -> IO CalendarTime
393 clockToCalendarTime_reentrant fun is_utc (TOD secs psec) = do
394   withObject (fromIntegral secs :: CTime)  $ \ p_timer -> do
395     allocaBytes (#const sizeof(struct tm)) $ \ p_tm -> do
396       fun p_timer p_tm
397       clockToCalendarTime_aux is_utc p_tm psec
398
399 clockToCalendarTime_aux :: Bool -> Ptr CTm -> Integer -> IO CalendarTime
400 clockToCalendarTime_aux is_utc p_tm psec = do
401     sec   <-  (#peek struct tm,tm_sec  ) p_tm :: IO CInt
402     min   <-  (#peek struct tm,tm_min  ) p_tm :: IO CInt
403     hour  <-  (#peek struct tm,tm_hour ) p_tm :: IO CInt
404     mday  <-  (#peek struct tm,tm_mday ) p_tm :: IO CInt
405     mon   <-  (#peek struct tm,tm_mon  ) p_tm :: IO CInt
406     year  <-  (#peek struct tm,tm_year ) p_tm :: IO CInt
407     wday  <-  (#peek struct tm,tm_wday ) p_tm :: IO CInt
408     yday  <-  (#peek struct tm,tm_yday ) p_tm :: IO CInt
409     isdst <-  (#peek struct tm,tm_isdst) p_tm :: IO CInt
410     zone  <-  zone p_tm
411     tz    <-  gmtoff p_tm
412     
413     tzname <- peekCString zone
414     
415     let month  | mon >= 0 && mon <= 11 = toEnum (fromIntegral mon)
416                | otherwise             = error ("toCalendarTime: illegal month value: " ++ show mon)
417     
418     return (CalendarTime 
419                 (1900 + fromIntegral year) 
420                 month
421                 (fromIntegral mday)
422                 (fromIntegral hour)
423                 (fromIntegral min)
424                 (fromIntegral sec)
425                 psec
426                 (toEnum (fromIntegral wday))
427                 (fromIntegral yday)
428                 (if is_utc then "UTC" else tzname)
429                 (if is_utc then 0     else fromIntegral tz)
430                 (if is_utc then False else isdst /= 0))
431
432
433 toClockTime :: CalendarTime -> ClockTime
434 toClockTime (CalendarTime year mon mday hour min sec psec 
435                           _wday _yday _tzname tz isdst) =
436
437      -- `isDst' causes the date to be wrong by one hour...
438      -- FIXME: check, whether this works on other arch's than Linux, too...
439      -- 
440      -- so we set it to (-1) (means `unknown') and let `mktime' determine
441      -- the real value...
442     let isDst = -1 :: CInt in   -- if isdst then (1::Int) else 0
443
444     if psec < 0 || psec > 999999999999 then
445         error "Time.toClockTime: picoseconds out of range"
446     else if tz < -43200 || tz > 43200 then
447         error "Time.toClockTime: timezone offset out of range"
448     else
449       unsafePerformIO $ do
450       allocaBytes (#const sizeof(struct tm)) $ \ p_tm -> do
451         (#poke struct tm,tm_sec  ) p_tm (fromIntegral sec  :: CInt)
452         (#poke struct tm,tm_min  ) p_tm (fromIntegral min  :: CInt)
453         (#poke struct tm,tm_hour ) p_tm (fromIntegral hour :: CInt)
454         (#poke struct tm,tm_mday ) p_tm (fromIntegral mday :: CInt)
455         (#poke struct tm,tm_mon  ) p_tm (fromIntegral (fromEnum mon) :: CInt)
456         (#poke struct tm,tm_year ) p_tm (fromIntegral year - 1900 :: CInt)
457         (#poke struct tm,tm_isdst) p_tm isDst
458         t <- throwIf (== -1) (\_ -> "Time.toClockTime: invalid input")
459                 (mktime p_tm)
460         -- 
461         -- mktime expects its argument to be in the local timezone, but
462         -- toUTCTime makes UTC-encoded CalendarTime's ...
463         -- 
464         -- Since there is no any_tz_struct_tm-to-time_t conversion
465         -- function, we have to fake one... :-) If not in all, it works in
466         -- most cases (before, it was the other way round...)
467         -- 
468         -- Luckily, mktime tells us, what it *thinks* the timezone is, so,
469         -- to compensate, we add the timezone difference to mktime's
470         -- result.
471         -- 
472         gmtoff <- gmtoff p_tm
473         let res = fromIntegral t - tz + fromIntegral gmtoff
474         return (TOD (fromIntegral res) 0)
475
476 -- -----------------------------------------------------------------------------
477 -- Converting time values to strings.
478
479 calendarTimeToString  :: CalendarTime -> String
480 calendarTimeToString  =  formatCalendarTime defaultTimeLocale "%c"
481
482 formatCalendarTime :: TimeLocale -> String -> CalendarTime -> String
483 formatCalendarTime l fmt (CalendarTime year mon day hour min sec _
484                                        wday yday tzname _ _) =
485         doFmt fmt
486   where doFmt ('%':'-':cs) = doFmt ('%':cs) -- padding not implemented
487         doFmt ('%':'_':cs) = doFmt ('%':cs) -- padding not implemented
488         doFmt ('%':c:cs)   = decode c ++ doFmt cs
489         doFmt (c:cs) = c : doFmt cs
490         doFmt "" = ""
491
492         decode 'A' = fst (wDays l  !! fromEnum wday) -- day of the week, full name
493         decode 'a' = snd (wDays l  !! fromEnum wday) -- day of the week, abbrev.
494         decode 'B' = fst (months l !! fromEnum mon)  -- month, full name
495         decode 'b' = snd (months l !! fromEnum mon)  -- month, abbrev
496         decode 'h' = snd (months l !! fromEnum mon)  -- ditto
497         decode 'C' = show2 (year `quot` 100)         -- century
498         decode 'c' = doFmt (dateTimeFmt l)           -- locale's data and time format.
499         decode 'D' = doFmt "%m/%d/%y"
500         decode 'd' = show2 day                       -- day of the month
501         decode 'e' = show2' day                      -- ditto, padded
502         decode 'H' = show2 hour                      -- hours, 24-hour clock, padded
503         decode 'I' = show2 (to12 hour)               -- hours, 12-hour clock
504         decode 'j' = show3 yday                      -- day of the year
505         decode 'k' = show2' hour                     -- hours, 24-hour clock, no padding
506         decode 'l' = show2' (to12 hour)              -- hours, 12-hour clock, no padding
507         decode 'M' = show2 min                       -- minutes
508         decode 'm' = show2 (fromEnum mon+1)          -- numeric month
509         decode 'n' = "\n"
510         decode 'p' = (if hour < 12 then fst else snd) (amPm l) -- am or pm
511         decode 'R' = doFmt "%H:%M"
512         decode 'r' = doFmt (time12Fmt l)
513         decode 'T' = doFmt "%H:%M:%S"
514         decode 't' = "\t"
515         decode 'S' = show2 sec                       -- seconds
516         decode 's' = show2 sec                       -- number of secs since Epoch. (ToDo.)
517         decode 'U' = show2 ((yday + 7 - fromEnum wday) `div` 7) -- week number, starting on Sunday.
518         decode 'u' = show (let n = fromEnum wday in  -- numeric day of the week (1=Monday, 7=Sunday)
519                            if n == 0 then 7 else n)
520         decode 'V' =                                 -- week number (as per ISO-8601.)
521             let (week, days) =                       -- [yep, I've always wanted to be able to display that too.]
522                    (yday + 7 - if fromEnum wday > 0 then 
523                                fromEnum wday - 1 else 6) `divMod` 7
524             in  show2 (if days >= 4 then
525                           week+1 
526                        else if week == 0 then 53 else week)
527
528         decode 'W' =                                 -- week number, weeks starting on monday
529             show2 ((yday + 7 - if fromEnum wday > 0 then 
530                                fromEnum wday - 1 else 6) `div` 7)
531         decode 'w' = show (fromEnum wday)            -- numeric day of the week, weeks starting on Sunday.
532         decode 'X' = doFmt (timeFmt l)               -- locale's preferred way of printing time.
533         decode 'x' = doFmt (dateFmt l)               -- locale's preferred way of printing dates.
534         decode 'Y' = show year                       -- year, including century.
535         decode 'y' = show2 (year `rem` 100)          -- year, within century.
536         decode 'Z' = tzname                          -- timezone name
537         decode '%' = "%"
538         decode c   = [c]
539
540
541 show2, show2', show3 :: Int -> String
542 show2 x = [intToDigit (x `quot` 10), intToDigit (x `rem` 10)]
543
544 show2' x = if x < 10 then [ ' ', intToDigit x] else show2 x
545
546 show3 x = intToDigit (x `quot` 100) : show2 (x `rem` 100)
547
548 to12 :: Int -> Int
549 to12 h = let h' = h `mod` 12 in if h' == 0 then 12 else h'
550
551 -- Useful extensions for formatting TimeDiffs.
552
553 timeDiffToString :: TimeDiff -> String
554 timeDiffToString = formatTimeDiff defaultTimeLocale "%c"
555
556 formatTimeDiff :: TimeLocale -> String -> TimeDiff -> String
557 formatTimeDiff l fmt td@(TimeDiff year month day hour min sec _)
558  = doFmt fmt
559   where 
560    doFmt ""         = ""
561    doFmt ('%':'-':cs) = doFmt ('%':cs) -- padding not implemented
562    doFmt ('%':'_':cs) = doFmt ('%':cs) -- padding not implemented
563    doFmt ('%':c:cs) = decode c ++ doFmt cs
564    doFmt (c:cs)     = c : doFmt cs
565
566    decode spec =
567     case spec of
568       'B' -> fst (months l !! fromEnum month)
569       'b' -> snd (months l !! fromEnum month)
570       'h' -> snd (months l !! fromEnum month)
571       'c' -> defaultTimeDiffFmt td
572       'C' -> show2 (year `quot` 100)
573       'D' -> doFmt "%m/%d/%y"
574       'd' -> show2 day
575       'e' -> show2' day
576       'H' -> show2 hour
577       'I' -> show2 (to12 hour)
578       'k' -> show2' hour
579       'l' -> show2' (to12 hour)
580       'M' -> show2 min
581       'm' -> show2 (fromEnum month + 1)
582       'n' -> "\n"
583       'p' -> (if hour < 12 then fst else snd) (amPm l)
584       'R' -> doFmt "%H:%M"
585       'r' -> doFmt (time12Fmt l)
586       'T' -> doFmt "%H:%M:%S"
587       't' -> "\t"
588       'S' -> show2 sec
589       's' -> show2 sec -- Implementation-dependent, sez the lib doc..
590       'X' -> doFmt (timeFmt l)
591       'x' -> doFmt (dateFmt l)
592       'Y' -> show year
593       'y' -> show2 (year `rem` 100)
594       '%' -> "%"
595       c   -> [c]
596
597    defaultTimeDiffFmt (TimeDiff year month day hour min sec _) =
598        foldr (\ (v,s) rest -> 
599                   (if v /= 0 
600                      then show v ++ ' ':(addS v s)
601                        ++ if null rest then "" else ", "
602                      else "") ++ rest
603              )
604              ""
605              (zip [year, month, day, hour, min, sec] (intervals l))
606
607    addS v s = if abs v == 1 then fst s else snd s
608
609
610 -- -----------------------------------------------------------------------------
611 -- Foreign time interface (POSIX)
612
613 type CTm = () -- struct tm
614
615 #if HAVE_LOCALTIME_R
616 foreign import unsafe localtime_r :: Ptr CTime -> Ptr CTm -> IO (Ptr CTm)
617 #else
618 foreign import unsafe localtime   :: Ptr CTime -> IO (Ptr CTm)
619 #endif
620 #if HAVE_GMTIME_R
621 foreign import unsafe gmtime_r    :: Ptr CTime -> Ptr CTm -> IO (Ptr CTm)
622 #else
623 foreign import unsafe gmtime      :: Ptr CTime -> IO (Ptr CTm)
624 #endif
625 foreign import unsafe mktime      :: Ptr CTm   -> IO CTime
626 foreign import unsafe time        :: Ptr CTime -> IO CTime
627
628 #if HAVE_GETTIMEOFDAY
629 type CTimeVal = ()
630 foreign import unsafe gettimeofday :: Ptr CTimeVal -> Ptr () -> IO CInt
631 #endif
632
633 #if HAVE_FTIME
634 type CTimeB = ()
635 #ifndef mingw32_TARGET_OS
636 foreign import unsafe ftime :: Ptr CTimeB -> IO CInt
637 #else
638 foreign import unsafe ftime :: Ptr CTimeB -> IO ()
639 #endif
640 #endif