Skip to content

Commit 78c656f

Browse files
dra27rjbou
authored andcommitted
Overhaul parent process detection
Read the entire process ancestry in a single snapshot and then return the full image names to opam. This makes the shell analysis slightly more efficient. The full image paths rather than just the executable names pave the way for opam to be able to initialise PowerShell properly.
1 parent 47e64f2 commit 78c656f

File tree

6 files changed

+121
-113
lines changed

6 files changed

+121
-113
lines changed

master_changes.md

+1
Original file line numberDiff line numberDiff line change
@@ -405,6 +405,7 @@ users)
405405
* [BUG] Fix case insensitive variable handling [#5356 @dra27]
406406
* Use OCaml code to copy/move/remove directories instead of unix commands [#4823 @kit-ty-kate - fix #1073]
407407
* Update Windows-on-Windows detection for ARM [#5541 @dra27]
408+
* Overhaul parent process detection [#5541 @dra27]
408409

409410
## Test
410411
* Update crowbar with compare functions [#4918 @rjbou]

src/core/opamStd.ml

+6-30
Original file line numberDiff line numberDiff line change
@@ -1060,36 +1060,13 @@ module OpamSys = struct
10601060
else
10611061
fun x -> x
10621062

1063-
let windows_max_ancestor_depth = 5
1064-
1065-
(** [windows_ancestor_process_names] finds the names of the parent of the
1066-
current process and all of its ancestors up to [max_ancestor_depth]
1067-
in length.
1068-
1069-
The immediate parent of the current process will be first in the list.
1070-
*)
1071-
let windows_ancestor_process_names () =
1072-
let rec helper pid depth =
1073-
if depth > windows_max_ancestor_depth then []
1074-
else
1075-
try
1076-
OpamStubs.(getProcessName pid ::
1077-
helper
1078-
(getParentProcessID pid)
1079-
(depth + 1))
1080-
with Failure _ -> []
1081-
in
1082-
lazy (
1083-
try
1084-
let parent = OpamStubs.getCurrentProcessID () in
1085-
helper (OpamStubs.getParentProcessID parent) 0
1086-
with Failure _ -> []
1087-
)
1063+
let windows_process_ancestry = Lazy.from_fun OpamStubs.getProcessAncestry
10881064

10891065
type shell_choice = Accept of shell
10901066

10911067
let windows_get_shell =
1092-
let categorize_process = function
1068+
let categorize_process (_, image) =
1069+
match String.lowercase_ascii (Filename.basename image) with
10931070
| "powershell.exe" | "powershell_ise.exe" ->
10941071
Some (Accept (SH_pwsh Powershell))
10951072
| "pwsh.exe" -> Some (Accept (SH_pwsh Powershell_pwsh))
@@ -1101,9 +1078,8 @@ module OpamSys = struct
11011078
(shell_of_string (Filename.chop_suffix name ".exe"))
11021079
in
11031080
lazy (
1104-
let ancestors = Lazy.force (windows_ancestor_process_names ()) in
1105-
match (List.map String.lowercase_ascii ancestors |>
1106-
OpamList.filter_map categorize_process) with
1081+
let lazy ancestors = windows_process_ancestry in
1082+
match OpamList.filter_map categorize_process ancestors with
11071083
| [] -> None
11081084
| Accept most_relevant_shell :: _ -> Some most_relevant_shell
11091085
)
@@ -1337,7 +1313,7 @@ module Win32 = struct
13371313
end
13381314

13391315
let (set_parent_pid, parent_putenv) =
1340-
let ppid = ref (lazy (OpamStubs.(getCurrentProcessID () |> getParentProcessID))) in
1316+
let ppid = ref (OpamCompat.Lazy.map (function (_::(pid, _)::_) -> pid | _ -> 0l) OpamSys.windows_process_ancestry) in
13411317
let parent_putenv = lazy (
13421318
let {contents = lazy ppid} = ppid in
13431319
let our_architecture = OpamStubs.getProcessArchitecture None in

src/core/opamStubs.dummy.ml

+1-2
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,6 @@ let getProcessArchitecture = that's_a_no_no
3333
let process_putenv _ = that's_a_no_no
3434
let shGetFolderPath _ = that's_a_no_no
3535
let sendMessageTimeout _ _ _ _ _ = that's_a_no_no
36-
let getParentProcessID = that's_a_no_no
37-
let getProcessName = that's_a_no_no
36+
let getProcessAncestry = that's_a_no_no
3837
let getConsoleAlias _ = that's_a_no_no
3938
let win_create_process _ _ _ _ _ = that's_a_no_no

src/core/opamStubs.mli

+5-10
Original file line numberDiff line numberDiff line change
@@ -117,16 +117,11 @@ val sendMessageTimeout :
117117
return value from SendMessageTimeout, [snd] depends on both the message and
118118
[fst]. See https://msdn.microsoft.com/en-us/library/windows/desktop/ms644952.aspx *)
119119

120-
val getParentProcessID : int32 -> int32
121-
(** Windows only. [getParentProcessID pid] returns the process ID of the parent
122-
of [pid].
123-
124-
@raise Failure If walking the process tree fails to find the process. *)
125-
126-
val getProcessName : int32 -> string
127-
(** Windows only. [getProcessName pid] returns the executable name of [pid].
128-
129-
@raise Failure If the process does not exist. *)
120+
val getProcessAncestry : unit -> (int32 * string) list
121+
(** Windows only. Returns the pid and full path to the image for each entry in
122+
the ancestry list for this process, starting with the process itself. If an
123+
image name can't be determined, then [""] is returned; on failure, returns
124+
[[]]. *)
130125

131126
val getConsoleAlias : string -> string -> string
132127
(** Windows only. [getConsoleAlias alias exeName] retrieves the value for a

src/stubs/win32/opamWin32Stubs.ml

+1-2
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,5 @@ external getProcessArchitecture : int32 option -> 'a = "OPAMW_GetProcessArchitec
3232
external process_putenv : int32 -> string -> string -> bool = "OPAMW_process_putenv"
3333
external shGetFolderPath : int -> 'a -> string = "OPAMW_SHGetFolderPath"
3434
external sendMessageTimeout : nativeint -> int -> int -> 'a -> 'b -> 'c -> int * 'd = "OPAMW_SendMessageTimeout_byte" "OPAMW_SendMessageTimeout"
35-
external getParentProcessID : int32 -> int32 = "OPAMW_GetParentProcessID"
36-
external getProcessName : int32 -> string = "OPAMW_GetProcessName"
35+
external getProcessAncestry : unit -> (int32 * string) list = "OPAMW_GetProcessAncestry"
3736
external getConsoleAlias : string -> string -> string = "OPAMW_GetConsoleAlias"

src/stubs/win32/opamWindows.c

+107-69
Original file line numberDiff line numberDiff line change
@@ -70,45 +70,6 @@ static HKEY roots[] =
7070
HKEY_LOCAL_MACHINE,
7171
HKEY_USERS};
7272

73-
/*
74-
* OPAMW_process_putenv is implemented using Process Injection.
75-
* Idea inspired by Bill Stewart's editvar
76-
* (see http://www.westmesatech.com/editv.html)
77-
* Full technical details at http://www.codeproject.com/Articles/4610/Three-Ways-to-Inject-Your-Code-into-Another-Proces#section_3
78-
*/
79-
80-
static char* getProcessInfo(HANDLE hProcessSnapshot,
81-
DWORD processId,
82-
PROCESSENTRY32 *entry)
83-
{
84-
entry->dwSize = sizeof(PROCESSENTRY32);
85-
86-
if (hProcessSnapshot == INVALID_HANDLE_VALUE)
87-
return "getProcessInfo: could not create snapshot";
88-
89-
/*
90-
* Locate our process
91-
*/
92-
if (!Process32First(hProcessSnapshot, entry))
93-
{
94-
CloseHandle(hProcessSnapshot);
95-
return "getProcessInfo: could not walk process tree";
96-
}
97-
else
98-
{
99-
while (entry->th32ProcessID != processId)
100-
{
101-
if (!Process32Next(hProcessSnapshot, entry))
102-
{
103-
CloseHandle(hProcessSnapshot);
104-
return "getProcessInfo: could not find process!";
105-
}
106-
}
107-
}
108-
109-
return NULL;
110-
}
111-
11273
char* InjectSetEnvironmentVariable(DWORD, LPCWSTR, LPCWSTR);
11374

11475
/* Actual primitives from here */
@@ -545,6 +506,13 @@ CAMLprim value OPAMW_HasGlyph(value checker, value scalar)
545506
return Val_bool(index != 0xffff);
546507
}
547508

509+
/*
510+
* OPAMW_process_putenv is implemented using Process Injection.
511+
* Idea inspired by Bill Stewart's editvar
512+
* (see http://www.westmesatech.com/editv.html)
513+
* Full technical details at http://www.codeproject.com/Articles/4610/Three-Ways-to-Inject-Your-Code-into-Another-Proces#section_3
514+
*/
515+
548516
CAMLprim value OPAMW_process_putenv(value pid, value key, value val)
549517
{
550518
char* result;
@@ -650,41 +618,111 @@ CAMLprim value OPAMW_SendMessageTimeout_byte(value * v, int n)
650618
return OPAMW_SendMessageTimeout(v[0], v[1], v[2], v[3], v[4], v[5]);
651619
}
652620

653-
CAMLprim value OPAMW_GetParentProcessID(value processId)
621+
CAMLprim value OPAMW_GetProcessAncestry(value unit)
654622
{
623+
CAMLparam0();
624+
CAMLlocal3(result, tail, info);
655625
PROCESSENTRY32 entry;
656-
char* msg;
657-
/*
658-
* Create a Toolhelp Snapshot of running processes
659-
*/
660-
HANDLE hProcessSnapshot = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0);
661-
662-
if ((msg = getProcessInfo(hProcessSnapshot, Int32_val(processId), &entry)))
663-
caml_failwith(msg);
664-
665-
/*
666-
* Finished with the snapshot
667-
*/
668-
CloseHandle(hProcessSnapshot);
669-
670-
return caml_copy_int32(entry.th32ParentProcessID);
671-
}
672-
673-
CAMLprim value OPAMW_GetProcessName(value processId)
674-
{
675-
CAMLparam1(processId);
676-
677-
PROCESSENTRY32 entry;
678-
DWORD parent_pid;
679-
char* msg;
680-
HANDLE hProcessSnapshot = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0);
626+
HANDLE hProcessSnapshot, hProcess;
627+
value cell;
628+
ULARGE_INTEGER *processes, *cur;
629+
int capacity = 512;
630+
int length = 0;
631+
DWORD target = GetCurrentProcessId();
632+
BOOL read_entry = TRUE;
633+
WCHAR ExeName[MAX_PATH + 1];
634+
DWORD dwSize;
681635

682-
if ((msg = getProcessInfo(hProcessSnapshot, Int32_val(processId), &entry)))
683-
caml_failwith(msg);
636+
result = caml_alloc_small(2, 0);
637+
Field(result, 0) = Val_int(0);
638+
Field(result, 1) = Val_int(0);
639+
tail = result;
640+
641+
/* Snapshot running processes */
642+
hProcessSnapshot = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0);
643+
if (hProcessSnapshot != INVALID_HANDLE_VALUE) {
644+
entry.dwSize = sizeof(PROCESSENTRY32);
645+
/* Read the first entry (just because it's a special function) */
646+
if (Process32First(hProcessSnapshot, &entry)) {
647+
if ((processes = (ULARGE_INTEGER *)malloc(capacity * sizeof(ULARGE_INTEGER)))) {
648+
/* Initialise the processes array */
649+
if (entry.th32ProcessID == 0) {
650+
processes->QuadPart = 0LL;
651+
} else {
652+
length = 1;
653+
processes->LowPart = entry.th32ProcessID;
654+
processes->HighPart = entry.th32ParentProcessID;
655+
processes[1].QuadPart = 0LL;
656+
}
657+
658+
/* Build the process tree, starting with the current process */
659+
do {
660+
/* First search through processes we've already read */
661+
for (cur = processes; cur->QuadPart != 0; cur++) {
662+
if (cur->LowPart == target)
663+
break;
664+
}
665+
666+
if (cur->QuadPart == 0LL) {
667+
/* Keep reading process entries until we reach the end of the list */
668+
while ((read_entry = Process32Next(hProcessSnapshot, &entry))) {
669+
if (entry.th32ProcessID != 0) {
670+
if (++length >= capacity) {
671+
ULARGE_INTEGER *ptr;
672+
capacity += 512;
673+
ptr = (ULARGE_INTEGER *)realloc(processes, capacity * sizeof(ULARGE_INTEGER));
674+
if (ptr == NULL) {
675+
read_entry = FALSE;
676+
break;
677+
} else {
678+
processes = ptr;
679+
}
680+
}
681+
cur->LowPart = entry.th32ProcessID;
682+
cur->HighPart = entry.th32ParentProcessID;
683+
if (cur->LowPart == target) {
684+
cur[1].QuadPart = 0LL;
685+
break;
686+
} else {
687+
cur++;
688+
}
689+
}
690+
}
691+
if (!read_entry)
692+
break;
693+
}
694+
695+
/* Found it - construct the list entry */
696+
hProcess = OpenProcess(PROCESS_QUERY_LIMITED_INFORMATION, FALSE, target);
697+
if (hProcess != NULL) {
698+
dwSize = MAX_PATH + 1;
699+
if (!QueryFullProcessImageName(hProcess, 0, ExeName, &dwSize))
700+
ExeName[0] = L'\0';
701+
CloseHandle(hProcess);
702+
} else {
703+
ExeName[0] = L'\0';
704+
}
705+
info = caml_alloc_tuple(2);
706+
Store_field(info, 0, caml_copy_int32(target));
707+
Store_field(info, 1, caml_copy_string_of_utf16(ExeName));
708+
cell = caml_alloc_small(2, 0);
709+
Field(cell, 0) = info;
710+
Field(cell, 1) = Val_int(0);
711+
Store_field(tail, 1, cell);
712+
tail = cell;
713+
/* Search for this process's parent on the next round */
714+
target = cur->HighPart;
715+
/* Guard against looping by zeroing out the parent */
716+
cur->HighPart = 0;
717+
} while (1);
718+
}
719+
free(processes);
720+
}
684721

685-
CloseHandle(hProcessSnapshot);
722+
CloseHandle(hProcessSnapshot);
723+
}
686724

687-
CAMLreturn(caml_copy_string_of_utf16(entry.szExeFile));
725+
CAMLreturn(Field(result, 1));
688726
}
689727

690728
CAMLprim value OPAMW_GetConsoleAlias(value alias, value exe_name)

0 commit comments

Comments
 (0)