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