Browse Source

os2: process API for Darwin and most of it for BSDs

Laytan Laats 11 months ago
parent
commit
a66520ba57

+ 7 - 4
core/os/os2/process_linux.odin

@@ -576,10 +576,13 @@ _process_start :: proc(desc: Process_Desc) -> (process: Process, err: Error) {
 		success_byte: [1]u8
 		linux.write(child_pipe_fds[WRITE], success_byte[:])
 
-		if errno = linux.execveat(exe_fd, "", &cargs[0], env, {.AT_EMPTY_PATH}); errno != .NONE {
-			write_errno_to_parent_and_abort(child_pipe_fds[WRITE], errno)
-		}
-		unreachable()
+		errno = linux.execveat(exe_fd, "", &cargs[0], env, {.AT_EMPTY_PATH})
+
+		// NOTE: we can't tell the parent about this failure because we already wrote the success byte.
+		// So if this happens the user will just see the process failed when they call process_wait.
+
+		assert(errno != nil)
+		intrinsics.trap()
 	}
 
 	process.pid = int(pid)

+ 237 - 91
core/os/os2/process_posix.odin

@@ -3,9 +3,13 @@
 package os2
 
 import "base:runtime"
+
 import "core:time"
+import "core:strings"
+import "core:path/filepath"
 
