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