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