Skip to content

Commit

Permalink
Reformat; update CHANGES.md
Browse files Browse the repository at this point in the history
Signed-off-by: Louis Gesbert <[email protected]>
  • Loading branch information
AltGr committed Feb 11, 2021
1 parent 21a821b commit 632ccec
Show file tree
Hide file tree
Showing 2 changed files with 25 additions and 20 deletions.
2 changes: 2 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
Unreleased
----------

- Add a META rule for 'compiler-libs.native-toplevel' (#4175, @altgr)

- Fixed a bug that could result in needless recompilation under Windows due to
case differences in the result of `Sys.getcwd` (observed under `emacs`).
(#3966, @nojb).
Expand Down
43 changes: 23 additions & 20 deletions src/dune_rules/findlib/meta.ml
Original file line number Diff line number Diff line change
Expand Up @@ -136,17 +136,17 @@ let plugin p s = rule "plugin" [ Pos p ] Set s

let exists_if s = rule "exists_if" [] Set s

let archives ?(kind=[Mode.Byte; Mode.Native]) name =
let archives ?(kind = [ Mode.Byte; Mode.Native ]) name =
List.filter_map
[ Mode.Byte, archive, Mode.compiled_lib_ext
; Mode.Native, archive, Mode.compiled_lib_ext
; Mode.Byte, plugin, Mode.compiled_lib_ext
; Mode.Native, plugin, Mode.plugin_ext
]
~f:(fun (k, f, ext) ->
if List.mem k ~set:kind
then Some (f (Mode.to_string k) (name ^ ext k))
else None)
[ (Mode.Byte, archive, Mode.compiled_lib_ext)
; (Mode.Native, archive, Mode.compiled_lib_ext)
; (Mode.Byte, plugin, Mode.compiled_lib_ext)
; (Mode.Native, plugin, Mode.plugin_ext)
] ~f:(fun (k, f, ext) ->
if List.mem k ~set:kind then
Some (f (Mode.to_string k) (name ^ ext k))
else
None)

(* fake entry we use to pass down the list of toplevel modules for root_module *)
let main_modules names =
Expand All @@ -155,7 +155,8 @@ let main_modules names =

let builtins ~stdlib_dir ~version:ocaml_version =
let version = version "[distributed with Ocaml]" in
let simple name ?(labels = false) ?dir ?archive_name ?kind ?exists_if_ext deps =
let simple name ?(labels = false) ?dir ?archive_name ?kind ?exists_if_ext deps
=
let archive_name =
match archive_name with
| None -> name
Expand All @@ -176,11 +177,11 @@ let builtins ~stdlib_dir ~version:ocaml_version =
::
( match dir with
| None -> []
| Some d -> [ directory d ] ) @
( match exists_if_ext with
| None -> []
| Some ext -> [ exists_if (archive_name ^ ext) ] ) @
archives
| Some d -> [ directory d ] )
@ ( match exists_if_ext with
| None -> []
| Some ext -> [ exists_if (archive_name ^ ext) ] )
@ archives
}
in
let dummy name =
Expand All @@ -190,8 +191,8 @@ let builtins ~stdlib_dir ~version:ocaml_version =
in
let compiler_libs =
let sub name ?kind ?exists_if_ext deps =
Package (simple name deps ~archive_name:("ocaml" ^ name) ?kind
?exists_if_ext)
Package
(simple name deps ~archive_name:("ocaml" ^ name) ?kind ?exists_if_ext)
in
{ name = Some (Lib_name.of_string "compiler-libs")
; entries =
Expand All @@ -201,8 +202,10 @@ let builtins ~stdlib_dir ~version:ocaml_version =
; sub "common" []
; sub "bytecomp" [ "compiler-libs.common" ]
; sub "optcomp" [ "compiler-libs.common" ]
; sub "toplevel" [ "compiler-libs.bytecomp" ] ~kind:[Byte]
; sub "toplevel" [ "compiler-libs.optcomp"; "dynlink" ] ~kind:[Native]
; sub "toplevel" [ "compiler-libs.bytecomp" ] ~kind:[ Byte ]
; sub "toplevel"
[ "compiler-libs.optcomp"; "dynlink" ]
~kind:[ Native ]
~exists_if_ext:(Mode.compiled_lib_ext Native)
]
}
Expand Down

0 comments on commit 632ccec

Please sign in to comment.