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