Skip to content

Commit

Permalink
Merge pull request #1941 from nojb/explicit_js_mode
Browse files Browse the repository at this point in the history
Explicit js mode
  • Loading branch information
nojb authored Jul 22, 2019
2 parents c85fd6d + 998e1ca commit 4217520
Show file tree
Hide file tree
Showing 32 changed files with 247 additions and 53 deletions.
6 changes: 6 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,8 @@
is done to prevent the accidental collision with library dependencies of the
executable. (#2364, fixes #2292, @rgrinberg)

- Enable `(explicit_js_mode)` by default. (#1941, @nojb)

1.11.0 (unreleased)
-------------------

Expand Down Expand Up @@ -108,6 +110,10 @@
framework with a variable (#2313, @mlasson, original idea by @diml, review
by @rgrinberg).

- New binary kind `js` for executables in order to explicitly enable Javascript
targets, and a switch `(explicit_js_mode)` to require this mode in order to
declare JS targets corresponding to executables. (#1941, @nojb)

1.10.0 (04/06/2019)
-------------------

Expand Down
20 changes: 20 additions & 0 deletions doc/advanced-topics.rst
Original file line number Diff line number Diff line change
Expand Up @@ -268,6 +268,26 @@ Starting from dune 2.0, dune mangles compilation units of executables by
default. However, this can still be turned off using ``(wrapped_executables
false)``

.. _explicit-js-mode:

Explicit JS mode
================

By default, Javascript targets are defined for every bytecode executable that
dune knows about. This is not very precise and does not interact well with the
``@all`` alias (eg, the ``@all`` alias will try to build JS targets
corresponding to every ``test`` stanza). In order to better control the
compilation of JS targets, this behaviour can be turned off by using
``(explicit_js_mode)`` in the ``dune-project`` file.

When explicit JS mode is enabled, an explicit `js` mode needs to be added to the
``(modes ...)`` field of executables in order to trigger JS
compilation. Explicit JS targets declared like this will be attached to the
``@all`` alias.

Starting from dune 2.0 this new behaviour will be the default and JS compilation
of binaries will need to be explicitly declared.

.. _dialects-main:

Dialects
Expand Down
4 changes: 4 additions & 0 deletions doc/dune-files.rst
Original file line number Diff line number Diff line change
Expand Up @@ -341,6 +341,8 @@ compilation is not available.
- ``shared_object`` for producing object files that can be dynamically
loaded into an application. This mode can be used to write a plugin
in OCaml for a non-OCaml application.
- ``js`` for producing Javascript from bytecode executables, see
:ref:`explicit-js-mode`.

For instance the following ``executables`` stanza will produce byte
code executables and native shared objects:
Expand All @@ -359,6 +361,7 @@ Additionally, you can use the following short-hands:
- ``shared_object`` for ``(best shared_object)``
- ``byte`` for ``(byte exe)``
- ``native`` for ``(native exe)``
- ``js`` for ``(byte js)``

For instance the following ``modes`` fields are all equivalent:

Expand All @@ -381,6 +384,7 @@ native/best object .exe%{ext_obj}
byte shared_object .bc%{ext_dll}
native/best shared_object %{ext_dll}
byte c .bc.c
byte js .bc.js
================ ============= =================

Where ``%{ext_obj}`` and ``%{ext_dll}`` are the extensions for object
Expand Down
1 change: 1 addition & 0 deletions dune-project
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
(implicit_transitive_deps false)
(generate_opam_files true)
(wrapped_executables true)
(explicit_js_mode)

(license MIT)
(maintainers "Jane Street Group, LLC <[email protected]>")
Expand Down
5 changes: 4 additions & 1 deletion src/binary_kind.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ type t =
| Exe
| Object
| Shared_object
| Js

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

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

let to_dyn t =
let open Dyn.Encoder in
Expand All @@ -28,4 +31,4 @@ let to_dyn t =
let encode t =
Dune_lang.unsafe_atom_of_string (to_string t)

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

include Dune_lang.Conv with type t := t

Expand Down
1 change: 1 addition & 0 deletions src/cinaps.ml
Original file line number Diff line number Diff line change
Expand Up @@ -127,6 +127,7 @@ let gen_rules sctx t ~dir ~scope ~dir_kind =
~requires_compile:(Lib.Compile.direct_requires compile_info)
~requires_link:(Lib.Compile.requires_link compile_info)
~flags:(Ocaml_flags.of_list ["-w"; "-24"])
~js_of_ocaml:None
~dynlink:false
~package:None
in
Expand Down
2 changes: 1 addition & 1 deletion src/compilation_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -91,7 +91,7 @@ let create ~super_context ~scope ~expander ~obj_dir
?(dir_kind=Dune_lang.File_syntax.Dune)
~modules ~flags ~requires_compile ~requires_link
?(preprocessing=Preprocessing.dummy) ?(no_keep_locs=false)
~opaque ?stdlib ?js_of_ocaml ~dynlink ?sandbox ~package ?vimpl () =
~opaque ?stdlib ~js_of_ocaml ~dynlink ?sandbox ~package ?vimpl () =
let requires_compile =
if Dune_project.implicit_transitive_deps (Scope.project scope) then
Lazy.force requires_link
Expand Down
2 changes: 1 addition & 1 deletion src/compilation_context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ val create
-> ?no_keep_locs : bool
-> opaque : bool
-> ?stdlib : Dune_file.Library.Stdlib.t
-> ?js_of_ocaml : Dune_file.Js_of_ocaml.t
-> js_of_ocaml : Dune_file.Js_of_ocaml.t option
-> dynlink : bool
-> ?sandbox : bool
-> package : Package.t option
Expand Down
4 changes: 3 additions & 1 deletion src/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1526,6 +1526,7 @@ module Executables = struct

let byte = byte_exe
let native = native_exe
let js = make Byte Js

let installable_modes =
[exe; native; byte]
Expand All @@ -1536,6 +1537,7 @@ module Executables = struct
; "shared_object" , shared_object
; "byte" , byte
; "native" , native
; "js" , js
]

let simple =
Expand All @@ -1548,7 +1550,7 @@ module Executables = struct
(let+ mode = Mode_conf.decode
and+ kind = Binary_kind.decode
and+ loc = loc in
{ mode; kind; loc}))
{mode; kind; loc}))
~else_:simple

