Browse Source

Merge branch 'master' into sysinfo

Jeroen van Rijn 3 years ago
parent
commit
01e8668357

+ 1 - 1
core/math/ease/ease.odin

@@ -356,7 +356,7 @@ Flux_Tween :: struct($T: typeid) {
 flux_init :: proc($T: typeid, value_capacity := 8) -> Flux_Map(T) where intrinsics.type_is_float(T) {
 	return {
 		values = make(map[^T]Flux_Tween(T), value_capacity),
-		keys_to_be_deleted = make([dynamic]^T, 0, value_capacity)
+		keys_to_be_deleted = make([dynamic]^T, 0, value_capacity),
 	}
 }
 

+ 3 - 3
core/mem/virtual/growing_arena.odin

@@ -13,10 +13,10 @@ Growing_Arena :: struct {
 
 DEFAULT_MINIMUM_BLOCK_SIZE :: 1<<20 // 1 MiB should be enough
 
-growing_arena_init :: proc(arena: ^Static_Arena, reserved: uint = DEFAULT_MINIMUM_BLOCK_SIZE) -> (err: Allocator_Error) {
-	arena.block = memory_block_alloc(0, reserved, {}) or_return
+growing_arena_init :: proc(arena: ^Growing_Arena, reserved: uint = DEFAULT_MINIMUM_BLOCK_SIZE) -> (err: Allocator_Error) {
+	arena.curr_block = memory_block_alloc(0, reserved, {}) or_return
 	arena.total_used = 0
-	arena.total_reserved = arena.block.reserved
+	arena.total_reserved = arena.curr_block.reserved
 	return
 }
 

+ 28 - 0
core/slice/sort.odin

@@ -38,6 +38,20 @@ sort :: proc(data: $T/[]$E) where ORD(E) {
 	}
 }
 
+// sort sorts a slice
+// This sort is not guaranteed to be stable
+sort_with_indices :: proc(data: $T/[]$E, indices: []int) where ORD(E) {
+	when size_of(E) != 0 {
+		if n := len(data); n > 1 {
+			assert(len(data) == len(indices))
+			for _, idx in indices {
+				indices[idx] = idx
+			}
+			_quick_sort_general_with_indices(data, indices, 0, n, _max_depth(n), struct{}{}, .Ordered)
+		}
+	}
+}
+
 // sort_by sorts a slice with a given procedure to test whether two values are ordered "i < j"
 // This sort is not guaranteed to be stable
 sort_by :: proc(data: $T/[]$E, less: proc(i, j: E) -> bool) {
@@ -48,6 +62,20 @@ sort_by :: proc(data: $T/[]$E, less: proc(i, j: E) -> bool) {
 	}
 }
 
+// sort_by sorts a slice with a given procedure to test whether two values are ordered "i < j"
+// This sort is not guaranteed to be stable
+sort_by_with_indices :: proc(data: $T/[]$E, indices: []int, less: proc(i, j: E) -> bool) {
+	when size_of(E) != 0 {
+		if n := len(data); n > 1 {
+			assert(len(data) == len(indices))
+			for _, idx in indices {
+				indices[idx] = idx
+			}
+			_quick_sort_general_with_indices(data, indices, 0, n, _max_depth(n), less, .Less)
+		}
+	}
+}
+
 sort_by_cmp :: proc(data: $T/[]$E, cmp: proc(i, j: E) -> Ordering) {
 	when size_of(E) != 0 {
 		if n := len(data); n > 1 {

+ 177 - 0
core/slice/sort_private.odin

@@ -198,3 +198,180 @@ _stable_sort_general :: proc(data: $T/[]$E, call: $P, $KIND: Sort_Kind) where (O
 		}
 	}
 }
+
+_quick_sort_general_with_indices :: proc(data: $T/[]$E, indices: []int, a, b, max_depth: int, call: $P, $KIND: Sort_Kind) where (ORD(E) && KIND == .Ordered) || (KIND != .Ordered) #no_bounds_check {
+	less :: #force_inline proc(a, b: E, call: P) -> bool {
+		when KIND == .Ordered {
+			return a < b
+		} else when KIND == .Less {
+			return call(a, b)
+		} else when KIND == .Cmp {
+			return call(a, b) == .Less
+		} else {
+			#panic("unhandled Sort_Kind")
+		}
+	}
+
+	insertion_sort :: proc(data: $T/[]$E, indices: []int, a, b: int, call: P) #no_bounds_check {
+		for i in a+1..<b {
+			for j := i; j > a && less(data[j], data[j-1], call); j -= 1 {
+				swap(data, j, j-1)
+				swap(indices, j, j-1)
+			}
+		}
+	}
+
+	heap_sort :: proc(data: $T/[]$E, indices: []int, a, b: int, call: P) #no_bounds_check {
+		sift_down :: proc(data: T, indices: []int, lo, hi, first: int, call: P) #no_bounds_check {
+			root := lo
+			for {
+				child := 2*root + 1
+				if child >= hi {
+					break
+				}
+				if child+1 < hi && less(data[first+child], data[first+child+1], call) {
+					child += 1
+				}
+				if !less(data[first+root], data[first+child], call) {
+					return
+				}
+				swap(data, first+root, first+child)
+				swap(indices, first+root, first+child)
+				root = child
+			}
+		}
+
+
+		first, lo, hi := a, 0, b-a
+
+		for i := (hi-1)/2; i >= 0; i -= 1 {
+			sift_down(data, indices, i, hi, first, call)
+		}
+
+		for i := hi-1; i >= 0; i -= 1 {
+			swap(data, first, first+i)
+			swap(indices, first, first+i)
+			sift_down(data, indices, lo, i, first, call)
+		}
+	}
+
+	median3 :: proc(data: T, indices: []int, m1, m0, m2: int, call: P) #no_bounds_check {
+		if less(data[m1], data[m0], call) {
+			swap(data, m1, m0)
+			swap(indices, m1, m0)
+		}
+		if less(data[m2], data[m1], call) {
+			swap(data, m2, m1)
+			swap(indices, m2, m1)
+			if less(data[m1], data[m0], call) {
+				swap(data, m1, m0)
+				swap(indices, m1, m0)
+			}
+		}
+	}
+
+	do_pivot :: proc(data: T, indices: []int, lo, hi: int, call: P) -> (midlo, midhi: int) #no_bounds_check {
+		m := int(uint(lo+hi)>>1)
+		if hi-lo > 40 {
+			s := (hi-lo)/8
+			median3(data, indices, lo, lo+s, lo+s*2, call)
+			median3(data, indices, m, m-s, m+s, call)
+			median3(data, indices, hi-1, hi-1-s, hi-1-s*2, call)
+		}
+		median3(data, indices, lo, m, hi-1, call)
+
+		pivot := lo
+		a, c := lo+1, hi-1
+
+
+		for ; a < c && less(data[a], data[pivot], call); a += 1 {
+		}
+		b := a
+
+		for {
+			for ; b < c && !less(data[pivot], data[b], call); b += 1 { // data[b] <= pivot
+			}
+			for ; b < c && less(data[pivot], data[c-1], call); c -=1 { // data[c-1] > pivot
+			}
+			if b >= c {
+				break
+			}
+
+			swap(data, b, c-1)
+			swap(indices, b, c-1)
+			b += 1
+			c -= 1
+		}
+
+		protect := hi-c < 5
+		if !protect && hi-c < (hi-lo)/4 {
+			dups := 0
+			if !less(data[pivot], data[hi-1], call) {
+				swap(data, c, hi-1)
+				swap(indices, c, hi-1)
+				c += 1
+				dups += 1
+			}
+			if !less(data[b-1], data[pivot], call) {
+				b -= 1
+				dups += 1
+			}
+
+			if !less(data[m], data[pivot], call) {
+				swap(data, m, b-1)
+				swap(indices, m, b-1)
+				b -= 1
+				dups += 1
+			}
+			protect = dups > 1
+		}
+		if protect {
+			for {
+				for ; a < b && !less(data[b-1], data[pivot], call); b -= 1 {
+				}
+				for ; a < b && less(data[a], data[pivot], call); a += 1 {
+				}
+				if a >= b {
+					break
+				}
+				swap(data, a, b-1)
+				swap(indices, a, b-1)
+				a += 1
+				b -= 1
+			}
+		}
+		swap(data, pivot, b-1)
+		swap(indices, pivot, b-1)
+		return b-1, c
+	}
+
+	assert(len(data) == len(indices))
+
+	a, b, max_depth := a, b, max_depth
+
+	for b-a > 12 { // only use shell sort for lengths <= 12
+		if max_depth == 0 {
+			heap_sort(data, indices, a, b, call)
+			return
+		}
+		max_depth -= 1
+		mlo, mhi := do_pivot(data, indices, a, b, call)
+		if mlo-a < b-mhi {
+			_quick_sort_general_with_indices(data, indices, a, mlo, max_depth, call, KIND)
+			a = mhi
+		} else {
+			_quick_sort_general_with_indices(data, indices, mhi, b, max_depth, call, KIND)
+			b = mlo
+		}
+	}
+	if b-a > 1 {
+		// Shell short with gap 6
+		for i in a+6..<b {
+			if less(data[i], data[i-6], call) {
+				swap(data, i, i-6)
+				swap(indices, i, i-6)
+			}
+		}
+		insertion_sort(data, indices, a, b, call)
+	}
+}

