[project @ 1999-12-20 10:34:27 by simonpj]
[ghc-hetmet.git] / ghc / lib / std / Time.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1995-99
3 %
4 \section[Time]{Haskell 1.4 Time of Day Library}
5
6 The {\em Time} library provides standard functionality for
7 clock times, including timezone information (i.e, the functionality of
8 "time.h",  adapted to the Haskell environment), It follows RFC 1129 in
9 its use of Coordinated Universal Time (UTC).
10
11 \begin{code}
12 {-# OPTIONS -#include "cbits/timezone.h" -#include "cbits/stgio.h"  #-}
13 module Time 
14      (
15         Month(..)
16      ,  Day(..)
17
18      ,  ClockTime(..) -- non-standard, lib. report gives this as abstract
19      ,  getClockTime
20
21      ,  TimeDiff(..)
22      ,  noTimeDiff      -- non-standard (but useful when constructing TimeDiff vals.)
23      ,  diffClockTimes
24      ,  addToClockTime
25
26      ,  timeDiffToString  -- non-standard
27      ,  formatTimeDiff    -- non-standard
28
29      ,  CalendarTime(..)
30      ,  toCalendarTime
31      ,  toUTCTime
32      ,  toClockTime
33      ,  calendarTimeToString
34      ,  formatCalendarTime
35
36      ) where
37
38 #ifdef __HUGS__
39 import PreludeBuiltin
40 #else
41 import PrelGHC          ( RealWorld, (>#), (<#), (==#),
42                           newIntArray#, readIntArray#, 
43                           unsafeFreezeByteArray#,
44                           int2Integer#, negateInt# )
45 import PrelBase         ( Int(..) )
46 import PrelNum          ( Integer(..), fromInt )
47 import PrelIOBase       ( IO(..), unsafePerformIO, stToIO, constructErrorAndFail )
48 import PrelShow         ( showList__ )
49 import PrelPack         ( unpackCString, unpackCStringBA,
50                           new_ps_array, freeze_ps_array
51                         )
52 import PrelByteArr      ( MutableByteArray(..) )
53 import PrelHandle       ( Bytes )
54 import PrelAddr         ( Addr )
55
56 #endif
57
58 import Ix
59 import Char             ( intToDigit )
60 import Locale
61
62 \end{code}
63
64 One way to partition and give name to chunks of a year and a week:
65
66 \begin{code}
67 data Month
68  = January   | February | March    | April
69  | May       | June     | July     | August
70  | September | October  | November | December
71  deriving (Eq, Ord, Enum, Bounded, Ix, Read, Show)
72
73 data Day 
74  = Sunday   | Monday | Tuesday | Wednesday
75  | Thursday | Friday | Saturday
76  deriving (Eq, Ord, Enum, Bounded, Ix, Read, Show)
77
78 \end{code}
79
80 @ClockTime@ is an abstract type, used for the internal clock time.
81 Clock times may be compared, converted to strings, or converted to an
82 external calendar time @CalendarTime@.
83
84 \begin{code}
85 #ifdef __HUGS__
86 -- I believe Int64 is more than big enough.
87 -- In fact, I think one of Int32 or Word32 would do. - ADR
88 data ClockTime = TOD Int64 Int64 deriving (Eq, Ord)
89 #else
90 data ClockTime = TOD Integer            -- Seconds since 00:00:00 on 1 Jan 1970
91                      Integer            -- Picoseconds with the specified second
92                deriving (Eq, Ord)
93                 
94 #endif
95 \end{code}
96
97 When a @ClockTime@ is shown, it is converted to a string of the form
98 @"Mon Nov 28 21:45:41 GMT 1994"@.
99
100 For now, we are restricted to roughly:
101 Fri Dec 13 20:45:52 1901 through Tue Jan 19 03:14:07 2038, because
102 we use the C library routines based on 32 bit integers.
103
104 \begin{code}
105 #ifdef __HUGS__
106 #warning Show ClockTime is bogus
107 instance Show ClockTime
108 #else
109 instance Show ClockTime where
110     showsPrec p (TOD (S# i) _nsec) = 
111       case int2Integer# i of (# s, d #) -> showsPrec p (TOD (J# s d) _nsec)
112     showsPrec _ (TOD (J# s# d#) _nsec) = 
113       showString $ unsafePerformIO $ do
114             let buflen@(I# buflen#) = 50 -- big enough for error message
115             buf <- allocChars buflen 
116             if s# <# (negateInt# 1#) || s# ># 1# then
117                return "ClockTime.show{Time}: out of range"
118              else do
119                rc <- showTime (I# s#) d# buflen buf
120                if rc < 0 then
121                   return "ClockTime.show{Time}: internal error"
122                 else do
123                   ba <- stToIO (freeze_ps_array buf buflen#)
124                   return (unpackCStringBA ba)
125
126     showList = showList__ (showsPrec 0)
127 #endif
128 \end{code}
129
130
131 @CalendarTime@ is a user-readable and manipulable
132 representation of the internal $ClockTime$ type.  The
133 numeric fields have the following ranges.
134
135 \begin{verbatim}
136 Value         Range             Comments
137 -----         -----             --------
138
139 year    -maxInt .. maxInt       [Pre-Gregorian dates are inaccurate]
140 mon           0 .. 11           [Jan = 0, Dec = 11]
141 day           1 .. 31
142 hour          0 .. 23
143 min           0 .. 59
144 sec           0 .. 61           [Allows for two leap seconds]
145 picosec       0 .. (10^12)-1    [This could be over-precise?]
146 wday          0 .. 6            [Sunday = 0, Saturday = 6]
147 yday          0 .. 365          [364 in non-Leap years]
148 tz       -43200 .. 43200        [Variation from UTC in seconds]
149 \end{verbatim}
150
151 The {\em tzname} field is the name of the time zone.  The {\em isdst}
152 field indicates whether Daylight Savings Time would be in effect.
153
154 \begin{code}
155 data CalendarTime 
156  = CalendarTime  {
157      ctYear    :: Int,
158      ctMonth   :: Month,
159      ctDay     :: Int,
160      ctHour    :: Int,
161      ctMin     :: Int,
162      ctSec     :: Int,
163 #ifdef __HUGS__
164      ctPicosec :: Int64,
165 #else
166      ctPicosec :: Integer,
167 #endif
168      ctWDay    :: Day,
169      ctYDay    :: Int,
170      ctTZName  :: String,
171      ctTZ      :: Int,
172      ctIsDST   :: Bool
173  }
174  deriving (Eq,Ord,Read,Show)
175
176 \end{code}
177
178 The @TimeDiff@ type records the difference between two clock times in
179 a user-readable way.
180
181 \begin{code}
182 data TimeDiff
183  = TimeDiff {
184      tdYear    :: Int,
185      tdMonth   :: Int,
186      tdDay     :: Int,
187      tdHour    :: Int,
188      tdMin     :: Int,
189      tdSec     :: Int,
190 #ifdef __HUGS__
191      tdPicosec :: Int64   -- not standard
192 #else
193      tdPicosec :: Integer -- not standard
194 #endif
195    }
196    deriving (Eq,Ord,Read,Show)
197
198 noTimeDiff :: TimeDiff
199 noTimeDiff = TimeDiff 0 0 0 0 0 0 0
200 \end{code}
201
202 @getClockTime@ returns the current time in its internal representation.
203
204 \begin{code}
205 getClockTime :: IO ClockTime
206 getClockTime = do
207     i1 <- malloc1
208     i2 <- malloc1
209     rc <- primGetClockTime i1 i2
210     if rc == 0 
211         then do
212             sec  <- cvtUnsigned i1
213             nsec <- cvtUnsigned i2
214             return (TOD sec (nsec * 1000))
215         else
216             constructErrorAndFail "getClockTime"
217
218 #ifdef __HUGS__
219 malloc1 = primNewByteArray sizeof_int64
220 cvtUnsigned arr = primReadInt64Array arr 0
221 #else
222 malloc1 :: IO (MutableByteArray RealWorld Int)
223 malloc1 = IO $ \ s# ->
224   case newIntArray# 1# s# of 
225    (# s2#, barr# #) -> (# s2#, MutableByteArray bot bot barr# #)
226   where 
227         bot = error "Time.malloc1"
228
229    --  The C routine fills in an unsigned word.  We don't have 
230    --   `unsigned2Integer#,' so we freeze the data bits and use them 
231    --   for an MP_INT structure.  Note that zero is still handled specially,
232    --   although (J# 1# (ptr to 0#)) is probably acceptable to gmp.
233
234 cvtUnsigned :: MutableByteArray RealWorld Int -> IO Integer
235 cvtUnsigned (MutableByteArray _ _ arr#) = IO $ \ s# ->
236   case readIntArray# arr# 0# s# of 
237     (# s2#, r# #) | r# ==# 0#  -> (# s2#, 0 #)
238                   | otherwise  ->
239                      case unsafeFreezeByteArray# arr# s2# of
240                        (# s3#, frozen# #) -> (# s3#, J# 1# frozen# #)
241 #endif
242 \end{code}
243
244 @addToClockTime@ {\em d} {\em t} adds a time difference {\em d} and a
245 clock time {\em t} to yield a new clock time.  The difference {\em d}
246 may be either positive or negative.  @[diffClockTimes@ {\em t1} {\em
247 t2} returns the difference between two clock times {\em t1} and {\em
248 t2} as a @TimeDiff@.
249
250
251 \begin{code}
252 addToClockTime  :: TimeDiff  -> ClockTime -> ClockTime
253 addToClockTime (TimeDiff year mon day hour min sec psec) 
254                (TOD c_sec c_psec) = 
255         let
256           sec_diff = fromInt sec + 60 * fromInt min + 3600 * fromInt hour + 24 * 3600 * fromInt day
257           cal      = toUTCTime (TOD (c_sec + sec_diff) (c_psec + psec))
258
259           new_mon  = fromEnum (ctMonth cal) + r_mon 
260           (month', yr_diff)
261             | new_mon < 0  = (toEnum (12 + new_mon), (-1))
262             | new_mon > 11 = (toEnum (new_mon `mod` 12), 1)
263             | otherwise    = (toEnum new_mon, 0)
264             
265           (r_yr, r_mon) = mon `quotRem` 12
266
267           year' = ctYear cal + year + r_yr + yr_diff
268         in
269         toClockTime cal{ctMonth=month', ctYear=year'}
270
271 diffClockTimes  :: ClockTime -> ClockTime -> TimeDiff
272 diffClockTimes tod_a tod_b =
273   let
274    CalendarTime year_a mon_a day_a hour_a min_a sec_a psec_a _ _ _ _ _ = toUTCTime tod_a
275    CalendarTime year_b mon_b day_b hour_b min_b sec_b psec_b _ _ _ _ _ = toUTCTime tod_b
276   in
277   TimeDiff (year_a - year_b) 
278            (fromEnum mon_a  - fromEnum mon_b) 
279            (day_a  - day_b)
280            (hour_a - hour_b)
281            (min_a  - min_b)
282            (sec_a  - sec_b)
283            (psec_a - psec_b)
284 \end{code}
285
286 @toCalendarTime@ {\em t} converts {\em t} to a local time, modified by
287 the current timezone and daylight savings time settings.  @toUTCTime@
288 {\em t} converts {\em t} into UTC time.  @toClockTime@ {\em l}
289 converts {\em l} into the corresponding internal @ClockTime@.  The
290 {\em wday}, {\em yday}, {\em tzname}, and {\em isdst} fields are
291 ignored.
292
293 \begin{code}
294 #ifdef __HUGS__
295 toCalendarTime :: ClockTime -> IO CalendarTime
296 toCalendarTime (TOD sec psec) = do
297     res    <- allocWords sizeof_int64
298     zoneNm <- allocChars 32
299     prim_SETZONE res zoneNm
300     rc <- prim_toLocalTime sec res
301     if rc /= 0
302      then constructErrorAndFail "Time.toCalendarTime: out of range"
303      else do
304        sec   <-  get_tm_sec   res
305        min   <-  get_tm_min   res
306        hour  <-  get_tm_hour  res
307        mday  <-  get_tm_mday  res
308        mon   <-  get_tm_mon   res
309        year  <-  get_tm_year  res
310        wday  <-  get_tm_wday  res
311        yday  <-  get_tm_yday  res
312        isdst <-  get_tm_isdst res
313        zone  <-  prim_ZONE    res
314        tz    <-  prim_GMTOFF  res
315        tzname <- primUnpackCString zone
316        return (CalendarTime (1900+year) mon mday hour min sec psec 
317                             (toEnum wday) yday tzname tz (isdst /= 0))
318
319 toUTCTime :: ClockTime -> CalendarTime
320 toUTCTime  (TOD sec psec) = unsafePerformIO $ do
321        res    <- allocWords sizeof_int64
322        zoneNm <- allocChars 32
323        prim_SETZONE res zoneNm
324        rc <- prim_toUTCTime sec res
325        if rc /= 0
326         then error "Time.toUTCTime: out of range"
327         else do
328             sec   <- get_tm_sec  res
329             min   <- get_tm_min  res
330             hour  <- get_tm_hour res
331             mday  <- get_tm_mday res
332             mon   <- get_tm_mon  res
333             year  <- get_tm_year res
334             wday  <- get_tm_wday res
335             yday  <- get_tm_yday res
336             return (CalendarTime (1900+year) mon mday hour min sec psec 
337                           (toEnum wday) yday "UTC" 0 False)
338
339 toClockTime :: CalendarTime -> ClockTime
340 toClockTime (CalendarTime year mon mday hour min sec psec wday yday tzname tz isdst) =
341     if psec < 0 || psec > 999999999999 then
342         error "Time.toClockTime: picoseconds out of range"
343     else if tz < -43200 || tz > 43200 then
344         error "Time.toClockTime: timezone offset out of range"
345     else
346         unsafePerformIO ( do
347             res <- allocWords sizeof_int64
348             rc <- toClockSec year (fromEnum mon) mday hour min sec isDst res
349             if rc /= (0::Int)
350              then do
351                tm <- primReadInt64Array res 0
352                return (TOD tm psec)
353              else error "Time.toClockTime: can't perform conversion"
354         )
355     where
356      isDst = if isdst then (1::Int) else 0
357 #else
358 toCalendarTime :: ClockTime -> IO CalendarTime
359 toCalendarTime (TOD (S# i) psec) 
360   = case int2Integer# i of (# s, d #) -> toCalendarTime (TOD (J# s d) psec)
361 toCalendarTime (TOD (J# s# d#) psec) = do
362     res    <- allocWords sizeof_struct_tm
363     zoneNm <- allocChars 32
364     prim_SETZONE res zoneNm
365     rc     <- prim_toLocalTime (I# s#) d# res
366     if rc == 0
367      then constructErrorAndFail "Time.toCalendarTime: out of range"
368      else do
369        sec   <-  get_tm_sec res
370        min   <-  get_tm_min res
371        hour  <-  get_tm_hour res
372        mday  <-  get_tm_mday res
373        mon   <-  get_tm_mon  res
374        year  <-  get_tm_year res
375        wday  <-  get_tm_wday res
376        yday  <-  get_tm_yday res
377        isdst <-  get_tm_isdst res
378        zone  <-  get_ZONE res
379        tz    <-  get_GMTOFF res
380        let tzname = unpackCString zone
381            month  
382             | mon >= 0 && mon <= 11 = toEnum mon
383             | otherwise             = error ("toCalendarTime: illegal month value: " ++ show mon)
384             
385        return (CalendarTime (1900+year) month mday hour min sec psec 
386                             (toEnum wday) yday tzname tz (isdst /= (0::Int)))
387
388 toUTCTime :: ClockTime -> CalendarTime
389 toUTCTime (TOD (S# i) psec) 
390   = case int2Integer# i of (# s, d #) -> toUTCTime (TOD (J# s d) psec)
391 toUTCTime  (TOD (J# s# d#) psec) = unsafePerformIO $ do
392        res    <- allocWords sizeof_struct_tm
393        zoneNm <- allocChars 32
394        prim_SETZONE res zoneNm
395        rc     <-  prim_toUTCTime (I# s#) d# res
396        if rc == 0
397         then error "Time.toUTCTime: out of range"
398         else do
399             sec   <- get_tm_sec res
400             min   <- get_tm_min res
401             hour  <- get_tm_hour res
402             mday  <- get_tm_mday res
403             mon   <- get_tm_mon res
404             year  <- get_tm_year res
405             wday  <- get_tm_wday res
406             yday  <- get_tm_yday res
407             let
408              month  
409               | mon >= 0 && mon <= 11 = toEnum mon
410               | otherwise             = error ("toCalendarTime: illegal month value: " ++ show mon)
411
412             return (CalendarTime (1900+year) month mday hour min sec psec 
413                           (toEnum wday) yday "UTC" 0 False)
414
415 toClockTime :: CalendarTime -> ClockTime
416 toClockTime (CalendarTime year mon mday hour min sec psec _wday _yday _tzname tz isdst) =
417     if psec < 0 || psec > 999999999999 then
418         error "Time.toClockTime: picoseconds out of range"
419     else if tz < -43200 || tz > 43200 then
420         error "Time.toClockTime: timezone offset out of range"
421     else
422         unsafePerformIO ( do
423             res <- malloc1
424             rc  <- toClockSec year (fromEnum mon) mday hour min sec isDst res
425             if rc /= 0
426              then do
427                i <- cvtUnsigned res
428                return (TOD i psec)
429              else error "Time.toClockTime: can't perform conversion"
430         )
431     where
432      isDst = if isdst then (1::Int) else 0
433 #endif
434
435
436 -- (copied from PosixUtil, for now)
437 -- Allocate a mutable array of characters with no indices.
438
439 #ifdef __HUGS__
440 allocChars :: Int -> IO (PrimMutableByteArray RealWorld)
441 allocChars size = primNewByteArray size
442
443 -- Allocate a mutable array of words with no indices
444
445 allocWords :: Int -> IO (PrimMutableByteArray RealWorld)
446 allocWords size = primNewByteArray size
447 #else
448 allocChars :: Int -> IO (MutableByteArray RealWorld Int)
449 allocChars (I# size#) = stToIO (new_ps_array size#)
450
451 -- Allocate a mutable array of words with no indices
452
453 allocWords :: Int -> IO (MutableByteArray RealWorld Int)
454 allocWords (I# size#) = IO $ \ s# ->
455     case newIntArray# size# s# of 
456       (# s2#, barr# #) -> 
457         (# s2#, MutableByteArray bot bot barr# #)
458   where
459     bot = error "Time.allocWords"
460 #endif
461 \end{code}
462
463 \begin{code}
464 calendarTimeToString  :: CalendarTime -> String
465 calendarTimeToString  =  formatCalendarTime defaultTimeLocale "%c"
466
467 formatCalendarTime :: TimeLocale -> String -> CalendarTime -> String
468 formatCalendarTime l fmt (CalendarTime year mon day hour min sec _
469                                        wday yday tzname _ _) =
470         doFmt fmt
471   where doFmt ('%':c:cs) = decode c ++ doFmt cs
472         doFmt (c:cs) = c : doFmt cs
473         doFmt "" = ""
474
475         decode 'A' = fst (wDays l  !! fromEnum wday) -- day of the week, full name
476         decode 'a' = snd (wDays l  !! fromEnum wday) -- day of the week, abbrev.
477         decode 'B' = fst (months l !! fromEnum mon)  -- month, full name
478         decode 'b' = snd (months l !! fromEnum mon)  -- month, abbrev
479         decode 'h' = snd (months l !! fromEnum mon)  -- ditto
480         decode 'C' = show2 (year `quot` 100)         -- century
481         decode 'c' = doFmt (dateTimeFmt l)           -- locale's data and time format.
482         decode 'D' = doFmt "%m/%d/%y"
483         decode 'd' = show2 day                       -- day of the month
484         decode 'e' = show2' day                      -- ditto, padded
485         decode 'H' = show2 hour                      -- hours, 24-hour clock, padded
486         decode 'I' = show2 (to12 hour)               -- hours, 12-hour clock
487         decode 'j' = show3 yday                      -- day of the year
488         decode 'k' = show2' hour                     -- hours, 24-hour clock, no padding
489         decode 'l' = show2' (to12 hour)              -- hours, 12-hour clock, no padding
490         decode 'M' = show2 min                       -- minutes
491         decode 'm' = show2 (fromEnum mon+1)          -- numeric month
492         decode 'n' = "\n"
493         decode 'p' = (if hour < 12 then fst else snd) (amPm l) -- am or pm
494         decode 'R' = doFmt "%H:%M"
495         decode 'r' = doFmt (time12Fmt l)
496         decode 'T' = doFmt "%H:%M:%S"
497         decode 't' = "\t"
498         decode 'S' = show2 sec                       -- seconds
499         decode 's' = show2 sec                       -- number of secs since Epoch. (ToDo.)
500         decode 'U' = show2 ((yday + 7 - fromEnum wday) `div` 7) -- week number, starting on Sunday.
501         decode 'u' = show (let n = fromEnum wday in  -- numeric day of the week (1=Monday, 7=Sunday)
502                            if n == 0 then 7 else n)
503         decode 'V' =                                 -- week number (as per ISO-8601.)
504             let (week, days) =                       -- [yep, I've always wanted to be able to display that too.]
505                    (yday + 7 - if fromEnum wday > 0 then 
506                                fromEnum wday - 1 else 6) `divMod` 7
507             in  show2 (if days >= 4 then
508                           week+1 
509                        else if week == 0 then 53 else week)
510
511         decode 'W' =                                 -- week number, weeks starting on monday
512             show2 ((yday + 7 - if fromEnum wday > 0 then 
513                                fromEnum wday - 1 else 6) `div` 7)
514         decode 'w' = show (fromEnum wday)            -- numeric day of the week, weeks starting on Sunday.
515         decode 'X' = doFmt (timeFmt l)               -- locale's preferred way of printing time.
516         decode 'x' = doFmt (dateFmt l)               -- locale's preferred way of printing dates.
517         decode 'Y' = show year                       -- year, including century.
518         decode 'y' = show2 (year `rem` 100)          -- year, within century.
519         decode 'Z' = tzname                          -- timezone name
520         decode '%' = "%"
521         decode c   = [c]
522
523
524 show2, show2', show3 :: Int -> String
525 show2 x = [intToDigit (x `quot` 10), intToDigit (x `rem` 10)]
526
527 show2' x = if x < 10 then [ ' ', intToDigit x] else show2 x
528
529 show3 x = intToDigit (x `quot` 100) : show2 (x `rem` 100)
530
531 to12 :: Int -> Int
532 to12 h = let h' = h `mod` 12 in if h' == 0 then 12 else h'
533 \end{code}
534
535 Useful extensions for formatting TimeDiffs.
536
537 \begin{code}
538 timeDiffToString :: TimeDiff -> String
539 timeDiffToString = formatTimeDiff defaultTimeLocale "%c"
540
541 formatTimeDiff :: TimeLocale -> String -> TimeDiff -> String
542 formatTimeDiff l fmt (TimeDiff year month day hour min sec _)
543  = doFmt fmt
544   where 
545    doFmt ""         = ""
546    doFmt ('%':c:cs) = decode c ++ doFmt cs
547    doFmt (c:cs)     = c : doFmt cs
548
549    decode spec =
550     case spec of
551       'B' -> fst (months l !! fromEnum month)
552       'b' -> snd (months l !! fromEnum month)
553       'h' -> snd (months l !! fromEnum month)
554       'C' -> show2 (year `quot` 100)
555       'D' -> doFmt "%m/%d/%y"
556       'd' -> show2 day
557       'e' -> show2' day
558       'H' -> show2 hour
559       'I' -> show2 (to12 hour)
560       'k' -> show2' hour
561       'l' -> show2' (to12 hour)
562       'M' -> show2 min
563       'm' -> show2 (fromEnum month + 1)
564       'n' -> "\n"
565       'p' -> (if hour < 12 then fst else snd) (amPm l)
566       'R' -> doFmt "%H:%M"
567       'r' -> doFmt (time12Fmt l)
568       'T' -> doFmt "%H:%M:%S"
569       't' -> "\t"
570       'S' -> show2 sec
571       's' -> show2 sec -- Implementation-dependent, sez the lib doc..
572       'X' -> doFmt (timeFmt l)
573       'x' -> doFmt (dateFmt l)
574       'Y' -> show year
575       'y' -> show2 (year `rem` 100)
576       '%' -> "%"
577       c   -> [c]
578
579 \end{code}
580
581 \begin{code}
582 foreign import "libHS_cbits" "get_tm_sec"   unsafe get_tm_sec   :: MBytes -> IO Int
583 foreign import "libHS_cbits" "get_tm_min"   unsafe get_tm_min   :: MBytes -> IO Int
584 foreign import "libHS_cbits" "get_tm_hour"  unsafe get_tm_hour  :: MBytes -> IO Int
585 foreign import "libHS_cbits" "get_tm_mday"  unsafe get_tm_mday  :: MBytes -> IO Int
586 foreign import "libHS_cbits" "get_tm_mon"   unsafe get_tm_mon   :: MBytes -> IO Int
587 foreign import "libHS_cbits" "get_tm_year"  unsafe get_tm_year  :: MBytes -> IO Int
588 foreign import "libHS_cbits" "get_tm_wday"  unsafe get_tm_wday  :: MBytes -> IO Int
589 foreign import "libHS_cbits" "get_tm_yday"  unsafe get_tm_yday  :: MBytes -> IO Int
590 foreign import "libHS_cbits" "get_tm_isdst" unsafe get_tm_isdst :: MBytes -> IO Int
591                            
592 foreign import "libHS_cbits" "prim_ZONE"    prim_ZONE    :: Bytes -> IO Addr
593 foreign import "libHS_cbits" "prim_GMTOFF"  prim_GMTOFF  :: Bytes -> IO Int
594                            
595 foreign import "libHS_cbits" "sizeof_struct_tm" sizeof_struct_tm :: Int
596
597 #ifdef __HUGS__
598 -- believed to be at least 1 bit (the sign bit!) bigger than sizeof_time_t
599 sizeof_int64 :: Int
600 sizeof_int64 = 8
601 #endif
602
603 type MBytes = MutableByteArray RealWorld Int
604
605 foreign import "libHS_cbits" "sizeof_time_t"    sizeof_time_t    :: Int
606
607 foreign import "libHS_cbits" "prim_SETZONE" unsafe prim_SETZONE :: MBytes -> MBytes -> IO ()
608 #ifdef __HUGS__
609 foreign import "libHS_cbits" "prim_toLocalTime"  unsafe prim_toLocalTime :: Int64 -> MBytes -> IO Int
610 foreign import "libHS_cbits" "prim_toUTCTime"    unsafe prim_toUTCTime   :: Int64 -> MBytes -> IO Int
611 #else
612 foreign import "libHS_cbits" "toLocalTime"  unsafe prim_toLocalTime :: Int -> Bytes -> MBytes -> IO Int
613 foreign import "libHS_cbits" "toUTCTime"    unsafe prim_toUTCTime   :: Int -> Bytes -> MBytes -> IO Int
614 #endif
615
616 foreign import "libHS_cbits" "get_ZONE"  unsafe get_ZONE   :: MBytes -> IO Addr
617 foreign import "libHS_cbits" "GMTOFF"    unsafe get_GMTOFF :: MBytes -> IO Int
618
619
620 foreign import "libHS_cbits" "toClockSec" unsafe 
621             toClockSec   :: Int -> Int -> Int -> Int -> Int 
622                          -> Int -> Int -> MBytes -> IO Int
623
624 foreign import "libHS_cbits" "getClockTime"  unsafe 
625            primGetClockTime :: MutableByteArray RealWorld Int
626                             -> MutableByteArray RealWorld Int
627                             -> IO Int
628 foreign import "libHS_cbits" "showTime" unsafe 
629            showTime :: Int
630                     -> Bytes
631                     -> Int
632                     -> MBytes
633                     -> IO Int
634 \end{code}