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