@@ -194,6 +194,27 @@ let jsoo ~dir sctx =
194194 " js_of_ocaml"
195195;;
196196
197+ let jsoo_memo ~dir sctx =
198+ Super_context. resolve_program_memo
199+ sctx
200+ ~dir
201+ ~loc: None
202+ ~where: Original_path
203+ ~hint: install_jsoo_hint
204+ " js_of_ocaml"
205+ ;;
206+
207+ let jsoo_has_shapes ~dir sctx =
208+ let * jsoo = jsoo_memo ~dir sctx in
209+ let + jsoo_version = Version. jsoo_version jsoo in
210+ match jsoo_version with
211+ | Some version ->
212+ (match Version. compare version (5 , 8 ) with
213+ | Lt -> false
214+ | Gt | Eq -> true )
215+ | None -> false
216+ ;;
217+
197218type sub_command =
198219 | Compile
199220 | Link
@@ -427,15 +448,14 @@ let build_cm' sctx ~dir ~in_context ~src ~target ~config ~shapes ~sourcemap =
427448 js_of_ocaml_rule sctx ~sub_command: Compile ~dir ~flags ~spec ~target ~config ~sourcemap
428449;;
429450
430- let shapes_enabled = true
431-
432451let build_cm cctx ~dir ~in_context ~src ~obj_dir ~config :config_opt =
433452 let name = with_js_ext (Path. basename src) in
434453 let target = in_obj_dir ~obj_dir ~config: config_opt [ name ] in
435454 let sctx = Compilation_context. super_context cctx in
436455 let ctx = Super_context. context sctx |> Context. build_context in
456+ let + jsoo_has_shapes = jsoo_has_shapes ~dir sctx in
437457 let shapes =
438- if shapes_enabled
458+ if jsoo_has_shapes
439459 then
440460 Some
441461 (let open Action_builder.O in
@@ -475,7 +495,10 @@ let setup_separate_compilation_rules sctx components =
475495 let config = Config. of_string s_config in
476496 let pkg = Lib_name. parse_string_exn (Loc. none, s_pkg) in
477497 let ctx = Super_context. context sctx in
478- let * installed_libs = Lib.DB. installed ctx in
498+ let * installed_libs = Lib.DB. installed ctx
499+ and * jsoo_has_shapes =
500+ jsoo_has_shapes ~dir: (Context. build_context ctx).build_dir sctx
501+ in
479502 Lib.DB. find installed_libs pkg
480503 >> = (function
481504 | None -> Memo. return ()
@@ -512,7 +535,7 @@ let setup_separate_compilation_rules sctx components =
512535 in
513536 let target = in_build_dir build_context ~config [ lib_name; with_js_ext name ] in
514537 let shapes =
515- if shapes_enabled
538+ if jsoo_has_shapes
516539 then (* FIXME: we should load shapes *)
517540 Some (Action_builder. return [] )
518541 else None
0 commit comments