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