[project @ 2001-01-26 16:16:19 by rrt]
[ghc-hetmet.git] / ghc / lib / std / Time.hsc
1 {-# OPTIONS -optc-DNON_POSIX_SOURCE #-}
2 -- JRS 010117: we had to say NON_POSIX_SOURCE to get the resulting .hc
3 -- to compile on sparc-solaris.  Blargh.
4
5 -- -----------------------------------------------------------------------------
6 -- $Id: Time.hsc,v 1.7 2001/01/26 16:16:19 rrt Exp $
7 --
8 -- (c) The University of Glasgow, 1995-2001
9 --
10
11 {-
12 Haskell 98 Time of Day Library
13 ------------------------------
14
15 The Time library provides standard functionality for clock times,
16 including timezone information (i.e, the functionality of "time.h",
17 adapted to the Haskell environment), It follows RFC 1129 in its use of
18 Coordinated Universal Time (UTC).
19
20 2000/06/17 <michael.weber@post.rwth-aachen.de>:
21 RESTRICTIONS:
22   * min./max. time diff currently is restricted to
23     [minBound::Int, maxBound::Int]
24
25   * surely other restrictions wrt. min/max bounds
26
27
28 NOTES:
29   * printing times
30
31     `showTime' (used in `instance Show ClockTime') always prints time
32     converted to the local timezone (even if it is taken from
33     `(toClockTime . toUTCTime)'), whereas `calendarTimeToString'
34     honors the tzone & tz fields and prints UTC or whatever timezone
35     is stored inside CalendarTime.
36
37     Maybe `showTime' should be changed to use UTC, since it would
38     better correspond to the actual representation of `ClockTime'
39     (can be done by replacing localtime(3) by gmtime(3)).
40
41
42 BUGS:
43   * add proper handling of microsecs, currently, they're mostly
44     ignored
45
46   * `formatFOO' case of `%s' is currently broken...
47
48
49 TODO:
50   * check for unusual date cases, like 1970/1/1 00:00h, and conversions
51     between different timezone's etc.
52
53   * check, what needs to be in the IO monad, the current situation
54     seems to be a bit inconsistent to me
55
56   * check whether `isDst = -1' works as expected on other arch's
57     (Solaris anyone?)
58
59   * add functions to parse strings to `CalendarTime' (some day...)
60
61   * implement padding capabilities ("%_", "%-") in `formatFOO'
62
63   * add rfc822 timezone (+0200 is CEST) representation ("%z") in `formatFOO'
64 -}
65
66 module Time 
67      (
68         Month(..)
69      ,  Day(..)
70
71      ,  ClockTime(..) -- non-standard, lib. report gives this as abstract
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 "config.h"
93
94 #if defined(HAVE_GETTIMEOFDAY)
95 #  ifdef HAVE_SYS_TIME_H
96 #   include <sys/time.h>
97 #  endif
98 #elif defined(HAVE_GETCLOCK)
99 # ifdef HAVE_SYS_TIMERS_H
100 #  define POSIX_4D9 1
101 #  include <sys/timers.h>
102 # endif
103 #elif defined(HAVE_TIME_H)
104 # include <time.h>
105 #endif
106
107 #ifdef HAVE_WINDOWS_H
108 #include <windows.h>
109 #include <sys/types.h>
110 #include <sys/timeb.h>
111 #endif
112
113 import Ix
114 import Locale
115         
116 import PrelMarshalAlloc
117 import PrelMarshalUtils
118 import PrelMarshalError
119 import PrelStorable
120 import PrelCString
121 import PrelCTypesISO
122 import PrelCTypes
123 import PrelCError
124 import PrelInt
125 import PrelPtr
126 import PrelIOBase
127 import PrelShow
128 import PrelNum
129 import PrelBase
130
131 -- One way to partition and give name to chunks of a year and a week:
132
133 data Month
134  = January   | February | March    | April
135  | May       | June     | July     | August
136  | September | October  | November | December
137  deriving (Eq, Ord, Enum, Bounded, Ix, Read, Show)
138
139 data Day 
140  = Sunday   | Monday | Tuesday | Wednesday
141  | Thursday | Friday | Saturday
142  deriving (Eq, Ord, Enum, Bounded, Ix, Read, Show)
143
144 -- @ClockTime@ is an abstract type, used for the internal clock time.
145 -- Clock times may be compared, converted to strings, or converted to an
146 -- external calendar time @CalendarTime@.
147
148 data ClockTime = TOD Integer            -- Seconds since 00:00:00 on 1 Jan 1970
149                      Integer            -- Picoseconds with the specified second
150                deriving (Eq, Ord)
151
152 -- When a @ClockTime@ is shown, it is converted to a string of the form
153 -- @"Mon Nov 28 21:45:41 GMT 1994"@.
154
155 -- For now, we are restricted to roughly:
156 -- Fri Dec 13 20:45:52 1901 through Tue Jan 19 03:14:07 2038, because
157 -- we use the C library routines based on 32 bit integers.
158
159 instance Show ClockTime where
160     showsPrec _ (TOD secs _nsec) = 
161       showString $ unsafePerformIO $ do
162             withObject (fromIntegral secs :: CTime)  $ \ p_timer -> do
163               p_tm <- localtime p_timer -- can't fail, according to POSIX
164               allocaBytes 64 $ \ p_buf -> do  -- big enough for error message
165                 r <- strftime p_buf 50 "%a %b %d %H:%M:%S %Z %Y"## p_tm
166                 if r == 0 
167                   then return "ClockTime.show{Time}: internal error"
168                   else peekCString p_buf
169
170     showList = showList__ (showsPrec 0)
171
172 {-
173 @CalendarTime@ is a user-readable and manipulable
174 representation of the internal $ClockTime$ type.  The
175 numeric fields have the following ranges.
176
177 \begin{verbatim}
178 Value         Range             Comments
179 -----         -----             --------
180
181 year    -maxInt .. maxInt       [Pre-Gregorian dates are inaccurate]
182 mon           0 .. 11           [Jan = 0, Dec = 11]
183 day           1 .. 31
184 hour          0 .. 23
185 min           0 .. 59
186 sec           0 .. 61           [Allows for two leap seconds]
187 picosec       0 .. (10^12)-1    [This could be over-precise?]
188 wday          0 .. 6            [Sunday = 0, Saturday = 6]
189 yday          0 .. 365          [364 in non-Leap years]
190 tz       -43200 .. 43200        [Variation from UTC in seconds]
191 \end{verbatim}
192
193 The {\em tzname} field is the name of the time zone.  The {\em isdst}
194 field indicates whether Daylight Savings Time would be in effect.
195 -}
196
197 data CalendarTime 
198  = CalendarTime  {
199      ctYear    :: Int,
200      ctMonth   :: Month,
201      ctDay     :: Int,
202      ctHour    :: Int,
203      ctMin     :: Int,
204      ctSec     :: Int,
205      ctPicosec :: Integer,
206      ctWDay    :: Day,
207      ctYDay    :: Int,
208      ctTZName  :: String,
209      ctTZ      :: Int,
210      ctIsDST   :: Bool
211  }
212  deriving (Eq,Ord,Read,Show)
213
214 -- The @TimeDiff@ type records the difference between two clock times in
215 -- a user-readable way.
216
217 data TimeDiff
218  = TimeDiff {
219      tdYear    :: Int,
220      tdMonth   :: Int,
221      tdDay     :: Int,
222      tdHour    :: Int,
223      tdMin     :: Int,
224      tdSec     :: Int,
225      tdPicosec :: Integer -- not standard
226    }
227    deriving (Eq,Ord,Read,Show)
228
229 noTimeDiff :: TimeDiff
230 noTimeDiff = TimeDiff 0 0 0 0 0 0 0
231
232 -- -----------------------------------------------------------------------------
233 -- getClockTime returns the current time in its internal representation.
234
235 #if HAVE_GETTIMEOFDAY
236 getClockTime = do
237   allocaBytes (#const sizeof(struct timeval)) $ \ p_timeval -> do
238     throwErrnoIfMinus1_ "getClockTime" $ gettimeofday p_timeval nullPtr
239     sec  <- (#peek struct timeval,tv_sec)  p_timeval :: IO CLong
240     usec <- (#peek struct timeval,tv_usec) p_timeval :: IO CLong
241     return (TOD (fromIntegral sec) ((fromIntegral usec) * 1000))
242  
243 #elif HAVE_FTIME
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,millitm) 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 zone   :: Ptr CTm -> IO (Ptr CChar)
337 gmtoff :: Ptr CTm -> IO CLong
338 #if HAVE_TM_ZONE
339 zone x      = (#peek struct tm,tm_zone) x
340 gmtoff x    = (#peek struct tm,tm_gmtoff) x
341
342 #else /* ! HAVE_TM_ZONE */
343 # if HAVE_TZNAME || _WIN32
344 #  if cygwin32_TARGET_OS
345 #   define tzname _tzname
346 #  endif
347 #  ifndef mingw32_TARGET_OS
348 foreign label tzname :: Ptr (Ptr CChar)
349 #  endif
350 zone x = do 
351   dst <- (#peek struct tm,tm_isdst) x
352   if dst then peekElemOff tzname 1 else peekElemOff tzname 0
353 # else /* ! HAVE_TZNAME */
354 -- We're in trouble. If you should end up here, please report this as a bug.
355 #  error "Don't know how to get at timezone name on your OS."
356 # endif /* ! HAVE_TZNAME */
357
358 -- Get the offset in secs from UTC, if (struct tm) doesn't supply it. */
359 #if defined(mingw32_TARGET_OS) || defined(cygwin32_TARGET_OS)
360 #define timezone _timezone
361 #endif
362
363 # if HAVE_ALTZONE
364 foreign label altzone  :: Ptr CTime
365 foreign label timezone :: Ptr CTime
366 gmtoff x = do 
367   dst <- (#peek struct tm,tm_isdst) x
368   tz <- if dst then peek altzone else peek timezone
369   return (fromIntegral tz)
370 #  define GMTOFF(x)      (((struct tm *)x)->tm_isdst ? altzone : timezone )
371 # else /* ! HAVE_ALTZONE */
372 -- Assume that DST offset is 1 hour ...
373 gmtoff x = do 
374   dst <- (#peek struct tm,tm_isdst) x
375   tz  <- peek timezone
376   if dst then return (fromIntegral tz - 3600) else return tz
377 # endif /* ! HAVE_ALTZONE */
378 #endif  /* ! HAVE_TM_ZONE */
379
380 -- -----------------------------------------------------------------------------
381 -- toCalendarTime t converts t to a local time, modified by
382 -- the current timezone and daylight savings time settings.  toUTCTime
383 -- t converts t into UTC time.  toClockTime l converts l into the 
384 -- corresponding internal ClockTime.  The wday, yday, tzname, and isdst fields
385 -- are ignored.
386
387
388 toCalendarTime :: ClockTime -> IO CalendarTime
389 toCalendarTime =  clockToCalendarTime localtime False
390
391 toUTCTime      :: ClockTime -> CalendarTime
392 toUTCTime      =  unsafePerformIO . clockToCalendarTime gmtime True
393
394 -- ToDo: should be made thread safe, because localtime uses static storage,
395 -- or use the localtime_r version.
396 clockToCalendarTime :: (Ptr CTime -> IO (Ptr CTm)) -> Bool -> ClockTime
397          -> IO CalendarTime
398 clockToCalendarTime fun is_utc (TOD secs psec) = do
399   withObject (fromIntegral secs :: CTime)  $ \ p_timer -> do
400     p_tm <- fun p_timer         -- can't fail, according to POSIX
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 foreign import unsafe localtime :: Ptr CTime -> IO (Ptr CTm)
616 foreign import unsafe gmtime    :: Ptr CTime -> IO (Ptr CTm)
617 foreign import unsafe strftime  :: Ptr CChar -> CSize -> Addr## -> Ptr CTm -> IO CSize
618 foreign import unsafe mktime    :: Ptr CTm   -> IO CTime
619 foreign import unsafe time      :: Ptr CTime -> IO CTime
620
621 #if HAVE_GETTIMEOFDAY
622 type CTimeVal = ()
623 foreign import unsafe gettimeofday :: Ptr CTimeVal -> Ptr () -> IO CInt
624 #endif
625
626 #if HAVE_FTIME
627 type CTimeB = ()
628 foreign import unsafe ftime :: Ptr CTimeB -> IO CInt
629 #endif