+ 24 - 16
core/sys/windows/kernel32.odin

@@ -24,6 +24,8 @@ foreign kernel32 {
 	                       lpMode: LPDWORD) -> BOOL ---
 	SetConsoleMode :: proc(hConsoleHandle: HANDLE,
 	                       dwMode: DWORD) -> BOOL ---
+	SetConsoleCursorPosition :: proc(hConsoleHandle: HANDLE,
+						   dwCursorPosition: COORD) -> BOOL ---
 
 	GetFileInformationByHandle :: proc(hFile: HANDLE, lpFileInformation: LPBY_HANDLE_FILE_INFORMATION) -> BOOL ---
 	SetHandleInformation :: proc(hObject: HANDLE,
@@ -94,6 +96,15 @@ foreign kernel32 {
 		dwCreationFlags: DWORD,
 		lpThreadId: LPDWORD,
 	) -> HANDLE ---
+	CreateRemoteThread :: proc(
+		hProcess: HANDLE,
+		lpThreadAttributes: LPSECURITY_ATTRIBUTES,
+		dwStackSize: SIZE_T,
+		lpStartAddress: proc "stdcall" (rawptr) -> DWORD,
+		lpParameter: LPVOID,
+		dwCreationFlags: DWORD,
+		lpThreadId: LPDWORD,
+	) -> HANDLE ---
 	SwitchToThread :: proc() -> BOOL ---
 	ResumeThread :: proc(thread: HANDLE) -> DWORD ---
 	GetThreadPriority :: proc(thread: HANDLE) -> c_int ---
@@ -326,6 +337,15 @@ foreign kernel32 {
 	SetEndOfFile :: proc(hFile: HANDLE) -> BOOL ---
 
 	CreatePipe :: proc(hReadPipe, hWritePipe: ^HANDLE, lpPipeAttributes: LPSECURITY_ATTRIBUTES, nSize: DWORD) -> BOOL ---
+
+	ConnectNamedPipe :: proc(hNamedPipe: HANDLE, lpOverlapped: LPOVERLAPPED,) -> BOOL ---
+	DisconnectNamedPipe :: proc(hNamedPipe: HANDLE,) -> BOOL ---
+	WaitNamedPipeW :: proc(lpNamedPipeName: LPCWSTR, nTimeOut: DWORD,) -> BOOL ---
+
+	SetConsoleCtrlHandler :: proc(HandlerRoutine: PHANDLER_ROUTINE, Add: BOOL) -> BOOL ---
+	GenerateConsoleCtrlEvent :: proc(dwCtrlEvent: DWORD, dwProcessGroupId: DWORD) -> BOOL ---
+	FreeConsole :: proc() -> BOOL ---
+	GetConsoleWindow :: proc() -> HWND ---
 }
 
 
@@ -787,21 +807,6 @@ foreign kernel32 {
 	) -> BOOL ---
 }
 
