Skip to content

Commit

Permalink
feature(jsoo): recognize toplevel variant
Browse files Browse the repository at this point in the history
Signed-off-by: Hugo Heuzard <[email protected]>
  • Loading branch information
hhugo authored and rgrinberg committed Jan 28, 2023
1 parent 819052b commit 86bc1bf
Show file tree
Hide file tree
Showing 2 changed files with 14 additions and 4 deletions.
2 changes: 1 addition & 1 deletion CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,7 @@ Unreleased
enabled (#6645, @hhugo)

- Fix *js_of_ocaml* separate compilation rules when `--enable=effects`
or `--enable=use-js-string` is used. (#6714, #6828, @hhugo)
,`--enable=use-js-string` or `--toplevel` is used. (#6714, #6828, #6920, @hhugo)

- Fix *js_of_ocaml* separate compilation in presence of linkall (#6832, #6916, @hhugo)

Expand Down
16 changes: 13 additions & 3 deletions src/dune_rules/jsoo/jsoo_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -16,19 +16,25 @@ end = struct
type t =
{ js_string : bool option
; effects : bool option
; toplevel : bool option
}

let default = { js_string = None; effects = None }
let default = { js_string = None; effects = None; toplevel = None }

let bool_opt = [ None; Some true; Some false ]

let all =
List.concat_map bool_opt ~f:(fun js_string ->
List.concat_map bool_opt ~f:(fun effects -> [ { js_string; effects } ]))
List.concat_map bool_opt ~f:(fun effects ->
List.concat_map bool_opt ~f:(fun toplevel ->
[ { js_string; effects; toplevel } ])))

let get t =
List.filter_map
[ ("use-js-string", t.js_string); ("effects", t.effects) ]
[ ("use-js-string", t.js_string)
; ("effects", t.effects)
; ("toplevel", t.toplevel)
]
~f:(fun (n, v) ->
match v with
| None -> None
Expand All @@ -38,6 +44,7 @@ end = struct
match name with
| "use-js-string" -> { acc with js_string = Some v }
| "effects" -> { acc with effects = Some v }
| "toplevel" -> { acc with toplevel = Some v }
| _ -> acc

let path t =
Expand Down Expand Up @@ -72,12 +79,15 @@ end = struct
match String.drop_prefix maybe_disable ~prefix:"--disable=" with
| Some name -> loop (set acc name false) rest
| _ -> assert false)
| "--toplevel" :: rest -> loop (set acc "toplevel" true) rest
| _ :: rest -> loop acc rest
in
loop default l

let to_flags t =
List.concat_map (get t) ~f:(function
| "toplevel", true -> [ "--toplevel" ]
| "toplevel", false -> []
| name, true -> [ "--enable"; name ]
| name, false -> [ "--disable"; name ])
end
Expand Down

0 comments on commit 86bc1bf

Please sign in to comment.