1 /******************************** -*- C -*- ****************************
2  *
3  * System specific implementation module.
4  *
5  * This module contains implementations of various operating system
6  * specific routines.  This module should encapsulate most (or all)
7  * of these calls so that the rest of the code is portable.
8  *
9  *
10  ***********************************************************************/
11 
12 /***********************************************************************
13  *
14  * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009
15  * Free Software Foundation, Inc.
16  * Written by Steve Byrne.
17  *
18  * This file is part of GNU Smalltalk.
19  *
20  * GNU Smalltalk is free software; you can redistribute it and/or modify it
21  * under the terms of the GNU General Public License as published by the Free
22  * Software Foundation; either version 2, or (at your option) any later
23  * version.
24  *
25  * Linking GNU Smalltalk statically or dynamically with other modules is
26  * making a combined work based on GNU Smalltalk.  Thus, the terms and
27  * conditions of the GNU General Public License cover the whole
28  * combination.
29  *
30  * In addition, as a special exception, the Free Software Foundation
31  * give you permission to combine GNU Smalltalk with free software
32  * programs or libraries that are released under the GNU LGPL and with
33  * independent programs running under the GNU Smalltalk virtual machine.
34  *
35  * You may copy and distribute such a system following the terms of the
36  * GNU GPL for GNU Smalltalk and the licenses of the other code
37  * concerned, provided that you include the source code of that other
38  * code when and as the GNU GPL requires distribution of source code.
39  *
40  * Note that people who make modified versions of GNU Smalltalk are not
41  * obligated to grant this special exception for their modified
42  * versions; it is their choice whether to do so.  The GNU General
43  * Public License gives permission to release a modified version without
44  * this exception; this exception also makes it possible to release a
45  * modified version which carries forward this exception.
46  *
47  * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
48  * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
49  * FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License for
50  * more details.
51  *
52  * You should have received a copy of the GNU General Public License along with
53  * GNU Smalltalk; see the file COPYING.	 If not, write to the Free Software
54  * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
55  *
56  ***********************************************************************/
57 
58 
59 #include "gstpriv.h"
60 
61 #ifdef HAVE_UTIME_H
62 # include <utime.h>
63 #endif
64 
65 #ifdef HAVE_SYS_TIMES_H
66 # include <sys/times.h>
67 #endif
68 
69 #ifdef HAVE_SYS_TIMEB_H
70 #include <sys/timeb.h>
71 #endif
72 
73 #define TM_YEAR_BASE 1900
74 
75 /* Yield A - B, measured in seconds.
76    This function is copied from the GNU C Library.  */
77 static int
tm_diff(struct tm * a,struct tm * b)78 tm_diff (struct tm *a,
79 	 struct tm *b)
80 {
81   /* Compute intervening leap days correctly even if year is negative.
82      Take care to avoid int overflow in leap day calculations, but it's
83      OK to assume that A and B are close to each other.  */
84   int a4 = (a->tm_year >> 2) + (TM_YEAR_BASE >> 2) - !(a->tm_year & 3);
85   int b4 = (b->tm_year >> 2) + (TM_YEAR_BASE >> 2) - !(b->tm_year & 3);
86   int a100 = a4 / 25 - (a4 % 25 < 0);
87   int b100 = b4 / 25 - (b4 % 25 < 0);
88   int a400 = a100 >> 2;
89   int b400 = b100 >> 2;
90   int intervening_leap_days = (a4 - b4) - (a100 - b100) + (a400 - b400);
91   int years = a->tm_year - b->tm_year;
92   int days = (365 * years + intervening_leap_days
93 	      + (a->tm_yday - b->tm_yday));
94   return (60 * (60 * (24 * days + (a->tm_hour - b->tm_hour))
95 		+ (a->tm_min - b->tm_min)) + (a->tm_sec - b->tm_sec));
96 }
97 
98 time_t
_gst_adjust_time_zone(time_t t)99 _gst_adjust_time_zone (time_t t)
100 {
101   struct tm save_tm, *decoded_time;
102   time_t bias;
103 
104 #ifdef LOCALTIME_CACHE
105   tzset ();
106 #endif
107   decoded_time = localtime (&t);
108   save_tm = *decoded_time;
109   decoded_time = gmtime (&t);
110   bias = tm_diff (&save_tm, decoded_time);
111 
112   return (t + bias);
113 }
114 
115 long
_gst_current_time_zone_bias(void)116 _gst_current_time_zone_bias (void)
117 {
118   time_t now;
119   long bias;
120   struct tm save_tm, *decoded_time;
121 
122   time (&now);
123 
124 #ifdef LOCALTIME_CACHE
125   tzset ();
126 #endif
127 
128   decoded_time = localtime (&now);
129   save_tm = *decoded_time;
130   decoded_time = gmtime (&now);
131   bias = tm_diff (&save_tm, decoded_time);
132   return (bias);
133 }
134 
135 time_t
_gst_get_time(void)136 _gst_get_time (void)
137 {
138   time_t now;
139   time (&now);
140 
141   return (_gst_adjust_time_zone (now));
142 }
143 
144 uint64_t
_gst_get_milli_time(void)145 _gst_get_milli_time (void)
146 {
147   return _gst_get_ns_time() / 1000000;
148 }
149 
150