-@(default_calling_convention="stdcall")
-foreign kernel32 {
-	@(link_name="SetConsoleCtrlHandler") set_console_ctrl_handler :: proc(handler: Handler_Routine, add: BOOL) -> BOOL ---
-}
-
-Handler_Routine :: proc(dwCtrlType: Control_Event) -> BOOL
-
-Control_Event :: enum DWORD {
-	control_c = 0,
-	_break    = 1,
-	close     = 2,
-	logoff    = 5,
-	shutdown  = 6,
-}
-
 @(default_calling_convention="stdcall")
 foreign kernel32 {
 	GetProductInfo :: proc(
@@ -811,4 +816,7 @@ foreign kernel32 {
 		SpMinorVersion: DWORD,
 		product_type: ^Windows_Product_Type,
 	) -> BOOL ---
-}
+}
+
+HandlerRoutine :: proc "stdcall" (dwCtrlType: DWORD) -> BOOL
+PHANDLER_ROUTINE :: HandlerRoutine

+ 58 - 1
core/sys/windows/types.odin

@@ -979,6 +979,35 @@ WS_TILEDWINDOW      : UINT : WS_OVERLAPPED | WS_CAPTION | WS_SYSMENU | WS_THICKF
 WS_VISIBLE          : UINT : 0x1000_0000
 WS_VSCROLL          : UINT : 0x0020_0000
 
