Skip to content

Commit

Permalink
Extend explicit_js_mode to libraries
Browse files Browse the repository at this point in the history
Signed-off-by: Nicolás Ojeda Bär <n.oje.bar@gmail.com>
  • Loading branch information
nojb committed Apr 4, 2019
1 parent 4fd8134 commit 3cbbec1
Show file tree
Hide file tree
Showing 7 changed files with 17 additions and 16 deletions.
5 changes: 1 addition & 4 deletions src/binary_kind.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@ type t =
| Exe
| Object
| Shared_object
| Js

let decode =
let open Dune_lang.Decoder in
Expand All @@ -14,20 +13,18 @@ let decode =
; "exe" , return Exe
; "object" , return Object
; "shared_object" , return Shared_object
; "js" , Syntax.since Stanza.syntax (1, 9) >>> return Js
]

let to_string = function
| C -> "c"
| Exe -> "exe"
| Object -> "object"
| Shared_object -> "shared_object"
| Js -> "js"

let pp fmt t =
Format.pp_print_string fmt (to_string t)

let encode t =
Dune_lang.unsafe_atom_of_string (to_string t)

let all = [C; Exe; Object; Shared_object; Js]
let all = [C; Exe; Object; Shared_object]
1 change: 0 additions & 1 deletion src/binary_kind.mli
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@ type t =
| Exe
| Object
| Shared_object
| Js

include Dune_lang.Conv with type t := t

Expand Down
10 changes: 7 additions & 3 deletions src/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -745,6 +745,7 @@ module Mode_conf = struct
| Byte
| Native
| Best
| Js
let compare (a : t) b = compare a b
end
include T
Expand All @@ -754,12 +755,14 @@ module Mode_conf = struct
[ "byte" , Byte
; "native", Native
; "best" , Best
; "js" , Js
]

let to_string = function
| Byte -> "byte"
| Native -> "native"
| Best -> "best"
| Js -> "js"

let pp fmt t =
Format.pp_print_string fmt (to_string t)
Expand All @@ -776,7 +779,7 @@ module Mode_conf = struct

let eval t ~has_native =
let has_best = mem t Best in
let byte = mem t Byte || (has_best && (not has_native)) in
let byte = mem t Js || mem t Byte || (has_best && (not has_native)) in
let native = has_native && (mem t Native || has_best) in
{ Mode.Dict.byte; native }
end
Expand Down Expand Up @@ -1309,7 +1312,7 @@ module Executables = struct
let shared_object = make Best Shared_object

let byte_exe = make Byte Exe
let byte_js = make Byte Js
let js = make Js Exe

let native_exe = make Native Exe
let native_object = make Native Object
Expand All @@ -1327,7 +1330,7 @@ module Executables = struct
; "shared_object" , shared_object
; "byte" , byte
; "native" , native
; "js" , byte_js
; "js" , js
]

let simple =
Expand Down Expand Up @@ -1449,6 +1452,7 @@ module Executables = struct
match mode.mode with
| Native | Best -> ".exe"
| Byte -> ".bc"
| Js -> ".bc.js"
in
Names.install_conf names ~ext
in
Expand Down
3 changes: 2 additions & 1 deletion src/dune_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -154,6 +154,7 @@ module Mode_conf : sig
| Byte
| Native
| Best (** [Native] if available and [Byte] if not *)
| Js

val decode : t Dune_lang.Decoder.t
val compare : t -> t -> Ordering.t
Expand Down Expand Up @@ -273,7 +274,7 @@ module Executables : sig
val object_ : t
val shared_object : t
val byte : t
val byte_js : t
val js : t
val native : t

val compare : t -> t -> Ordering.t
Expand Down
7 changes: 3 additions & 4 deletions src/exe.ml
Original file line number Diff line number Diff line change
Expand Up @@ -60,25 +60,25 @@ module Linkage = struct
| Byte -> Byte
| Native -> Native
| Best -> Native
| Js -> Byte
in
let real_mode : Mode.t =
match m.mode with
| Byte -> Byte
| Native -> Native
| Best -> if Option.is_some ctx.ocamlopt then Native else Byte
| Js -> Byte
in
let ext =
match wanted_mode, m.kind with
| Byte , C -> ".bc.c"
| Native , C -> Errors.fail m.loc "C file generation only supports bytecode!"
| Byte , Exe -> ".bc"
| Byte , Exe -> if m.mode = Js then ".bc.js" else ".bc"
| Native , Exe -> ".exe"
| Byte , Object -> ".bc" ^ ctx.ext_obj
| Native , Object -> ".exe" ^ ctx.ext_obj
| Byte , Shared_object -> ".bc" ^ ctx.ext_dll
| Native , Shared_object -> ctx.ext_dll
| Byte , Js -> ".bc.js"
| Native , Js -> Errors.fail m.loc "Javascript generation only supports bytecode!"
in
let flags =
match m.kind with
Expand Down Expand Up @@ -107,7 +107,6 @@ module Linkage = struct
| Byte ->
so_flags
end
| Js -> []
in
{ ext
; mode = real_mode
Expand Down
4 changes: 2 additions & 2 deletions src/exe_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -47,14 +47,14 @@ let executables_rules ~sctx ~dir ~dir_kind ~expander
Module.Name.pp mod_name)
in

let has_js = Dune_file.Executables.Link_mode.(Set.mem exes.modes byte_js) in
let has_js = Dune_file.Executables.Link_mode.(Set.mem exes.modes js) in

let linkages =
let module L = Dune_file.Executables.Link_mode in
let ctx = SC.context sctx in
let modes =
if has_js then
L.Set.remove (L.Set.add exes.modes L.byte) L.byte_js
L.Set.remove (L.Set.add exes.modes L.byte) L.js
else
exes.modes
in
Expand Down
3 changes: 2 additions & 1 deletion src/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -338,6 +338,7 @@ module Gen (P : sig val sctx : Super_context.t end) = struct
let modules = Compilation_context.modules cctx in
let js_of_ocaml = lib.buildable.js_of_ocaml in
let vimpl = Compilation_context.vimpl cctx in
let explicit_js_mode = Dune_project.explicit_js_mode (Scope.project (Compilation_context.scope cctx)) in
let modules =
match lib.stdlib with
| Some { exit_module = Some name; _ } -> begin
Expand Down Expand Up @@ -387,7 +388,7 @@ module Gen (P : sig val sctx : Super_context.t end) = struct
build_lib lib ~expander ~flags ~dir ~mode ~top_sorted_modules
~modules));
(* Build *.cma.js *)
if modes.byte then
if Mode_conf.(Set.mem lib.modes Js) || (not explicit_js_mode && modes.byte) then
SC.add_rules sctx ~dir (
let src =
Library.archive lib ~dir
Expand Down

0 comments on commit 3cbbec1

Please sign in to comment.