-import "core:sys/posix"
+import kq "core:sys/kqueue"
+import    "core:sys/posix"
 
 _exit :: proc "contextless" (code: int) -> ! {
 	posix.exit(i32(code))
@@ -51,141 +55,286 @@ _process_start :: proc(desc: Process_Desc) -> (process: Process, err: Error) {
 		return
 	}
 
+	TEMP_ALLOCATOR_GUARD()
+
+	// search PATH if just a plain name is provided.
+	exe_builder := strings.builder_make(temp_allocator())
+	exe_name    := desc.command[0]
+	if strings.index_byte(exe_name, '/') < 0 {
+		path_env  := get_env("PATH", temp_allocator())
+		path_dirs := filepath.split_list(path_env, temp_allocator())
+
+		found: bool
+		for dir in path_dirs {
+			strings.builder_reset(&exe_builder)
+			strings.write_string(&exe_builder, dir)
+			strings.write_byte(&exe_builder, '/')
+			strings.write_string(&exe_builder, exe_name)
+
+			if exe_fd := posix.open(strings.to_cstring(&exe_builder), {.CLOEXEC, .EXEC}); exe_fd == -1 {
+				continue
+			} else {
+				posix.close(exe_fd)
+				found = true
+				break
+			}
+		}
+		if !found {
+			// check in cwd to match windows behavior
+			strings.builder_reset(&exe_builder)
+			strings.write_string(&exe_builder, desc.working_dir)
+			if len(desc.working_dir) > 0 && desc.working_dir[len(desc.working_dir)-1] != '/' {
+			strings.write_byte(&exe_builder, '/')
+			}
+			strings.write_string(&exe_builder, "./")
+			strings.write_string(&exe_builder, exe_name)
+
+			// "hello/./world" is fine right?
+
+			if exe_fd := posix.open(strings.to_cstring(&exe_builder), {.CLOEXEC, .EXEC}); exe_fd == -1 {
+				err = .Not_Exist
+				return
+			} else {
+				posix.close(exe_fd)
+			}
+		}
+	} else {
+		strings.builder_reset(&exe_builder)
+		strings.write_string(&exe_builder, exe_name)
+
+		if exe_fd := posix.open(strings.to_cstring(&exe_builder), {.CLOEXEC, .EXEC}); exe_fd == -1 {
+			err = .Not_Exist
+			return
+		} else {
+			posix.close(exe_fd)
+		}
+	}
+
 	cwd: cstring; if desc.working_dir != "" {
 		cwd = temp_cstring(desc.working_dir)
 	}
 
-	cmd := make([]cstring, len(desc.command)+1, temp_allocator())
+	cmd := make([]cstring, len(desc.command) + 1, temp_allocator())
 	for part, i in desc.command {
 		cmd[i] = temp_cstring(part)
 	}
 
+	env: [^]cstring
+	if desc.env == nil {
+		// take this process's current environment
+		env = posix.environ
+	} else {
+		cenv := make([]cstring, len(desc.env) + 1, temp_allocator())
+		for env, i in desc.env {
+			cenv[i] = temp_cstring(env)
+		}
+		env = raw_data(cenv)
+	}
+
+	READ  :: 0
+	WRITE :: 1
+
+	pipe: [2]posix.FD
+	if posix.pipe(&pipe) != .OK {
+		err = _get_platform_error()
+		return
+	}
+	defer posix.close(pipe[WRITE])
+	defer posix.close(pipe[READ])
+
+	if posix.fcntl(pipe[READ], .SETFD, i32(posix.FD_CLOEXEC)) == -1 {
+		err = _get_platform_error()
+		return
+	}
+	if posix.fcntl(pipe[WRITE], .SETFD, i32(posix.FD_CLOEXEC)) == -1 {
+		err = _get_platform_error()
+		return
+	}
+
 	switch pid := posix.fork(); pid {
 	case -1:
 		err = _get_platform_error()
 		return
 
 	case 0:
-		// NOTE(laytan): would need to use execvp and look up the command in the PATH.
-		assert(len(desc.env) == 0, "unimplemented: process_start with env")
+		abort :: proc(parent_fd: posix.FD) -> ! {
+			#assert(len(posix.Errno) < max(u8))
+			errno := u8(posix.errno())
+			posix.write(parent_fd, &errno, 1)
+			runtime.trap()
+		}
 
-		null := posix.open("/dev/null", { .RDWR, .CLOEXEC })
-		assert(null != -1) // TODO: Does this happen/need to be handled?
+		null := posix.open("/dev/null", {.RDWR})
+		if null == -1 { abort(pipe[WRITE]) }
 
 		stderr := (^File_Impl)(desc.stderr.impl).fd if desc.stderr != nil else null
 		stdout := (^File_Impl)(desc.stdout.impl).fd if desc.stdout != nil else null
 		stdin  := (^File_Impl)(desc.stdin.impl).fd  if desc.stdin  != nil else null
 
-		posix.dup2(stderr, posix.STDERR_FILENO)
-		posix.dup2(stdout, posix.STDOUT_FILENO)
-		posix.dup2(stdin,  posix.STDIN_FILENO )
-
-		// NOTE(laytan): is this how we should handle these?
-		// Maybe we can try to `stat` the cwd in the parent before forking?
-		// Does that mean no other errors could happen in chdir?
-		// How about execvp?
+		if posix.dup2(stderr, posix.STDERR_FILENO) == -1 { abort(pipe[WRITE]) }
+		if posix.dup2(stdout, posix.STDOUT_FILENO) == -1 { abort(pipe[WRITE]) }
+		if posix.dup2(stdin,  posix.STDIN_FILENO ) == -1 { abort(pipe[WRITE]) }
 
 		if cwd != nil {
-			if posix.chdir(cwd) != .OK {
-				posix.exit(i32(posix.errno())) // TODO: handle, or is it fine this way?
-			}
+			if posix.chdir(cwd) != .OK { abort(pipe[WRITE]) }
 		}
 
-		posix.execvp(cmd[0], raw_data(cmd))
-		posix.exit(i32(posix.errno())) // TODO: handle, or is it fine this way?
+		ok := u8(0)
+		posix.write(pipe[WRITE], &ok, 1)
+
+		res := posix.execve(strings.to_cstring(&exe_builder), raw_data(cmd), env)
+
+		// NOTE: we can't tell the parent about this failure because we already wrote the success byte.
+		// So if this happens the user will just see the process failed when they call process_wait.
+
+		assert(res == -1)
+		runtime.trap()
 
 	case:
-		fmt.println("returning")
-		process, _ = _process_open(int(pid), {})
+		errno: posix.Errno
+		for {
+			errno_byte: u8
+			switch posix.read(pipe[READ], &errno_byte, 1) {
+			case 1:
+				errno = posix.Errno(errno_byte)
+			case:
+				errno = posix.errno()
+				if errno == .EINTR {
+					continue
+				} else {
+					// If the read failed, something weird happened. Do not return the read
+					// error so the user knows to wait on it.
+					errno = nil
+				}
+			}
+			break
+		}
+
+		if errno != nil {
+			// We can assume it trapped here.
+
+			for {
+				info: posix.siginfo_t
+				wpid := posix.waitid(.P_PID, posix.id_t(process.pid), &info, {.EXITED})
+				if wpid == -1 && posix.errno() == .EINTR {
+					continue
+				}
+				break
+			}
+
+			err = errno
+			return
+		}
+
 		process.pid = int(pid)
+		process, _ = _process_open(int(pid), {})
 		return
 	}
 }
 
