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