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