+WS_EX_ACCEPTFILES           : UINT : 0x0000_0010
+WS_EX_APPWINDOW             : UINT : 0x0004_0000
+WS_EX_CLIENTEDGE            : UINT : 0x0000_0200
+WS_EX_COMPOSITED            : UINT : 0x0200_0000
+WS_EX_CONTEXTHELP           : UINT : 0x0000_0400
+WS_EX_CONTROLPARENT         : UINT : 0x0001_0000
+WS_EX_DLGMODALFRAME         : UINT : 0x0000_0001
+WS_EX_DRAGDETECT            : UINT : 0x0000_0002 // undocumented
+WS_EX_LAYERED               : UINT : 0x0008_0000
+WS_EX_LAYOUTRTL             : UINT : 0x0040_0000
+WS_EX_LEFT                  : UINT : 0x0000_0000
+WS_EX_LEFTSCROLLBAR         : UINT : 0x0000_4000
+WS_EX_LTRREADING            : UINT : 0x0000_0000
+WS_EX_MDICHILD              : UINT : 0x0000_0040
+WS_EX_NOACTIVATE            : UINT : 0x0800_0000
+WS_EX_NOINHERITLAYOUT       : UINT : 0x0010_0000
+WS_EX_NOPARENTNOTIFY        : UINT : 0x0000_0004
+WS_EX_NOREDIRECTIONBITMAP   : UINT : 0x0020_0000
+WS_EX_OVERLAPPEDWINDOW      : UINT : WS_EX_WINDOWEDGE | WS_EX_CLIENTEDGE
+WS_EX_PALETTEWINDOW         : UINT : WS_EX_WINDOWEDGE | WS_EX_TOOLWINDOW | WS_EX_TOPMOST
+WS_EX_RIGHT                 : UINT : 0x0000_1000
+WS_EX_RIGHTSCROLLBAR        : UINT : 0x0000_0000
+WS_EX_RTLREADING            : UINT : 0x0000_2000
+WS_EX_STATICEDGE            : UINT : 0x0002_0000
+WS_EX_TOOLWINDOW            : UINT : 0x0000_0080
+WS_EX_TOPMOST               : UINT : 0x0000_0008
+WS_EX_TRANSPARENT           : UINT : 0x0000_0020
+WS_EX_WINDOWEDGE            : UINT : 0x0000_0100
+
 PBS_SMOOTH   :: 0x01
 PBS_VERTICAL :: 0x04
 
