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