-import "core:fmt"
-import "core:nbio/kqueue"
-
 _process_wait :: proc(process: Process, timeout: time.Duration) -> (process_state: Process_State, err: Error) {
 	process_state.pid = process.pid
 
-	if !process_posix_handle_still_valid(process) {
-		err = Platform_Error(posix.Errno.ESRCH)
-		return
-	}
+	_process_handle_still_valid(process) or_return
 
-	// prev := posix.signal(.SIGALRM, proc "c" (_: posix.Signal) {
-	// 	context = runtime.default_context()
-	// 	fmt.println("alarm")
-	// })
-	// defer posix.signal(.SIGALRM, prev)
+	// timeout >  0 = use kqueue to wait (with a timeout) on process exit
+	// timeout == 0 = use waitid with WNOHANG so it returns immediately
+	// timeout >  0 = use waitid without WNOHANG so it waits indefinitely
 	//
-	// posix.alarm(u32(time.duration_seconds(timeout)))
-	// defer posix.alarm(0)
+	// at the end use waitid to actually reap the process and get it's status
 
-	// TODO: if there's no timeout, don't set up a kqueue.
+	if timeout > 0 {
+		timeout := timeout
 
-	// TODO: if timeout is 0, don't set up a kqueue and use NO_HANG.
+		queue := kq.kqueue() or_return
+		defer posix.close(queue)
 
-	kq, qerr := kqueue.kqueue()
-	if qerr != nil {
-		err = Platform_Error(qerr)
-		return
-	}
+		changelist, eventlist: [1]kq.KEvent
 
-	changelist, eventlist: [1]kqueue.KEvent
-
-	changelist[0] = {
-		ident  = uintptr(process.pid),
-		filter = .Proc,
-		flags  = { .Add },
-		fflags = {
-			fproc = 0x80000000,
-		},
-	}
-
-	// NOTE: could this be interrupted which means it should be looped and subtracting the timeout on EINTR.
+		changelist[0] = {
+			ident  = uintptr(process.pid),
+			filter = .Proc,
+			flags  = { .Add },
+			fflags = {
+				fproc = { .Exit },
+			},
+		}
 
-	n, eerr := kqueue.kevent(kq, changelist[:], eventlist[:], &{
-		seconds     = i64(timeout / time.Second),
-		nanoseconds = i64(timeout % time.Second),
-	})
-	if eerr != nil {
-		err = Platform_Error(eerr)
-		return
-	}
+		for {
+			start := time.tick_now()
+			n, kerr := kq.kevent(queue, changelist[:], eventlist[:], &{
+				tv_sec  = posix.time_t(timeout / time.Second),
+				tv_nsec = i64(timeout % time.Second),
+			})
+			if kerr == .EINTR {
+				timeout -= time.tick_since(start)
+				continue
+			} else if kerr != nil {
+				err = kerr
+				return
+			} else if n == 0 {
+				err = .Timeout
+				_process_state_update_times(process, &process_state)
+				return
+			} else {
+				_process_state_update_times(process, &process_state)
+				break
+			}
+		}
+	} else {
+		flags := posix.Wait_Flags{.EXITED, .NOWAIT}
+		if timeout == 0 {
+			flags += {.NOHANG}
+		}
 
-	if n == 0 {
-		err = .Timeout
+		info: posix.siginfo_t
+		for {
+			wpid := posix.waitid(.P_PID, posix.id_t(process.pid), &info, flags)
+			if wpid == -1 {
+				if errno := posix.errno(); errno == .EINTR {
+					continue
+				} else {
+					err = _get_platform_error()
+					return
+				}
+			}
+			break
+		}
 
-		// TODO: populate the time fields.
+		_process_state_update_times(process, &process_state)
 
-		return
+		if info.si_signo == nil {
+			assert(timeout == 0)
+			err = .Timeout
+			return
+		}
 	}
 
-	// NOTE(laytan): should this be looped untill WIFEXITED/WIFSIGNALED?
-
-	status: i32
-	wpid := posix.waitpid(posix.pid_t(process.pid), &status, {})
-	if wpid == -1 {
-		err = _get_platform_error()
-		return
+	info: posix.siginfo_t
+	for {
+		wpid := posix.waitid(.P_PID, posix.id_t(process.pid), &info, {.EXITED})
+		if wpid == -1 {
+			if errno := posix.errno(); errno == .EINTR {
+				continue
+			} else {
+				err = _get_platform_error()
+				return
+			}
+		}
+		break
 	}
 
-	process_state.exited = true
-
-	// TODO: populate times
-
-	switch {
-	case posix.WIFEXITED(status):
-		fmt.printfln("child exited, status=%v", posix.WEXITSTATUS(status))
-		process_state.exit_code = int(posix.WEXITSTATUS(status))
-		process_state.success   = true
-	case posix.WIFSIGNALED(status):
-		fmt.printfln("child killed (signal %v)", posix.WTERMSIG(status))
-		process_state.exit_code = int(posix.WTERMSIG(status))
+	switch info.si_code.chld {
+	case:                      unreachable()
+	case .CONTINUED, .STOPPED: unreachable()
+	case .EXITED:
+		process_state.exited    = true
+		process_state.exit_code = int(info.si_status)
+		process_state.success   = process_state.exit_code == 0
+	case .KILLED, .DUMPED, .TRAPPED:
+		process_state.exited    = true
+		process_state.exit_code = int(info.si_status)
 		process_state.success   = false
-	case:
-		fmt.panicf("unexpected status (%x)", status)
 	}
 
 	return
@@ -196,10 +345,7 @@ _process_close :: proc(process: Process) -> Error {
 }
 
 _process_kill :: proc(process: Process) -> (err: Error) {
-	if !process_posix_handle_still_valid(process) {
-		err = Platform_Error(posix.Errno.ESRCH)
-		return
-	}
+	_process_handle_still_valid(process) or_return
 
 	if posix.kill(posix.pid_t(process.pid), .SIGKILL) != .OK {
 		err = _get_platform_error()

+ 44 - 20
core/os/os2/process_posix_darwin.odin

@@ -8,6 +8,7 @@ import "core:bytes"
 import "core:sys/darwin"
 import "core:sys/posix"
 import "core:sys/unix"
+import "core:time"
 
 foreign import lib "system:System.framework"
 
@@ -19,8 +20,6 @@ foreign lib {
 	) -> posix.result ---
 }
 
-import "core:fmt"
-
 _process_info_by_pid :: proc(pid: int, selection: Process_Info_Fields, allocator: runtime.Allocator) -> (info: Process_Info, err: Error) {
 	get_pidinfo :: proc(pid: int, selection: Process_Info_Fields) -> (ppid: u32, prio: Maybe(i32), uid: posix.uid_t, ok: bool) {
 		// Short info is enough and requires less permissions if the priority isn't requested.
@@ -258,31 +257,56 @@ _process_list :: proc(allocator: runtime.Allocator) -> (list: []int, err: Error)
 }
 
 _process_open :: proc(pid: int, flags: Process_Open_Flags) -> (process: Process, err: Error) {
-
-	// NOTE(laytan): pids can get reused, and afaik posix/macos doesn't have a unique identifier
-	// for a specific process execution, next best thing to me is checking the time the process
-	// started as some extra "uniqueness". We could also hash a bunch of the fields in this info.
-
-	// This incidentally also checks if the pid is actually valid so that's nice.
-
-	pinfo: darwin.proc_bsdinfo
-	ret := darwin.proc_pidinfo(posix.pid_t(pid), .BSDINFO, 0, &pinfo, size_of(pinfo))
-	if ret <= 0 {
+	rusage: darwin.rusage_info_v0
+	if ret := darwin.proc_pid_rusage(posix.pid_t(pid), .V0, &rusage); ret != 0 {
 		err = _get_platform_error()
 		return
 	}
 
-	assert(ret == size_of(pinfo))
-	process = { int(pid), uintptr(pinfo.pbi_start_tvusec) }
+	// XOR fold the UUID so it fits the handle, I think this is enough to verify pid uniqueness.
+	#assert(size_of(uintptr) == size_of(u64))
+	a := intrinsics.unaligned_load((^u64)(&rusage.ri_uuid))
+	b := intrinsics.unaligned_load((^u64)(&rusage.ri_uuid[8]))
+	process.handle = uintptr(a ~ b)
+
+	process.pid = int(pid)
 	return
 }
 
-process_posix_handle_still_valid :: proc(p: Process) -> bool {
-	pinfo: darwin.proc_bsdinfo
-	ret := darwin.proc_pidinfo(posix.pid_t(p.pid), .BSDINFO, 0, &pinfo, size_of(pinfo))
-	if ret <= 0 {
-		return false
+_process_handle_still_valid :: proc(p: Process) -> Error {
+	rusage: darwin.rusage_info_v0
+	if ret := darwin.proc_pid_rusage(posix.pid_t(p.pid), .V0, &rusage); ret != 0 {
+		return _get_platform_error()
+	}
+
+	// XOR fold the UUID so it fits the handle, I think this is enough to verify pid uniqueness.
+	#assert(size_of(uintptr) == size_of(u64))
+	a := intrinsics.unaligned_load((^u64)(&rusage.ri_uuid))
+	b := intrinsics.unaligned_load((^u64)(&rusage.ri_uuid[8]))
+	handle := uintptr(a ~ b)
+
+	if p.handle != handle {
+		return posix.Errno.ESRCH
+	}
+
+	return nil
+}
+
+_process_state_update_times :: proc(p: Process, state: ^Process_State) {
+	rusage: darwin.rusage_info_v0
+	if ret := darwin.proc_pid_rusage(posix.pid_t(p.pid), .V0, &rusage); ret != 0 {
+		return
 	}
 
-	return uintptr(pinfo.pbi_start_tvusec) == p.handle
+	// NOTE(laytan): I have no clue if this is correct, the output seems correct comparing it with `time`'s output.
+	HZ :: 20000000
+
+	state.user_time   = (
+		(time.Duration(rusage.ri_user_time) / HZ * time.Second) +
+		 time.Duration(rusage.ri_user_time  % HZ))
+	state.system_time = (
+		(time.Duration(rusage.ri_system_time) / HZ * time.Second) +
+		 time.Duration(rusage.ri_system_time % HZ))
+
+	return
 }

+ 13 - 0
core/os/os2/process_posix_other.odin

@@ -13,3 +13,16 @@ _process_list :: proc(allocator: runtime.Allocator) -> (list: []int, err: Error)
 	err = .Unsupported
 	return
 }
+
+_process_open :: proc(pid: int, flags: Process_Open_Flags) -> (process: Process, err: Error) {
+	err = .Unsupported
+	return
+}
+
+_process_handle_still_valid :: proc(p: Process) -> Error {
+	return nil
+}
+
+_process_state_update_times :: proc(p: Process, state: ^Process_State) {
+	return
+}

+ 24 - 0
core/sys/darwin/proc.odin

@@ -12,6 +12,7 @@ foreign lib {
 	proc_pidinfo     :: proc(pid: posix.pid_t, flavor: PID_Info_Flavor, arg: i64, buffer: rawptr, buffersize: i32) -> i32 ---
 	proc_pidpath     :: proc(pid: posix.pid_t, buffer: [^]byte, buffersize: u32) -> i32 ---
 	proc_listallpids :: proc(buffer: [^]i32, buffersize: i32) -> i32 ---
+	proc_pid_rusage  :: proc(pid: posix.pid_t, flavor: Pid_Rusage_Flavor, buffer: rawptr) -> i32 ---
 }
 
 MAXCOMLEN :: 16
@@ -166,3 +167,26 @@ PID_Info_Flavor :: enum i32 {
 }
 
 PIDPATHINFO_MAXSIZE :: 4*posix.PATH_MAX
+
+Pid_Rusage_Flavor :: enum i32 {
+	V0,
+	V1,
+	V2,
+	V3,
+	V4,
+	V5,
+}
+
+rusage_info_v0 :: struct {
+	ri_uuid:               [16]u8,
+	ri_user_time:          u64,
+	ri_system_time:        u64,
+	ri_pkg_idle_wkups:     u64,
+	ri_interrupt_wkups:    u64,
+	ri_pageins:            u64,
+	ri_wired_size:         u64,
+	ri_resident_size:      u64,
+	ri_phys_footprint:     u64,
+	ri_proc_start_abstime: u64,
+	ri_proc_exit_abstime:  u64,
+}

+ 256 - 0
core/sys/kqueue/kqueue.odin

@@ -0,0 +1,256 @@
+//+build darwin, netbsd, openbsd, freebsd
+package kqueue
+
+when ODIN_OS == .Darwin {
+	foreign import lib "system:System.framework"
+} else {
+	foreign import lib "system:c"
+}
+
+import "base:intrinsics"
+
+import "core:c"
+import "core:sys/posix"
+
+KQ :: posix.FD
+
+kqueue :: proc() -> (kq: KQ, err: posix.Errno) {
+	kq = _kqueue()
+	if kq == -1 {
+		err = posix.errno()
+	}
+	return
+}
+
+kevent :: proc(kq: KQ, change_list: []KEvent, event_list: []KEvent, timeout: ^posix.timespec) -> (n_events: c.int, err: posix.Errno) {
+	n_events = _kevent(
+		kq,
+		raw_data(change_list),
+		c.int(len(change_list)),
+		raw_data(event_list),
+		c.int(len(event_list)),
+		timeout,
+	)
+	if n_events == -1 {
+		err = posix.errno()
+	}
+	return
+}
+
+Flag :: enum _Flags_Backing {
+	Add      = log2(0x0001), // Add event to kq (implies .Enable).
+	Delete   = log2(0x0002), // Delete event from kq.
+	Enable   = log2(0x0004), // Enable event.
+	Disable  = log2(0x0008), // Disable event (not reported).
+	One_Shot = log2(0x0010), // Only report one occurrence.
+	Clear    = log2(0x0020), // Clear event state after reporting.
+	Receipt  = log2(0x0040), // Force immediate event output.
+	Dispatch = log2(0x0080), // Disable event after reporting.
+
+	Error    = log2(0x4000), // Error, data contains errno.
+	EOF      = log2(0x8000), // EOF detected.
+}
+Flags :: bit_set[Flag; _Flags_Backing]
+
+Filter :: enum _Filter_Backing {
+	Read   = _FILTER_READ,   // Check for read availability on the file descriptor.
+	Write  = _FILTER_WRITE,  // Check for write availability on the file descriptor.
+	AIO    = _FILTER_AIO,    // Attached to AIO requests.
+	VNode  = _FILTER_VNODE,  // Check for changes to the subject file.
+	Proc   = _FILTER_PROC,   // Check for changes to the subject process.
+	Signal = _FILTER_SIGNAL, // Check for signals delivered to the process.
+	Timer  = _FILTER_TIMER,  // Timers.
+}
+
+RW_Flag :: enum u32 {
+	Low_Water_Mark = log2(0x00000001),
+}
+RW_Flags :: bit_set[RW_Flag; u32]
+
+VNode_Flag :: enum u32 {
+	Delete = log2(0x00000001), // Deleted.
+	Write  = log2(0x00000002), // Contents changed.
+	Extend = log2(0x00000004), // Size increased.
+	Attrib = log2(0x00000008), // Attributes changed.
+	Link   = log2(0x00000010), // Link count changed.
+	Rename = log2(0x00000020), // Renamed.
+	Revoke = log2(0x00000040), // Access was revoked.
+}
+VNode_Flags :: bit_set[VNode_Flag; u32]
+
+Proc_Flag :: enum u32 {
+	Exit   = log2(0x80000000), // Process exited.
+	Fork   = log2(0x40000000), // Process forked.
+	Exec   = log2(0x20000000), // Process exec'd.
+	Signal = log2(0x08000000), // Shared with `Filter.Signal`.
+}
+Proc_Flags :: bit_set[Proc_Flag; u32]
+
+Timer_Flag :: enum u32 {
+	Seconds   = log2(0x00000001),     // Data is seconds.
+	USeconds  = log2(0x00000002),     // Data is microseconds.
+	NSeconds  = log2(_NOTE_NSECONDS), // Data is nanoseconds.
+	Absolute  = log2(_NOTE_ABSOLUTE), // Absolute timeout.
+}
+Timer_Flags :: bit_set[Timer_Flag; u32]
+
+when ODIN_OS == .Darwin {
+
+	_Filter_Backing :: distinct i16
+	_Flags_Backing  :: distinct u16
+
+	_FILTER_READ   :: -1
+	_FILTER_WRITE  :: -2
+	_FILTER_AIO    :: -3
+	_FILTER_VNODE  :: -4
+	_FILTER_PROC   :: -5
+	_FILTER_SIGNAL :: -6
+	_FILTER_TIMER  :: -7
+
+	_NOTE_NSECONDS :: 0x00000004
+	_NOTE_ABSOLUTE :: 0x00000008
+
+	KEvent :: struct #align(4) {
+		// Value used to identify this event. The exact interpretation is determined by the attached filter.
+		ident:  uintptr,
+		// Filter for event.
+		filter: Filter,
+		// General flags.
+		flags:  Flags,
+		// Filter specific flags.
+		fflags: struct #raw_union {
+			rw:    RW_Flags,
+			vnode: VNode_Flags,
+			fproc: Proc_Flags,
+			// vm:    VM_Flags,
+			timer: Timer_Flags,
+		},
+		// Filter specific data.
+		data:   c.long /* intptr_t */,
+		// Opaque user data passed through the kernel unchanged.
+		udata:  rawptr,
+	}
+
+} else when ODIN_OS == .FreeBSD {
+
+	_Filter_Backing :: distinct i16
+	_Flags_Backing  :: distinct u16
+
+	_FILTER_READ   :: -1
+	_FILTER_WRITE  :: -2
+	_FILTER_AIO    :: -3
+	_FILTER_VNODE  :: -4
+	_FILTER_PROC   :: -5
+	_FILTER_SIGNAL :: -6
+	_FILTER_TIMER  :: -7
+
+	_NOTE_NSECONDS :: 0x00000004
+	_NOTE_ABSOLUTE :: 0x00000008
+
+	KEvent :: struct {
+		// Value used to identify this event. The exact interpretation is determined by the attached filter.
+		ident:  uintptr,
+		// Filter for event.
+		filter: Filter,
+		// General flags.
+		flags:  Flags,
+		// Filter specific flags.
+		fflags: struct #raw_union {
+			rw:    RW_Flags,
+			vnode: VNode_Flags,
+			fproc: Proc_Flags,
+			// vm:    VM_Flags,
+			timer: Timer_Flags,
+		},
+		// Filter specific data.
+		data:   i64,
+		// Opaque user data passed through the kernel unchanged.
+		udata:  rawptr,
+		// Extensions.
+		ext: [4]u64,
+	}
+} else when ODIN_OS == .NetBSD {
+
+	_Filter_Backing :: distinct u32
+	_Flags_Backing  :: distinct u32
+
+	_FILTER_READ   :: 0
+	_FILTER_WRITE  :: 1
+	_FILTER_AIO    :: 2
+	_FILTER_VNODE  :: 3
+	_FILTER_PROC   :: 4
+	_FILTER_SIGNAL :: 5
+	_FILTER_TIMER  :: 6
+
+	_NOTE_NSECONDS :: 0x00000003
+	_NOTE_ABSOLUTE :: 0x00000010
+
+	KEvent :: struct #align(4) {
+		// Value used to identify this event. The exact interpretation is determined by the attached filter.
+		ident:  uintptr,
+		// Filter for event.
+		filter: Filter,
+		// General flags.
+		flags:  Flags,
+		// Filter specific flags.
+		fflags: struct #raw_union {
+			rw:    RW_Flags,
+			vnode: VNode_Flags,
+			fproc: Proc_Flags,
+			// vm:    VM_Flags,
+			timer: Timer_Flags,
+		},
+		// Filter specific data.
+		data:   i64,
+		// Opaque user data passed through the kernel unchanged.
+		udata:  rawptr,
+		// Extensions.
+		ext: [4]u64,
+	}
+} else when ODIN_OS == .OpenBSD {
+
+	_Filter_Backing :: distinct i16
+	_Flags_Backing  :: distinct u16
+
+	_FILTER_READ   :: -1
+	_FILTER_WRITE  :: -2
+	_FILTER_AIO    :: -3
+	_FILTER_VNODE  :: -4
+	_FILTER_PROC   :: -5
+	_FILTER_SIGNAL :: -6
+	_FILTER_TIMER  :: -7
+
+	_NOTE_NSECONDS :: 0x00000003
+	_NOTE_ABSOLUTE :: 0x00000010
+
+	KEvent :: struct #align(4) {
+		// Value used to identify this event. The exact interpretation is determined by the attached filter.
+		ident:  uintptr,
+		// Filter for event.
+		filter: Filter,
+		// General flags.
+		flags:  Flags,
+		// Filter specific flags.
+		fflags: struct #raw_union {
+			rw:    RW_Flags,
+			vnode: VNode_Flags,
+			fproc: Proc_Flags,
+			// vm:    VM_Flags,
+			timer: Timer_Flags,
+		},
+		// Filter specific data.
+		data:   i64,
+		// Opaque user data passed through the kernel unchanged.
+		udata:  rawptr,
+	}
+}
+
+@(private)
+log2 :: intrinsics.constant_log2
+
+foreign lib {
+	@(link_name="kqueue")
+	_kqueue :: proc() -> KQ ---
+	@(link_name="kevent")
+	_kevent :: proc(kq: KQ, change_list: [^]KEvent, n_changes: c.int, event_list: [^]KEvent, n_events: c.int, timeout: ^posix.timespec) -> c.int ---
+}