@@ -213,6 +213,27 @@ let wasmoo ~dir sctx =
213213 Super_context. resolve_program sctx ~dir ~loc: None " wasm_of_ocaml"
214214;;
215215
216+ let jsoo_memo ~dir sctx =
217+ Super_context. resolve_program_memo
218+ sctx
219+ ~dir
220+ ~loc: None
221+ ~where: Original_path
222+ ~hint: install_jsoo_hint
223+ " js_of_ocaml"
224+ ;;
225+
226+ let jsoo_has_shapes ~dir sctx =
227+ let * jsoo = jsoo_memo ~dir sctx in
228+ let + jsoo_version = Version. jsoo_version jsoo in
229+ match jsoo_version with
230+ | Some version ->
231+ (match Version. compare version (5 , 8 ) with
232+ | Lt -> false
233+ | Gt | Eq -> true )
234+ | None -> false
235+ ;;
236+
216237type sub_command =
217238 | Compile
218239 | Link
@@ -477,8 +498,26 @@ let link_rule
477498 ~config: None
478499;;
479500
480- let build_cm' sctx ~dir ~in_context ~mode ~src ~target ~config ~sourcemap =
481- let spec = Command.Args. Dep src in
501+ let build_cm' sctx ~dir ~in_context ~mode ~src ~target ~config ~shapes ~sourcemap =
502+ let spec =
503+ Command.Args. (
504+ S
505+ [ Dep src
506+ ; (match shapes, (mode : Js_of_ocaml.Mode.t ) with
507+ | Some shapes , JS ->
508+ S
509+ [ A " --shapes"
510+ ; Hidden_targets
511+ [ Path.Build. set_extension target ~ext: Js_of_ocaml.Ext. js_shape ]
512+ ; Dyn
513+ (let open Action_builder.O in
514+ let + shapes = shapes in
515+ S (List. map shapes ~f: (fun s -> S [ A " --load" ; Dep s ])))
516+ ]
517+ | Some _ , Wasm -> S []
518+ | None , _ -> S [] )
519+ ])
520+ in
482521 let flags = in_context.Js_of_ocaml.In_context. flags in
483522 js_of_ocaml_rule
484523 sctx
@@ -493,17 +532,51 @@ let build_cm' sctx ~dir ~in_context ~mode ~src ~target ~config ~sourcemap =
493532 ~sourcemap
494533;;
495534
496- let build_cm sctx ~dir ~in_context ~mode ~src ~obj_dir ~config =
535+ let build_cm cctx ~dir ~in_context ~mode ~src ~obj_dir ~config : config_opt =
497536 let name = with_js_ext ~mode (Path. basename src) in
498- let target = in_obj_dir ~obj_dir ~config [ name ] in
537+ let target = in_obj_dir ~obj_dir ~config: config_opt [ name ] in
538+ let sctx = Compilation_context. super_context cctx in
539+ let ctx = Super_context. context sctx |> Context. build_context in
540+ let + jsoo_has_shapes =
541+ match mode with
542+ | JS -> jsoo_has_shapes ~dir sctx
543+ | Wasm -> Memo. return false
544+ in
545+ let shapes =
546+ if jsoo_has_shapes
547+ then
548+ Some
549+ (let open Action_builder.O in
550+ let + libs = Resolve.Memo. read (Compilation_context. requires_link cctx)
551+ and + config =
552+ match config_opt with
553+ | None ->
554+ let flags = in_context.Js_of_ocaml.In_context. flags in
555+ js_of_ocaml_flags sctx ~dir ~mode flags
556+ |> Action_builder. bind ~f: (fun (x : _ Js_of_ocaml.Flags.t ) -> x.compile)
557+ |> Action_builder. map ~f: Config. of_flags
558+ | Some config -> Action_builder. return config
559+ in
560+ Path. build
561+ (in_build_dir
562+ ctx
563+ ~config
564+ [ " stdlib" ; " stdlib.cma" ^ Js_of_ocaml.Ext. js_shape ])
565+ :: List. concat_map libs ~f: (fun lib ->
566+ List. map
567+ (jsoo_archives ~mode ctx config lib)
568+ ~f: (Path. set_extension ~ext: Js_of_ocaml.Ext. js_shape)))
569+ else None
570+ in
499571 build_cm'
500572 sctx
501573 ~dir
502574 ~in_context
503575 ~mode
504576 ~src
505577 ~target
506- ~config: (Option. map config ~f: Action_builder. return)
578+ ~shapes
579+ ~config: (Option. map config_opt ~f: Action_builder. return)
507580 ~sourcemap: Js_of_ocaml.Sourcemap. Inline
508581;;
509582
@@ -514,7 +587,10 @@ let setup_separate_compilation_rules sctx components =
514587 let config = Config. of_string s_config in
515588 let pkg = Lib_name. parse_string_exn (Loc. none, s_pkg) in
516589 let ctx = Super_context. context sctx in
517- let * installed_libs = Lib.DB. installed ctx in
590+ let * installed_libs = Lib.DB. installed ctx
591+ and * jsoo_has_shapes =
592+ jsoo_has_shapes ~dir: (Context. build_context ctx).build_dir sctx
593+ in
518594 Lib.DB. find installed_libs pkg
519595 >> = (function
520596 | None -> Memo. return ()
@@ -546,6 +622,12 @@ let setup_separate_compilation_rules sctx components =
546622 let target =
547623 in_build_dir build_context ~config [ lib_name; with_js_ext ~mode name ]
548624 in
625+ let shapes =
626+ if jsoo_has_shapes
627+ then (* FIXME: we should load shapes *)
628+ Some (Action_builder. return [] )
629+ else None
630+ in
549631 build_cm'
550632 sctx
551633 ~dir
@@ -555,6 +637,7 @@ let setup_separate_compilation_rules sctx components =
555637 ~target
556638 ~config: (Some (Action_builder. return config))
557639 ~sourcemap: Js_of_ocaml.Sourcemap. Inline
640+ ~shapes
558641 |> Super_context. add_rule sctx ~dir )))
559642;;
560643
0 commit comments