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