@@ -41,62 +41,6 @@ let js_env = compute_env ~mode:JS
4141let wasm_env = compute_env ~mode: Wasm
4242let jsoo_env ~dir ~mode = (Js_of_ocaml.Mode. select ~mode ~js: js_env ~wasm: wasm_env) ~dir
4343
44- module Version = struct
45- type t = int * int
46-
47- let of_string s : t option =
48- let s =
49- match
50- String. findi s ~f: (function
51- | '+' | '-' | '~' -> true
52- | _ -> false )
53- with
54- | None -> s
55- | Some i -> String. take s i
56- in
57- try
58- match String. split s ~on: '.' with
59- | [] -> None
60- | [ major ] -> Some (int_of_string major, 0 )
61- | major :: minor :: _ -> Some (int_of_string major, int_of_string minor)
62- with
63- | _ -> None
64- ;;
65-
66- let compare (ma1 , mi1 ) (ma2 , mi2 ) =
67- match Int. compare ma1 ma2 with
68- | Eq -> Int. compare mi1 mi2
69- | n -> n
70- ;;
71-
72- let impl_version bin =
73- let * _ = Build_system. build_file bin in
74- Memo. of_reproducible_fiber
75- @@ Process. run_capture_line ~display: Quiet Strict bin [ " --version" ]
76- |> Memo. map ~f: of_string
77- ;;
78-
79- let version_memo = Memo. create " jsoo-version" ~input: (module Path ) impl_version
80-
81- let jsoo_version jsoo =
82- match jsoo with
83- | Ok jsoo_path -> Memo. exec version_memo jsoo_path
84- | Error e -> Action.Prog.Not_found. raise e
85- ;;
86- end
87-
88- let install_jsoo_hint = " opam install js_of_ocaml-compiler"
89-
90- let jsoo ~dir sctx =
91- Super_context. resolve_program
92- sctx
93- ~dir
94- ~loc: None
95- ~where: Original_path
96- ~hint: install_jsoo_hint
97- " js_of_ocaml"
98- ;;
99-
10044module Config : sig
10145 type t
10246
@@ -248,6 +192,52 @@ end = struct
248192 ;;
249193end
250194
195+ module Version = struct
196+ type t = int * int
197+
198+ let of_string s : t option =
199+ let s =
200+ match
201+ String. findi s ~f: (function
202+ | '+' | '-' | '~' -> true
203+ | _ -> false )
204+ with
205+ | None -> s
206+ | Some i -> String. take s i
207+ in
208+ try
209+ match String. split s ~on: '.' with
210+ | [] -> None
211+ | [ major ] -> Some (int_of_string major, 0 )
212+ | major :: minor :: _ -> Some (int_of_string major, int_of_string minor)
213+ with
214+ | _ -> None
215+ ;;
216+
217+ let compare (ma1 , mi1 ) (ma2 , mi2 ) =
218+ match Int. compare ma1 ma2 with
219+ | Eq -> Int. compare mi1 mi2
220+ | n -> n
221+ ;;
222+
223+ let impl_version bin =
224+ let * _ = Build_system. build_file bin in
225+ Memo. of_reproducible_fiber
226+ @@ Process. run_capture_line ~display: Quiet Strict bin [ " --version" ]
227+ |> Memo. map ~f: of_string
228+ ;;
229+
230+ let version_memo = Memo. create " jsoo-version" ~input: (module Path ) impl_version
231+
232+ let jsoo_version jsoo =
233+ match jsoo with
234+ | Ok jsoo_path -> Memo. exec version_memo jsoo_path
235+ | Error e -> Action.Prog.Not_found. raise e
236+ ;;
237+ end
238+
239+ let install_jsoo_hint = " opam install js_of_ocaml-compiler"
240+
251241let in_build_dir (ctx : Build_context.t ) ~config args =
252242 Path.Build.L. relative ctx.build_dir (" .js" :: Config. path config :: args)
253243;;
@@ -270,6 +260,16 @@ let in_obj_dir' ~obj_dir ~config args =
270260 Path.L. relative dir args
271261;;
272262
263+ let jsoo ~dir sctx =
264+ Super_context. resolve_program
265+ sctx
266+ ~dir
267+ ~loc: None
268+ ~where: Original_path
269+ ~hint: install_jsoo_hint
270+ " js_of_ocaml"
271+ ;;
272+
273273let wasmoo ~dir sctx =
274274 (* TODO add a hint when wasm_of_ocaml released on opam *)
275275 Super_context. resolve_program sctx ~dir ~loc: None " wasm_of_ocaml"
0 commit comments