@@ -1629,6 +1658,8 @@ CONDITION_VARIABLE_INIT :: CONDITION_VARIABLE{}
 SRWLOCK_INIT :: SRWLOCK{}
 
 DETACHED_PROCESS: DWORD : 0x00000008
+CREATE_NEW_CONSOLE: DWORD : 0x00000010
+CREATE_NO_WINDOW: DWORD : 0x08000000
 CREATE_NEW_PROCESS_GROUP: DWORD : 0x00000200
 CREATE_UNICODE_ENVIRONMENT: DWORD : 0x00000400
 STARTF_USESTDHANDLES: DWORD : 0x00000100
@@ -1690,6 +1721,7 @@ PIPE_WAIT: DWORD : 0x00000000
 PIPE_TYPE_BYTE: DWORD : 0x00000000
 PIPE_REJECT_REMOTE_CLIENTS: DWORD : 0x00000008
 PIPE_READMODE_BYTE: DWORD : 0x00000000
+PIPE_ACCEPT_REMOTE_CLIENTS: DWORD : 0x00000000
 
 FD_SETSIZE :: 64
 
@@ -3378,4 +3410,29 @@ Windows_Product_Type :: enum DWORD {
 	UNDEFINED                           = 0x00000000, // An unknown product
 	WEB_SERVER                          = 0x00000011, // Web Server (full installation)
 	WEB_SERVER_CORE                     = 0x0000001D, // Web Server (core installation)
-}
+}
+
+ENABLE_ECHO_INPUT : DWORD : 0x0004
+ENABLE_INSERT_MODE : DWORD : 0x0020
+ENABLE_LINE_INPUT : DWORD : 0x0002
+ENABLE_MOUSE_INPUT : DWORD : 0x0010
+ENABLE_PROCESSED_INPUT : DWORD : 0x0001
+ENABLE_QUICK_EDIT_MODE : DWORD : 0x0040
+ENABLE_WINDOW_INPUT : DWORD : 0x0008
+ENABLE_VIRTUAL_TERMINAL_INPUT : DWORD : 0x0200
+ENABLE_PROCESSED_OUTPUT : DWORD : 0x0001
+ENABLE_WRAP_AT_EOL_OUTPUT : DWORD : 0x0002
+ENABLE_VIRTUAL_TERMINAL_PROCESSING : DWORD : 0x0004
+DISABLE_NEWLINE_AUTO_RETURN : DWORD : 0x0008
+ENABLE_LVB_GRID_WORLDWIDE : DWORD : 0x0010
+
+CTRL_C_EVENT : DWORD : 0
+CTRL_BREAK_EVENT : DWORD : 1
+CTRL_CLOSE_EVENT : DWORD : 2
+CTRL_LOGOFF_EVENT : DWORD : 5
+CTRL_SHUTDOWN_EVENT : DWORD : 6
+
+COORD :: struct {
+	X: SHORT,
+	Y: SHORT,
+}

+ 2 - 0
core/sys/windows/winerror.odin

@@ -42,6 +42,8 @@ ERROR_TIMEOUT                : DWORD : 1460
 ERROR_DATATYPE_MISMATCH      : DWORD : 1629
 ERROR_UNSUPPORTED_TYPE       : DWORD : 1630
 ERROR_NOT_SAME_OBJECT        : DWORD : 1656
+ERROR_PIPE_CONNECTED         : DWORD : 0x80070217
+ERROR_PIPE_BUSY              : DWORD : 231
 
 E_NOTIMPL :: HRESULT(-0x7fff_bfff) // 0x8000_4001
 

+ 7 - 0
src/check_builtin.cpp

