Skip to content

Commit

Permalink
fix
Browse files Browse the repository at this point in the history
  • Loading branch information
hhugo committed Jul 10, 2023
1 parent 98dbb58 commit 8a9d9a4
Showing 1 changed file with 23 additions and 15 deletions.
38 changes: 23 additions & 15 deletions src/dune_rules/jsoo/jsoo_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ module Config : sig

val of_flags : string list -> t

val to_flags : t -> string list
val to_flags : current:string list -> t -> string list
end = struct
type t =
{ js_string : bool option
Expand Down Expand Up @@ -84,12 +84,16 @@ end = struct
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 ])
let to_flags ~current t =
current
:: List.map (get t) ~f:(function
| "toplevel", true ->
if List.mem current "--toplevel" ~equal:String.equal then []
else [ "--toplevel" ]
| "toplevel", false -> []
| name, true -> [ "--enable"; name ]
| name, false -> [ "--disable"; name ])
|> List.concat
end

module Version = struct
Expand Down Expand Up @@ -175,23 +179,27 @@ let js_of_ocaml_rule sctx ~sub_command ~dir ~(flags : _ Js_of_ocaml.Flags.t)
let open Memo.O in
let+ jsoo = jsoo ~dir sctx
and+ flags = Super_context.js_of_ocaml_flags sctx ~dir flags in
let flags =
match sub_command with
| Compile -> flags.compile
| Link -> flags.link
| Build_runtime -> flags.build_runtime
in
Command.run ~dir:(Path.build dir) jsoo
[ (match sub_command with
| Compile -> S []
| Link -> A "link"
| Build_runtime -> A "build-runtime")
; Command.Args.dyn
(match sub_command with
| Compile -> flags.compile
| Link -> flags.link
| Build_runtime -> flags.build_runtime)
; (match config with
| None -> S []
| None ->
Dyn
(Action_builder.map flags ~f:(fun flags ->
Command.Args.S (List.map flags ~f:(fun x -> Command.Args.A x))))
| Some config ->
Dyn
(Action_builder.map config ~f:(fun config ->
(Action_builder.map2 flags config ~f:(fun flags config ->
Command.Args.S
(List.map (Config.to_flags config) ~f:(fun x ->
(List.map (Config.to_flags ~current:flags config) ~f:(fun x ->
Command.Args.A x)))))
; A "-o"
; Target target
Expand Down

0 comments on commit 8a9d9a4

Please sign in to comment.