1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 2003-2016. All Rights Reserved.
5  *
6  * Licensed under the Apache License, Version 2.0 (the "License");
7  * you may not use this file except in compliance with the License.
8  * You may obtain a copy of the License at
9  *
10  *     http://www.apache.org/licenses/LICENSE-2.0
11  *
12  * Unless required by applicable law or agreed to in writing, software
13  * distributed under the License is distributed on an "AS IS" BASIS,
14  * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15  * See the License for the specific language governing permissions and
16  * limitations under the License.
17  *
18  * %CopyrightEnd%
19  */
20 
21 #include <windows.h>
22 #include <stdio.h>
23 #include <stdlib.h>
24 #include "init_file.h"
25 
26 typedef int ErlexecFunction(int, char **, HANDLE, int);
27 
28 #define INI_FILENAME L"erl.ini"
29 #define INI_SECTION "erlang"
30 #define ERLEXEC_BASENAME L"erlexec.dll"
31 
32 static void get_parameters(void);
33 static void error(char* format, ...);
34 
35 static wchar_t *erlexec_name;
36 static wchar_t *erlexec_dir;
37 
38 #ifdef WIN32_WERL
39 #define WERL 1
wWinMain(HINSTANCE hInstance,HINSTANCE hPrevInstance,PWSTR szCmdLine,int iCmdShow)40 int WINAPI wWinMain(HINSTANCE hInstance, HINSTANCE hPrevInstance,
41 		    PWSTR szCmdLine, int iCmdShow)
42 {
43     int argc = __argc;
44     wchar_t **argv = __wargv;
45 #else
46 #define WERL 0
47 int wmain(int argc, wchar_t **argv)
48 {
49 #endif
50   HANDLE erlexec_handle; /* Instance */
51   ErlexecFunction *win_erlexec;
52   wchar_t *path = malloc(100*sizeof(wchar_t));
53   wchar_t *wslpath = malloc(100*sizeof(wchar_t));
54   wchar_t *npath;
55   int pathlen, wslpathlen;
56   char ** utf8argv;
57   int i, len;
58 
59   get_parameters();
60 
61   if ((pathlen = GetEnvironmentVariableW(L"PATH",path,100)) == 0) {
62     error("No PATH variable (!)");
63   } else if (pathlen > 100) {
64     path = realloc(path,pathlen*sizeof(wchar_t));
65     GetEnvironmentVariableW(L"PATH",path,pathlen);
66   }
67 
68   if ((wslpathlen = GetEnvironmentVariableW(L"WSLENV",wslpath,100)) > 0) {
69       if ((wslpathlen = GetEnvironmentVariableW(L"WSLPATH",wslpath,100)) > 0) {
70           if (wslpathlen > 100) {
71               wslpath = realloc(wslpath,wslpathlen*sizeof(wchar_t));
72               GetEnvironmentVariableW(L"WSLPATH",wslpath,wslpathlen);
73           }
74           wslpathlen = wcslen(wslpath);
75       }
76   }
77   /* Add size for path delimiters and eos */
78   pathlen = (wcslen(path) + wslpathlen + wcslen(erlexec_dir) + 3);
79   npath = (wchar_t *) malloc(pathlen*sizeof(wchar_t));
80   if(wslpathlen > 0) {
81       swprintf(npath,pathlen,L"%s;%s;%s",erlexec_dir,path,wslpath);
82   } else {
83       swprintf(npath,pathlen,L"%s;%s",erlexec_dir,path);
84   }
85   SetEnvironmentVariableW(L"PATH",npath);
86 
87   if ((erlexec_handle = LoadLibraryW(erlexec_name)) == NULL) {
88     error("Could not load module %S.",erlexec_name);
89   }
90 
91   if ((win_erlexec = (ErlexecFunction *)
92        GetProcAddress(erlexec_handle,"win_erlexec")) == NULL) {
93     error("Could not find entry point \"win_erlexec\" in %S.", erlexec_name);
94   }
95 
96   /* Convert argv to utf8 */
97   utf8argv = malloc((argc+1) * sizeof(char*));
98   for (i=0; i<argc; i++) {
99       len = WideCharToMultiByte(CP_UTF8, 0, argv[i], -1, NULL, 0, NULL, NULL);
100       utf8argv[i] = malloc(len*sizeof(char));
101       WideCharToMultiByte(CP_UTF8, 0, argv[i], -1, utf8argv[i], len, NULL, NULL);
102   }
103   utf8argv[argc] = NULL;
104 
105 #ifdef HARDDEBUG
106 	{
107 	    wchar_t tempbuf[2048] = L"";
108 	    wchar_t *sbuf;
109 	    int i;
110 	    sbuf=tempbuf;
111 	    sbuf += swprintf(sbuf, 2048, L"utf16: %d\n", argc);
112 	    for (i = 0; i < argc; ++i) {
113 		sbuf += swprintf(sbuf, 2048, L"|%s|", argv[i]);
114 	    };
115 	    sbuf += swprintf(sbuf, 2048, L"\nutf8: \n");
116 	    for (i = 0; i < argc; ++i) {
117 		sbuf += swprintf(sbuf, 2048, L"|%S|", utf8argv[i]);
118 	    };
119 	    MessageBoxW(NULL, tempbuf, L"erl_exec args", MB_OK|MB_ICONERROR);
120 	}
121 #endif
122 
123   return (*win_erlexec)(argc,utf8argv,erlexec_handle,WERL);
124 
125 }
126 
127 
128 static wchar_t *replace_filename(wchar_t *path, wchar_t *new_base)
129 {
130     int plen = wcslen(path);
131     wchar_t *res = malloc((plen+wcslen(new_base)+1)*sizeof(wchar_t));
132     wchar_t *p;
133 
134     wcscpy(res,path);
135     for (p = res+plen-1 ;p >= res && *p != L'\\'; --p)
136         ;
137     *(p+1) =L'\0';
138     wcscat(res,new_base);
139     return res;
140 }
141 
142 static char *do_lookup_in_section(InitSection *inis, char *name,
143 				  char *section, wchar_t *filename)
144 {
145     char *p = lookup_init_entry(inis, name);
146 
147     if (p == NULL) {
148 	error("Could not find key %s in section %s of file %S",
149 	      name,section,filename);
150     }
151     return p;
152 }
153 
154 static void copy_latest_vsn(wchar_t *latest_vsn, wchar_t *next_vsn)
155 {
156     /* Copy */
157     wchar_t *lp;
158     wchar_t *np;
159     /* Find vsn */
160     for (lp = next_vsn+wcslen(next_vsn)-1 ;lp >= next_vsn && *lp != L'\\'; --lp)
161         ;
162     /* lp =+ length("erts-"); */
163     for (np = next_vsn+wcslen(next_vsn)-1 ;np >= next_vsn && *np != L'\\'; --np)
164         ;
165     /* np =+ length("erts-"); */
166 
167     for (; lp && np; ++lp, ++np) {
168 	if (*lp == *np) {
169 	    continue;
170 	}
171 	if (*np == L'.' || *np == L'\0' || *np <= *lp) {
172 	/* */
173 	    return;
174 	}
175 	if (*lp == L'.' || *lp == L'\0') {
176 	    wcscpy(latest_vsn, next_vsn);
177 	    return;
178 	}
179     }
180     return;
181 }
182 
183 static wchar_t *find_erlexec_dir2(wchar_t *install_dir)
184 {
185     /* List install dir and look for latest erts-vsn */
186 
187     HANDLE dir_handle;	        /* Handle to directory. */
188     wchar_t wildcard[MAX_PATH];	/* Wildcard to search for. */
189     WIN32_FIND_DATAW find_data;  /* Data found by FindFirstFile() or FindNext(). */
190     wchar_t latest_vsn[MAX_PATH];
191 
192     /* Setup wildcard */
193     int length = wcslen(install_dir);
194     wchar_t *p;
195 
196     if (length+3 >= MAX_PATH) {
197 	error("Cannot find erlexec.exe");
198     }
199 
200     wcscpy(wildcard, install_dir);
201     p = wildcard+length-1;
202     if (*p != L'/' && *p != L'\\')
203 	*++p = L'\\';
204     wcscpy(++p, L"erts-*");
205 
206     /* Find first dir */
207     dir_handle = FindFirstFileW(wildcard, &find_data);
208     if (dir_handle == INVALID_HANDLE_VALUE) {
209 	/* No erts-vsn found*/
210 	return NULL;
211     }
212     wcscpy(latest_vsn, find_data.cFileName);
213 
214     /* Find the rest */
215     while(FindNextFileW(dir_handle, &find_data)) {
216 	copy_latest_vsn(latest_vsn, find_data.cFileName);
217     }
218 
219     FindClose(dir_handle);
220 
221     p = (wchar_t *) malloc((wcslen(install_dir)+1+wcslen(latest_vsn)+4+1)*sizeof(wchar_t));
222 
223     wcscpy(p,install_dir);
224     wcscat(p,L"\\");
225     wcscat(p,latest_vsn);
226     wcscat(p,L"\\bin");
227     return p;
228 }
229 
230 static wchar_t *find_erlexec_dir(wchar_t *erlpath)
231 {
232     /* Assume that the path to erl is absolute and
233      * that it is not a symbolic link*/
234 
235     wchar_t *dir =_wcsdup(erlpath);
236     wchar_t *p;
237     wchar_t *p2;
238 
239     /* Chop of base name*/
240     for (p = dir+wcslen(dir)-1 ;p >= dir && *p != L'\\'; --p)
241         ;
242     *p =L'\0';
243     p--;
244 
245     /* Check if dir path is like ...\install_dir\erts-vsn\bin */
246     for (;p >= dir && *p != L'\\'; --p)
247         ;
248     p--;
249     for (p2 = p;p2 >= dir && *p2 != '\\'; --p2)
250         ;
251     p2++;
252     if (wcsncmp(p2, L"erts-", wcslen(L"erts-")) == 0) {
253 	p = _wcsdup(dir);
254 	free(dir);
255 	return p;
256     }
257 
258     /* Assume that dir path is like ...\install_dir\bin */
259     *++p =L'\0'; /* chop off bin dir */
260 
261     p = find_erlexec_dir2(dir);
262     free(dir);
263     if (p == NULL) {
264 	error("Cannot find erlexec.exe");
265     } else {
266 	return p;
267     }
268 }
269 
270 static void get_parameters(void)
271 {
272     wchar_t buffer[MAX_PATH];
273     wchar_t *ini_filename;
274     HANDLE module = GetModuleHandle(NULL);
275     InitFile *inif;
276     InitSection *inis;
277     char *utf8dir;
278     int len;
279 
280 
281     if (module == NULL) {
282         error("Cannot GetModuleHandle()");
283     }
284 
285     if (GetModuleFileNameW(module,buffer,MAX_PATH) == 0) {
286         error("Could not GetModuleFileName");
287     }
288 
289     ini_filename = replace_filename(buffer,INI_FILENAME);
290 
291     if ((inif = load_init_file(ini_filename)) == NULL) {
292 	erlexec_dir = find_erlexec_dir(ini_filename);
293 	SetEnvironmentVariableW(L"ERLEXEC_DIR", erlexec_dir);
294     } else {
295 
296       if ((inis = lookup_init_section(inif,INI_SECTION)) == NULL) {
297 	error("Could not find section %s in init file %S",
298 	      INI_SECTION, ini_filename);
299       }
300 
301       utf8dir = do_lookup_in_section(inis, "Bindir", INI_SECTION, ini_filename);
302       len = MultiByteToWideChar(CP_UTF8, 0, utf8dir, -1, NULL, 0);
303       erlexec_dir = malloc(len*sizeof(wchar_t));
304       MultiByteToWideChar(CP_UTF8, 0, utf8dir, -1, erlexec_dir, len);
305       if(len == 0) {
306 	  error("Bindir is not a valid utf8 '%s' in init file %S",
307 		utf8dir, ini_filename);
308       }
309       free_init_file(inif);
310     }
311 
312     erlexec_name = malloc((wcslen(erlexec_dir) + wcslen(ERLEXEC_BASENAME) + 2)*sizeof(wchar_t));
313     wcscpy(erlexec_name,erlexec_dir);
314     wcscat(erlexec_name, L"\\" ERLEXEC_BASENAME);
315 
316     free(ini_filename);
317 }
318 
319 
320 static void error(char* format, ...)
321 {
322     char sbuf[2048];
323     va_list ap;
324 
325     va_start(ap, format);
326     vsprintf(sbuf, format, ap);
327     va_end(ap);
328 
329 #ifndef WIN32_WERL
330 	fprintf(stderr, "%s\n", sbuf);
331 #else
332 	MessageBox(NULL, sbuf, "Werl", MB_OK|MB_ICONERROR);
333 #endif
334     exit(1);
335 }
336 
337