@@ -341,6 +341,13 @@ bool check_builtin_objc_procedure(CheckerContext *c, Operand *operand, Ast *call
 		for (isize i = 2+arg_offset; i < ce->args.count; i++) {
 			Operand x = {};
 			check_expr(c, &x, ce->args[i]);
+			if (is_type_untyped(x.type)) {
+				gbString e = expr_to_string(x.expr);
+				gbString t = type_to_string(x.type);
+				error(x.expr, "'%.*s' expects typed parameters, got %s of type %s", LIT(builtin_name), e, t);
+				gb_string_free(t);
+				gb_string_free(e);
+			}
 			param_types[i-arg_offset] = x.type;
 		}
 

+ 4 - 1
src/check_expr.cpp

@@ -8769,7 +8769,10 @@ ExprKind check_selector_call_expr(CheckerContext *c, Operand *o, Ast *node, Type
 	Ast *first_arg = x.expr->SelectorExpr.expr;
 	GB_ASSERT(first_arg != nullptr);
 
-	first_arg->state_flags |= StateFlag_SelectorCallExpr;
+	Entity *e = entity_of_node(se->expr);
+	if (!(e != nullptr && (e->kind == Entity_Procedure || e->kind == Entity_ProcGroup))) {
+		first_arg->state_flags |= StateFlag_SelectorCallExpr;
+	}
 
 	Type *pt = base_type(x.type);
 	GB_ASSERT(pt->kind == Type_Proc);

+ 1 - 1
src/llvm_backend_expr.cpp

@@ -1924,7 +1924,7 @@ lbValue lb_emit_conv(lbProcedure *p, lbValue value, Type *t) {
 		}
 		if (dst->Union.variants.count == 1) {
 			Type *vt = dst->Union.variants[0];
-			if (internal_check_is_assignable_to(src, vt)) {
+			if (internal_check_is_assignable_to(src_type, vt)) {
 				value = lb_emit_conv(p, value, vt);
 				lbAddr parent = lb_add_local_generated(p, t, true);
 				lb_emit_store_union_variant(p, parent.addr, value, vt);

+ 2 - 3
src/llvm_backend_proc.cpp

@@ -2867,9 +2867,9 @@ lbValue lb_build_call_expr_internal(lbProcedure *p, Ast *expr) {
 		return y;
 	}
 
-	Ast *pexpr = unparen_expr(ce->proc);
+	Ast *proc_expr = unparen_expr(ce->proc);
 	if (proc_mode == Addressing_Builtin) {
-		Entity *e = entity_of_node(pexpr);
+		Entity *e = entity_of_node(proc_expr);
 		BuiltinProcId id = BuiltinProc_Invalid;
 		if (e != nullptr) {
 			id = cast(BuiltinProcId)e->Builtin.id;
@@ -2881,7 +2881,6 @@ lbValue lb_build_call_expr_internal(lbProcedure *p, Ast *expr) {
 
 	// NOTE(bill): Regular call
 	lbValue value = {};
-	Ast *proc_expr = unparen_expr(ce->proc);
 
 	Entity *proc_entity = entity_of_node(proc_expr);
 	if (proc_entity != nullptr) {

+ 12 - 2
src/llvm_backend_stmt.cpp

@@ -646,7 +646,7 @@ void lb_build_range_stmt_struct_soa(lbProcedure *p, AstRangeStmt *rs, Scope *sco
 
 
 	lbAddr array = lb_build_addr(p, expr);
-	if (is_type_pointer(type_deref(lb_addr_type(array)))) {
+	if (is_type_pointer(lb_addr_type(array))) {
 		array = lb_addr(lb_addr_load(p, array));
 	}
 	lbValue count = lb_soa_struct_len(p, lb_addr_load(p, array));
@@ -1959,8 +1959,18 @@ void lb_build_assign_stmt(lbProcedure *p, AstAssignStmt *as) {
 	} else {
 		lbAddr lhs = lb_build_addr(p, as->lhs[0]);
 		lbValue value = lb_build_expr(p, as->rhs[0]);
-
 		Type *lhs_type = lb_addr_type(lhs);
+
+		// NOTE(bill): Allow for the weird edge case of:
+		// array *= matrix
+		if (op == Token_Mul && is_type_matrix(value.type) && is_type_array(lhs_type)) {
+			lbValue old_value = lb_addr_load(p, lhs);
+			Type *type = old_value.type;
+			lbValue new_value = lb_emit_vector_mul_matrix(p, old_value, value, type);
+			lb_addr_store(p, lhs, new_value);
+			return;
+		}
+
 		if (is_type_array(lhs_type)) {
 			lb_build_assign_stmt_array(p, op, lhs, value);
 			return;

+ 6 - 1
tests/core/build.bat

@@ -69,4 +69,9 @@ echo ---
 echo ---
 echo Running core:text/i18n tests
 echo ---
-%PATH_TO_ODIN% run text\i18n %COMMON% -out:test_core_i18n.exe
+%PATH_TO_ODIN% run text\i18n %COMMON% -out:test_core_i18n.exe
+
+echo ---
+echo Running core:slice tests
+echo ---
+%PATH_TO_ODIN% run slice %COMMON% -out:test_core_slice.exe

+ 97 - 0
tests/core/slice/test_core_slice.odin

@@ -0,0 +1,97 @@
+package test_core_slice
+
+import "core:slice"
+import "core:testing"
+import "core:fmt"
+import "core:os"
+import "core:math/rand"
+
+TEST_count := 0
+TEST_fail  := 0
+
+when ODIN_TEST {
+	expect  :: testing.expect
+	log     :: testing.log
+} else {
+	expect  :: proc(t: ^testing.T, condition: bool, message: string, loc := #caller_location) {
+		TEST_count += 1
+		if !condition {
+			TEST_fail += 1
+			fmt.printf("[%v] %v\n", loc, message)
+			return
+		}
+	}
+	log     :: proc(t: ^testing.T, v: any, loc := #caller_location) {
+		fmt.printf("[%v] ", loc)
+		fmt.printf("log: %v\n", v)
+	}
+}
+
+main :: proc() {
+	t := testing.T{}
+	test_sort_with_indices(&t)
+
+	fmt.printf("%v/%v tests successful.\n", TEST_count - TEST_fail, TEST_count)
+	if TEST_fail > 0 {
+		os.exit(1)
+	}
+}
+
+@test
+test_sort_with_indices :: proc(t: ^testing.T) {
+	seed := rand.uint64()
+	fmt.printf("Random seed: %v\n", seed)
+
+	// Test sizes are all prime.
+	test_sizes :: []int{7, 13, 347, 1031, 10111, 100003}
+
+	for test_size in test_sizes {
+		fmt.printf("Sorting %v random u64 values along with index.\n", test_size)
+
+		r := rand.create(seed)
+
+		vals  := make([]u64, test_size)
+		f_idx := make([]int, test_size) // Forward index, will be sorted
+		r_idx := make([]int, test_size) // Reverse index
+
+		defer {
+			delete(vals)
+			delete(f_idx)
+			delete(r_idx)
+		}
+
+		// Set up test values
+		for _, i in vals {
+			vals[i]     = rand.uint64(&r)
+			f_idx[i] = i
+		}
+
+		// Sort
+		slice.sort_with_indices(vals, f_idx)
+
+		// Verify sorted test values
+		rand.init(&r, seed)
+
+		for v, i in f_idx {
+			r_idx[v] = i
+		}
+
+		last: u64
+		for v, i in vals {
+			if i > 0 {
+				val_pass := v >= last
+				expect(t, val_pass, "Expected values to have been sorted.")
+				if !val_pass {
+					break
+				}
+			}
+
+			idx_pass := vals[r_idx[i]] == rand.uint64(&r)
+			expect(t, idx_pass, "Expected index to have been sorted.")
+			if !idx_pass {
+				break
+			}
+			last = v
+		}
+	}
+}

+ 1 - 1
vendor/sdl2/sdl2.odin

@@ -200,7 +200,7 @@ Locale :: struct {
 
 @(default_calling_convention="c", link_prefix="SDL_")
 foreign lib {
-	GetPreferredLocales :: proc() -> ^Locale ---
+	GetPreferredLocales :: proc() -> [^]Locale ---
 }
 
 // misc