Skip to content

Commit

Permalink
refactor(melange): make modes field an Ordered_set_lang instance
Browse files Browse the repository at this point in the history
Signed-off-by: Antonio Nuno Monteiro <[email protected]>
  • Loading branch information
anmonteiro committed Dec 1, 2022
1 parent 1e835d9 commit 5ed44f1
Show file tree
Hide file tree
Showing 2 changed files with 35 additions and 4 deletions.
32 changes: 29 additions & 3 deletions src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -467,6 +467,15 @@ module Mode_conf = struct

let to_dyn t = Dyn.variant (to_string t) []

let equal x y =
match (x, y) with
| Ocaml o1, Ocaml o2 -> (
match compare o1 o2 with
| Eq -> true
| _ -> false)
| Ocaml _, _ | _, Ocaml _ -> false
| Melange, Melange -> true

module Map = struct
type nonrec 'a t =
{ ocaml : 'a Map.t
Expand Down Expand Up @@ -609,9 +618,7 @@ module Library = struct
Ordered_set_lang.Unexpanded.field "c_library_flags"
and+ virtual_deps =
field "virtual_deps" (repeat (located Lib_name.decode)) ~default:[]
and+ modes =
field "modes" Mode_conf.Lib.Set.decode
~default:(Mode_conf.Lib.Set.default stanza_loc)
and+ modes = field_o "modes" Ordered_set_lang.decode
and+ kind = field "kind" Lib_kind.decode ~default:Lib_kind.Normal
and+ optional = field_b "optional"
and+ no_dynlink = field_b "no_dynlink"
Expand Down Expand Up @@ -712,6 +719,25 @@ module Library = struct
(Package.Name.to_string (Package.name public.package))
]
in
let modes =
match modes with
| None -> Mode_conf.Lib.Set.default stanza_loc
| Some modes ->
let modes =
Ordered_set_lang.eval modes
~parse:(fun ~loc s ->
let mode =
Dune_lang.Decoder.parse Mode_conf.Lib.decode
(Dune_project.parsing_context project)
(Atom (loc, Dune_lang.Atom.of_string s))
in
(mode, Mode_conf.Kind.Requested loc))
~eq:(fun (a, _) (b, _) -> Mode_conf.Lib.equal a b)
~standard:[ (Ocaml Best, Mode_conf.Kind.Requested stanza_loc) ]
in
let modes = Mode_conf.Lib.Set.of_list modes in
modes
in
Option.both virtual_modules implements
|> Option.iter ~f:(fun (virtual_modules, (_, impl)) ->
User_error.raise
Expand Down
7 changes: 6 additions & 1 deletion test/blackbox-tests/test-cases/melange/promote-with-lib.t
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Test melange.emit promotion
$ mkdir lib
$ cat > lib/dune <<EOF
> (library
> (modes melange)
> (modes :standard melange)
> (name mylib))
> EOF

Expand All @@ -34,6 +34,11 @@ Test melange.emit promotion

$ dune build @dist

Library has `(modes :standard)` so it also builds for bytecode / native

$ dune build lib/.mylib.objs/byte/mylib.cmo
$ dune build lib/.mylib.objs/native/mylib.cmx

Targets are promoted to the source tree

$ ls ./dist
Expand Down

0 comments on commit 5ed44f1

Please sign in to comment.