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_SYS_WAIT_H
62 #include <sys/wait.h>
63 #endif
64 
65 #ifndef O_BINARY
66 #define O_BINARY     0
67 #endif
68 
69 #ifdef HAVE_SPAWNL
70 #include <process.h>
71 #ifndef P_WAIT
72 #define P_WAIT       0
73 #define P_NOWAIT     1
74 #define P_OVERLAY    2
75 #define P_NOWAITO    3
76 #define P_DETACH     4
77 #endif /* !P_WAIT */
78 #endif /* HAVE_SPAWNL */
79 
80 #if defined FASYNC && !defined O_ASYNC
81 #define O_ASYNC FASYNC
82 #endif
83 
84 #ifndef PATH_MAX
85 #define PATH_MAX  1024		/* max length of a file and path */
86 #endif
87 
88 #ifndef MAXSYMLINKS
89 #define MAXSYMLINKS 5
90 #endif
91 
92 char *
_gst_get_full_file_name(const char * name)93 _gst_get_full_file_name (const char *name)
94 {
95   char *rpath, *dest;
96   const char *start, *end, *rpath_limit;
97   long int path_max;
98 #ifdef HAVE_READLINK
99   int num_links = 0;
100   char *extra_buf = NULL;
101 #endif
102 
103 #ifdef PATH_MAX
104   path_max = PATH_MAX;
105 #else
106   path_max = pathconf (name, _PC_PATH_MAX);
107   if (path_max <= 0)
108     path_max = 1024;
109 #endif
110 
111   rpath = malloc (path_max);
112   if (rpath == NULL)
113     return NULL;
114   rpath_limit = rpath + path_max;
115 
116   if (name[0] != '/')
117     {
118       if (!getcwd (rpath, path_max))
119 	goto error;
120 
121       dest = strchr (rpath, '\0');
122     }
123   else
124     {
125       rpath[0] = '/';
126       dest = rpath + 1;
127     }
128 
129   for (start = end = name; *start; start = end)
130     {
131       struct stat st;
132 
133       /* Skip sequence of multiple path-separators.  */
134       while (*start == '/')
135 	++start;
136 
137       /* Find end of path component.  */
138       for (end = start; *end && *end != '/'; ++end)
139 	/* Nothing.  */;
140 
141       if (end - start == 0)
142 	break;
143       else if (end - start == 1 && start[0] == '.')
144 	/* nothing */;
145       else if (end - start == 2 && start[0] == '.' && start[1] == '.')
146 	{
147 	  /* Back up to previous component, ignore if at root already.  */
148 	  if (dest > rpath + 1)
149 	    while ((--dest)[-1] != '/');
150 	}
151       else
152 	{
153 	  size_t new_size;
154 
155 	  if (dest[-1] != '/')
156 	    *dest++ = '/';
157 
158 	  if (dest + (end - start) >= rpath_limit)
159 	    {
160 	      ptrdiff_t dest_offset = dest - rpath;
161 	      char *new_rpath;
162 
163 	      new_size = rpath_limit - rpath;
164 	      if (end - start + 1 > path_max)
165 		new_size += end - start + 1;
166 	      else
167 		new_size += path_max;
168 	      new_rpath = (char *) realloc (rpath, new_size);
169 	      if (new_rpath == NULL)
170 		goto error;
171 	      rpath = new_rpath;
172 	      rpath_limit = rpath + new_size;
173 
174 	      dest = rpath + dest_offset;
175 	    }
176 
177 	  memcpy (dest, start, end - start);
178 	  dest += end - start;
179 	  *dest = '\0';
180 
181 	  if (lstat (rpath, &st) < 0)
182 	    goto error;
183 
184 #if HAVE_READLINK
185 	  if (S_ISLNK (st.st_mode))
186 	    {
187 	      char *buf;
188 	      size_t len;
189 	      int n;
190 
191 	      if (++num_links > MAXSYMLINKS)
192 		{
193 		  errno = ELOOP;
194 		  goto error;
195 		}
196 
197 	      buf = alloca (path_max);
198 	      n = readlink (rpath, buf, path_max - 1);
199 	      if (n < 0)
200 		{
201 		  int saved_errno = errno;
202 		  errno = saved_errno;
203 		  goto error;
204 		}
205 	      buf[n] = '\0';
206 	      if (!extra_buf)
207 		extra_buf = alloca (path_max);
208 
209 	      len = strlen (end);
210 	      if ((long int) (n + len) >= path_max)
211 		{
212 		  errno = ENAMETOOLONG;
213 		  goto error;
214 		}
215 
216 	      /* Careful here, end may be a pointer into extra_buf... */
217 	      memmove (&extra_buf[n], end, len + 1);
218 	      name = end = memcpy (extra_buf, buf, n);
219 
220 	      if (buf[0] == '/')
221 		dest = rpath + 1;	/* It's an absolute symlink */
222 	      else
223 		/* Back up to previous component, ignore if at root already: */
224 		if (dest > rpath + 1)
225 		  while ((--dest)[-1] != '/');
226 	    }
227 #endif
228 	}
229     }
230   if (dest > rpath + 1 && dest[-1] == '/')
231     --dest;
232   *dest = '\0';
233   return rpath;
234 
235 error:
236   {
237     int saved_errno = errno;
238     free (rpath);
239     errno = saved_errno;
240   }
241   return NULL;
242 }
243 
244 
245 static void
sigchld_handler(int signum)246 sigchld_handler (int signum)
247 {
248 #ifdef HAVE_WAITPID
249   int pid, status, serrno;
250   serrno = errno;
251   do
252     pid = waitpid (-1, &status, WNOHANG);
253   while (pid > 0);
254   errno = serrno;
255 #endif
256 
257   /* Pass it to the SIGIO handler, it might reveal a POLLHUP event.  */
258   raise (SIGIO);
259   _gst_set_signal_handler (SIGCHLD, sigchld_handler);
260 }
261 
262 /* Use sockets or pipes.  */
263 int
_gst_open_pipe(const char * command,const char * mode)264 _gst_open_pipe (const char *command,
265 		const char *mode)
266 {
267   int fd[2];
268   int our_fd, child_fd;
269   int access;
270   int result;
271 
272   _gst_set_signal_handler (SIGCHLD, sigchld_handler);
273   access = strchr (mode, '+') ? O_RDWR :
274     (mode[0] == 'r' ? O_RDONLY : O_WRONLY);
275 
276   if (access == O_RDWR)
277     {
278       result = socketpair (AF_UNIX, SOCK_STREAM, 0, fd);
279       our_fd = fd[1];
280       child_fd = fd[0];
281     }
282   else
283     {
284       result = pipe (fd);
285       our_fd = access == O_RDONLY ? fd[0] : fd[1];
286       child_fd = access == O_RDONLY ? fd[1] : fd[0];
287     }
288 
289   if (result == -1)
290     return -1;
291 
292   _gst_set_signal_handler (SIGPIPE, SIG_DFL);
293   _gst_set_signal_handler (SIGFPE, SIG_DFL);
294 
295 #ifdef HAVE_SPAWNL
296   {
297     /* Prepare file descriptors, saving the old ones so that we can keep
298        them.  */
299     int save_stdin = -1, save_stdout = -1, save_stderr = -1;
300     if (access != O_WRONLY)
301       {
302         save_stdout = dup (1);
303         save_stderr = dup (2);
304         dup2 (child_fd, 1);
305         dup2 (child_fd, 2);
306       }
307     if (access != O_RDONLY)
308       {
309         save_stdin = dup (0);
310         dup2 (child_fd, 0);
311       }
312 
313     result = spawnl (P_NOWAIT, "/bin/sh", "/bin/sh", "-c", command, NULL);
314 
315     if (save_stdin != -1)
316       {
317         dup2 (save_stdin, 0);
318         close (save_stdin);
319       }
320 
321     if (save_stdout != -1)
322       {
323         dup2 (save_stdout, 1);
324         close (save_stdout);
325       }
326 
327     if (save_stderr != -1)
328       {
329         dup2 (save_stderr, 2);
330         close (save_stderr);
331       }
332   }
333 #else /* !HAVE_SPAWNL */
334   /* We suppose it is a system that has fork.  */
335   result = fork ();
336   if (result == 0)
337     {
338       /* Child process */
339       close (our_fd);
340       if (access != O_WRONLY)
341 	dup2 (child_fd, 1);
342       if (access != O_RDONLY)
343         dup2 (child_fd, 0);
344 
345       _exit (system (command) >= 0);
346       /*NOTREACHED*/
347     }
348 
349 #endif /* !HAVE_SPAWNL */
350 
351   close (child_fd);
352   _gst_set_signal_handler (SIGPIPE, SIG_IGN);
353   _gst_set_signal_handler (SIGFPE, SIG_IGN);
354 
355   if (result == -1)
356     {
357       int save_errno;
358       save_errno = errno;
359       close (our_fd);
360       errno = save_errno;
361       return (-1);
362     }
363   else
364     return (our_fd);
365 }
366 
367