@@ -956,10 +956,15 @@ module Library = struct
956956 ; asm_files : asm_file list
957957 }
958958
959- let keep_asm { File_kind. syntax; arch; os; assembler = _ } ~ccomp_type ~architecture =
959+ let keep_asm
960+ { File_kind. syntax; arch; os; assembler = _ }
961+ ~ccomp_type
962+ ~architecture
963+ ~os_type
964+ =
960965 (match os with
961- | Some `Unix -> Sys. os_type = " Unix"
962- | Some `Win -> Sys. os_type = " Win32"
966+ | Some `Unix -> String. equal os_type " Unix"
967+ | Some `Win -> String. equal os_type " Win32"
963968 | None -> true )
964969 && (match syntax, ccomp_type with
965970 | `Intel , "msvc" -> true
@@ -987,6 +992,8 @@ module Library = struct
987992 ; special_builtin_support = build_info_module
988993 }
989994 ~ocaml_config
995+ ~word_size
996+ ~os_type
990997 =
991998 let files = scan ~dir ~scan_subdirs in
992999 let modules =
@@ -1064,23 +1071,23 @@ module Library = struct
10641071 then (
10651072 let extra_flags =
10661073 if String. is_prefix ~prefix: " blake3_" fn
1067- then (
1068- match architecture with
1069- | "x86" | "i386" | "i486" | "i586" | "i686" ->
1074+ then
1075+ if String. equal os_type " Cygwin " || String. equal word_size " 32 "
1076+ then
10701077 [ " -DBLAKE3_NO_SSE2"
10711078 ; " -DBLAKE3_NO_SSE41"
10721079 ; " -DBLAKE3_NO_AVX2"
10731080 ; " -DBLAKE3_NO_AVX512"
10741081 ]
1075- | _ -> [] )
1082+ else []
10761083 else []
10771084 in
10781085 `Left { flags = extra_flags @ c.flags; name = fn })
10791086 else `Skip
10801087 | Ml | Mli | Mly | Mll -> `Middle fn
10811088 | Header -> `Skip
10821089 | Asm asm ->
1083- if keep_asm asm ~ccomp_type ~architecture
1090+ if keep_asm asm ~ccomp_type ~architecture ~os_type
10841091 then (
10851092 let out_file = Filename. chop_extension fn ^ ext_obj in
10861093 `Right
@@ -1192,7 +1199,12 @@ let get_dependencies libraries =
11921199 deps
11931200;;
11941201
1195- let assemble_libraries { local_libraries; target = _ , main ; _ } ~ocaml_config =
1202+ let assemble_libraries
1203+ { local_libraries; target = _ , main ; _ }
1204+ ~ocaml_config
1205+ ~word_size
1206+ ~os_type
1207+ =
11961208 (* In order to assemble all the sources in one place, the executables
11971209 modules are also put in a namespace *)
11981210 let task_lib =
@@ -1206,7 +1218,8 @@ let assemble_libraries { local_libraries; target = _, main; _ } ~ocaml_config =
12061218 ; special_builtin_support = None
12071219 }
12081220 in
1209- local_libraries @ [ task_lib ] |> Fiber. parallel_map ~f: (Library. process ~ocaml_config )
1221+ local_libraries @ [ task_lib ]
1222+ |> Fiber. parallel_map ~f: (Library. process ~ocaml_config ~word_size ~os_type )
12101223;;
12111224
12121225type status =
@@ -1404,7 +1417,9 @@ let main () =
14041417 | Unix. Unix_error (Unix. EEXIST, _ , _ ) -> () );
14051418 Config. ocaml_config ()
14061419 >> = fun ocaml_config ->
1407- assemble_libraries ~ocaml_config task
1420+ let word_size = String.Map. find " word_size" ocaml_config in
1421+ let os_type = String.Map. find " os_type" ocaml_config in
1422+ assemble_libraries ~ocaml_config ~word_size ~os_type task
14081423 >> = fun libraries ->
14091424 let c_files =
14101425 List. map ~f: (fun (lib : Library.t ) -> lib.c_files) libraries |> List. concat
0 commit comments