let simple_encode link_mode =
Expand Down
2 changes: 2 additions & 0 deletions src/dune_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -332,6 +332,8 @@ module Executables : sig
val shared_object : t
val byte : t
val native : t
val byte_exe : t
val js : t

val compare : t -> t -> Ordering.t

Expand Down
14 changes: 13 additions & 1 deletion src/dune_project.ml
Original file line number Diff line number Diff line change
Expand Up @@ -209,6 +209,7 @@ type t =
; generate_opam_files : bool
; file_key : File_key.t
; dialects : Dialect.DB.t
; explicit_js_mode : bool
}

let equal = (==)
Expand All @@ -232,6 +233,7 @@ let implicit_transitive_deps t = t.implicit_transitive_deps
let allow_approx_merlin t = t.allow_approx_merlin
let generate_opam_files t = t.generate_opam_files
let dialects t = t.dialects
let explicit_js_mode t = t.explicit_js_mode

let to_dyn
{ name ; root ; version ; source; license; authors
Expand All @@ -240,7 +242,7 @@ let to_dyn
; extension_args = _; stanza_parser = _ ; packages
; implicit_transitive_deps ; wrapped_executables ; dune_version
; allow_approx_merlin ; generate_opam_files
; file_key ; dialects } =
; file_key ; dialects ; explicit_js_mode } =
let open Dyn.Encoder in
record
[ "name", Name.to_dyn name
Expand All @@ -265,6 +267,7 @@ let to_dyn
; "generate_opam_files", bool generate_opam_files
; "file_key", string file_key
; "dialects", Dialect.DB.to_dyn dialects
; "explicit_js_mode", bool explicit_js_mode
]

let find_extension_args t key =
Expand Down Expand Up @@ -530,6 +533,9 @@ let implicit_transitive_deps_default ~(lang : Lang.Instance.t) =
let wrapped_executables_default ~(lang : Lang.Instance.t) =
lang.version >= (2, 0)

let explicit_js_mode_default ~(lang : Lang.Instance.t) =
lang.version >= (2, 0)

let anonymous = lazy (
let lang = get_dune_lang () in
let name = Name.anonymous_root in
Expand All @@ -545,6 +551,7 @@ let anonymous = lazy (
in
let implicit_transitive_deps = implicit_transitive_deps_default ~lang in
let wrapped_executables = wrapped_executables_default ~lang in
let explicit_js_mode = explicit_js_mode_default ~lang in
let root = Path.Source.root in
let file_key = File_key.make ~root ~name in
{ name
Expand All @@ -569,6 +576,7 @@ let anonymous = lazy (
; generate_opam_files = false
; file_key
; dialects = Dialect.DB.builtin
; explicit_js_mode
})

let default_name ~dir ~packages =
Expand Down Expand Up @@ -636,6 +644,8 @@ let parse ~dir ~lang ~opam_packages ~file =
~check:(Syntax.since Stanza.syntax (1, 10))
and+ dialects = multi_field "dialect"
(Syntax.since Stanza.syntax (1, 11) >>> located Dialect.decode)
and+ explicit_js_mode =
field_b "explicit_js_mode" ~check:(Syntax.since Stanza.syntax (1, 11))
in
let homepage =
match homepage, source with
Expand Down Expand Up @@ -750,6 +760,7 @@ let parse ~dir ~lang ~opam_packages ~file =
; allow_approx_merlin
; generate_opam_files
; dialects
; explicit_js_mode
})

let load_dune_project ~dir opam_packages =
Expand Down Expand Up @@ -798,6 +809,7 @@ let make_jbuilder_project ~dir opam_packages =
; generate_opam_files = false
; wrapped_executables = false
; dialects
; explicit_js_mode = false
}

let load ~dir ~files =
Expand Down
1 change: 1 addition & 0 deletions src/dune_project.mli
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,7 @@ val stanza_parser : t -> Stanza.t list Dune_lang.Decoder.t
val allow_approx_merlin : t -> bool
val generate_opam_files : t -> bool
val dialects : t -> Dialect.DB.t
val explicit_js_mode : t -> bool

val equal : t -> t -> bool
val hash : t -> int
Expand Down
Loading

0 comments on commit 4217520

Please sign in to comment.