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