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