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