Skip to content

Commit

Permalink
Initial support for jsoo config
Browse files Browse the repository at this point in the history
Signed-off-by: Hugo Heuzard <[email protected]>
  • Loading branch information
hhugo committed Dec 20, 2022
1 parent 27e8d71 commit 6ca2b58
Show file tree
Hide file tree
Showing 22 changed files with 356 additions and 207 deletions.
2 changes: 1 addition & 1 deletion boot/libs.ml
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
let executables = [ "main" ]

let external_libraries = [ "unix"; "threads.posix" ]
let external_libraries = [ "unix"; "threads"; "threads.posix" ]

let local_libraries =
[ ("otherlibs/ordering", Some "Ordering", false, None)
Expand Down
15 changes: 4 additions & 11 deletions src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -920,13 +920,6 @@ module Library = struct
in
let foreign_dll_files = foreign_dll_files conf ~dir ~ext_dll in
let exit_module = Option.bind conf.stdlib ~f:(fun x -> x.exit_module) in
let jsoo_archive =
(* XXX we shouldn't access the directory of the obj_dir directly. We
should use something like [Obj_dir.Archive.obj] instead *)
if modes.ocaml.byte then
Some (archive ~dir:(Obj_dir.obj_dir obj_dir) ".cma.js")
else None
in
let virtual_ =
Option.map conf.virtual_modules ~f:(fun _ -> Lib_info.Source.Local)
in
Expand Down Expand Up @@ -987,9 +980,9 @@ module Library = struct
~orig_src_dir ~obj_dir ~version ~synopsis ~main_module_name ~sub_systems
~requires ~foreign_objects ~plugins ~archives ~ppx_runtime_deps
~foreign_archives ~native_archives ~foreign_dll_files ~jsoo_runtime
~jsoo_archive ~preprocess ~enabled ~virtual_deps ~dune_version ~virtual_
~entry_modules ~implements ~default_implementation ~modes ~modules:Local
~wrapped ~special_builtin_support ~exit_module ~instrumentation_backend
~preprocess ~enabled ~virtual_deps ~dune_version ~virtual_ ~entry_modules
~implements ~default_implementation ~modes ~modules:Local ~wrapped
~special_builtin_support ~exit_module ~instrumentation_backend
end

module Plugin = struct
Expand Down Expand Up @@ -1449,7 +1442,7 @@ module Executables = struct
| Byte, Shared_object -> ".bc" ^ ext_dll
| Native, Shared_object -> ext_dll
| mode, Plugin -> Mode.plugin_ext mode
| Byte, Js -> ".bc.js"
| Byte, Js -> Js_of_ocaml.Ext.exe
| Native, Js ->
User_error.raise ~loc
[ Pp.text "Javascript generation only supports bytecode!" ])
Expand Down
9 changes: 4 additions & 5 deletions src/dune_rules/dune_package.ml
Original file line number Diff line number Diff line change
Expand Up @@ -180,7 +180,6 @@ module Lib = struct
let version = None in
let main_module_name = Lib_info.Inherited.This main_module_name in
let foreign_objects = Lib_info.Source.External foreign_objects in
let jsoo_archive = None in
let preprocess = Preprocess.Per_module.no_preprocessing () in
let virtual_deps = [] in
let dune_version = None in
Expand All @@ -198,10 +197,10 @@ module Lib = struct
~sub_systems ~requires ~foreign_objects ~plugins ~archives
~ppx_runtime_deps ~foreign_archives
~native_archives:(Files native_archives) ~foreign_dll_files:[]
~jsoo_runtime ~jsoo_archive ~preprocess ~enabled ~virtual_deps
~dune_version ~virtual_ ~entry_modules ~implements
~default_implementation ~modes ~modules ~wrapped
~special_builtin_support ~exit_module:None ~instrumentation_backend
~jsoo_runtime ~preprocess ~enabled ~virtual_deps ~dune_version
~virtual_ ~entry_modules ~implements ~default_implementation ~modes
~modules ~wrapped ~special_builtin_support ~exit_module:None
~instrumentation_backend
in
{ info; main_module_name })

Expand Down
26 changes: 11 additions & 15 deletions src/dune_rules/exe.ml
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ module Linkage = struct

let is_native x = x.mode = Native

let is_js x = x.mode = Byte && x.ext = ".bc.js"
let is_js x = x.mode = Byte && x.ext = Js_of_ocaml.Ext.exe

let is_byte x = x.mode = Byte && not (is_js x)

Expand All @@ -46,7 +46,7 @@ module Linkage = struct
| Error _ -> custom context
| Ok _ -> native

let js = { mode = Byte; ext = ".bc.js"; flags = [] }
let js = { mode = Byte; ext = Js_of_ocaml.Ext.exe; flags = [] }

let is_plugin t =
List.mem (List.map ~f:Mode.plugin_ext Mode.all) t.ext ~equal:String.equal
Expand Down Expand Up @@ -202,27 +202,21 @@ let link_exe ~loc ~name ~(linkage : Linkage.t) ~cm_files ~link_time_code_gen
| Some p -> Promote p)
action_with_targets

