Skip to content

Commit 096fc39

Browse files
committed
refactor(boot): simplify handling of arch values
We unify the type of architectures which allows us to simplify some of the conditional compilation based on architecture. Signed-off-by: Ali Caglayan <[email protected]>
1 parent ff0765d commit 096fc39

File tree

1 file changed

+15
-16
lines changed

1 file changed

+15
-16
lines changed

boot/duneboot.ml

Lines changed: 15 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -1168,13 +1168,13 @@ end
11681168
module File_kind = struct
11691169
type asm =
11701170
{ syntax : [ `Gas | `Intel ]
1171-
; arch : [ `Amd64 ] option
1171+
; arch : Arch.t option
11721172
; os : [ `Win | `Unix ] option
11731173
; assembler : [ `C_comp | `Msvc_asm ]
11741174
}
11751175

11761176
type c =
1177-
{ arch : [ `Arm64 | `X86 ] option
1177+
{ arch : Arch.t option
11781178
; flags : string list
11791179
}
11801180

@@ -1213,11 +1213,11 @@ module File_kind = struct
12131213
let fn = Filename.remove_extension fn in
12141214
let check suffix = String.ends_with fn ~suffix in
12151215
if check "x86-64_unix"
1216-
then Some `Unix, Some `Amd64, `C_comp
1216+
then Some `Unix, Some `amd64, `C_comp
12171217
else if check "x86-64_windows_gnu"
1218-
then Some `Win, Some `Amd64, `C_comp
1218+
then Some `Win, Some `amd64, `C_comp
12191219
else if check "x86-64_windows_msvc"
1220-
then Some `Win, Some `Amd64, `Msvc_asm
1220+
then Some `Win, Some `amd64, `Msvc_asm
12211221
else None, None, `C_comp
12221222
in
12231223
Some (Asm { syntax; arch; os; assembler })
@@ -1227,7 +1227,7 @@ module File_kind = struct
12271227
let check suffix = String.ends_with fn ~suffix in
12281228
let x86 gnu _msvc =
12291229
(* CR rgrinberg: select msvc flags on windows *)
1230-
Some `X86, gnu
1230+
Some `amd64, gnu
12311231
in
12321232
if check "_sse2"
12331233
then x86 [ "-msse2" ] [ "/arch:SSE2" ]
@@ -1238,7 +1238,7 @@ module File_kind = struct
12381238
else if check "_avx512"
12391239
then x86 [ "-mavx512f"; "-mavx512vl"; "-mavx512bw" ] [ "/arch:AVX512" ]
12401240
else if String.ends_with fn ~suffix:"_neon"
1241-
then Some `Arm64, []
1241+
then Some `arm64, []
12421242
else None, []
12431243
in
12441244
Some (C { arch; flags })
@@ -1415,6 +1415,12 @@ module Library = struct
14151415
; asm_files : Source.asm_file list
14161416
}
14171417

1418+
let is_target_arch ~architecture (arch : Arch.t option) =
1419+
match arch with
1420+
| None -> true
1421+
| Some arch -> architecture = arch
1422+
;;
1423+
14181424
let keep_asm
14191425
{ File_kind.syntax; arch; os; assembler = _ }
14201426
~ccomp_type
@@ -1430,18 +1436,11 @@ module Library = struct
14301436
| `Gas, `Msvc -> false
14311437
| `Gas, _ -> true
14321438
| `Intel, _ -> false)
1433-
&&
1434-
match arch, architecture with
1435-
| None, _ -> true
1436-
| Some `Amd64, `amd64 -> true
1437-
| Some `Amd64, _ -> false
1439+
&& is_target_arch ~architecture arch
14381440
;;
14391441

14401442
let keep_c { File_kind.arch; flags = _ } ~architecture =
1441-
match arch with
1442-
| None -> true
1443-
| Some `Arm64 -> architecture = `arm64
1444-
| Some `X86 -> architecture = `amd64
1443+
is_target_arch ~architecture arch
14451444
;;
14461445

14471446
let make_c (c : File_kind.c) ~fn ~os_type ~word_size =

0 commit comments

Comments
 (0)