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_PARAM_H
62 # include <sys/param.h>
63 #endif
64 
65 /* Get declaration of _NSGetExecutablePath on MacOS X 10.2 or newer.  */
66 #if HAVE_MACH_O_DYLD_H
67 # define ENUM_DYLD_BOOL
68 # include <mach-o/dyld.h>
69 #endif
70 
71 #ifdef __linux__
72 /* File descriptor of the executable, used for double checking.  */
73 static int executable_fd = -1;
74 #endif
75 
76 /* The path to the executable, derived from argv[0].  */
77 const char *_gst_executable_path = NULL;
78 
79 /* Tests whether a given pathname may belong to the executable.  */
80 static mst_Boolean
maybe_executable(const char * filename)81 maybe_executable (const char *filename)
82 {
83   if (!_gst_file_is_executable (filename))
84     return false;
85 
86 #ifdef __linux__
87   if (executable_fd >= 0)
88     {
89       /* If we already have an executable_fd, check that filename points to
90 	 the same inode.  */
91       struct stat statexe, statfile;
92 
93       if (fstat (executable_fd, &statexe) < 0
94 	  || stat (filename, &statfile) < 0
95 	  || !(statfile.st_dev
96 	       && statfile.st_dev == statexe.st_dev
97 	       && statfile.st_ino == statexe.st_ino))
98 	return false;
99 
100       close (executable_fd);
101       executable_fd = -1;
102     }
103 #endif
104 
105   return true;
106 }
107 
108 /* Determine the full pathname of the current executable, freshly allocated.
109    Return NULL if unknown.  Guaranteed to work on Linux and Win32, Mac OS X.
110    Likely to work on the other Unixes (maybe except BeOS), under most
111    conditions.  */
112 static char *
find_executable(const char * argv0)113 find_executable (const char *argv0)
114 {
115 #ifdef PATH_MAX
116   int path_max = PATH_MAX;
117 #else
118   int path_max = pathconf (name, _PC_PATH_MAX);
119   if (path_max <= 0)
120     path_max = 1024;
121 #endif
122 
123 #if HAVE_MACH_O_DYLD_H && HAVE__NSGETEXECUTABLEPATH
124   char *location = alloca (path_max);
125   uint32_t length = path_max;
126   if (_NSGetExecutablePath (location, &length) == 0 && location[0] == '/')
127     return _gst_get_full_file_name (location);
128 
129 #elif defined __linux__
130   /* The executable is accessible as /proc/<pid>/exe.  In newer Linux
131      versions, also as /proc/self/exe.  Linux >= 2.1 provides a symlink
132      to the true pathname; older Linux versions give only device and ino,
133      enclosed in brackets, which we cannot use here.  */
134   {
135     char buf[6 + 10 + 5];
136     char *location = xmalloc (path_max + 1);
137     ssize_t n;
138 
139     sprintf (buf, "/proc/%d/exe", getpid ());
140     n = readlink (buf, location, path_max);
141     if (n > 0 && location[0] != '[')
142       {
143         location[n] = '\0';
144         return location;
145       }
146     if (executable_fd < 0)
147       executable_fd = open (buf, O_RDONLY, 0);
148   }
149 #endif
150 
151   if (*argv0 == '-')
152     argv0++;
153 
154   /* Guess the executable's full path.  We assume the executable has been
155      called via execlp() or execvp() with properly set up argv[0].
156      exec searches paths without slashes in the directory list given
157      by $PATH.  */
158   if (!strchr (argv0, '/'))
159     {
160       const char *p_next = getenv ("PATH");
161       const char *p;
162 
163       while ((p = p_next) != NULL)
164 	{
165 	  char *concat_name;
166 
167 	  p_next = strchr (p, ':');
168 	  /* An empty PATH element designates the current directory.  */
169 	  if (p_next == p + 1)
170 	    concat_name = xstrdup (argv0);
171 	  else if (!p_next)
172 	    asprintf (&concat_name, "%s/%s", p, argv0);
173 	  else
174 	    asprintf (&concat_name, "%.*s/%s", (int)(p_next++ - p), p, argv0);
175 
176 	  if (maybe_executable (concat_name))
177 	    {
178 	      char *full_path = _gst_get_full_file_name (concat_name);
179 	      free (concat_name);
180 	      return full_path;
181 	    }
182 
183 	  free (concat_name);
184 	}
185       /* Not found in the PATH, assume the current directory.  */
186     }
187 
188   if (maybe_executable (argv0))
189     return _gst_get_full_file_name (argv0);
190 
191   /* No way to find the executable.  */
192 #ifdef __linux__
193   close (executable_fd);
194   executable_fd = -1;
195 #endif
196   return NULL;
197 }
198 
199 void
_gst_set_executable_path(const char * argv0)200 _gst_set_executable_path (const char *argv0)
201 {
202   _gst_executable_path = find_executable (argv0);
203 }
204