let link_js ~name ~loc ~cm_files ~promote ~link_time_code_gen cctx =
let link_js ~name ~loc ~obj_dir ~top_sorted_modules ~promote ~link_time_code_gen
cctx =
let in_context =
CC.js_of_ocaml cctx |> Option.value ~default:Js_of_ocaml.In_context.default
in
let other_cm =
let link_time_code_gen =
let open Memo.O in
let+ { Link_time_code_gen.to_link; force_linkall = _ } =
Resolve.read_memo link_time_code_gen
in
List.map to_link ~f:(function
| Lib_flags.Lib_and_module.Lib lib -> `Lib lib
| Module (obj_dir, m) ->
let path =
Obj_dir.Module.cm_file_exn obj_dir m ~kind:(Ocaml (Mode.cm_kind Byte))
in
`Mod path)
to_link
in
let src = exe_path_from_name cctx ~name ~linkage:Linkage.byte_for_jsoo in
let top_sorted_cms = Cm_files.top_sorted_cms cm_files ~mode:Mode.Byte in
Jsoo_rules.build_exe cctx ~loc ~in_context ~src ~cm:top_sorted_cms ~promote
~link_time_code_gen:other_cm
Jsoo_rules.build_exe cctx ~loc ~in_context ~src ~obj_dir ~top_sorted_modules
~promote ~link_time_code_gen

type dep_graphs = { for_exes : Module.t list Action_builder.t list }

Expand Down Expand Up @@ -263,7 +257,9 @@ let link_many ?(link_args = Action_builder.return Command.Args.empty) ?o_files
let+ () =
Memo.parallel_iter linkages ~f:(fun linkage ->
if Linkage.is_js linkage then
link_js ~loc ~name ~cm_files ~promote cctx ~link_time_code_gen
let obj_dir = CC.obj_dir cctx in
link_js ~loc ~name ~obj_dir ~top_sorted_modules ~promote cctx
~link_time_code_gen
else
let* link_time_code_gen =
match Linkage.is_plugin linkage with
Expand Down
7 changes: 3 additions & 4 deletions src/dune_rules/findlib/findlib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -358,7 +358,6 @@ end = struct
let foreign_objects = Lib_info.Source.External [] in
let plugins = plugins t in
let jsoo_runtime = jsoo_runtime t in
let jsoo_archive = None in
let preprocess = Preprocess.Per_module.no_preprocessing () in
let virtual_ = None in
let default_implementation = None in
Expand Down Expand Up @@ -444,9 +443,9 @@ end = struct
~sub_systems ~requires ~foreign_objects ~plugins ~archives
~ppx_runtime_deps ~foreign_archives
~native_archives:(Files native_archives) ~foreign_dll_files:[]
~jsoo_runtime ~jsoo_archive ~preprocess ~enabled ~virtual_deps
~dune_version ~virtual_ ~implements ~default_implementation ~modes
~modules ~wrapped ~special_builtin_support ~exit_module:None
~jsoo_runtime ~preprocess ~enabled ~virtual_deps ~dune_version
~virtual_ ~implements ~default_implementation ~modes ~modules ~wrapped
~special_builtin_support ~exit_module:None
~instrumentation_backend:None ~entry_modules
in
Dune_package.Lib.of_findlib info
Expand Down
6 changes: 2 additions & 4 deletions src/dune_rules/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -102,10 +102,8 @@ end = struct
; cctx = Some (exes.buildable.loc, cctx)
; js =
Some
(List.concat_map exes.names ~f:(fun (_, exe) ->
List.map
[ exe ^ ".bc.js"; exe ^ ".bc.runtime.js" ]
~f:(Path.Build.relative dir)))
(List.map exes.names ~f:(fun (_, exe) ->
Path.Build.relative dir (exe ^ Js_of_ocaml.Ext.exe)))
; source_dirs = None
})
| Alias alias ->
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/inline_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -214,7 +214,7 @@ include Sub_system.Register_end_point (struct
let ext =
match mode with
| Native | Best -> ".exe"
| Javascript -> ".bc.js"
| Javascript -> Js_of_ocaml.Ext.exe
| Byte -> ".bc"
in
let custom_runner =
Expand Down
12 changes: 12 additions & 0 deletions src/dune_rules/js_of_ocaml.ml
Original file line number Diff line number Diff line change
@@ -1,6 +1,18 @@
open Import
open Dune_lang.Decoder

module Ext = struct
type t = string

let exe = ".bc.js"

let cmo = ".cmo.js"

let cma = ".cma.js"

let runtime = ".bc.runtime.js"
end

let field_oslu name = Ordered_set_lang.Unexpanded.field name

module Flags = struct
Expand Down
12 changes: 12 additions & 0 deletions src/dune_rules/js_of_ocaml.mli
Original file line number Diff line number Diff line change
@@ -1,5 +1,17 @@
open Import

module Ext : sig
type t = string

val exe : t

val cmo : t

val cma : t

val runtime : t
end

module Flags : sig
type 'flags t =
{ build_runtime : 'flags
Expand Down
Loading

0 comments on commit 6ca2b58

Please sign in to comment.