[project @ 2001-04-25 14:36:48 by simonmar]
[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.12 2001/04/25 14:36:48 simonmar 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         -- instance Eq, Ord
73         -- instance Show (non-standard)
74
75      ,  getClockTime
76
77      ,  TimeDiff(..)
78      ,  noTimeDiff      -- non-standard (but useful when constructing TimeDiff vals.)
79      ,  diffClockTimes
80      ,  addToClockTime
81
82      ,  normalizeTimeDiff -- non-standard
83      ,  timeDiffToString  -- non-standard
84      ,  formatTimeDiff    -- non-standard
85
86      ,  CalendarTime(..)
87      ,  toCalendarTime
88      ,  toUTCTime
89      ,  toClockTime
90      ,  calendarTimeToString
91      ,  formatCalendarTime
92
93      ) where
94
95 #include "config.h"
96
97 #if defined(HAVE_GETTIMEOFDAY)
98 #  ifdef HAVE_SYS_TIME_H
99 #   include <sys/time.h>
100 #  endif
101 #elif defined(HAVE_GETCLOCK)
102 # ifdef HAVE_SYS_TIMERS_H
103 #  define POSIX_4D9 1
104 #  include <sys/timers.h>
105 # endif
106 #endif
107
108 #if defined(HAVE_TIME_H)
109 # include <time.h>
110 #endif
111
112 #ifdef HAVE_SYS_TYPES_H
113 #include <sys/types.h>
114 #endif
115
116 #ifdef HAVE_SYS_TIMEB_H
117 #include <sys/timeb.h>
118 #endif
119
120 #ifdef HAVE_WINDOWS_H
121 #include <windows.h>
122 #endif
123
124 import Ix
125 import Locale
126         
127 import PrelMarshalAlloc
128 import PrelMarshalUtils
129 import PrelMarshalError
130 import PrelStorable
131 import PrelCString
132 import PrelCTypesISO
133 import PrelCTypes
134 import PrelCError
135 import PrelInt
136 import PrelPtr
137 import PrelIOBase
138 import PrelShow
139 import PrelNum
140 import PrelBase
141
142 -- One way to partition and give name to chunks of a year and a week:
143
144 data Month
145  = January   | February | March    | April
146  | May       | June     | July     | August
147  | September | October  | November | December
148  deriving (Eq, Ord, Enum, Bounded, Ix, Read, Show)
149
150 data Day 
151  = Sunday   | Monday | Tuesday | Wednesday
152  | Thursday | Friday | Saturday
153  deriving (Eq, Ord, Enum, Bounded, Ix, Read, Show)
154
155 -- @ClockTime@ is an abstract type, used for the internal clock time.
156 -- Clock times may be compared, converted to strings, or converted to an
157 -- external calendar time @CalendarTime@.
158
159 data ClockTime = TOD Integer            -- Seconds since 00:00:00 on 1 Jan 1970
160                      Integer            -- Picoseconds with the specified second
161                deriving (Eq, Ord)
162
163 -- When a ClockTime is shown, it is converted to a CalendarTime in the current
164 -- timezone and then printed.  FIXME: This is arguably wrong, since we can't
165 -- get the current timezone without being in the IO monad.
166
167 instance Show ClockTime where
168     showsPrec _ t = showString (calendarTimeToString 
169                                  (unsafePerformIO (toCalendarTime t)))
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 = toInteger sec +
269                      60 * toInteger min +
270                      3600 * toInteger hour +
271                      24 * 3600 * toInteger day
272           cal      = toUTCTime (TOD (c_sec + sec_diff) (c_psec + psec))
273                                                        -- FIXME! ^^^^
274           new_mon  = fromEnum (ctMonth cal) + r_mon 
275           (month', yr_diff)
276             | new_mon < 0  = (toEnum (12 + new_mon), (-1))
277             | new_mon > 11 = (toEnum (new_mon `mod` 12), 1)
278             | otherwise    = (toEnum new_mon, 0)
279             
280           (r_yr, r_mon) = mon `quotRem` 12
281
282           year' = ctYear cal + year + r_yr + yr_diff
283         in
284         toClockTime cal{ctMonth=month', ctYear=year'}
285
286 diffClockTimes  :: ClockTime -> ClockTime -> TimeDiff
287 -- diffClockTimes is meant to be the dual to `addToClockTime'.
288 -- If you want to have the TimeDiff properly splitted, use
289 -- `normalizeTimeDiff' on this function's result
290 --
291 -- CAVEAT: see comment of normalizeTimeDiff
292 diffClockTimes (TOD sa pa) (TOD sb pb) =
293     noTimeDiff{ tdSec     = fromIntegral (sa - sb) 
294                 -- FIXME: can handle just 68 years...
295               , tdPicosec = pa - pb
296               }
297
298
299 normalizeTimeDiff :: TimeDiff -> TimeDiff
300 -- FIXME: handle psecs properly
301 -- FIXME: ?should be called by formatTimeDiff automagically?
302 --
303 -- when applied to something coming out of `diffClockTimes', you loose
304 -- the duality to `addToClockTime', since a year does not always have
305 -- 365 days, etc.
306 --
307 -- apply this function as late as possible to prevent those "rounding"
308 -- errors
309 normalizeTimeDiff td =
310   let
311       rest0 = tdSec td 
312                + 60 * (tdMin td 
313                     + 60 * (tdHour td 
314                          + 24 * (tdDay td 
315                               + 30 * (tdMonth td 
316                                    + 365 * tdYear td))))
317
318       (diffYears,  rest1)    = rest0 `quotRem` (365 * 24 * 3600)
319       (diffMonths, rest2)    = rest1 `quotRem` (30 * 24 * 3600)
320       (diffDays,   rest3)    = rest2 `quotRem` (24 * 3600)
321       (diffHours,  rest4)    = rest3 `quotRem` 3600
322       (diffMins,   diffSecs) = rest4 `quotRem` 60
323   in
324       td{ tdYear = diffYears
325         , tdMonth = diffMonths
326         , tdDay   = diffDays
327         , tdHour  = diffHours
328         , tdMin   = diffMins
329         , tdSec   = diffSecs
330         }
331
332 -- -----------------------------------------------------------------------------
333 -- How do we deal with timezones on this architecture?
334
335 -- The POSIX way to do it is through the global variable tzname[].
336 -- But that's crap, so we do it The BSD Way if we can: namely use the
337 -- tm_zone and tm_gmtoff fields of struct tm, if they're available.
338
339 zone   :: Ptr CTm -> IO (Ptr CChar)
340 gmtoff :: Ptr CTm -> IO CLong
341 #if HAVE_TM_ZONE
342 zone x      = (#peek struct tm,tm_zone) x
343 gmtoff x    = (#peek struct tm,tm_gmtoff) x
344
345 #else /* ! HAVE_TM_ZONE */
346 # if HAVE_TZNAME || _WIN32
347 #  if cygwin32_TARGET_OS
348 #   define tzname _tzname
349 #  endif
350 #  ifndef mingw32_TARGET_OS
351 foreign label tzname :: Ptr (Ptr CChar)
352 #  else
353 foreign import "ghcTimezone" unsafe timezone :: Ptr CLong
354 foreign import "ghcTzname" unsafe tzname :: Ptr (Ptr CChar)
355 #   def inline long  *ghcTimezone(void) { return &_timezone; }
356 #   def inline char **ghcTzname(void) { return _tzname; }
357 #  endif
358 zone x = do 
359   dst <- (#peek struct tm,tm_isdst) x
360   if dst then peekElemOff tzname 1 else peekElemOff tzname 0
361 # else /* ! HAVE_TZNAME */
362 -- We're in trouble. If you should end up here, please report this as a bug.
363 #  error "Don't know how to get at timezone name on your OS."
364 # endif /* ! HAVE_TZNAME */
365
366 -- Get the offset in secs from UTC, if (struct tm) doesn't supply it. */
367 #if defined(mingw32_TARGET_OS) || defined(cygwin32_TARGET_OS)
368 #define timezone _timezone
369 #endif
370
371 # if HAVE_ALTZONE
372 foreign label altzone  :: Ptr CTime
373 foreign label timezone :: Ptr CTime
374 gmtoff x = do 
375   dst <- (#peek struct tm,tm_isdst) x
376   tz <- if dst then peek altzone else peek timezone
377   return (fromIntegral tz)
378 #  define GMTOFF(x)      (((struct tm *)x)->tm_isdst ? altzone : timezone )
379 # else /* ! HAVE_ALTZONE */
380 -- Assume that DST offset is 1 hour ...
381 gmtoff x = do 
382   dst <- (#peek struct tm,tm_isdst) x
383   tz  <- peek timezone
384   if dst then return (fromIntegral tz - 3600) else return tz
385 # endif /* ! HAVE_ALTZONE */
386 #endif  /* ! HAVE_TM_ZONE */
387
388 -- -----------------------------------------------------------------------------
389 -- toCalendarTime t converts t to a local time, modified by
390 -- the current timezone and daylight savings time settings.  toUTCTime
391 -- t converts t into UTC time.  toClockTime l converts l into the 
392 -- corresponding internal ClockTime.  The wday, yday, tzname, and isdst fields
393 -- are ignored.
394
395
396 toCalendarTime :: ClockTime -> IO CalendarTime
397 toCalendarTime =  clockToCalendarTime localtime False
398
399 toUTCTime      :: ClockTime -> CalendarTime
400 toUTCTime      =  unsafePerformIO . clockToCalendarTime gmtime True
401
402 -- ToDo: should be made thread safe, because localtime uses static storage,
403 -- or use the localtime_r version.
404 clockToCalendarTime :: (Ptr CTime -> IO (Ptr CTm)) -> Bool -> ClockTime
405          -> IO CalendarTime
406 clockToCalendarTime fun is_utc (TOD secs psec) = do
407   withObject (fromIntegral secs :: CTime)  $ \ p_timer -> do
408     p_tm <- fun p_timer         -- can't fail, according to POSIX
409     sec   <-  (#peek struct tm,tm_sec  ) p_tm :: IO CInt
410     min   <-  (#peek struct tm,tm_min  ) p_tm :: IO CInt
411     hour  <-  (#peek struct tm,tm_hour ) p_tm :: IO CInt
412     mday  <-  (#peek struct tm,tm_mday ) p_tm :: IO CInt
413     mon   <-  (#peek struct tm,tm_mon  ) p_tm :: IO CInt
414     year  <-  (#peek struct tm,tm_year ) p_tm :: IO CInt
415     wday  <-  (#peek struct tm,tm_wday ) p_tm :: IO CInt
416     yday  <-  (#peek struct tm,tm_yday ) p_tm :: IO CInt
417     isdst <-  (#peek struct tm,tm_isdst) p_tm :: IO CInt
418     zone  <-  zone p_tm
419     tz    <-  gmtoff p_tm
420     
421     tzname <- peekCString zone
422     
423     let month  | mon >= 0 && mon <= 11 = toEnum (fromIntegral mon)
424                | otherwise             = error ("toCalendarTime: illegal month value: " ++ show mon)
425     
426     return (CalendarTime 
427                 (1900 + fromIntegral year) 
428                 month
429                 (fromIntegral mday)
430                 (fromIntegral hour)
431                 (fromIntegral min)
432                 (fromIntegral sec)
433                 psec
434                 (toEnum (fromIntegral wday))
435                 (fromIntegral yday)
436                 (if is_utc then "UTC" else tzname)
437                 (if is_utc then 0     else fromIntegral tz)
438                 (if is_utc then False else isdst /= 0))
439
440
441 toClockTime :: CalendarTime -> ClockTime
442 toClockTime (CalendarTime year mon mday hour min sec psec 
443                           _wday _yday _tzname tz isdst) =
444
445      -- `isDst' causes the date to be wrong by one hour...
446      -- FIXME: check, whether this works on other arch's than Linux, too...
447      -- 
448      -- so we set it to (-1) (means `unknown') and let `mktime' determine
449      -- the real value...
450     let isDst = -1 :: CInt in   -- if isdst then (1::Int) else 0
451
452     if psec < 0 || psec > 999999999999 then
453         error "Time.toClockTime: picoseconds out of range"
454     else if tz < -43200 || tz > 43200 then
455         error "Time.toClockTime: timezone offset out of range"
456     else
457       unsafePerformIO $ do
458       allocaBytes (#const sizeof(struct tm)) $ \ p_tm -> do
459         (#poke struct tm,tm_sec  ) p_tm (fromIntegral sec  :: CInt)
460         (#poke struct tm,tm_min  ) p_tm (fromIntegral min  :: CInt)
461         (#poke struct tm,tm_hour ) p_tm (fromIntegral hour :: CInt)
462         (#poke struct tm,tm_mday ) p_tm (fromIntegral mday :: CInt)
463         (#poke struct tm,tm_mon  ) p_tm (fromIntegral (fromEnum mon) :: CInt)
464         (#poke struct tm,tm_year ) p_tm (fromIntegral year - 1900 :: CInt)
465         (#poke struct tm,tm_isdst) p_tm isDst
466         t <- throwIf (== -1) (\_ -> "Time.toClockTime: invalid input")
467                 (mktime p_tm)
468         -- 
469         -- mktime expects its argument to be in the local timezone, but
470         -- toUTCTime makes UTC-encoded CalendarTime's ...
471         -- 
472         -- Since there is no any_tz_struct_tm-to-time_t conversion
473         -- function, we have to fake one... :-) If not in all, it works in
474         -- most cases (before, it was the other way round...)
475         -- 
476         -- Luckily, mktime tells us, what it *thinks* the timezone is, so,
477         -- to compensate, we add the timezone difference to mktime's
478         -- result.
479         -- 
480         gmtoff <- gmtoff p_tm
481         let res = fromIntegral t - tz + fromIntegral gmtoff
482         return (TOD (fromIntegral res) 0)
483
484 -- -----------------------------------------------------------------------------
485 -- Converting time values to strings.
486
487 calendarTimeToString  :: CalendarTime -> String
488 calendarTimeToString  =  formatCalendarTime defaultTimeLocale "%c"
489
490 formatCalendarTime :: TimeLocale -> String -> CalendarTime -> String
491 formatCalendarTime l fmt (CalendarTime year mon day hour min sec _
492                                        wday yday tzname _ _) =
493         doFmt fmt
494   where doFmt ('%':'-':cs) = doFmt ('%':cs) -- padding not implemented
495         doFmt ('%':'_':cs) = doFmt ('%':cs) -- padding not implemented
496         doFmt ('%':c:cs)   = decode c ++ doFmt cs
497         doFmt (c:cs) = c : doFmt cs
498         doFmt "" = ""
499
500         decode 'A' = fst (wDays l  !! fromEnum wday) -- day of the week, full name
501         decode 'a' = snd (wDays l  !! fromEnum wday) -- day of the week, abbrev.
502         decode 'B' = fst (months l !! fromEnum mon)  -- month, full name
503         decode 'b' = snd (months l !! fromEnum mon)  -- month, abbrev
504         decode 'h' = snd (months l !! fromEnum mon)  -- ditto
505         decode 'C' = show2 (year `quot` 100)         -- century
506         decode 'c' = doFmt (dateTimeFmt l)           -- locale's data and time format.
507         decode 'D' = doFmt "%m/%d/%y"
508         decode 'd' = show2 day                       -- day of the month
509         decode 'e' = show2' day                      -- ditto, padded
510         decode 'H' = show2 hour                      -- hours, 24-hour clock, padded
511         decode 'I' = show2 (to12 hour)               -- hours, 12-hour clock
512         decode 'j' = show3 yday                      -- day of the year
513         decode 'k' = show2' hour                     -- hours, 24-hour clock, no padding
514         decode 'l' = show2' (to12 hour)              -- hours, 12-hour clock, no padding
515         decode 'M' = show2 min                       -- minutes
516         decode 'm' = show2 (fromEnum mon+1)          -- numeric month
517         decode 'n' = "\n"
518         decode 'p' = (if hour < 12 then fst else snd) (amPm l) -- am or pm
519         decode 'R' = doFmt "%H:%M"
520         decode 'r' = doFmt (time12Fmt l)
521         decode 'T' = doFmt "%H:%M:%S"
522         decode 't' = "\t"
523         decode 'S' = show2 sec                       -- seconds
524         decode 's' = show2 sec                       -- number of secs since Epoch. (ToDo.)
525         decode 'U' = show2 ((yday + 7 - fromEnum wday) `div` 7) -- week number, starting on Sunday.
526         decode 'u' = show (let n = fromEnum wday in  -- numeric day of the week (1=Monday, 7=Sunday)
527                            if n == 0 then 7 else n)
528         decode 'V' =                                 -- week number (as per ISO-8601.)
529             let (week, days) =                       -- [yep, I've always wanted to be able to display that too.]
530                    (yday + 7 - if fromEnum wday > 0 then 
531                                fromEnum wday - 1 else 6) `divMod` 7
532             in  show2 (if days >= 4 then
533                           week+1 
534                        else if week == 0 then 53 else week)
535
536         decode 'W' =                                 -- week number, weeks starting on monday
537             show2 ((yday + 7 - if fromEnum wday > 0 then 
538                                fromEnum wday - 1 else 6) `div` 7)
539         decode 'w' = show (fromEnum wday)            -- numeric day of the week, weeks starting on Sunday.
540         decode 'X' = doFmt (timeFmt l)               -- locale's preferred way of printing time.
541         decode 'x' = doFmt (dateFmt l)               -- locale's preferred way of printing dates.
542         decode 'Y' = show year                       -- year, including century.
543         decode 'y' = show2 (year `rem` 100)          -- year, within century.
544         decode 'Z' = tzname                          -- timezone name
545         decode '%' = "%"
546         decode c   = [c]
547
548
549 show2, show2', show3 :: Int -> String
550 show2 x = [intToDigit (x `quot` 10), intToDigit (x `rem` 10)]
551
552 show2' x = if x < 10 then [ ' ', intToDigit x] else show2 x
553
554 show3 x = intToDigit (x `quot` 100) : show2 (x `rem` 100)
555
556 to12 :: Int -> Int
557 to12 h = let h' = h `mod` 12 in if h' == 0 then 12 else h'
558
559 -- Useful extensions for formatting TimeDiffs.
560
561 timeDiffToString :: TimeDiff -> String
562 timeDiffToString = formatTimeDiff defaultTimeLocale "%c"
563
564 formatTimeDiff :: TimeLocale -> String -> TimeDiff -> String
565 formatTimeDiff l fmt td@(TimeDiff year month day hour min sec _)
566  = doFmt fmt
567   where 
568    doFmt ""         = ""
569    doFmt ('%':'-':cs) = doFmt ('%':cs) -- padding not implemented
570    doFmt ('%':'_':cs) = doFmt ('%':cs) -- padding not implemented
571    doFmt ('%':c:cs) = decode c ++ doFmt cs
572    doFmt (c:cs)     = c : doFmt cs
573
574    decode spec =
575     case spec of
576       'B' -> fst (months l !! fromEnum month)
577       'b' -> snd (months l !! fromEnum month)
578       'h' -> snd (months l !! fromEnum month)
579       'c' -> defaultTimeDiffFmt td
580       'C' -> show2 (year `quot` 100)
581       'D' -> doFmt "%m/%d/%y"
582       'd' -> show2 day
583       'e' -> show2' day
584       'H' -> show2 hour
585       'I' -> show2 (to12 hour)
586       'k' -> show2' hour
587       'l' -> show2' (to12 hour)
588       'M' -> show2 min
589       'm' -> show2 (fromEnum month + 1)
590       'n' -> "\n"
591       'p' -> (if hour < 12 then fst else snd) (amPm l)
592       'R' -> doFmt "%H:%M"
593       'r' -> doFmt (time12Fmt l)
594       'T' -> doFmt "%H:%M:%S"
595       't' -> "\t"
596       'S' -> show2 sec
597       's' -> show2 sec -- Implementation-dependent, sez the lib doc..
598       'X' -> doFmt (timeFmt l)
599       'x' -> doFmt (dateFmt l)
600       'Y' -> show year
601       'y' -> show2 (year `rem` 100)
602       '%' -> "%"
603       c   -> [c]
604
605    defaultTimeDiffFmt (TimeDiff year month day hour min sec _) =
606        foldr (\ (v,s) rest -> 
607                   (if v /= 0 
608                      then show v ++ ' ':(addS v s)
609                        ++ if null rest then "" else ", "
610                      else "") ++ rest
611              )
612              ""
613              (zip [year, month, day, hour, min, sec] (intervals l))
614
615    addS v s = if abs v == 1 then fst s else snd s
616
617
618 -- -----------------------------------------------------------------------------
619 -- Foreign time interface (POSIX)
620
621 type CTm = () -- struct tm
622
623 foreign import unsafe localtime :: Ptr CTime -> IO (Ptr CTm)
624 foreign import unsafe gmtime    :: Ptr CTime -> IO (Ptr CTm)
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