From c33f23ec43d6580a47a01de619991089a75ab243 Mon Sep 17 00:00:00 2001 From: Hugo Heuzard Date: Tue, 20 May 2025 15:58:14 +0200 Subject: [PATCH 01/13] Compiler: add BitSet.clear --- compiler/lib/stdlib.ml | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/compiler/lib/stdlib.ml b/compiler/lib/stdlib.ml index 9ae41a24e1..bc2742ea93 100644 --- a/compiler/lib/stdlib.ml +++ b/compiler/lib/stdlib.ml @@ -879,6 +879,8 @@ module BitSet : sig val next_free : t -> int -> int val next_mem : t -> int -> int + + val clear : t -> unit end = struct type t = { mutable arr : int array } @@ -886,6 +888,8 @@ end = struct let create' n = { arr = Array.make ((n / Sys.int_size) + 1) 0 } + let clear t = Array.fill t.arr 0 (Array.length t.arr) 0 + let size t = Array.length t.arr * Sys.int_size let mem t i = From efc9ce2a4cc8d2dbb2a7b7ef6d97c651aff61e97 Mon Sep 17 00:00:00 2001 From: Hugo Heuzard Date: Tue, 20 May 2025 13:02:36 +0200 Subject: [PATCH 02/13] Compiler: move return_values to Code --- compiler/lib/code.ml | 24 ++++++++++++++++++++++++ compiler/lib/code.mli | 2 ++ compiler/lib/global_flow.ml | 26 -------------------------- 3 files changed, 26 insertions(+), 26 deletions(-) diff --git a/compiler/lib/code.ml b/compiler/lib/code.ml index eceb923f11..4399705188 100644 --- a/compiler/lib/code.ml +++ b/compiler/lib/code.ml @@ -845,6 +845,30 @@ let rec last_instr l = | [ i ] | [ i; Event _ ] -> Some i | _ :: rem -> last_instr rem +(* Compute the list of variables containing the return values of each + function *) +let return_values p = + fold_closures + p + (fun name_opt _ (pc, _) _ rets -> + match name_opt with + | None -> rets + | Some name -> + let s = + traverse + { fold = fold_children } + (fun pc s -> + let block = Addr.Map.find pc p.blocks in + match block.branch with + | Return x -> Var.Set.add x s + | _ -> s) + pc + p.blocks + Var.Set.empty + in + Var.Map.add name s rets) + Var.Map.empty + let equal p1 p2 = p1.start = p2.start && Addr.Map.equal diff --git a/compiler/lib/code.mli b/compiler/lib/code.mli index c7b3696673..bc9dcab0e8 100644 --- a/compiler/lib/code.mli +++ b/compiler/lib/code.mli @@ -290,6 +290,8 @@ val fold_children_skip_try_body : 'c fold_blocs val poptraps : block Addr.Map.t -> Addr.t -> Addr.Set.t +val return_values : program -> Var.Set.t Var.Map.t + val traverse : fold_blocs_poly -> (Addr.t -> 'c -> 'c) -> Addr.t -> block Addr.Map.t -> 'c -> 'c diff --git a/compiler/lib/global_flow.ml b/compiler/lib/global_flow.ml index 315fb00e14..d3eeb8f929 100644 --- a/compiler/lib/global_flow.ml +++ b/compiler/lib/global_flow.ml @@ -45,32 +45,6 @@ let add_to_list h x v = Var.Hashtbl.replace h x (v :: associated_list h x) (****) -(* Compute the list of variables containing the return values of each - function *) -let return_values p = - Code.fold_closures - p - (fun name_opt _ (pc, _) _ rets -> - match name_opt with - | None -> rets - | Some name -> - let s = - Code.traverse - { fold = fold_children } - (fun pc s -> - let block = Addr.Map.find pc p.blocks in - match block.branch with - | Return x -> Var.Set.add x s - | _ -> s) - pc - p.blocks - Var.Set.empty - in - Var.Map.add name s rets) - Var.Map.empty - -(****) - (* A variable is either let-bound, or a parameter, to which we associate a set of possible arguments. *) From 77383c7fbf5094afe4e6f5e1ba1b38257b730846 Mon Sep 17 00:00:00 2001 From: Hugo Heuzard Date: Tue, 20 May 2025 15:54:11 +0200 Subject: [PATCH 03/13] Compiler: propagate arity across unit boundary - Propagate shape information through the flow analysis --- compiler/bin-js_of_ocaml/build_fs.ml | 2 +- compiler/bin-js_of_ocaml/cmd_arg.ml | 22 ++- compiler/bin-js_of_ocaml/cmd_arg.mli | 2 + compiler/bin-js_of_ocaml/compile.ml | 105 +++++++++---- compiler/bin-wasm_of_ocaml/compile.ml | 4 +- compiler/lib/config.ml | 2 + compiler/lib/config.mli | 2 + compiler/lib/driver.ml | 124 +++++++++++---- compiler/lib/driver.mli | 9 +- compiler/lib/flow.ml | 102 +++++++++--- compiler/lib/flow.mli | 7 + compiler/lib/ocaml_compiler.ml | 40 +++++ compiler/lib/ocaml_compiler.mli | 7 + compiler/lib/parse_bytecode.ml | 122 ++++++++++----- compiler/lib/pure_fun.ml | 7 +- compiler/lib/pure_fun.mli | 4 + compiler/lib/shape.ml | 174 +++++++++++++++++++++ compiler/lib/shape.mli | 63 ++++++++ compiler/tests-compiler/sourcemap.ml | 52 +++--- compiler/tests-full/dune | 37 +++++ compiler/tests-full/m1.ml | 1 + compiler/tests-full/m2.ml | 1 + compiler/tests-full/m3.ml | 3 + compiler/tests-full/shapes.cma.expected.js | 86 ++++++++++ compiler/tests-full/stdlib.cma.expected.js | 91 ++++++++++- 25 files changed, 914 insertions(+), 155 deletions(-) create mode 100644 compiler/lib/shape.ml create mode 100644 compiler/lib/shape.mli create mode 100644 compiler/tests-full/m1.ml create mode 100644 compiler/tests-full/m2.ml create mode 100644 compiler/tests-full/m3.ml create mode 100644 compiler/tests-full/shapes.cma.expected.js diff --git a/compiler/bin-js_of_ocaml/build_fs.ml b/compiler/bin-js_of_ocaml/build_fs.ml index 27dfe0c97c..710b69ae72 100644 --- a/compiler/bin-js_of_ocaml/build_fs.ml +++ b/compiler/bin-js_of_ocaml/build_fs.ml @@ -75,7 +75,7 @@ function jsoo_create_file_extern(name,content){ let code = Code.prepend Code.empty instr in Filename.gen_file output_file (fun chan -> let pfs_fmt = Pretty_print.to_out_channel chan in - let (_ : Source_map.info) = + let (_ : Source_map.info * Shape.t StringMap.t) = Driver.f ~standalone:true ~wrap_with_fun:`Iife diff --git a/compiler/bin-js_of_ocaml/cmd_arg.ml b/compiler/bin-js_of_ocaml/cmd_arg.ml index 203a4fa784..2b2d5b2ea6 100644 --- a/compiler/bin-js_of_ocaml/cmd_arg.ml +++ b/compiler/bin-js_of_ocaml/cmd_arg.ml @@ -64,6 +64,8 @@ type t = ; static_env : (string * string) list ; wrap_with_fun : [ `Iife | `Named of string | `Anonymous ] ; target_env : Target_env.t + ; shape_files : string list + ; write_shape : bool ; (* toplevel *) dynlink : bool ; linkall : bool @@ -114,6 +116,14 @@ let options = let doc = "Set output file name to [$(docv)]." in Arg.(value & opt (some string) None & info [ "o" ] ~docv:"FILE" ~doc) in + let shape_files = + let doc = "load shape file [$(docv)]." in + Arg.(value & opt_all string [] & info [ "load-shape" ] ~docv:"FILE" ~doc) + in + let write_shape = + let doc = "Emit shape files" in + Arg.(value & flag & info [ "write-shape" ] ~doc) + in let input_file = let doc = "Compile the bytecode program [$(docv)]. " @@ -317,7 +327,9 @@ let options = input_file js_files keep_unit_names - effects = + effects + shape_files + write_shape = let inline_source_content = not sourcemap_don't_inline_content in let chop_extension s = try Filename.chop_extension s with Invalid_argument _ -> s in let runtime_files = js_files in @@ -388,6 +400,8 @@ let options = ; source_map ; keep_unit_names ; effects + ; shape_files + ; write_shape } in let t = @@ -420,7 +434,9 @@ let options = $ input_file $ js_files $ keep_unit_names - $ effects) + $ effects + $ shape_files + $ write_shape) in Term.ret t @@ -649,6 +665,8 @@ let options_runtime_only = ; source_map ; keep_unit_names = false ; effects + ; shape_files = [] + ; write_shape = false } in let t = diff --git a/compiler/bin-js_of_ocaml/cmd_arg.mli b/compiler/bin-js_of_ocaml/cmd_arg.mli index 331dc12b93..8be8344fb1 100644 --- a/compiler/bin-js_of_ocaml/cmd_arg.mli +++ b/compiler/bin-js_of_ocaml/cmd_arg.mli @@ -37,6 +37,8 @@ type t = | `Anonymous ] ; target_env : Target_env.t + ; shape_files : string list + ; write_shape : bool ; (* toplevel *) dynlink : bool ; linkall : bool diff --git a/compiler/bin-js_of_ocaml/compile.ml b/compiler/bin-js_of_ocaml/compile.ml index a64a1f53f2..357fced377 100644 --- a/compiler/bin-js_of_ocaml/compile.ml +++ b/compiler/bin-js_of_ocaml/compile.ml @@ -42,6 +42,7 @@ let source_map_enabled : Source_map.Encoding_spec.t option -> bool = function | Some _ -> true let output_gen + ~write_shape ~standalone ~custom_header ~build_info @@ -53,7 +54,15 @@ let output_gen Driver.configure fmt; if standalone then header ~custom_header fmt; if Config.Flag.header () then jsoo_header fmt build_info; - let sm = f ~standalone ~source_map (k, fmt) in + let sm, shapes = f ~standalone ~shapes:write_shape ~source_map (k, fmt) in + (if write_shape + then + match output_file with + | `Stdout -> () + | `Name name -> + Shape.Store.save' + (Filename.remove_extension name ^ Shape.Store.ext) + (StringMap.bindings shapes)); match source_map, sm with | None, _ | _, None -> () | Some { output_file = output; source_map; keep_empty }, Some sm -> @@ -71,7 +80,6 @@ let output_gen Pretty_print.newline fmt; Pretty_print.string fmt (Printf.sprintf "//# sourceMappingURL=%s\n" urlData) in - match output_file with | `Stdout -> f stdout `Stdout | `Name name -> Filename.gen_file name (fun chan -> f chan `File) @@ -132,6 +140,11 @@ let sourcemap_of_infos ~base l = let sourcemap_of_info ~base info = sourcemap_of_infos ~base [ info ] +let map_fst f (x, y) = f x, y + +let merge_shape a b = + StringMap.union (fun _name s1 s2 -> if Shape.equal s1 s2 then Some s1 else None) a b + let run { Cmd_arg.common ; profile @@ -156,6 +169,8 @@ let run ; keep_unit_names ; include_runtime ; effects + ; shape_files + ; write_shape } = let source_map_base = Option.map ~f:(fun spec -> spec.Source_map.Encoding_spec.source_map) source_map @@ -172,6 +187,7 @@ let run | `Name _, _ -> ()); List.iter params ~f:(fun (s, v) -> Config.Param.set s v); List.iter static_env ~f:(fun (s, v) -> Eval.set_static_env s v); + List.iter shape_files ~f:(fun fn -> Shape.Store.load' fn); let t = Timer.make () in let include_dirs = List.filter_map (include_dirs @ [ "+stdlib/" ]) ~f:(fun d -> Findlib.find [] d) @@ -251,6 +267,7 @@ let run (one : Parse_bytecode.one) ~check_sourcemap ~standalone + ~shapes ~(source_map : Source_map.Encoding_spec.t option) ~link output_file = @@ -269,6 +286,7 @@ let run let code = Code.prepend one.code instr in Driver.f ~standalone + ~shapes ?profile ~link ~wrap_with_fun @@ -292,6 +310,7 @@ let run let res = Driver.f ~standalone + ~shapes ?profile ~link ~wrap_with_fun @@ -313,6 +332,7 @@ let run let output_partial (cmo : Cmo_format.compilation_unit) ~standalone + ~shapes ~source_map code ((_, fmt) as output_file) = @@ -320,7 +340,14 @@ let run let uinfo = Unit_info.of_cmo cmo in Pretty_print.string fmt "\n"; Pretty_print.string fmt (Unit_info.to_string uinfo); - output code ~check_sourcemap:true ~source_map ~standalone ~link:`No output_file + output + code + ~check_sourcemap:true + ~source_map + ~standalone + ~shapes + ~link:`No + output_file in let output_partial_runtime ~standalone ~source_map ((_, fmt) as output_file) = assert (not standalone); @@ -371,12 +398,13 @@ let run { code; cmis = StringSet.empty; debug = Parse_bytecode.Debug.default_summary } in output_gen + ~write_shape ~standalone:true ~custom_header ~build_info:(Build_info.create `Runtime) ~source_map (fst output_file) - (fun ~standalone ~source_map ((_, fmt) as output_file) -> + (fun ~standalone ~shapes ~source_map ((_, fmt) as output_file) -> Pretty_print.string fmt "\n"; Pretty_print.string fmt (Unit_info.to_string uinfo); output @@ -384,9 +412,10 @@ let run ~check_sourcemap:false ~source_map ~standalone + ~shapes ~link:`All output_file - |> sourcemap_of_info ~base:source_map_base) + |> map_fst (sourcemap_of_info ~base:source_map_base)) | (`Stdin | `File _) as bytecode -> let kind, ic, close_ic, include_dirs = match bytecode with @@ -419,20 +448,22 @@ let run in if times () then Format.eprintf " parsing: %a@." Timer.print t1; output_gen + ~write_shape ~standalone:true ~custom_header ~build_info:(Build_info.create `Exe) ~source_map (fst output_file) - (fun ~standalone ~source_map output_file -> + (fun ~standalone ~shapes ~source_map output_file -> output code ~check_sourcemap:true ~standalone + ~shapes ~source_map ~link:(if linkall then `All else `Needed) output_file - |> sourcemap_of_info ~base:source_map_base) + |> map_fst (sourcemap_of_info ~base:source_map_base)) | `Cmo cmo -> let output_file = match output_file, keep_unit_names with @@ -457,20 +488,26 @@ let run in if times () then Format.eprintf " parsing: %a@." Timer.print t1; output_gen + ~write_shape ~standalone:false ~custom_header ~build_info:(Build_info.create `Cmo) ~source_map output_file - (fun ~standalone ~source_map output -> + (fun ~standalone ~shapes ~source_map output -> match include_runtime with | true -> - let sm1 = output_partial_runtime ~standalone ~source_map output in - let sm2 = output_partial cmo code ~standalone ~source_map output in - sourcemap_of_infos ~base:source_map_base [ sm1; sm2 ] + let sm1, sh1 = + output_partial_runtime ~standalone ~shapes ~source_map output + in + let sm2, sh2 = + output_partial cmo code ~standalone ~shapes ~source_map output + in + ( sourcemap_of_infos ~base:source_map_base [ sm1; sm2 ] + , merge_shape sh1 sh2 ) | false -> - output_partial cmo code ~standalone ~source_map output - |> sourcemap_of_info ~base:source_map_base) + output_partial cmo code ~standalone ~shapes ~source_map output + |> map_fst (sourcemap_of_info ~base:source_map_base)) | `Cma cma when keep_unit_names -> (if include_runtime then @@ -486,14 +523,15 @@ let run failwith "use [-o dirname/] or remove [--keep-unit-names]" in output_gen + ~write_shape ~standalone:false ~custom_header ~build_info:(Build_info.create `Runtime) ~source_map (`Name output_file) - (fun ~standalone ~source_map output -> - output_partial_runtime ~standalone ~source_map output - |> sourcemap_of_info ~base:source_map_base)); + (fun ~standalone ~shapes ~source_map output -> + output_partial_runtime ~standalone ~shapes ~source_map output + |> map_fst (sourcemap_of_info ~base:source_map_base))); List.iter cma.lib_units ~f:(fun cmo -> let output_file = match output_file with @@ -522,23 +560,26 @@ let run t1 (Ocaml_compiler.Cmo_format.name cmo); output_gen + ~write_shape ~standalone:false ~custom_header ~build_info:(Build_info.create `Cma) ~source_map (`Name output_file) - (fun ~standalone ~source_map output -> - output_partial ~standalone ~source_map cmo code output - |> sourcemap_of_info ~base:source_map_base)) + (fun ~standalone ~shapes ~source_map output -> + output_partial ~standalone ~shapes ~source_map cmo code output + |> map_fst (sourcemap_of_info ~base:source_map_base))) | `Cma cma -> - let f ~standalone ~source_map output = - let source_map_runtime = + let f ~standalone ~shapes ~source_map output = + (* Always compute shapes because it can be used by other units of the cma *) + let shapes = shapes || true in + let runtime = if not include_runtime then None - else Some (output_partial_runtime ~standalone ~source_map output) + else Some (output_partial_runtime ~standalone ~shapes ~source_map output) in - let source_map_units = + let units = List.map cma.lib_units ~f:(fun cmo -> let t1 = Timer.make () in let code = @@ -556,16 +597,22 @@ let run Timer.print t1 (Ocaml_compiler.Cmo_format.name cmo); - output_partial ~standalone ~source_map cmo code output) + output_partial ~standalone ~shapes ~source_map cmo code output) + in + let sm_and_shapes = + match runtime with + | None -> units + | Some x -> x :: units in - let sm = - match source_map_runtime with - | None -> source_map_units - | Some x -> x :: source_map_units + let shapes = + List.fold_left sm_and_shapes ~init:StringMap.empty ~f:(fun acc (_, s) -> + merge_shape s acc) in - sourcemap_of_infos ~base:source_map_base sm + ( sourcemap_of_infos ~base:source_map_base (List.map sm_and_shapes ~f:fst) + , shapes ) in output_gen + ~write_shape ~standalone:false ~custom_header ~build_info:(Build_info.create `Cma) diff --git a/compiler/bin-wasm_of_ocaml/compile.ml b/compiler/bin-wasm_of_ocaml/compile.ml index d0f39f6c28..8b9ee787df 100644 --- a/compiler/bin-wasm_of_ocaml/compile.ml +++ b/compiler/bin-wasm_of_ocaml/compile.ml @@ -246,7 +246,7 @@ let generate_prelude ~out_file = let code, uinfo = Parse_bytecode.predefined_exceptions () in let profile = Profile.O1 in let Driver.{ program; variable_uses; in_cps; deadcode_sentinal; _ }, global_flow_data = - Driver.optimize_for_wasm ~profile code + Driver.optimize_for_wasm ~profile ~shapes:false code in let context = Generate.start () in let _ = @@ -400,7 +400,7 @@ let run let standalone = Option.is_none unit_name in let Driver.{ program; variable_uses; in_cps; deadcode_sentinal; _ }, global_flow_data = - Driver.optimize_for_wasm ~profile code + Driver.optimize_for_wasm ~profile ~shapes:false code in let context = Generate.start () in let toplevel_name, generated_js = diff --git a/compiler/lib/config.ml b/compiler/lib/config.ml index db97d62450..c5cab8ffe7 100644 --- a/compiler/lib/config.ml +++ b/compiler/lib/config.ml @@ -106,6 +106,8 @@ module Flag = struct let auto_link = o ~name:"auto-link" ~default:true let es6 = o ~name:"es6" ~default:false + + let load_shapes_auto = o ~name:"load-shapes-auto" ~default:false end module Param = struct diff --git a/compiler/lib/config.mli b/compiler/lib/config.mli index 71642430bf..09c8b6ab1a 100644 --- a/compiler/lib/config.mli +++ b/compiler/lib/config.mli @@ -76,6 +76,8 @@ module Flag : sig val es6 : unit -> bool + val load_shapes_auto : unit -> bool + val enable : string -> unit val disable : string -> unit diff --git a/compiler/lib/driver.ml b/compiler/lib/driver.ml index 4581c38d5d..680a105a48 100644 --- a/compiler/lib/driver.ml +++ b/compiler/lib/driver.ml @@ -23,12 +23,15 @@ let debug = Debug.find "main" let times = Debug.find "times" +let debug_shapes = Debug.find "shapes" + type optimized_result = { program : Code.program ; variable_uses : Deadcode.variable_uses ; trampolined_calls : Effects.trampolined_calls ; in_cps : Effects.in_cps ; deadcode_sentinal : Code.Var.t + ; shapes : Shape.t StringMap.t } let should_export = function @@ -93,9 +96,54 @@ let phi p = let ( +> ) f g x = g (f x) -let map_fst f (x, y) = f x, y +let map_fst5 f (x, y, z, t, u) = f x, y, z, t, u -let effects_and_exact_calls ~keep_flow_data ~deadcode_sentinal (profile : Profile.t) p = +let collects_shapes ~shapes (p : Code.program) = + if debug_shapes () || shapes + then ( + let t = Timer.make () in + let shapes = ref StringMap.empty in + Code.Addr.Map.iter + (fun _ block -> + List.iter block.Code.body ~f:(fun i -> + match i with + | Code.Let + ( _ + , Prim + ( Extern "caml_register_global" + , [ _code; Pv block; Pc (NativeString name) ] ) ) -> + let name = + match name with + | Byte s -> s + | Utf (Utf8 s) -> s + in + shapes := StringMap.add name block !shapes + | _ -> ())) + p.blocks; + let map = + if StringMap.is_empty !shapes + then StringMap.empty + else + let _, info = Flow.f p in + let pure = Pure_fun.f p in + let return_values = Code.return_values p in + StringMap.filter_map + (fun _ x -> + match Flow.the_shape_of ~return_values ~pure info x with + | Top -> None + | (Function _ | Block _) as s -> Some s) + !shapes + in + if times () then Format.eprintf " shapes: %a@." Timer.print t; + map) + else StringMap.empty + +let effects_and_exact_calls + ~keep_flow_data + ~deadcode_sentinal + ~shapes + (profile : Profile.t) + p = let fast = match Config.effects (), profile with | (`Cps | `Double_translation), _ -> false @@ -116,20 +164,24 @@ let effects_and_exact_calls ~keep_flow_data ~deadcode_sentinal (profile : Profil match Config.effects () with | `Cps | `Double_translation -> if debug () then Format.eprintf "Effects...@."; + let shapes = collects_shapes ~shapes p in let p, trampolined_calls, in_cps = Effects.f ~flow_info:info ~live_vars p in - (p, (trampolined_calls, in_cps, None)) - |> map_fst - (match Config.target () with - | `Wasm -> Fun.id - | `JavaScript -> Lambda_lifting.f) + let p = + match Config.target () with + | `Wasm -> p + | `JavaScript -> Lambda_lifting.f p + in + p, trampolined_calls, in_cps, None, shapes | `Disabled | `Jspi -> let p = Specialize.f ~function_arity:(fun f -> Global_flow.function_arity info f) p in + let shapes = collects_shapes ~shapes p in ( p - , ( (Code.Var.Set.empty : Effects.trampolined_calls) - , (Code.Var.Set.empty : Effects.in_cps) - , global_flow_data ) ) + , (Code.Var.Set.empty : Effects.trampolined_calls) + , (Code.Var.Set.empty : Effects.in_cps) + , global_flow_data + , shapes ) let print p = if debug () then Code.Print.program Format.err_formatter (fun _ _ -> "") p; @@ -176,7 +228,7 @@ let generate ~exported_runtime ~wrap_with_fun ~warn_on_unhandled_effect - { program; variable_uses; trampolined_calls; deadcode_sentinal; in_cps } = + { program; variable_uses; trampolined_calls; deadcode_sentinal; in_cps; shapes = _ } = if times () then Format.eprintf "Start Generation...@."; let should_export = should_export wrap_with_fun in Generate.f @@ -617,7 +669,7 @@ let link_and_pack ?(standalone = true) ?(wrap_with_fun = `Iife) ?(link = `No) p |> pack ~wrap_with_fun ~standalone |> check_js -let optimize ~profile ~keep_flow_data p = +let optimize ~shapes ~profile ~keep_flow_data p = let deadcode_sentinal = (* If deadcode is disabled, this field is just fresh variable *) Code.Var.fresh_n "dummy" @@ -630,31 +682,35 @@ let optimize ~profile ~keep_flow_data p = | O2 -> o2 | O3 -> o3) +> specialize_js_once_after - +> effects_and_exact_calls ~keep_flow_data ~deadcode_sentinal profile - +> map_fst + +> effects_and_exact_calls ~keep_flow_data ~deadcode_sentinal ~shapes profile + +> map_fst5 (match Config.target (), Config.effects () with | `JavaScript, `Disabled -> Generate_closure.f | `JavaScript, (`Cps | `Double_translation) | `Wasm, (`Disabled | `Jspi | `Cps) -> Fun.id | `JavaScript, `Jspi | `Wasm, `Double_translation -> assert false) - +> map_fst deadcode' + +> map_fst5 deadcode' in if times () then Format.eprintf "Start Optimizing...@."; let t = Timer.make () in - let (program, variable_uses), (trampolined_calls, in_cps, global_flow_info) = opt p in + let (program, variable_uses), trampolined_calls, in_cps, global_flow_info, shapes = + opt p + in let () = if times () then Format.eprintf " optimizations : %a@." Timer.print t in - ( { program; variable_uses; trampolined_calls; in_cps; deadcode_sentinal } + ( { program; variable_uses; trampolined_calls; in_cps; deadcode_sentinal; shapes } , global_flow_info ) -let optimize_for_wasm ~profile p = - let optimized_code, global_flow_data = optimize ~profile ~keep_flow_data:true p in +let optimize_for_wasm ~shapes ~profile p = + let optimized_code, global_flow_data = + optimize ~shapes ~profile ~keep_flow_data:true p + in ( optimized_code , match global_flow_data with | Some data -> data | None -> Global_flow.f ~fast:false optimized_code.program ) -let full ~standalone ~wrap_with_fun ~profile ~link ~source_map ~formatter p = - let optimized_code, _ = optimize ~profile ~keep_flow_data:false p in +let full ~standalone ~wrap_with_fun ~shapes ~profile ~link ~source_map ~formatter p = + let optimized_code, _ = optimize ~shapes ~profile ~keep_flow_data:false p in let exported_runtime = not standalone in let emit formatter = generate ~exported_runtime ~wrap_with_fun ~warn_on_unhandled_effect:standalone @@ -663,11 +719,21 @@ let full ~standalone ~wrap_with_fun ~profile ~link ~source_map ~formatter p = +> name_variables +> output formatter ~source_map () in - emit formatter optimized_code - -let full_no_source_map ~formatter ~standalone ~wrap_with_fun ~profile ~link p = - let (_ : Source_map.info) = - full ~standalone ~wrap_with_fun ~profile ~link ~source_map:false ~formatter p + let shapes = optimized_code.shapes in + StringMap.iter + (fun name shape -> + Shape.Store.set ~name shape; + if debug_shapes () + then + Pretty_print.string + formatter + (Printf.sprintf "//# shape: %s:%s\n" name (Shape.to_string shape))) + shapes; + emit formatter optimized_code, shapes + +let full_no_source_map ~formatter ~shapes ~standalone ~wrap_with_fun ~profile ~link p = + let (_ : Source_map.info * _) = + full ~shapes ~standalone ~wrap_with_fun ~profile ~link ~source_map:false ~formatter p in () @@ -675,11 +741,12 @@ let f ?(standalone = true) ?(wrap_with_fun = `Iife) ?(profile = Profile.O1) + ?(shapes = false) ~link ~source_map ~formatter p = - full ~standalone ~wrap_with_fun ~profile ~link ~source_map ~formatter p + full ~standalone ~wrap_with_fun ~shapes ~profile ~link ~source_map ~formatter p let f' ?(standalone = true) @@ -688,12 +755,13 @@ let f' ~link formatter p = - full_no_source_map ~formatter ~standalone ~wrap_with_fun ~profile ~link p + full_no_source_map ~formatter ~shapes:false ~standalone ~wrap_with_fun ~profile ~link p let from_string ~prims ~debug s formatter = let p = Parse_bytecode.from_string ~prims ~debug s in full_no_source_map ~formatter + ~shapes:false ~standalone:false ~wrap_with_fun:`Anonymous ~profile:O1 diff --git a/compiler/lib/driver.mli b/compiler/lib/driver.mli index 418e6d71e4..5630d18e50 100644 --- a/compiler/lib/driver.mli +++ b/compiler/lib/driver.mli @@ -18,16 +18,20 @@ * Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. *) +open Stdlib + type optimized_result = { program : Code.program ; variable_uses : Deadcode.variable_uses ; trampolined_calls : Effects.trampolined_calls ; in_cps : Effects.in_cps ; deadcode_sentinal : Code.Var.t + ; shapes : Shape.t StringMap.t } val optimize_for_wasm : - profile:Profile.t + shapes:bool + -> profile:Profile.t -> Code.program -> optimized_result * (Global_flow.state * Global_flow.info) @@ -35,11 +39,12 @@ val f : ?standalone:bool -> ?wrap_with_fun:[ `Iife | `Anonymous | `Named of string ] -> ?profile:Profile.t + -> ?shapes:bool -> link:[ `All | `All_from of string list | `Needed | `No ] -> source_map:bool -> formatter:Pretty_print.t -> Code.program - -> Source_map.info + -> Source_map.info * Shape.t StringMap.t val f' : ?standalone:bool diff --git a/compiler/lib/flow.ml b/compiler/lib/flow.ml index adf814ec9e..13de7ffb74 100644 --- a/compiler/lib/flow.ml +++ b/compiler/lib/flow.ml @@ -156,15 +156,18 @@ let propagate1 deps defs st x = | Constant _ | Apply _ | Prim _ | Special _ | Closure _ | Block _ -> Var.Set.singleton x | Field (y, n, _) -> - var_set_lift - (fun z -> - match defs.(Var.idx z) with - | Expr (Block (_, a, _, _)) when n < Array.length a -> - let t = a.(n) in - add_dep deps x t; - Var.Tbl.get st t - | Phi _ | Param | Expr _ -> Var.Set.empty) - (Var.Tbl.get st y)) + if Shape.State.mem x + then Var.Set.singleton x + else + var_set_lift + (fun z -> + match defs.(Var.idx z) with + | Expr (Block (_, a, _, _)) when n < Array.length a -> + let t = a.(n) in + add_dep deps x t; + Var.Tbl.get st t + | Phi _ | Param | Expr _ -> Var.Set.empty) + (Var.Tbl.get st y)) module G = Dgraph.Make_Imperative (Var) (Var.ISet) (Var.Tbl) @@ -301,16 +304,17 @@ let propagate2 defs known_origins possibly_mutable st x = match e with | Constant _ | Closure _ | Apply _ | Prim _ | Block _ | Special _ -> false | Field (y, n, _) -> - Var.Tbl.get st y - || Var.Set.exists - (fun z -> - match defs.(Var.idx z) with - | Expr (Block (_, a, _, _)) -> - n >= Array.length a - || Var.ISet.mem possibly_mutable z - || Var.Tbl.get st a.(n) - | Phi _ | Param | Expr _ -> true) - (Var.Tbl.get known_origins y)) + (not (Shape.State.mem x)) + && (Var.Tbl.get st y + || Var.Set.exists + (fun z -> + match defs.(Var.idx z) with + | Expr (Block (_, a, _, _)) -> + n >= Array.length a + || Var.ISet.mem possibly_mutable z + || Var.Tbl.get st a.(n) + | Phi _ | Param | Expr _ -> true) + (Var.Tbl.get known_origins y))) module Domain2 = struct type t = bool @@ -458,6 +462,66 @@ let direct_approx (info : Info.t) x = y | _ -> None +let the_shape_of ~return_values ~pure info x = + let rec loop info x acc : Shape.t = + if Var.Set.mem x acc + then Top + else + let acc = Var.Set.add x acc in + get_approx + info + (fun x -> + match Shape.State.get x with + | Some shape -> shape + | None -> ( + match info.info_defs.(Var.idx x) with + | Expr (Block (_, a, _, Immutable)) -> + Shape.Block (List.map ~f:(fun x -> loop info x acc) (Array.to_list a)) + | Expr (Closure (l, _, _)) -> + let pure = Pure_fun.pure pure x in + let res = + match Var.Map.find x return_values with + | exception Not_found -> Shape.Top + | set -> + let set = Var.Set.remove x set in + if Var.Set.is_empty set + then Shape.Top + else + let first = Var.Set.choose set in + Var.Set.fold + (fun x s1 -> + let s2 = loop info x acc in + Shape.merge s1 s2) + set + (loop info first acc) + in + Shape.Function { arity = List.length l; pure; res } + | Expr (Special (Alias_prim name)) -> ( + try + let arity = Primitive.arity name in + let pure = Primitive.is_pure name in + Shape.Function { arity; pure; res = Top } + with _ -> Top) + | Expr (Apply { f; args; _ }) -> + let shape = loop info f (Var.Set.add f acc) in + let rec loop n' shape = + match shape with + | Shape.Function { arity = n; pure; res } -> + if n = n' + then res + else if n' < n + then Shape.Function { arity = n - n'; pure; res } + else loop (n' - n) res + | Shape.Block _ | Shape.Top -> Shape.Top + in + loop (List.length args) shape + | _ -> Shape.Top)) + Top + (fun u v -> Shape.merge u v) + x + in + loop info x Var.Set.empty + let build_subst (info : Info.t) vars = let nv = Var.count () in let subst = Array.init nv ~f:(fun i -> Var.of_idx i) in diff --git a/compiler/lib/flow.mli b/compiler/lib/flow.mli index d7c49f621e..58b4e1afb0 100644 --- a/compiler/lib/flow.mli +++ b/compiler/lib/flow.mli @@ -67,3 +67,10 @@ val the_block_contents_of : Info.t -> Code.prim_arg -> Code.Var.t array option val the_int : Info.t -> Code.prim_arg -> Targetint.t option val f : Code.program -> Code.program * Info.t + +val the_shape_of : + return_values:Code.Var.Set.t Code.Var.Map.t + -> pure:Pure_fun.t + -> Info.t + -> Code.Var.t + -> Shape.t diff --git a/compiler/lib/ocaml_compiler.ml b/compiler/lib/ocaml_compiler.ml index 00d35a06b3..0c4ed37a34 100644 --- a/compiler/lib/ocaml_compiler.ml +++ b/compiler/lib/ocaml_compiler.ml @@ -37,6 +37,46 @@ let rec constant_of_const c : Code.constant = let l = Array.of_list (List.map l ~f:constant_of_const) in Tuple (tag, l, Unknown) +type module_or_not = + | Module + | Not_module + | Unknown + +let rec is_module_in_summary deep ident' summary = + match summary with + (* Unknown *) + | Env.Env_empty -> deep, Unknown + (* Module *) + | Env.Env_module (summary, ident, _, _) + | Env.Env_functor_arg (summary, ident) + | Env.Env_persistent (summary, ident) -> + if Ident.same ident ident' + then deep, Module + else is_module_in_summary (deep + 1) ident' summary + (* Not_module *) + | Env.Env_modtype (summary, ident, _) | Env.Env_extension (summary, ident, _) -> + if Ident.same ident ident' + then deep, Not_module + else is_module_in_summary (deep + 1) ident' summary + (* Lowercase ident *) + | Env.Env_value (summary, ident, _) + | Env.Env_type (summary, ident, _) + | Env.Env_class (summary, ident, _) + | Env.Env_cltype (summary, ident, _) -> + ignore (ident : Ident.t); + is_module_in_summary (deep + 1) ident' summary + (* Other, no ident *) + | Env.Env_open (summary, _) + | Env.Env_constraints (summary, _) + | Env.Env_copy_types summary + | Env.Env_value_unbound (summary, _, _) + | Env.Env_module_unbound (summary, _, _) -> + is_module_in_summary (deep + 1) ident' summary + +let is_module_in_summary ident summary = + let _deep, b = is_module_in_summary 0 ident summary in + b + module Symtable = struct (* Copied from ocaml/bytecomp/symtable.ml *) module Num_tbl (M : Map.S) = struct diff --git a/compiler/lib/ocaml_compiler.mli b/compiler/lib/ocaml_compiler.mli index afcb137b29..0c4c31dd8a 100644 --- a/compiler/lib/ocaml_compiler.mli +++ b/compiler/lib/ocaml_compiler.mli @@ -18,6 +18,13 @@ val constant_of_const : Lambda.structured_constant -> Code.constant +type module_or_not = + | Module + | Not_module + | Unknown + +val is_module_in_summary : Ident.t -> Env.summary -> module_or_not + module Symtable : sig module Global : sig type t = diff --git a/compiler/lib/parse_bytecode.ml b/compiler/lib/parse_bytecode.ml index e6bb26b7cf..5a864d4979 100644 --- a/compiler/lib/parse_bytecode.ml +++ b/compiler/lib/parse_bytecode.ml @@ -585,6 +585,9 @@ module State = struct ; env_offset : int ; handlers : handler list ; globals : globals + ; immutable : unit Code.Var.Hashtbl.t + ; module_or_not : Ocaml_compiler.module_or_not Ident.Tbl.t + ; includes : string list } let fresh_var state = @@ -669,8 +672,17 @@ module State = struct let pop_handler state = { state with handlers = List.tl state.handlers } - let initial g = - { accu = Unset; stack = []; env = [||]; env_offset = 0; handlers = []; globals = g } + let initial includes g immutable = + { accu = Unset + ; stack = [] + ; env = [||] + ; env_offset = 0 + ; handlers = [] + ; globals = g + ; immutable + ; module_or_not = Ident.Tbl.create 0 + ; includes + } let rec print_stack f l = match l with @@ -693,20 +705,37 @@ module State = struct print_env st.env - let rec name_rec debug i l s summary = + let maybe_module ident = + match (Ident.name ident).[0] with + | 'A' .. 'Z' -> true + | _ -> false + + let rec name_rec debug st i l s summary = match l, s with | [], _ -> () | (j, ident) :: lrem, Var v :: srem when i = j -> + (if maybe_module ident && not (Code.Var.Hashtbl.mem st.immutable v) + then + match Ident.Tbl.find st.module_or_not ident with + | Module -> Code.Var.Hashtbl.add st.immutable v () + | Not_module -> () + | (exception Not_found) | Unknown -> ( + match Ocaml_compiler.is_module_in_summary ident summary with + | Module -> + Ident.Tbl.add st.module_or_not ident Module; + Code.Var.Hashtbl.add st.immutable v () + | Not_module -> Ident.Tbl.add st.module_or_not ident Not_module + | Unknown -> ())); Var.set_name v (Ident.name ident); - name_rec debug (i + 1) lrem srem summary - | (j, _) :: _, _ :: srem when i < j -> name_rec debug (i + 1) l srem summary + name_rec debug st (i + 1) lrem srem summary + | (j, _) :: _, _ :: srem when i < j -> name_rec debug st (i + 1) l srem summary | _ -> assert false let name_vars st debug pc = if Debug.names debug then let l, summary = Debug.find debug pc in - name_rec debug 0 l st.stack summary + name_rec debug st 0 l st.stack summary let rec make_stack i state = if i = 0 @@ -799,6 +828,12 @@ let get_global state instrs i = let x, state = State.fresh_var state in if debug_parser () then Format.printf "%a = CONST(%d)@." Var.print x i; g.vars.(i) <- Some x; + (match g.named_value.(i) with + | None -> () + | Some name -> ( + match Shape.Store.load ~name ~paths:state.includes with + | None -> () + | Some shape -> Shape.State.assign x shape)); x, state, instrs | false, `Wasm -> ( (* Reference to another compilation units in case of separate @@ -850,6 +885,8 @@ let string_of_addr debug_data addr = in Printf.sprintf "%s:%s-%s %s" file (pos loc.loc_start) (pos loc.loc_end) kind) +let is_immutable _instr _infos _pc = (* We don't know yet *) Maybe_mutable + let rec compile_block blocks joins debug_data code pc state : unit = match Addr.Map.find_opt pc !tagged_blocks with | Some old_state -> ( @@ -1355,6 +1392,7 @@ and compile infos pc state (instrs : instr list) = let j = getu code (pc + 2) in let y, state = State.fresh_var state in if debug_parser () then Format.printf "%a = %a[%d]@." Var.print y Var.print x j; + Shape.State.propagate x j y; compile infos (pc + 3) state (Let (y, Field (x, j, Non_float)) :: instrs) | PUSHGETGLOBALFIELD -> let state = State.push state in @@ -1364,6 +1402,7 @@ and compile infos pc state (instrs : instr list) = let j = getu code (pc + 2) in let y, state = State.fresh_var state in if debug_parser () then Format.printf "%a = %a[%d]@." Var.print y Var.print x j; + Shape.State.propagate x j y; compile infos (pc + 3) state (Let (y, Field (x, j, Non_float)) :: instrs) | SETGLOBAL -> let i = getu code (pc + 1) in @@ -1377,47 +1416,36 @@ and compile infos pc state (instrs : instr list) = let x, state = State.fresh_var state in if debug_parser () then Format.printf "%a = 0@." Var.print x; let instrs = register_global g i instrs in + Code.Var.Hashtbl.add state.immutable (access_global g i) (); compile infos (pc + 2) state (Let (x, const 0) :: instrs) | ATOM0 -> let x, state = State.fresh_var state in if debug_parser () then Format.printf "%a = ATOM(0)@." Var.print x; - compile - infos - (pc + 1) - state - (Let (x, Block (0, [||], Unknown, Maybe_mutable)) :: instrs) + let imm = is_immutable instr infos pc in + compile infos (pc + 1) state (Let (x, Block (0, [||], Unknown, imm)) :: instrs) | ATOM -> let i = getu code (pc + 1) in let x, state = State.fresh_var state in if debug_parser () then Format.printf "%a = ATOM(%d)@." Var.print x i; - compile - infos - (pc + 2) - state - (Let (x, Block (i, [||], Unknown, Maybe_mutable)) :: instrs) + let imm = is_immutable instr infos pc in + compile infos (pc + 2) state (Let (x, Block (i, [||], Unknown, imm)) :: instrs) | PUSHATOM0 -> let state = State.push state in let x, state = State.fresh_var state in if debug_parser () then Format.printf "%a = ATOM(0)@." Var.print x; - compile - infos - (pc + 1) - state - (Let (x, Block (0, [||], Unknown, Maybe_mutable)) :: instrs) + let imm = is_immutable instr infos pc in + compile infos (pc + 1) state (Let (x, Block (0, [||], Unknown, imm)) :: instrs) | PUSHATOM -> let state = State.push state in let i = getu code (pc + 1) in let x, state = State.fresh_var state in if debug_parser () then Format.printf "%a = ATOM(%d)@." Var.print x i; - compile - infos - (pc + 2) - state - (Let (x, Block (i, [||], Unknown, Maybe_mutable)) :: instrs) + let imm = is_immutable instr infos pc in + compile infos (pc + 2) state (Let (x, Block (i, [||], Unknown, imm)) :: instrs) | MAKEBLOCK -> let size = getu code (pc + 1) in let tag = getu code (pc + 2) in @@ -1432,22 +1460,24 @@ and compile infos pc state (instrs : instr list) = Format.printf "%d = %a; " i Var.print (List.nth contents i) done; Format.printf "}@."); + let imm = is_immutable instr infos pc in compile infos (pc + 3) state - (Let (x, Block (tag, Array.of_list contents, Unknown, Maybe_mutable)) :: instrs) + (Let (x, Block (tag, Array.of_list contents, Unknown, imm)) :: instrs) | MAKEBLOCK1 -> let tag = getu code (pc + 1) in let y = State.accu state in let x, state = State.fresh_var state in if debug_parser () then Format.printf "%a = { 0 = %a; }@." Var.print x Var.print y; + let imm = is_immutable instr infos pc in compile infos (pc + 2) state - (Let (x, Block (tag, [| y |], Unknown, Maybe_mutable)) :: instrs) + (Let (x, Block (tag, [| y |], Unknown, imm)) :: instrs) | MAKEBLOCK2 -> let tag = getu code (pc + 1) in let y = State.accu state in @@ -1457,11 +1487,12 @@ and compile infos pc state (instrs : instr list) = if debug_parser () then Format.printf "%a = { 0 = %a; 1 = %a; }@." Var.print x Var.print y Var.print z; + let imm = is_immutable instr infos pc in compile infos (pc + 2) (State.pop 1 state) - (Let (x, Block (tag, [| y; z |], Unknown, Maybe_mutable)) :: instrs) + (Let (x, Block (tag, [| y; z |], Unknown, imm)) :: instrs) | MAKEBLOCK3 -> let tag = getu code (pc + 1) in let y = State.accu state in @@ -1481,11 +1512,12 @@ and compile infos pc state (instrs : instr list) = z Var.print t; + let imm = is_immutable instr infos pc in compile infos (pc + 2) (State.pop 2 state) - (Let (x, Block (tag, [| y; z; t |], Unknown, Maybe_mutable)) :: instrs) + (Let (x, Block (tag, [| y; z; t |], Unknown, imm)) :: instrs) | MAKEFLOATBLOCK -> let size = getu code (pc + 1) in let state = State.push state in @@ -1499,34 +1531,39 @@ and compile infos pc state (instrs : instr list) = Format.printf "%d = %a; " i Var.print (List.nth contents i) done; Format.printf "}@."); + let imm = is_immutable instr infos pc in compile infos (pc + 2) state - (Let (x, Block (254, Array.of_list contents, Unknown, Maybe_mutable)) :: instrs) + (Let (x, Block (254, Array.of_list contents, Unknown, imm)) :: instrs) | GETFIELD0 -> let y = State.accu state in let x, state = State.fresh_var state in if debug_parser () then Format.printf "%a = %a[0]@." Var.print x Var.print y; + Shape.State.propagate y 0 x; compile infos (pc + 1) state (Let (x, Field (y, 0, Non_float)) :: instrs) | GETFIELD1 -> let y = State.accu state in let x, state = State.fresh_var state in if debug_parser () then Format.printf "%a = %a[1]@." Var.print x Var.print y; + Shape.State.propagate y 1 x; compile infos (pc + 1) state (Let (x, Field (y, 1, Non_float)) :: instrs) | GETFIELD2 -> let y = State.accu state in let x, state = State.fresh_var state in if debug_parser () then Format.printf "%a = %a[2]@." Var.print x Var.print y; + Shape.State.propagate y 2 x; compile infos (pc + 1) state (Let (x, Field (y, 2, Non_float)) :: instrs) | GETFIELD3 -> let y = State.accu state in let x, state = State.fresh_var state in if debug_parser () then Format.printf "%a = %a[3]@." Var.print x Var.print y; + Shape.State.propagate y 3 x; compile infos (pc + 1) state (Let (x, Field (y, 3, Non_float)) :: instrs) | GETFIELD -> let y = State.accu state in @@ -1534,6 +1571,7 @@ and compile infos pc state (instrs : instr list) = let x, state = State.fresh_var state in if debug_parser () then Format.printf "%a = %a[%d]@." Var.print x Var.print y n; + Shape.State.propagate y n x; compile infos (pc + 2) state (Let (x, Field (y, n, Non_float)) :: instrs) | GETFLOATFIELD -> let y = State.accu state in @@ -2500,18 +2538,28 @@ type one = ; debug : Debug.summary } -let parse_bytecode code globals debug_data = - let state = State.initial globals in +let parse_bytecode ~includes code globals debug_data = + let immutable = Code.Var.Hashtbl.create 0 in + let state = State.initial includes globals immutable in Code.Var.reset (); let blocks', joins = Blocks.analyse code in + Shape.State.reset (); let p = if not (Blocks.is_empty blocks') then ( let start = 0 in + compile_block blocks' joins debug_data code start state; let blocks = Addr.Map.mapi (fun _ (state, instr, last) -> + let instr = + List.map instr ~f:(function + | Let (x, Block (tag, args, k, Maybe_mutable)) + when Code.Var.Hashtbl.mem immutable x -> + Let (x, Block (tag, args, k, Immutable)) + | x -> x) + in { params = (match state with | Some state -> State.stack_vars state @@ -2677,7 +2725,7 @@ let from_exe Ocaml_compiler.Symtable.GlobalMap.iter symbols ~f:(fun id n -> globals.named_value.(n) <- Some (Ocaml_compiler.Symtable.Global.name id); globals.is_exported.(n) <- true); - let p = parse_bytecode code globals debug_data in + let p = parse_bytecode ~includes code globals debug_data in (* register predefined exception *) let body = List.fold_left predefined_exceptions ~init:[] ~f:(fun body (i, name) -> @@ -2807,7 +2855,7 @@ let from_bytes ~prims ~debug (code : bytecode) = t in let globals = make_globals 0 [||] prims in - let p = parse_bytecode code globals debug_data in + let p = parse_bytecode ~includes:[] code globals debug_data in let gdata = Var.fresh_n "global_data" in let need_gdata = ref false in let find_name i = @@ -2939,7 +2987,7 @@ module Reloc = struct globals end -let from_compilation_units ~includes:_ ~include_cmis ~debug_data l = +let from_compilation_units ~includes ~include_cmis ~debug_data l = let reloc = Reloc.create () in List.iter l ~f:(fun (compunit, code) -> Reloc.step1 reloc compunit code); List.iter l ~f:(fun (compunit, code) -> Reloc.step2 reloc compunit code); @@ -2948,7 +2996,7 @@ let from_compilation_units ~includes:_ ~include_cmis ~debug_data l = let l = List.map l ~f:(fun (_, c) -> Bytes.to_string c) in String.concat ~sep:"" l in - let prog = parse_bytecode code globals debug_data in + let prog = parse_bytecode ~includes code globals debug_data in let gdata = Var.fresh_n "global_data" in let need_gdata = ref false in let body = diff --git a/compiler/lib/pure_fun.ml b/compiler/lib/pure_fun.ml index da4a9c59aa..153cfc157e 100644 --- a/compiler/lib/pure_fun.ml +++ b/compiler/lib/pure_fun.ml @@ -27,11 +27,16 @@ open Code (****) +let pure pure_funs x = Var.Set.mem x pure_funs + +let empty = Var.Set.empty + let pure_expr pure_funs e = match e with | Block _ | Field _ | Closure _ | Constant _ -> true | Special (Alias_prim _) -> true - | Apply { f; exact; _ } -> exact && Var.Set.mem f pure_funs + | Apply { f; exact; _ } -> + exact && (Var.Set.mem f pure_funs || Shape.State.is_pure_fun f) | Prim (p, _l) -> ( match p with | Extern f -> Primitive.is_pure f diff --git a/compiler/lib/pure_fun.mli b/compiler/lib/pure_fun.mli index f0adbf272c..7d373c9fe9 100644 --- a/compiler/lib/pure_fun.mli +++ b/compiler/lib/pure_fun.mli @@ -24,4 +24,8 @@ val pure_expr : t -> Code.expr -> bool val pure_instr : t -> Code.instr -> bool +val pure : t -> Code.Var.t -> bool + +val empty : t + val f : Code.program -> t diff --git a/compiler/lib/shape.ml b/compiler/lib/shape.ml new file mode 100644 index 0000000000..764a1571e0 --- /dev/null +++ b/compiler/lib/shape.ml @@ -0,0 +1,174 @@ +(* Js_of_ocaml compiler + * http://www.ocsigen.org/js_of_ocaml/ + * Copyright (C) 2024 Hugo Heuzard + * + * This program is free software; you can redistribute it and/or modify + * it under the terms of the GNU Lesser General Public License as published by + * the Free Software Foundation, with linking exception; + * either version 2.1 of the License, or (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU Lesser General Public License for more details. + * + * You should have received a copy of the GNU Lesser General Public License + * along with this program; if not, write to the Free Software + * Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. + *) + +open! Stdlib + +type t = + | Top + | Block of t list + | Function of + { arity : int + ; pure : bool + ; res : t + } + +type shape = t + +let rec equal a b = + match a, b with + | Top, Top -> true + | ( Function { arity = a1; pure = p1; res = r1 } + , Function { arity = a2; pure = p2; res = r2 } ) -> + a1 = a2 && Bool.(p1 = p2) && equal r1 r2 + | Block b1, Block b2 -> ( + try List.for_all2 ~f:equal b1 b2 with Invalid_argument _ -> false) + | Top, (Function _ | Block _) | Function _, (Top | Block _) | Block _, (Top | Function _) + -> false + +let rec merge (u : t) (v : t) = + match u, v with + | ( Function { arity = a1; pure = p1; res = r1 } + , Function { arity = a2; pure = p2; res = r2 } ) -> + if a1 = a2 then Function { arity = a1; pure = p1 && p2; res = merge r1 r2 } else Top + | Block b1, Block b2 -> + if List.length b1 = List.length b2 then Block (List.map2 b1 b2 ~f:merge) else Top + | Top, _ | _, Top -> Top + | Function _, Block _ | Block _, Function _ -> Top + +let rec to_string (shape : t) = + match shape with + | Top -> "N" + | Block l -> "[" ^ String.concat ~sep:"," (List.map ~f:to_string l) ^ "]" + | Function { arity; pure; res } -> + Printf.sprintf + "F(%d)%s%s" + arity + (if pure then "*" else "") + (match res with + | Top -> "" + | _ -> "->" ^ to_string res) + +module Store = struct + let ext = ".jsoo-shape" + + let filename ~dir ~name = Filename.concat dir (name ^ ext) + + let t = String.Hashtbl.create 17 + + let loaded = String.Hashtbl.create 17 + + let set ~name shape = String.Hashtbl.replace t name shape + + let get ~name = String.Hashtbl.find_opt t name + + let magic = "JsooShape000" + + let load' fn = + let ic = open_in_bin fn in + let m = really_input_string ic (String.length magic) in + if not (String.equal m magic) + then failwith (Printf.sprintf "Invalid magic number for shape file %s" fn); + let shapes : (string * shape) list = Marshal.from_channel ic in + close_in ic; + List.iter shapes ~f:(fun (name, shape) -> set ~name shape) + + let load ~name ~paths = + if String.Hashtbl.mem t name + then get ~name + else if not (Config.Flag.load_shapes_auto ()) + then None + else + match Fs.find_in_path paths (filename ~dir:"." ~name) with + | Some f -> + load' f; + get ~name + | None -> + let rec scan : _ -> shape option = function + | [] -> None + | dir :: xs -> ( + let l = + Sys.readdir dir + |> Array.to_list + |> List.sort ~cmp:String.compare + |> List.map ~f:(fun n -> Filename.concat dir n) + in + match + List.find_map l ~f:(fun s -> + if Filename.check_suffix s ext && not (String.Hashtbl.mem loaded s) + then ( + load' s; + String.Hashtbl.add loaded s (); + match get ~name with + | None -> None + | Some shape -> Some (s, shape)) + else None) + with + | None -> scan xs + | Some (fn, shape) -> + Format.eprintf "Shape: %s loaded from %s\n" name fn; + Some shape) + in + scan paths + + let save' fn (l : (string * shape) list) = + let oc = open_out_bin fn in + output_string oc magic; + Marshal.to_channel oc l []; + close_out oc + + let save ~name ~dir = + match get ~name with + | None -> failwith (Printf.sprintf "Don't know any shape for %s" name) + | Some shape -> + let fn = filename ~dir ~name in + save' fn [ name, shape ] +end + +module State = struct + type nonrec t = + { table : t Code.Var.Hashtbl.t + ; cache : BitSet.t + } + + let t : t = { table = Code.Var.Hashtbl.create 17; cache = BitSet.create () } + + let assign x shape = + Code.Var.Hashtbl.replace t.table x shape; + BitSet.set t.cache (Code.Var.idx x) + + let propagate x offset target = + match Code.Var.Hashtbl.find_opt t.table x with + | None -> () + | Some (Top | Function _) -> () + | Some (Block l) -> assign target (List.nth l offset) + + let mem x = BitSet.mem t.cache (Code.Var.idx x) + + let get x = if mem x then Code.Var.Hashtbl.find_opt t.table x else None + + let is_pure_fun x = + match Code.Var.Hashtbl.find_opt t.table x with + | None -> false + | Some (Top | Block _) -> false + | Some (Function { pure; _ }) -> pure + + let reset () = + Code.Var.Hashtbl.clear t.table; + BitSet.clear t.cache +end diff --git a/compiler/lib/shape.mli b/compiler/lib/shape.mli new file mode 100644 index 0000000000..180840f9d6 --- /dev/null +++ b/compiler/lib/shape.mli @@ -0,0 +1,63 @@ +(* Js_of_ocaml compiler + * http://www.ocsigen.org/js_of_ocaml/ + * Copyright (C) 2024 Hugo Heuzard + * + * This program is free software; you can redistribute it and/or modify + * it under the terms of the GNU Lesser General Public License as published by + * the Free Software Foundation, with linking exception; + * either version 2.1 of the License, or (at your option) any later version. + * + * This program is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU Lesser General Public License for more details. + * + * You should have received a copy of the GNU Lesser General Public License + * along with this program; if not, write to the Free Software + * Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. + *) + +type t = + | Top + | Block of t list + | Function of + { arity : int + ; pure : bool + ; res : t + } + +val to_string : t -> string + +val equal : t -> t -> bool + +val merge : t -> t -> t + +module Store : sig + val ext : string + + val set : name:string -> t -> unit + + val get : name:string -> t option + + val load' : string -> unit + + val load : name:string -> paths:string list -> t option + + val save : name:string -> dir:string -> unit + + val save' : string -> (string * t) list -> unit +end + +module State : sig + val propagate : Code.Var.t -> int -> Code.Var.t -> unit + + val assign : Code.Var.t -> t -> unit + + val get : Code.Var.t -> t option + + val mem : Code.Var.t -> bool + + val is_pure_fun : Code.Var.t -> bool + + val reset : unit -> unit +end diff --git a/compiler/tests-compiler/sourcemap.ml b/compiler/tests-compiler/sourcemap.ml index ad83ae7cc8..661911190f 100644 --- a/compiler/tests-compiler/sourcemap.ml +++ b/compiler/tests-compiler/sourcemap.ml @@ -67,32 +67,32 @@ let%expect_test _ = -> print_mapping ~line_offset:gen_line ~col_offset:gen_column map)); [%expect {| - $ cat "test.ml" - 1: let id x = x - $ cat "test.js" - 1: - 2: //# unitInfo: Provides: Test - 3: (function(globalThis){ - 4: "use strict"; - 5: var runtime = globalThis.jsoo_runtime; - 6: function id(x){return x;} - 7: var Test = [0, id]; - 8: runtime.caml_register_global(0, Test, "Test"); - 9: return; - 10: } - 11: (globalThis)); - 12: - 13: //# sourceMappingURL=test.map - /builtin/blackbox.ml:1:0 -> 5:7 - /builtin/blackbox.ml:1:0 -> 5:17 - /builtin/blackbox.ml:1:0 -> 6:0 - /builtin/blackbox.ml:1:0 -> 6:12 - /builtin/blackbox.ml:1:0 -> 6:15 - /dune-root/test.ml:1:11 -> 6:18 - /dune-root/test.ml:1:12 -> 6:27 - /dune-root/test.ml:1:12 -> 7:0 - /dune-root/test.ml:1:12 -> 7:7 - /builtin/blackbox.ml:1:0 -> 7:14 + $ cat "test.ml" + 1: let id x = x + $ cat "test.js" + 1: + 2: //# unitInfo: Provides: Test + 3: (function(globalThis){ + 4: "use strict"; + 5: var runtime = globalThis.jsoo_runtime; + 6: function id(x){return x;} + 7: var Test = [0, id]; + 8: runtime.caml_register_global(0, Test, "Test"); + 9: return; + 10: } + 11: (globalThis)); + 12: + 13: //# sourceMappingURL=test.map + /builtin/blackbox.ml:1:0 -> 5:7 + /builtin/blackbox.ml:1:0 -> 5:17 + /builtin/blackbox.ml:1:0 -> 6:0 + /builtin/blackbox.ml:1:0 -> 6:12 + /builtin/blackbox.ml:1:0 -> 6:15 + /dune-root/test.ml:1:11 -> 6:18 + /dune-root/test.ml:1:12 -> 6:27 + /dune-root/test.ml:1:12 -> 7:0 + /dune-root/test.ml:1:12 -> 7:7 + /builtin/blackbox.ml:1:0 -> 7:14 |}] let%expect_test _ = diff --git a/compiler/tests-full/dune b/compiler/tests-full/dune index f4fef6cd83..67c542571f 100644 --- a/compiler/tests-full/dune +++ b/compiler/tests-full/dune @@ -11,6 +11,8 @@ --debug var --debuginfo + --debug + shapes %{lib:stdlib:stdlib.cma} -o %{targets}))) @@ -35,6 +37,41 @@ (action (diff stdlib.cma.expected.js stdlib.cma.output.js))) +(library + (name shapes) + (modules m1 m2 m3)) + +(rule + (targets shapes.cma.js) + (enabled_if + (= %{ocaml_version} "5.2.0")) + (action + (run + %{bin:js_of_ocaml} + --pretty + --debuginfo + --debug + shapes + %{dep:shapes.cma} + -o + %{targets}))) + +(rule + (targets shapes.cma.output.js) + (enabled_if + (= %{ocaml_version} "5.2.0")) + (action + (with-stdout-to + %{targets} + (run tail -n +3 %{dep:shapes.cma.js})))) + +(rule + (alias runtest) + (enabled_if + (= %{ocaml_version} "5.2.0")) + (action + (diff shapes.cma.expected.js shapes.cma.output.js))) + (rule (targets fs.output.js) (deps file1 file2) diff --git a/compiler/tests-full/m1.ml b/compiler/tests-full/m1.ml new file mode 100644 index 0000000000..0a01e76687 --- /dev/null +++ b/compiler/tests-full/m1.ml @@ -0,0 +1 @@ +let f () () = () diff --git a/compiler/tests-full/m2.ml b/compiler/tests-full/m2.ml new file mode 100644 index 0000000000..46cfe56e5e --- /dev/null +++ b/compiler/tests-full/m2.ml @@ -0,0 +1 @@ +let f () = print_endline "" diff --git a/compiler/tests-full/m3.ml b/compiler/tests-full/m3.ml new file mode 100644 index 0000000000..196093fbd7 --- /dev/null +++ b/compiler/tests-full/m3.ml @@ -0,0 +1,3 @@ +let f () = if Random.int 2 > 1 then M1.f else fun () () -> M2.f () + +let x = f () () () diff --git a/compiler/tests-full/shapes.cma.expected.js b/compiler/tests-full/shapes.cma.expected.js new file mode 100644 index 0000000000..8aabd47fe3 --- /dev/null +++ b/compiler/tests-full/shapes.cma.expected.js @@ -0,0 +1,86 @@ + +//# unitInfo: Provides: Shapes +//# shape: Shapes:[] +(function + (globalThis){ + "use strict"; + var runtime = globalThis.jsoo_runtime, Shapes = [0]; + runtime.caml_register_global(0, Shapes, "Shapes"); + return; + } + (globalThis)); + +//# unitInfo: Provides: Shapes__M1 +//# shape: Shapes__M1:[F(2)*] +(function + (globalThis){ + "use strict"; + var runtime = globalThis.jsoo_runtime; + function f(_a_, param){ + /*<>*/ return 0; + /*<>*/ } + var Shapes_M1 = /*<>*/ [0, f]; + runtime.caml_register_global(0, Shapes_M1, "Shapes__M1"); + return; + } + (globalThis)); + +//# unitInfo: Provides: Shapes__M2 +//# unitInfo: Requires: Stdlib +//# shape: Shapes__M2:[F(1)] +(function + (globalThis){ + "use strict"; + var runtime = globalThis.jsoo_runtime; + function caml_call1(f, a0){ + return (f.l >= 0 ? f.l : f.l = f.length) === 1 + ? f(a0) + : runtime.caml_call_gen(f, [a0]); + } + var + global_data = runtime.caml_get_global_data(), + cst = "", + Stdlib = global_data.Stdlib; + function f(param){ + /*<>*/ return caml_call1(Stdlib[46], cst) /*<>*/ ; + } + var Shapes_M2 = /*<>*/ [0, f]; + runtime.caml_register_global(2, Shapes_M2, "Shapes__M2"); + return; + } + (globalThis)); + +//# unitInfo: Provides: Shapes__M3 +//# unitInfo: Requires: Shapes__M1, Shapes__M2, Stdlib__Random +//# shape: Shapes__M3:[F(1)->F(2),N] +(function + (globalThis){ + "use strict"; + var runtime = globalThis.jsoo_runtime; + function caml_call1(f, a0){ + return (f.l >= 0 ? f.l : f.l = f.length) === 1 + ? f(a0) + : runtime.caml_call_gen(f, [a0]); + } + var + global_data = runtime.caml_get_global_data(), + Shapes_M2 = global_data.Shapes__M2, + Stdlib_Random = global_data.Stdlib__Random, + Shapes_M1 = global_data.Shapes__M1; + function f(param){ + /*<>*/ return 1 + < caml_call1(Stdlib_Random[5], 2) + ? Shapes_M1[1] + : function + (_a_, param){ + /*<>*/ return Shapes_M2[1].call + (null, 0) /*<>*/ ; + }; + } + var + x = /*<>*/ f(0)(0, 0), + Shapes_M3 = /*<>*/ [0, f, x]; + runtime.caml_register_global(3, Shapes_M3, "Shapes__M3"); + return; + /*<>*/ } + (globalThis)); diff --git a/compiler/tests-full/stdlib.cma.expected.js b/compiler/tests-full/stdlib.cma.expected.js index 838afc7814..9e9052dc72 100644 --- a/compiler/tests-full/stdlib.cma.expected.js +++ b/compiler/tests-full/stdlib.cma.expected.js @@ -1,5 +1,6 @@ //# unitInfo: Provides: CamlinternalFormatBasics +//# shape: CamlinternalFormatBasics:[F(2),F(1),F(2)] (function (globalThis){ "use strict"; @@ -349,6 +350,7 @@ //# unitInfo: Provides: Stdlib //# unitInfo: Requires: CamlinternalFormatBasics +//# shape: Stdlib:[F(1),F(1),N,N,N,N,N,N,N,N,N,N,N,N,N,F(2)*,F(2)*,F(1)*,N,N,F(1)*,N,N,N,N,N,N,F(2)*,F(1),F(1)*,F(1)*,F(1),F(1)*,F(1),F(1),F(1),F(2),N,N,N,F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(3),F(1),F(1),F(2),F(2),F(2),F(4),F(4),F(2),F(2),F(2),F(2),F(1),F(1),F(1),F(1),F(2),F(1),F(1),F(3),F(1),F(1),F(4),F(4),F(2),F(1),F(1),F(1),F(2),F(1),F(1),F(1),F(1),F(2),N,F(1)*,F(2),F(1),F(1),F(1),F(4),F(1),N] (function (globalThis){ "use strict"; @@ -980,7 +982,9 @@ (globalThis)); //# unitInfo: Provides: Stdlib__Either -(function(globalThis){ +//# shape: Stdlib__Either:[F(1)*,F(1)*,F(1)*,F(1)*,F(1)*,F(1)*,F(2),F(2),F(3),F(3),F(3),F(3),F(4),F(4)] +(function + (globalThis){ "use strict"; var runtime = globalThis.jsoo_runtime; function caml_call1(f, a0){ @@ -1096,6 +1100,7 @@ //# unitInfo: Provides: Stdlib__Sys //# unitInfo: Requires: Stdlib +//# shape: Stdlib__Sys:[N,F(1),N,N,[N],N,N,N,N,N,N,N,N,N,F(2)*,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,F(1)*,N,N,N,F(1),F(1),[F(2)*]] (function (globalThis){ "use strict"; @@ -1203,6 +1208,7 @@ //# unitInfo: Provides: Stdlib__Obj //# unitInfo: Requires: Stdlib, Stdlib__Sys +//# shape: Stdlib__Obj:[F(1)*,F(2),F(3),N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,N,[F(1),F(1)*,F(1)*],N] (function (globalThis){ "use strict"; @@ -1380,6 +1386,7 @@ //# unitInfo: Provides: Stdlib__Type //# unitInfo: Requires: Stdlib__Obj +//# shape: Stdlib__Type:[[F(1)*,F(1),F(2)*]] (function (globalThis){ "use strict"; @@ -1412,7 +1419,9 @@ (globalThis)); //# unitInfo: Provides: Stdlib__Atomic -(function(globalThis){ +//# shape: Stdlib__Atomic:[F(1)*,F(1),F(1),F(2),F(2),F(3),F(2),F(1),F(1)] +(function + (globalThis){ "use strict"; var runtime = globalThis.jsoo_runtime, @@ -1449,6 +1458,7 @@ //# unitInfo: Provides: CamlinternalLazy //# unitInfo: Requires: Stdlib, Stdlib__Obj +//# shape: CamlinternalLazy:[N,F(1),F(2)] (function (globalThis){ "use strict"; @@ -1525,6 +1535,7 @@ //# unitInfo: Provides: Stdlib__Lazy //# unitInfo: Requires: CamlinternalLazy, Stdlib, Stdlib__Obj +//# shape: Stdlib__Lazy:[N,F(2)*,F(1),F(1),F(2),F(1),F(1)] (function (globalThis){ "use strict"; @@ -1620,6 +1631,7 @@ //# unitInfo: Provides: Stdlib__Seq //# unitInfo: Requires: CamlinternalLazy, Stdlib, Stdlib__Atomic, Stdlib__Lazy +//# shape: Stdlib__Seq:[F(1),F(1),F(1),F(2),F(3),F(2),F(3),F(2),F(2),F(2),F(2),F(2),F(2),F(3),F(4),F(3),F(3),F(3),F(3),F(1)*,F(2)*,F(3)*,F(2),F(3),F(2)*,F(2),F(2),F(2)*->F(1)*,F(3),F(2)*->F(1),F(3),F(3),F(3)*->F(1)*,F(2),F(2),F(3),F(3),F(3),F(1)->F(1),N,F(1)->F(1),F(2),F(3),F(2),F(3),F(3),F(3),F(4),F(3),F(4),F(2)*,F(3)*->F(1),F(1)*,F(1)*,F(2)*,F(2)*,F(1)*->F(1),F(1)*->F(1),F(2)*] (function (globalThis){ "use strict"; @@ -2545,6 +2557,7 @@ //# unitInfo: Provides: Stdlib__Option //# unitInfo: Requires: Stdlib, Stdlib__Seq +//# shape: Stdlib__Option:[N,F(1)*,F(2)*,F(1),F(2),F(1)*,F(2),F(3),F(2),F(1)*,F(1)*,F(3),F(3),F(2)*,F(1)*,F(1)] (function (globalThis){ "use strict"; @@ -2670,6 +2683,7 @@ //# unitInfo: Provides: Stdlib__Result //# unitInfo: Requires: Stdlib, Stdlib__Seq +//# shape: Stdlib__Result:[F(1)*,F(1)*,F(2)*,F(1),F(1),F(2),F(1)*,F(2),F(2),F(3),F(2),F(2),F(1)*,F(1)*,F(4),F(4),F(1)*,F(1)*,F(1)] (function (globalThis){ "use strict"; @@ -2836,7 +2850,9 @@ (globalThis)); //# unitInfo: Provides: Stdlib__Bool -(function(globalThis){ +//# shape: Stdlib__Bool:[F(1)*,F(2)*,F(2)*,F(1)*,F(1)*,F(1)*,F(2)*,F(1)*] +(function + (globalThis){ "use strict"; var runtime = globalThis.jsoo_runtime, caml_hash = runtime.caml_hash; function equal(_b_, _a_){return _b_ === _a_ ? 1 : 0;} @@ -2874,6 +2890,7 @@ //# unitInfo: Provides: Stdlib__Char //# unitInfo: Requires: Stdlib +//# shape: Stdlib__Char:[F(1),F(1),F(1)*,F(1)*,F(2)*,F(2)*,F(2)*,F(1)*] (function (globalThis){ "use strict"; @@ -2975,6 +2992,7 @@ //# unitInfo: Provides: Stdlib__Uchar //# unitInfo: Requires: Stdlib +//# shape: Stdlib__Uchar:[N,N,N,N,F(1),F(1),F(1)*,F(1),F(1)*,F(1)*,F(1)*,F(1)*,F(1),F(1)*,F(2)*,F(2)*,F(2)*,F(1)*,F(1)*,F(1)*,F(1)*,F(2)*,F(1)*,F(1),F(1)] (function (globalThis){ "use strict"; @@ -3144,6 +3162,7 @@ //# unitInfo: Provides: Stdlib__List //# unitInfo: Requires: Stdlib +//# shape: Stdlib__List:[F(1),F(2),F(2),F(1)*,F(2)*,F(1),F(1),F(2),F(2),F(1),F(2),F(2),F(2),F(1),F(1),F(3),F(3),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(3),F(3),F(3),F(3),F(3),F(3),F(4),F(4),F(2),F(2),F(3),F(3),F(2),F(2),F(2),F(2),F(1)*->F(1),F(2),F(1)*->F(1),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(3),F(1)*->F(1)*,F(1)] (function (globalThis){ "use strict"; @@ -4779,7 +4798,9 @@ (globalThis)); //# unitInfo: Provides: Stdlib__Int -(function(globalThis){ +//# shape: Stdlib__Int:[N,N,N,F(1)*,N,N,F(1)*,F(2)*,F(2)*,F(2)*,F(2)*,F(1)*,F(2)*,F(1)*] +(function + (globalThis){ "use strict"; var runtime = globalThis.jsoo_runtime, caml_hash = runtime.caml_hash; function abs(x){ @@ -4827,6 +4848,7 @@ //# unitInfo: Provides: Stdlib__Bytes //# unitInfo: Requires: Stdlib, Stdlib__Char, Stdlib__Int, Stdlib__Seq, Stdlib__Sys, Stdlib__Uchar +//# shape: Stdlib__Bytes:[F(2),F(2),N,F(1),F(1),F(1),F(3),F(3),F(3),F(4),F(5),F(5),F(2),F(2),F(2),F(2),F(2),F(2),F(3),F(3),F(2),F(2),F(1),F(1),F(2),F(2),F(2),F(2),F(3),F(3),F(3),F(3),F(2),F(3),F(3),F(1),F(1),F(1),F(1),F(2)*,F(2)*,F(2),F(2),F(1),F(1)*,F(2),F(1)*->F(1),F(1)*->F(1),F(1),F(2),F(3),F(1),F(2),F(3),F(1),F(2),F(3),F(1),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(1)] (function (globalThis){ "use strict"; @@ -6388,6 +6410,7 @@ //# unitInfo: Provides: Stdlib__String //# unitInfo: Requires: Stdlib, Stdlib__Bytes +//# shape: Stdlib__String:[F(2),F(2),N,F(1),F(1),F(5),F(2),F(2)*,F(2)*,F(2)*,F(2),F(2),F(3),F(3),F(2),F(3),F(2),F(2),F(2),F(3),F(3),F(2),F(2),F(1),F(1),F(1),F(1),F(1),F(1),F(2),F(2),F(3),F(3),F(3),F(3),F(2),F(2),F(2),F(2),F(1),F(1),F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(2)] (function (globalThis){ "use strict"; @@ -6956,7 +6979,9 @@ (globalThis)); //# unitInfo: Provides: Stdlib__Unit -(function(globalThis){ +//# shape: Stdlib__Unit:[F(2)*,F(2)*,F(1)*] +(function + (globalThis){ "use strict"; var runtime = globalThis.jsoo_runtime, cst = "()"; function equal(_a_, param){ @@ -6976,6 +7001,7 @@ //# unitInfo: Provides: Stdlib__Marshal //# unitInfo: Requires: Stdlib, Stdlib__Bytes +//# shape: Stdlib__Marshal:[F(3),F(5),F(1),F(2),F(2),N,F(2),F(2)] (function (globalThis){ "use strict"; @@ -7056,6 +7082,7 @@ //# unitInfo: Provides: Stdlib__Array //# unitInfo: Requires: Stdlib, Stdlib__Seq, Stdlib__String +//# shape: Stdlib__Array:[F(2),F(3),F(3),F(2)*,F(1)*,F(3),F(1)*,F(4),F(5),F(1),F(1),F(2),F(2),F(2),F(2),F(2),F(2),F(3),F(3),F(3),F(3),F(3),F(2),F(2),F(3),F(3),F(2),F(2),F(2),F(2),F(2),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(1)*->F(1)*,F(1)*->F(1)*,F(1),[]] (function (globalThis){ "use strict"; @@ -8029,6 +8056,7 @@ //# unitInfo: Provides: Stdlib__Float //# unitInfo: Requires: Stdlib, Stdlib__Array, Stdlib__List, Stdlib__Seq +//# shape: Stdlib__Float:[N,N,N,F(1)*,F(1)*,N,N,N,N,N,N,N,N,N,F(1)*,F(1)*,F(1)*,F(1)*,F(1),F(1),F(2)*,F(2)*,F(2)*,F(2)*,F(2)*,F(2)*,F(2)*,F(2)*,F(2)*,F(1)*,N,N] (function (globalThis){ "use strict"; @@ -9138,6 +9166,7 @@ //# unitInfo: Provides: Stdlib__Int32 //# unitInfo: Requires: Stdlib, Stdlib__Sys +//# shape: Stdlib__Int32:[N,N,N,F(2),F(2),F(1)*,F(1)*,F(1)*,N,N,F(1)*,F(1)*,F(1),F(1)*,F(2)*,F(2)*,F(2)*,F(2)*,F(2)*,F(2)*,F(1)*] (function (globalThis){ "use strict"; @@ -9273,6 +9302,7 @@ //# unitInfo: Provides: Stdlib__Int64 //# unitInfo: Requires: Stdlib +//# shape: Stdlib__Int64:[N,N,N,F(2),F(2),F(1)*,F(1)*,F(1)*,N,N,F(1)*,F(1)*,F(1),F(1)*,F(2)*,F(2)*,F(2)*,F(2)*,F(2)*,F(2)*,F(1)*] (function (globalThis){ "use strict"; @@ -9421,6 +9451,7 @@ //# unitInfo: Provides: Stdlib__Nativeint //# unitInfo: Requires: Stdlib, Stdlib__Sys +//# shape: Stdlib__Nativeint:[N,N,N,F(2),F(2),F(1)*,F(1)*,F(1)*,N,N,N,F(1)*,F(1)*,F(1),F(1)*,F(2)*,F(2)*,F(2)*,F(2)*,F(2)*,F(2)*,F(1)*] (function (globalThis){ "use strict"; @@ -9544,6 +9575,7 @@ //# unitInfo: Provides: Stdlib__Lexing //# unitInfo: Requires: Stdlib, Stdlib__Bytes, Stdlib__Int, Stdlib__Sys +//# shape: Stdlib__Lexing:[N,F(2)*,F(2),F(2)*,F(2),F(2),F(1)*,F(1),F(2),F(1)*,F(1)*,F(1)*,F(1)*,F(1),F(1),F(3),F(3),F(2),F(2),F(3),F(3)] (function (globalThis){ "use strict"; @@ -9841,6 +9873,7 @@ //# unitInfo: Provides: Stdlib__Parsing //# unitInfo: Requires: Stdlib, Stdlib__Array, Stdlib__Lexing, Stdlib__Obj +//# shape: Stdlib__Parsing:[F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),F(1),N,F(1),N,F(4),F(2),F(1),F(1)*] (function (globalThis){ "use strict"; @@ -10099,6 +10132,7 @@ //# unitInfo: Provides: Stdlib__Set //# unitInfo: Requires: Stdlib, Stdlib__List, Stdlib__Seq +//# shape: Stdlib__Set:[F(1)*] (function (globalThis){ "use strict"; @@ -11158,6 +11192,7 @@ //# unitInfo: Provides: Stdlib__Map //# unitInfo: Requires: Stdlib, Stdlib__List, Stdlib__Seq +//# shape: Stdlib__Map:[F(1)*] (function (globalThis){ "use strict"; @@ -12201,6 +12236,7 @@ //# unitInfo: Provides: Stdlib__Stack //# unitInfo: Requires: Stdlib__List, Stdlib__Seq +//# shape: Stdlib__Stack:[N,F(1)*,F(2),F(1),F(1),F(1),F(1),F(1)*,F(1),F(1)*,F(1)*,F(1)*,F(2),F(3),F(1),F(2),F(1)] (function (globalThis){ "use strict"; @@ -12337,6 +12373,7 @@ //# unitInfo: Provides: Stdlib__Queue //# unitInfo: Requires: Stdlib__Seq +//# shape: Stdlib__Queue:[N,F(1)*,F(2),F(2),F(1),F(1),F(1),F(1),F(1)*,F(1),F(1),F(1),F(1),F(1)*,F(1)*,F(2),F(3),F(2),F(1)*->F(1)*,F(2),F(1)] (function (globalThis){ "use strict"; @@ -12553,6 +12590,7 @@ //# unitInfo: Provides: Stdlib__Buffer //# unitInfo: Requires: Stdlib, Stdlib__Bytes, Stdlib__Seq, Stdlib__String, Stdlib__Sys +//# shape: Stdlib__Buffer:[F(1)*,F(1),F(1),F(3),F(5),F(2),F(1)*,F(1),F(1),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(4),F(4),F(3),F(2),F(3),F(1)*->F(1),F(1)*->F(1),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2)] (function (globalThis){ "use strict"; @@ -13204,7 +13242,9 @@ (globalThis)); //# unitInfo: Provides: Stdlib__Mutex -(function(globalThis){ +//# shape: Stdlib__Mutex:[F(1),F(1),F(1),F(1),F(2)] +(function + (globalThis){ "use strict"; var runtime = globalThis.jsoo_runtime, @@ -13244,7 +13284,9 @@ (globalThis)); //# unitInfo: Provides: Stdlib__Condition -(function(globalThis){ +//# shape: Stdlib__Condition:[F(1),F(2),F(1),F(1)] +(function + (globalThis){ "use strict"; var runtime = globalThis.jsoo_runtime, @@ -13261,6 +13303,7 @@ //# unitInfo: Provides: Stdlib__Semaphore //# unitInfo: Requires: Stdlib, Stdlib__Condition, Stdlib__Mutex +//# shape: Stdlib__Semaphore:[[F(1),F(1),F(1),F(1),F(1)*],[F(1),F(1),F(1),F(1)]] (function (globalThis){ "use strict"; @@ -13370,6 +13413,7 @@ //# unitInfo: Provides: Stdlib__Domain //# unitInfo: Requires: Stdlib, Stdlib__Array, Stdlib__Atomic, Stdlib__Condition, Stdlib__List, Stdlib__Mutex +//# shape: Stdlib__Domain:[F(1),F(1),F(1)*,F(1),F(1),F(1),F(1),F(1),F(1),F(1),N] (function (globalThis){ "use strict"; @@ -13648,6 +13692,7 @@ //# unitInfo: Provides: CamlinternalFormat //# unitInfo: Requires: CamlinternalFormatBasics, Stdlib, Stdlib__Buffer, Stdlib__Bytes, Stdlib__Char, Stdlib__Int, Stdlib__String, Stdlib__Sys +//# shape: CamlinternalFormat:[F(2),F(1),F(1),F(2),F(1),F(2)*,F(3),F(3),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(1)*,F(1),F(1),F(1),F(1),F(1),F(2),F(2)] (function (globalThis){ "use strict"; @@ -20764,6 +20809,7 @@ //# unitInfo: Provides: Stdlib__Printf //# unitInfo: Requires: CamlinternalFormat, Stdlib, Stdlib__Buffer +//# shape: Stdlib__Printf:[F(2),F(1),F(1),F(1),F(2),F(2),F(2),F(3),F(3),F(2),F(3),F(3),F(2)] (function (globalThis){ "use strict"; @@ -20880,6 +20926,7 @@ //# unitInfo: Provides: Stdlib__Arg //# unitInfo: Requires: Stdlib, Stdlib__Array, Stdlib__Buffer, Stdlib__Int, Stdlib__List, Stdlib__Printf, Stdlib__String, Stdlib__Sys +//# shape: Stdlib__Arg:[F(3),F(3),F(5),F(5),F(5),F(3),N,N,F(2),F(2),F(2),N,F(1),F(1),F(2),F(2)] (function (globalThis){ "use strict"; @@ -21731,6 +21778,7 @@ //# unitInfo: Provides: Stdlib__Printexc //# unitInfo: Requires: Stdlib, Stdlib__Atomic, Stdlib__Buffer, Stdlib__Obj, Stdlib__Printf +//# shape: Stdlib__Printexc:[F(1),F(1),F(2),F(2),F(1),F(1),F(1),F(1),F(1),F(1),F(1)*,F(1)*,F(2),F(1),F(2),F(1),F(1),F(1),N,F(1)*,F(2),F(1),F(1),F(1),F(1),F(1)] (function (globalThis){ "use strict"; @@ -22339,6 +22387,7 @@ //# unitInfo: Provides: Stdlib__Fun //# unitInfo: Requires: Stdlib, Stdlib__Printexc +//# shape: Stdlib__Fun:[F(2)*,F(3),F(3),F(2),F(2),N] (function (globalThis){ "use strict"; @@ -22437,6 +22486,7 @@ //# unitInfo: Provides: Stdlib__Gc //# unitInfo: Requires: Stdlib, Stdlib__Atomic, Stdlib__Domain, Stdlib__Fun, Stdlib__Printf, Stdlib__Sys +//# shape: Stdlib__Gc:[F(1),F(1),F(2)*,F(2),F(1)*,F(1),F(1),F(1)*,F(1)*,N] (function (globalThis){ "use strict"; @@ -22634,6 +22684,7 @@ //# unitInfo: Provides: Stdlib__In_channel //# unitInfo: Requires: Stdlib, Stdlib__Bytes, Stdlib__Fun, Stdlib__Sys +//# shape: Stdlib__In_channel:[N,F(1),F(1),F(3),F(2),F(2),F(4),F(1),F(1),F(1),F(1),F(1),F(2),F(1),F(1),F(4),F(4),F(4),F(4),F(3),N,N,N,F(2),F(1),F(1)] (function (globalThis){ "use strict"; @@ -22990,6 +23041,7 @@ //# unitInfo: Provides: Stdlib__Out_channel //# unitInfo: Requires: Stdlib, Stdlib__Fun +//# shape: Stdlib__Out_channel:[N,N,F(1),F(1),F(3),F(2),F(2),F(4),F(1),F(1),F(2),F(2),F(2),F(2),F(4),F(4),F(4),F(1),F(1),N,N,N,F(2),F(1),F(2),F(1),F(1)] (function (globalThis){ "use strict"; @@ -23102,6 +23154,7 @@ //# unitInfo: Provides: Stdlib__Digest //# unitInfo: Requires: Stdlib, Stdlib__Bytes, Stdlib__Char, Stdlib__In_channel, Stdlib__Int, Stdlib__String +//# shape: Stdlib__Digest:[F(2)*,F(2)*,F(1),F(1),F(3),F(3),F(2),F(1),F(2),F(1),F(1),F(1),F(1),N,N,N,N] (function (globalThis){ "use strict"; @@ -23429,6 +23482,7 @@ //# unitInfo: Provides: Stdlib__Bigarray //# unitInfo: Requires: Stdlib, Stdlib__Array, Stdlib__Sys +//# shape: Stdlib__Bigarray:[N,N,N,N,N,N,N,N,N,N,N,N,N,N,F(1)*,N,N,N,N,N,N,N,F(1),F(1),F(1),F(1),F(2),F(1),F(2),F(3),F(4)] (function (globalThis){ "use strict"; @@ -24061,6 +24115,7 @@ //# unitInfo: Provides: Stdlib__Random //# unitInfo: Requires: Stdlib, Stdlib__Bigarray, Stdlib__Bytes, Stdlib__Digest, Stdlib__Domain, Stdlib__Int32, Stdlib__Int64, Stdlib__Nativeint, Stdlib__String, Stdlib__Sys +//# shape: Stdlib__Random:[F(1),F(1),F(1),F(1),F(1),F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(1),F(1),F(1),F(1),N,F(1),F(1),F(1)] (function (globalThis){ "use strict"; @@ -24638,6 +24693,7 @@ //# unitInfo: Provides: Stdlib__Hashtbl //# unitInfo: Requires: Stdlib, Stdlib__Array, Stdlib__Atomic, Stdlib__Domain, Stdlib__Int, Stdlib__Random, Stdlib__Seq, Stdlib__String, Stdlib__Sys +//# shape: Stdlib__Hashtbl:[F(2),F(1),F(1),F(1),F(3),F(2),F(2),F(2),F(2),F(2),F(3),F(2),F(2),F(3),F(1)*,F(1),F(1),F(2),F(1),F(1)*->F(1),F(1),F(1),F(2),F(2),F(1),F(1)*,F(1)*,F(1)*,F(2)*,F(3)*,F(4)*] (function (globalThis){ "use strict"; @@ -25753,6 +25809,7 @@ //# unitInfo: Provides: Stdlib__Weak //# unitInfo: Requires: Stdlib, Stdlib__Array, Stdlib__Int, Stdlib__Obj, Stdlib__Sys +//# shape: Stdlib__Weak:[F(1),F(1)*,F(3),F(2),F(2),F(2),F(4),F(5),F(1)] (function (globalThis){ "use strict"; @@ -26327,6 +26384,7 @@ //# unitInfo: Provides: Stdlib__Format //# unitInfo: Requires: CamlinternalFormat, Stdlib, Stdlib__Array, Stdlib__Buffer, Stdlib__Bytes, Stdlib__Domain, Stdlib__Int, Stdlib__List, Stdlib__Queue, Stdlib__Seq, Stdlib__Stack, Stdlib__String +//# shape: Stdlib__Format:[F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(4),F(3),F(2),F(1),F(3),F(2),F(5),F(4),F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(2)*,F(2),F(1),F(2),F(1),F(3),F(2),F(3),F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(1),N,F(2),F(1),F(2)*,F(1),F(2),F(1),F(2)*,F(1),F(1)*,F(3),F(2),F(3),F(2),F(2),F(1),F(2)*,F(1),F(2),F(1),F(2)*,F(1),F(2)*,F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(3),F(2),F(2),F(1),F(2)*,F(1),N,F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(2)*,F(1),F(2)*,F(1),F(2),F(1),F(3),F(2),F(2)*,F(1),F(2),F(1),F(2)*,F(1),F(2),F(1),F(2)*,F(1),F(1),F(1),N,F(1),N,F(1),F(1),N,F(1),N,F(1),F(1),F(2),F(2),F(1),F(1)*,F(1),F(1),F(1),F(2),F(1),F(5),F(4),F(4),F(4),F(2),F(4),F(4),F(4),F(1)*->F(1),F(1),F(1),F(1),F(1),F(1),F(2),F(3),F(2),F(3),F(2),F(2)] (function (globalThis){ "use strict"; @@ -28553,6 +28611,7 @@ //# unitInfo: Provides: Stdlib__Scanf //# unitInfo: Requires: CamlinternalFormat, CamlinternalFormatBasics, Stdlib, Stdlib__Buffer, Stdlib__Bytes, Stdlib__Int, Stdlib__Printf, Stdlib__String +//# shape: Stdlib__Scanf:[N,N,F(2),F(2),F(2),F(2),F(1),F(1),F(3),F(3),F(3),F(3),F(2),F(1)] (function (globalThis){ "use strict"; @@ -30770,6 +30829,7 @@ //# unitInfo: Provides: Stdlib__Callback //# unitInfo: Requires: Stdlib, Stdlib__Obj +//# shape: Stdlib__Callback:[F(2),F(2)] (function (globalThis){ "use strict"; @@ -30793,6 +30853,7 @@ //# unitInfo: Provides: CamlinternalOO //# unitInfo: Requires: Stdlib, Stdlib__Array, Stdlib__List, Stdlib__Map, Stdlib__Obj, Stdlib__Sys +//# shape: CamlinternalOO:[F(1),F(1),F(2),F(3),F(2),F(2),F(2),F(2),F(2),F(3),F(2),F(4),F(1),F(2),N,F(1),F(1),F(6),F(2),F(3),F(1)*,F(1),F(1),F(2),F(2),F(3),F(2),F(2),N,F(1)*] (function (globalThis){ "use strict"; @@ -31761,6 +31822,7 @@ //# unitInfo: Provides: Stdlib__Oo //# unitInfo: Requires: CamlinternalOO +//# shape: Stdlib__Oo:[F(1),F(1),F(1)] (function (globalThis){ "use strict"; @@ -31779,6 +31841,7 @@ //# unitInfo: Provides: CamlinternalMod //# unitInfo: Requires: CamlinternalLazy, CamlinternalOO, Stdlib, Stdlib__Obj +//# shape: CamlinternalMod:[F(2),F(3)] (function (globalThis){ "use strict"; @@ -31950,6 +32013,7 @@ //# unitInfo: Provides: Stdlib__Dynarray //# unitInfo: Requires: CamlinternalOO, Stdlib, Stdlib__Array, Stdlib__Obj, Stdlib__Printf, Stdlib__Seq, Stdlib__Sys +//# shape: Stdlib__Dynarray:[F(1)*,F(2),F(2),F(2),F(3),F(1)*,F(1)*,F(1),F(1),F(1),F(2),F(2),F(2),F(2),F(2),F(3),F(5),F(1),F(1),F(1),F(2),F(1),F(2),F(2),F(2),F(2),F(3),F(3),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(3),F(3),F(1),F(1),F(1),F(1),F(1),F(1),F(1)*,F(1),F(1)*,F(1)*,F(2),F(2),F(1),F(2),F(1)] (function (globalThis){ "use strict"; @@ -33265,6 +33329,7 @@ //# unitInfo: Provides: Stdlib__Ephemeron //# unitInfo: Requires: CamlinternalLazy, Stdlib, Stdlib__Array, Stdlib__Hashtbl, Stdlib__Int, Stdlib__List, Stdlib__Obj, Stdlib__Random, Stdlib__Seq, Stdlib__Sys +//# shape: Stdlib__Ephemeron:[N,N,N] (function (globalThis){ "use strict"; @@ -34525,6 +34590,7 @@ //# unitInfo: Provides: Stdlib__Filename //# unitInfo: Requires: Stdlib, Stdlib__Buffer, Stdlib__Domain, Stdlib__List, Stdlib__Printf, Stdlib__Random, Stdlib__String, Stdlib__Sys +//# shape: Stdlib__Filename:[N,N,N,F(2),F(1),F(1),F(2),F(2),F(2),F(1),F(1),F(1),F(1),F(1),N,F(3),F(5),F(4),F(1),F(1),F(1),F(5)] (function (globalThis){ "use strict"; @@ -35533,6 +35599,7 @@ //# unitInfo: Provides: Stdlib__Complex //# unitInfo: Requires: Stdlib, Stdlib__Float +//# shape: Stdlib__Complex:[N,N,N,F(1)*,F(1)*,F(2)*,F(2)*,F(2)*,F(1)*,F(2)*,F(1)*,F(1)*,F(1)*,F(1)*,F(2)*,F(1)*,F(1)*,F(2)*] (function (globalThis){ "use strict"; @@ -35671,6 +35738,7 @@ //# unitInfo: Provides: Stdlib__ArrayLabels //# unitInfo: Requires: Stdlib__Array +//# shape: Stdlib__ArrayLabels:[F(2),F(3),F(3),F(2)*,F(1)*,F(3),F(1)*,F(4),F(5),F(1),F(1),F(2),F(2),F(2),F(2),F(2),F(2),F(3),F(3),F(3),F(3),F(3),F(2),F(2),F(3),F(3),F(2),F(2),F(2),F(2),F(2),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(1)*->F(1)*,F(1)*->F(1)*,F(1),[]] (function (globalThis){ "use strict"; @@ -35771,6 +35839,7 @@ //# unitInfo: Provides: Stdlib__ListLabels //# unitInfo: Requires: Stdlib__List +//# shape: Stdlib__ListLabels:[F(1),F(2),F(2),F(1)*,F(2)*,F(1),F(1),F(2),F(2),F(1),F(2),F(2),F(2),F(1),F(1),F(3),F(3),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(3),F(3),F(3),F(3),F(3),F(3),F(4),F(4),F(2),F(2),F(3),F(3),F(2),F(2),F(2),F(2),F(1)*->F(1),F(2),F(1)*->F(1),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(3),F(1)*->F(1)*,F(1)] (function (globalThis){ "use strict"; @@ -35925,6 +35994,7 @@ //# unitInfo: Provides: Stdlib__BytesLabels //# unitInfo: Requires: Stdlib__Bytes +//# shape: Stdlib__BytesLabels:[F(2),F(2),N,F(1),F(1),F(1),F(3),F(3),F(3),F(4),F(5),F(5),F(2),F(2),F(2),F(2),F(2),F(2),F(3),F(3),F(2),F(2),F(1),F(1),F(2),F(2),F(2),F(2),F(3),F(3),F(3),F(3),F(2),F(3),F(3),F(1),F(1),F(1),F(1),F(2)*,F(2)*,F(2),F(2),F(1),F(1)*,F(2),F(1)*->F(1),F(1)*->F(1),F(1),F(2),F(3),F(1),F(2),F(3),F(1),F(2),F(3),F(1),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(3),F(1)] (function (globalThis){ "use strict"; @@ -36115,6 +36185,7 @@ //# unitInfo: Provides: Stdlib__StringLabels //# unitInfo: Requires: Stdlib__String +//# shape: Stdlib__StringLabels:[F(2),F(2),N,F(1),F(1),F(5),F(2),F(2)*,F(2)*,F(2)*,F(2),F(2),F(3),F(3),F(2),F(3),F(2),F(2),F(2),F(3),F(3),F(2),F(2),F(1),F(1),F(1),F(1),F(1),F(1),F(2),F(2),F(3),F(3),F(3),F(3),F(2),F(2),F(2),F(2),F(1),F(1),F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(2)] (function (globalThis){ "use strict"; @@ -36260,6 +36331,7 @@ //# unitInfo: Provides: Stdlib__MoreLabels //# unitInfo: Requires: Stdlib__Hashtbl, Stdlib__Map, Stdlib__Set +//# shape: Stdlib__MoreLabels:[[F(2),F(1),F(1),F(1),F(3),F(2),F(2),F(2),F(2),F(2),F(3),F(2),F(2),F(3),F(1)*,F(1),F(1),F(2),F(1),F(1)*->F(1),F(1),F(1),F(2),F(2),F(1),F(1)*,F(1)*,F(1)*,F(2)*,F(3)*,F(4)*],[F(1)*],[F(1)*]] (function (globalThis){ "use strict"; @@ -36276,7 +36348,9 @@ (globalThis)); //# unitInfo: Provides: Stdlib__StdLabels -(function(globalThis){ +//# shape: Stdlib__StdLabels:[] +(function + (globalThis){ "use strict"; var runtime = globalThis.jsoo_runtime, Stdlib_StdLabels = [0]; runtime.caml_register_global(0, Stdlib_StdLabels, "Stdlib__StdLabels"); @@ -36287,6 +36361,7 @@ //# unitInfo: Provides: Stdlib__Effect //# unitInfo: Requires: Stdlib, Stdlib__Callback, Stdlib__Printexc, Stdlib__Printf //# unitInfo: Effects_without_cps: true +//# shape: Stdlib__Effect:[N,N,[F(2),F(2),F(3),F(3),F(3)],N] (function (globalThis){ "use strict"; From 3a03a93c00a84928d30fbae7fddb18cfc21fde7e Mon Sep 17 00:00:00 2001 From: Hugo Heuzard Date: Tue, 20 May 2025 15:56:16 +0200 Subject: [PATCH 04/13] Compiler: use shapes to compute arity This reverts commit 9c0692f8af4d6fafdf0fc428f820cc9753897cc4. --- compiler/lib/driver.ml | 5 +- compiler/lib/specialize.ml | 32 +- compiler/lib/specialize.mli | 3 +- compiler/tests-full/stdlib.cma.expected.js | 4055 +++++++++----------- 4 files changed, 1914 insertions(+), 2181 deletions(-) diff --git a/compiler/lib/driver.ml b/compiler/lib/driver.ml index 680a105a48..c237302744 100644 --- a/compiler/lib/driver.ml +++ b/compiler/lib/driver.ml @@ -65,7 +65,10 @@ let inline profile p = let specialize_1 (p, info) = if debug () then Format.eprintf "Specialize...@."; - Specialize.f ~function_arity:(fun f -> Specialize.function_arity info f) p + let return_values = Code.Var.Map.empty in + Specialize.f + ~function_arity:(fun f -> Specialize.function_arity ~return_values info f) + p let specialize_js (p, info) = if debug () then Format.eprintf "Specialize js...@."; diff --git a/compiler/lib/specialize.ml b/compiler/lib/specialize.ml index 769e510c41..a6009fcc6d 100644 --- a/compiler/lib/specialize.ml +++ b/compiler/lib/specialize.ml @@ -19,7 +19,6 @@ *) open! Stdlib open Code -open Flow let times = Debug.find "times" @@ -27,33 +26,10 @@ let stats = Debug.find "stats" let debug_stats = Debug.find "stats-debug" -let function_arity info x = - let rec arity info x acc = - get_approx - info - (fun x -> - match Flow.Info.def info x with - | Some (Closure (l, _, _)) -> Some (List.length l) - | Some (Special (Alias_prim prim)) -> ( - try Some (Primitive.arity prim) with Not_found -> None) - | Some (Apply { f; args; _ }) -> ( - if List.mem ~eq:Var.equal f acc - then None - else - match arity info f (f :: acc) with - | Some n -> - let diff = n - List.length args in - if diff > 0 then Some diff else None - | None -> None) - | _ -> None) - None - (fun u v -> - match u, v with - | Some n, Some m when n = m -> u - | _ -> None) - x - in - arity info x [] +let function_arity ~return_values info x = + match Flow.the_shape_of ~return_values ~pure:Pure_fun.empty info x with + | Top | Block _ -> None + | Function { arity; _ } -> Some arity let add_event loc instrs = match loc with diff --git a/compiler/lib/specialize.mli b/compiler/lib/specialize.mli index 149f33bd76..5a1a8f7a2a 100644 --- a/compiler/lib/specialize.mli +++ b/compiler/lib/specialize.mli @@ -18,7 +18,8 @@ * Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. *) -val function_arity : Flow.Info.t -> Code.Var.t -> int option +val function_arity : + return_values:Code.Var.Set.t Code.Var.Map.t -> Flow.Info.t -> Code.Var.t -> int option val f : function_arity:(Code.Var.t -> int option) -> Code.program -> Code.program diff --git a/compiler/tests-full/stdlib.cma.expected.js b/compiler/tests-full/stdlib.cma.expected.js index 9e9052dc72..eb95ae0714 100644 --- a/compiler/tests-full/stdlib.cma.expected.js +++ b/compiler/tests-full/stdlib.cma.expected.js @@ -388,11 +388,6 @@ ? f(a0) : runtime.caml_call_gen(f, [a0]); } - function caml_call2(f, a0, a1){ - return (f.l >= 0 ? f.l : f.l = f.length) === 2 - ? f(a0, a1) - : runtime.caml_call_gen(f, [a0, a1]); - } var global_data = runtime.caml_get_global_data(), CamlinternalFormatBasics = global_data.CamlinternalFormatBasics, @@ -820,7 +815,7 @@ fmt1 = _f_[1], s2 = /*<>*/ "%," + str2; /*<>*/ return [0, - caml_call2(CamlinternalFormatBasics[3], fmt1, fmt2), + CamlinternalFormatBasics[3].call(null, fmt1, fmt2), str1 + s2] /*<>*/ ; /*<>*/ } var exit_function = /*<>*/ [0, flush_all]; @@ -1216,13 +1211,7 @@ runtime = globalThis.jsoo_runtime, cst_Obj_extension_constructor$1 = "Obj.extension_constructor", caml_check_bound = runtime.caml_check_bound, - caml_obj_tag = runtime.caml_obj_tag; - function caml_call1(f, a0){ - return (f.l >= 0 ? f.l : f.l = f.length) === 1 - ? f(a0) - : runtime.caml_call_gen(f, [a0]); - } - var + caml_obj_tag = runtime.caml_obj_tag, global_data = runtime.caml_get_global_data(), Stdlib = global_data.Stdlib, Stdlib_Sys = global_data.Stdlib__Sys; @@ -1255,13 +1244,14 @@ (is_block(slot) && /*<>*/ caml_obj_tag(slot) === 248){var name = /*<>*/ slot[1]; break a;} var name = - /*<>*/ /*<>*/ caml_call1 - (Stdlib[1], cst_Obj_extension_constructor$0); + /*<>*/ /*<>*/ Stdlib[1].call + (null, cst_Obj_extension_constructor$0); } /*<>*/ return caml_obj_tag(name) === 252 ? slot - : /*<>*/ caml_call1 - (Stdlib[1], cst_Obj_extension_constructor) /*<>*/ ; + : /*<>*/ Stdlib + [1].call + (null, cst_Obj_extension_constructor) /*<>*/ ; } function name(slot){ /*<>*/ return slot[1];} function id(slot){ /*<>*/ return slot[2];} @@ -1280,7 +1270,7 @@ _d_ = /*<>*/ 0 <= l ? 1 : 0, _e_ = _d_ ? l <= max_ephe_length ? 1 : 0 : _d_; if(1 - _e_) - /*<>*/ caml_call1(Stdlib[1], cst_Obj_Ephemeron_create); + /*<>*/ Stdlib[1].call(null, cst_Obj_Ephemeron_create); /*<>*/ return runtime.caml_ephe_create(l) /*<>*/ ; } function length(x){ @@ -1291,7 +1281,7 @@ _b_ = /*<>*/ 0 <= o ? 1 : 0, _d_ = _b_ ? o < /*<>*/ length(e) ? 1 : 0 : _b_, _c_ = /*<>*/ 1 - _d_; - return _c_ ? /*<>*/ caml_call1(Stdlib[1], msg) : _c_ /*<>*/ ; + return _c_ ? /*<>*/ Stdlib[1].call(null, msg) : _c_ /*<>*/ ; } function get_key(e, o){ /*<>*/ raise_if_invalid_offset @@ -1335,8 +1325,8 @@ : _a_; /*<>*/ return _b_; } - /*<>*/ return caml_call1 - (Stdlib[1], cst_Obj_Ephemeron_blit_key) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Obj_Ephemeron_blit_key) /*<>*/ ; } var Stdlib_Obj = @@ -1390,13 +1380,8 @@ (function (globalThis){ "use strict"; - var runtime = globalThis.jsoo_runtime; - function caml_call1(f, a0){ - return (f.l >= 0 ? f.l : f.l = f.length) === 1 - ? f(a0) - : runtime.caml_call_gen(f, [a0]); - } var + runtime = globalThis.jsoo_runtime, global_data = runtime.caml_get_global_data(), Stdlib_Obj = global_data.Stdlib__Obj, cst_Id = "Id", @@ -1406,8 +1391,8 @@ return [0, Id]; /*<>*/ } function uid(A){ - var _a_ = /*<>*/ caml_call1(Stdlib_Obj[22][1], A[1]); - /*<>*/ return caml_call1(Stdlib_Obj[22][3], _a_); + var _a_ = /*<>*/ Stdlib_Obj[22][1].call(null, A[1]); + /*<>*/ return Stdlib_Obj[22][3].call(null, _a_); } function provably_equal(A, B){ /*<>*/ return A[1] === B[1] ? _a_ : 0 /*<>*/ ; @@ -1545,18 +1530,13 @@ ? f(a0) : runtime.caml_call_gen(f, [a0]); } - function caml_call2(f, a0, a1){ - return (f.l >= 0 ? f.l : f.l = f.length) === 2 - ? f(a0, a1) - : runtime.caml_call_gen(f, [a0, a1]); - } var global_data = runtime.caml_get_global_data(), CamlinternalLazy = global_data.CamlinternalLazy, Stdlib_Obj = global_data.Stdlib__Obj, Undefined = CamlinternalLazy[1]; function force_val(l){ - /*<>*/ return caml_call2(CamlinternalLazy[3], 1, l) /*<>*/ ; + /*<>*/ return CamlinternalLazy[3].call(null, 1, l) /*<>*/ ; } function from_fun(f){ var x = /*<>*/ runtime.caml_obj_block(Stdlib_Obj[8], 1); @@ -1584,7 +1564,7 @@ var _d_ = x[1]; else{ if(246 !== _c_ && 244 !== _c_){var _d_ = x; break a;} - var _d_ = caml_call1(CamlinternalLazy[2], x); + var _d_ = CamlinternalLazy[2].call(null, x); } return caml_call1(f, _d_); }] /*<>*/ ; @@ -1599,7 +1579,7 @@ var _c_ = x[1]; else{ if(246 !== _b_ && 244 !== _b_){var _c_ = x; break a;} - var _c_ = caml_call1(CamlinternalLazy[2], x); + var _c_ = CamlinternalLazy[2].call(null, x); } return caml_call1(f, _c_); }] /*<>*/ ; @@ -1609,7 +1589,7 @@ var _b_ = x[1]; else{ if(246 !== _a_ && 244 !== _a_){var _b_ = x; break a;} - var _b_ = caml_call1(CamlinternalLazy[2], x); + var _b_ = CamlinternalLazy[2].call(null, x); } /*<>*/ return /*<>*/ from_val ( /*<>*/ caml_call1(f, _b_)) /*<>*/ ; @@ -1631,7 +1611,7 @@ //# unitInfo: Provides: Stdlib__Seq //# unitInfo: Requires: CamlinternalLazy, Stdlib, Stdlib__Atomic, Stdlib__Lazy -//# shape: Stdlib__Seq:[F(1),F(1),F(1),F(2),F(3),F(2),F(3),F(2),F(2),F(2),F(2),F(2),F(2),F(3),F(4),F(3),F(3),F(3),F(3),F(1)*,F(2)*,F(3)*,F(2),F(3),F(2)*,F(2),F(2),F(2)*->F(1)*,F(3),F(2)*->F(1),F(3),F(3),F(3)*->F(1)*,F(2),F(2),F(3),F(3),F(3),F(1)->F(1),N,F(1)->F(1),F(2),F(3),F(2),F(3),F(3),F(3),F(4),F(3),F(4),F(2)*,F(3)*->F(1),F(1)*,F(1)*,F(2)*,F(2)*,F(1)*->F(1),F(1)*->F(1),F(2)*] +//# shape: Stdlib__Seq:[F(1),F(1),F(1),F(2),F(3),F(2),F(3),F(2),F(2),F(2),F(2),F(2),F(2),F(3),F(4),F(3),F(3),F(3),F(3),F(1)*,F(2)*,F(3)*,F(2),F(3),F(2)*,F(2),F(2),F(2)*->F(1)*,F(3),F(2)*->F(1),F(3),F(3),F(3)*->F(1)*,F(2),F(2),F(3),F(3),F(3),F(1)->F(1),N,F(1)*->F(1),F(2),F(3),F(2),F(3),F(3),F(3),F(4),F(3),F(4),F(2)*,F(3)*->F(1),F(1)*,F(1)*,F(2)*,F(2)*,F(1)*->F(1),F(1)*->F(1),F(2)*] (function (globalThis){ "use strict"; @@ -2033,7 +2013,7 @@ /*<>*/ } function init(n, f){ /*<>*/ if(0 > n) - /*<>*/ return caml_call1(Stdlib[1], cst_Seq_init) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Seq_init) /*<>*/ ; var _n_ = /*<>*/ 0; return function(_o_){ /*<>*/ return init_aux(f, _n_, n, _o_);} /*<>*/ ; @@ -2128,7 +2108,7 @@ } function take(n, xs){ /*<>*/ if(n < 0) - /*<>*/ caml_call1(Stdlib[1], cst_Seq_take); + /*<>*/ Stdlib[1].call(null, cst_Seq_take); /*<>*/ return take_aux(n, xs) /*<>*/ ; } function drop(n, xs){ @@ -2152,7 +2132,7 @@ xs$0 = xs$1; } /*<>*/ } - : /*<>*/ caml_call1(Stdlib[1], cst_Seq_drop) /*<>*/ ; + : /*<>*/ Stdlib[1].call(null, cst_Seq_drop) /*<>*/ ; } function take_while(p, xs, param){ var match = /*<>*/ caml_call1(xs, 0); @@ -2210,12 +2190,12 @@ var xs$0 = /*<>*/ match[2], x = match[1]; /*<>*/ return [0, x, memoize(xs$0)] /*<>*/ ; /*<>*/ } - var s = /*<>*/ caml_call1(to_lazy, s$0); + var s = /*<>*/ to_lazy(s$0); /*<>*/ return function(param){ var _h_ = /*<>*/ runtime.caml_obj_tag(s); if(250 === _h_) return s[1]; if(246 !== _h_ && 244 !== _h_) return s; - return caml_call1(CamlinternalLazy[2], s) /*<>*/ ;} /*<>*/ ; + return CamlinternalLazy[2].call(null, s) /*<>*/ ;} /*<>*/ ; /*<>*/ } function once(xs){ function f(param){ @@ -2224,10 +2204,10 @@ var xs$0 = /*<>*/ match[2], x = match[1]; /*<>*/ return [0, x, once(xs$0)] /*<>*/ ; /*<>*/ } - var action = /*<>*/ caml_call1(Stdlib_Atomic[1], f); + var action = /*<>*/ Stdlib_Atomic[1].call(null, f); /*<>*/ return function(param){ var - f = /*<>*/ caml_call2(Stdlib_Atomic[5], action, failure); + f = /*<>*/ Stdlib_Atomic[5].call(null, action, failure); /*<>*/ return caml_call1(f, 0) /*<>*/ ;} /*<>*/ ; /*<>*/ } function zip(xs, ys, param){ @@ -2557,7 +2537,7 @@ //# unitInfo: Provides: Stdlib__Option //# unitInfo: Requires: Stdlib, Stdlib__Seq -//# shape: Stdlib__Option:[N,F(1)*,F(2)*,F(1),F(2),F(1)*,F(2),F(3),F(2),F(1)*,F(1)*,F(3),F(3),F(2)*,F(1)*,F(1)] +//# shape: Stdlib__Option:[N,F(1)*,F(2)*,F(1),F(2),F(1)*,F(2),F(3),F(2),F(1)*,F(1)*,F(3),F(3),F(2)*,F(1)*,F(1)*->F(1)*] (function (globalThis){ "use strict"; @@ -2587,7 +2567,7 @@ /*<>*/ } function get(param){ /*<>*/ if(! param) - /*<>*/ return caml_call1(Stdlib[1], cst_option_is_None) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_option_is_None) /*<>*/ ; var v = /*<>*/ param[1]; /*<>*/ return v; /*<>*/ } @@ -2654,9 +2634,12 @@ function to_seq(param){ /*<>*/ if(! param) /*<>*/ return Stdlib_Seq[20]; - var v = /*<>*/ param[1]; - /*<>*/ return caml_call1(Stdlib_Seq[21], v) /*<>*/ ; - } + var + v = /*<>*/ param[1], + _a_ = /*<>*/ Stdlib_Seq[21]; + return function(_b_){ + /*<>*/ return _a_(v, _b_);} /*<>*/ ; + /*<>*/ } var Stdlib_Option = /*<>*/ [0, @@ -2683,7 +2666,7 @@ //# unitInfo: Provides: Stdlib__Result //# unitInfo: Requires: Stdlib, Stdlib__Seq -//# shape: Stdlib__Result:[F(1)*,F(1)*,F(2)*,F(1),F(1),F(2),F(1)*,F(2),F(2),F(3),F(2),F(2),F(1)*,F(1)*,F(4),F(4),F(1)*,F(1)*,F(1)] +//# shape: Stdlib__Result:[F(1)*,F(1)*,F(2)*,F(1),F(1),F(2),F(1)*,F(2),F(2),F(3),F(2),F(2),F(1)*,F(1)*,F(4),F(4),F(1)*,F(1)*,F(1)*->F(1)*] (function (globalThis){ "use strict"; @@ -2718,14 +2701,13 @@ /*<>*/ } function get_ok(param){ /*<>*/ if(0 !== param[0]) - /*<>*/ return caml_call1 - (Stdlib[1], cst_result_is_Error) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_result_is_Error) /*<>*/ ; var v = /*<>*/ param[1]; /*<>*/ return v; /*<>*/ } function get_error(param){ /*<>*/ if(0 === param[0]) - /*<>*/ return caml_call1(Stdlib[1], cst_result_is_Ok) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_result_is_Ok) /*<>*/ ; var e = /*<>*/ param[1]; /*<>*/ return e; /*<>*/ } @@ -2819,9 +2801,12 @@ function to_seq(param){ /*<>*/ if(0 !== param[0]) /*<>*/ return Stdlib_Seq[20]; - var v = /*<>*/ param[1]; - /*<>*/ return caml_call1(Stdlib_Seq[21], v) /*<>*/ ; - } + var + v = /*<>*/ param[1], + _a_ = /*<>*/ Stdlib_Seq[21]; + return function(_b_){ + /*<>*/ return _a_(v, _b_);} /*<>*/ ; + /*<>*/ } var Stdlib_Result = /*<>*/ [0, @@ -2899,13 +2884,7 @@ caml_bytes_unsafe_set = runtime.caml_bytes_unsafe_set, caml_create_bytes = runtime.caml_create_bytes, caml_hash = runtime.caml_hash, - caml_string_of_bytes = runtime.caml_string_of_bytes; - function caml_call1(f, a0){ - return (f.l >= 0 ? f.l : f.l = f.length) === 1 - ? f(a0) - : runtime.caml_call_gen(f, [a0]); - } - var + caml_string_of_bytes = runtime.caml_string_of_bytes, global_data = runtime.caml_get_global_data(), cst = "\\\\", cst$0 = "\\'", @@ -2918,7 +2897,7 @@ function chr(n){ /*<>*/ if(0 <= n && 255 >= n) /*<>*/ return n; - /*<>*/ return caml_call1(Stdlib[1], cst_Char_chr) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Char_chr) /*<>*/ ; } function escaped(c){ a: @@ -3001,18 +2980,7 @@ cst_uchar_ml = "uchar.ml", caml_format_int = runtime.caml_format_int, caml_hash = runtime.caml_hash, - caml_maybe_attach_backtrace = runtime.caml_maybe_attach_backtrace; - function caml_call1(f, a0){ - return (f.l >= 0 ? f.l : f.l = f.length) === 1 - ? f(a0) - : runtime.caml_call_gen(f, [a0]); - } - function caml_call2(f, a0, a1){ - return (f.l >= 0 ? f.l : f.l = f.length) === 2 - ? f(a0, a1) - : runtime.caml_call_gen(f, [a0, a1]); - } - var + caml_maybe_attach_backtrace = runtime.caml_maybe_attach_backtrace, global_data = runtime.caml_get_global_data(), err_no_pred = "U+0000 has no predecessor", err_no_succ = "U+10FFFF has no successor", @@ -3028,7 +2996,7 @@ ? hi_bound : u === 1114111 - ? /*<>*/ caml_call1(Stdlib[1], err_no_succ) + ? /*<>*/ Stdlib[1].call(null, err_no_succ) : u + 1 | 0 /*<>*/ ; } function pred(u){ @@ -3036,7 +3004,7 @@ ? lo_bound : u === 0 - ? /*<>*/ caml_call1(Stdlib[1], err_no_pred) + ? /*<>*/ Stdlib[1].call(null, err_no_pred) : u - 1 | 0 /*<>*/ ; } function is_valid(i){ @@ -3053,11 +3021,11 @@ /*<>*/ if(is_valid(i)) /*<>*/ return i; var _f_ = - /*<>*/ /*<>*/ caml_call2 - (Stdlib[28], + /*<>*/ /*<>*/ Stdlib[28].call + (null, /*<>*/ caml_format_int("%X", i), cst_is_not_a_Unicode_scalar_va); - /*<>*/ return caml_call1(Stdlib[1], _f_); + /*<>*/ return Stdlib[1].call(null, _f_); } function is_char(u){ /*<>*/ return u < 256 ? 1 : 0; @@ -3069,12 +3037,10 @@ /*<>*/ if(255 >= u) /*<>*/ return u; var _e_ = - /*<>*/ caml_call2 - (Stdlib[28], - caml_format_int("%04X", u), - cst_is_not_a_latin1_character), - _f_ = /*<>*/ caml_call2(Stdlib[28], cst_U, _e_); - /*<>*/ return caml_call1(Stdlib[1], _f_) /*<>*/ ; + /*<>*/ Stdlib[28].call + (null, caml_format_int("%04X", u), cst_is_not_a_latin1_character), + _f_ = /*<>*/ Stdlib[28].call(null, cst_U, _e_); + /*<>*/ return Stdlib[1].call(null, _f_) /*<>*/ ; } function unsafe_to_char(_e_){ /*<>*/ return _e_;} function equal(_e_, _d_){return _e_ === _d_ ? 1 : 0;} @@ -3211,23 +3177,23 @@ /*<>*/ } function hd(param){ /*<>*/ if(! param) - /*<>*/ return caml_call1(Stdlib[2], cst_hd) /*<>*/ ; + /*<>*/ return Stdlib[2].call(null, cst_hd) /*<>*/ ; var a = /*<>*/ param[1]; /*<>*/ return a; /*<>*/ } function tl(param){ /*<>*/ if(! param) - /*<>*/ return caml_call1(Stdlib[2], cst_tl) /*<>*/ ; + /*<>*/ return Stdlib[2].call(null, cst_tl) /*<>*/ ; var l = /*<>*/ param[2]; /*<>*/ return l; /*<>*/ } function nth(l, n){ /*<>*/ if(0 > n) - /*<>*/ return caml_call1(Stdlib[1], cst_List_nth) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_List_nth) /*<>*/ ; var l$0 = /*<>*/ l, n$0 = n; for(;;){ /*<>*/ if(! l$0) - /*<>*/ return caml_call1(Stdlib[2], cst_nth) /*<>*/ ; + /*<>*/ return Stdlib[2].call(null, cst_nth) /*<>*/ ; var l$1 = /*<>*/ l$0[2], a = l$0[1]; /*<>*/ if(0 === n$0) /*<>*/ return a; var n$1 = /*<>*/ n$0 - 1 | 0; @@ -3237,7 +3203,7 @@ /*<>*/ } function nth_opt(l, n){ /*<>*/ if(0 > n) - /*<>*/ return caml_call1(Stdlib[1], cst_List_nth$0) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_List_nth$0) /*<>*/ ; var l$0 = /*<>*/ l, n$0 = n; for(;;){ /*<>*/ if(! l$0) /*<>*/ return 0; @@ -3281,7 +3247,7 @@ } function init(len, f){ /*<>*/ if(0 > len) - /*<>*/ return caml_call1(Stdlib[1], cst_List_init) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_List_init) /*<>*/ ; var last = /*<>*/ len - 1 | 0, i$1 = 0; /*<>*/ if(last < 0) /*<>*/ return 0; /*<>*/ if(0 === last) @@ -3320,7 +3286,7 @@ r = /*<>*/ param[2], l = param[1], _f_ = /*<>*/ flatten(r); - /*<>*/ return caml_call2(Stdlib[37], l, _f_); + /*<>*/ return Stdlib[37].call(null, l, _f_); } function map(f, param){ /*<>*/ if(! param) /*<>*/ return 0; @@ -3516,7 +3482,7 @@ break a; } /*<>*/ dst[offset + 1] = - caml_call1(Stdlib[1], cst_List_map2$0); + Stdlib[1].call(null, cst_List_map2$0); } /*<>*/ return [0, r1, block]; } @@ -3531,7 +3497,7 @@ } } else if(! l2) /*<>*/ return 0; - /*<>*/ return caml_call1(Stdlib[1], cst_List_map2) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_List_map2) /*<>*/ ; } function rev_map2(f, l1, l2){ var accu = /*<>*/ 0, l1$0 = l1, l2$0 = l2; @@ -3551,7 +3517,7 @@ } } else if(! l2$0) /*<>*/ return accu; - /*<>*/ return caml_call1(Stdlib[1], cst_List_rev_map2) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_List_rev_map2) /*<>*/ ; } } function iter2(f, l1$1, l2$1){ @@ -3567,7 +3533,7 @@ } } else if(! l2) /*<>*/ return 0; - /*<>*/ return caml_call1(Stdlib[1], cst_List_iter2) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_List_iter2) /*<>*/ ; } } function fold_left2(f, accu$1, l1$1, l2$1){ @@ -3588,7 +3554,7 @@ } } else if(! l2) /*<>*/ return accu; - /*<>*/ return caml_call1(Stdlib[1], cst_List_fold_left2) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_List_fold_left2) /*<>*/ ; } } function fold_right2(f, l1, l2, accu){ @@ -3603,7 +3569,7 @@ } } else if(! l2) /*<>*/ return accu; - /*<>*/ return caml_call1(Stdlib[1], cst_List_fold_right2) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_List_fold_right2) /*<>*/ ; } function for_all(p, param$0){ var param = /*<>*/ param$0; @@ -3647,7 +3613,7 @@ } } else if(! l2) /*<>*/ return 1; - /*<>*/ return caml_call1(Stdlib[1], cst_List_for_all2) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_List_for_all2) /*<>*/ ; } } function exists2(p, l1$1, l2$1){ @@ -3668,7 +3634,7 @@ } } else if(! l2) /*<>*/ return 0; - /*<>*/ return caml_call1(Stdlib[1], cst_List_exists2) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_List_exists2) /*<>*/ ; } } function mem(x, param$0){ @@ -4013,7 +3979,7 @@ /*<>*/ } function take(n, l){ /*<>*/ if(n < 0) - /*<>*/ caml_call1(Stdlib[1], cst_List_take); + /*<>*/ Stdlib[1].call(null, cst_List_take); /*<>*/ if(0 !== n && l){ var l$0 = l[2], @@ -4046,7 +4012,7 @@ /*<>*/ } function drop(n, rest){ /*<>*/ if(n < 0) - /*<>*/ caml_call1(Stdlib[1], cst_List_drop); + /*<>*/ Stdlib[1].call(null, cst_List_drop); var i = /*<>*/ 0, rest$0 = rest; for(;;){ /*<>*/ if(rest$0){ @@ -4184,7 +4150,7 @@ } } else if(! l2) /*<>*/ return 0; - /*<>*/ return caml_call1(Stdlib[1], cst_List_combine) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_List_combine) /*<>*/ ; } function merge(cmp, l1, l2){ /*<>*/ if(! l1) /*<>*/ return l2; @@ -4959,8 +4925,8 @@ /*<>*/ caml_blit_bytes(s, ofs, r, 0, len); /*<>*/ return r; } - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_sub_Bytes_sub) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_sub_Bytes_sub) /*<>*/ ; } function sub_string(b, ofs, len){ /*<>*/ return /*<>*/ caml_string_of_bytes @@ -4974,7 +4940,7 @@ a: { if(a < 0){if(! _L_ || match) break a;} else if(_L_ || ! match) break a; - /*<>*/ return caml_call1(Stdlib[1], cst_Bytes_extend) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Bytes_extend) /*<>*/ ; } /*<>*/ return c; /*<>*/ } @@ -4990,8 +4956,8 @@ var dstoff = /*<>*/ 0, srcoff = - left | 0; var cpylen = - /*<>*/ /*<>*/ caml_call2 - (Stdlib_Int[10], + /*<>*/ /*<>*/ Stdlib_Int[10].call + (null, /*<>*/ caml_ml_bytes_length(s) - srcoff | 0, len - dstoff | 0); /*<>*/ if(0 < cpylen) @@ -5002,8 +4968,8 @@ /*<>*/ if (0 <= ofs && 0 <= len && (caml_ml_bytes_length(s) - len | 0) >= ofs) /*<>*/ return caml_fill_bytes(s, ofs, len, c) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_fill_Bytes_fill) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_fill_Bytes_fill) /*<>*/ ; } function blit(s1, ofs1, s2, ofs2, len){ /*<>*/ if @@ -5014,7 +4980,7 @@ (caml_ml_bytes_length(s1) - len | 0) >= ofs1 && 0 <= ofs2 && (caml_ml_bytes_length(s2) - len | 0) >= ofs2) /*<>*/ return caml_blit_bytes(s1, ofs1, s2, ofs2, len) /*<>*/ ; - /*<>*/ return caml_call1(Stdlib[1], cst_Bytes_blit) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Bytes_blit) /*<>*/ ; } function blit_string(s1, ofs1, s2, ofs2, len){ /*<>*/ if @@ -5026,8 +4992,8 @@ && 0 <= ofs2 && (caml_ml_bytes_length(s2) - len | 0) >= ofs2) /*<>*/ return runtime.caml_blit_string (s1, ofs1, s2, ofs2, len) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_blit_Bytes_blit_str) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_blit_Bytes_blit_str) /*<>*/ ; } function iter(f, a){ var @@ -5080,7 +5046,7 @@ param = tl; } else{ - /*<>*/ acc = caml_call1(Stdlib[1], cst_Bytes_concat); + /*<>*/ acc = Stdlib[1].call(null, cst_Bytes_concat); param = tl; } } @@ -5480,15 +5446,15 @@ var l = /*<>*/ caml_ml_bytes_length(s); /*<>*/ if(0 <= i && l >= i) /*<>*/ return index_rec(s, l, i, c) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_index_from_Bytes_in) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_index_from_Bytes_in) /*<>*/ ; } function index_from_opt(s, i, c){ var l = /*<>*/ caml_ml_bytes_length(s); /*<>*/ if(0 <= i && l >= i) /*<>*/ return index_rec_opt(s, l, i, c) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_index_from_opt_Byte) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_index_from_opt_Byte) /*<>*/ ; } function rindex_rec(s, i$1, c){ var i = /*<>*/ i$1; @@ -5508,8 +5474,8 @@ function rindex_from(s, i, c){ /*<>*/ if(-1 <= i && caml_ml_bytes_length(s) > i) /*<>*/ return rindex_rec(s, i, c) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_rindex_from_Bytes_r) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_rindex_from_Bytes_r) /*<>*/ ; } function rindex_rec_opt(s, i$1, c){ var i = /*<>*/ i$1; @@ -5528,8 +5494,8 @@ function rindex_from_opt(s, i, c){ /*<>*/ if(-1 <= i && caml_ml_bytes_length(s) > i) /*<>*/ return rindex_rec_opt(s, i, c) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_rindex_from_opt_Byt) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_rindex_from_opt_Byt) /*<>*/ ; } function contains_from(s, i, c){ var l = /*<>*/ caml_ml_bytes_length(s); @@ -5544,8 +5510,8 @@ if(exn === Stdlib[8]) /*<>*/ return 0; /*<>*/ throw caml_maybe_attach_backtrace(exn, 0); } - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_contains_from_Bytes) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_contains_from_Bytes) /*<>*/ ; } function contains(s, c){ /*<>*/ return contains_from(s, 0, c) /*<>*/ ; @@ -5562,8 +5528,8 @@ if(exn === Stdlib[8]) /*<>*/ return 0; /*<>*/ throw caml_maybe_attach_backtrace(exn, 0); } - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_rcontains_from_Byte) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_rcontains_from_Byte) /*<>*/ ; } var compare = /*<>*/ runtime.caml_bytes_compare, @@ -5623,19 +5589,19 @@ var n = /*<>*/ [0, 0], buf = /*<>*/ [0, make(256, 0)]; - /*<>*/ caml_call2 - (Stdlib_Seq[4], + /*<>*/ Stdlib_Seq[4].call + (null, function(c){ /*<>*/ if(n[1] === caml_ml_bytes_length(buf[1])){ var new_len = - /*<>*/ /*<>*/ caml_call2 - (Stdlib_Int[10], + /*<>*/ /*<>*/ Stdlib_Int[10].call + (null, 2 * /*<>*/ caml_ml_bytes_length(buf[1]) | 0, Stdlib_Sys[12]); /*<>*/ if(caml_ml_bytes_length(buf[1]) === new_len) - /*<>*/ caml_call1 - (Stdlib[2], cst_Bytes_of_seq_cannot_grow_b); + /*<>*/ Stdlib[2].call + (null, cst_Bytes_of_seq_cannot_grow_b); var new_buf = /*<>*/ make(new_len, 0); /*<>*/ blit(buf[1], 0, new_buf, 0, n[1]); /*<>*/ buf[1] = new_buf; @@ -5782,8 +5748,8 @@ _e_ = [0, cst_bytes_ml, 831, 9], _f_ = [0, cst_bytes_ml, 820, 20]; function dec_ret(n, u){ - var _i_ = /*<>*/ caml_call1(Stdlib_Uchar[9], u); - /*<>*/ return caml_call2(Stdlib_Uchar[22], n, _i_); + var _i_ = /*<>*/ Stdlib_Uchar[9].call(null, u); + /*<>*/ return Stdlib_Uchar[22].call(null, n, _i_); } function not_in_x80_to_xBF(b){ /*<>*/ return 2 !== (b >>> 6 | 0) ? 1 : 0; @@ -5824,59 +5790,59 @@ case 0: var i$0 = /*<>*/ i + 1 | 0; /*<>*/ if(max < i$0) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var b1$4 = /*<>*/ caml_bytes_unsafe_get(b, i$0); /*<>*/ if(not_in_x80_to_x9F(b1$4)) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var i$1 = /*<>*/ i$0 + 1 | 0; /*<>*/ if(max < i$1) - /*<>*/ return caml_call1(dec_invalid, 2) /*<>*/ ; + /*<>*/ return dec_invalid(2) /*<>*/ ; var b2$3 = /*<>*/ caml_bytes_unsafe_get(b, i$1); /*<>*/ return not_in_x80_to_xBF(b2$3) - ? /*<>*/ caml_call1(dec_invalid, 2) + ? /*<>*/ dec_invalid(2) : /*<>*/ dec_ret (3, /*<>*/ utf_8_uchar_3(b0, b1$4, b2$3)) /*<>*/ ; case 3: var i$4 = /*<>*/ i + 1 | 0; /*<>*/ if(max < i$4) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var b1$2 = /*<>*/ caml_bytes_unsafe_get(b, i$4); /*<>*/ if(not_in_x90_to_xBF(b1$2)) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var i$5 = /*<>*/ i$4 + 1 | 0; /*<>*/ if(max < i$5) - /*<>*/ return caml_call1(dec_invalid, 2) /*<>*/ ; + /*<>*/ return dec_invalid(2) /*<>*/ ; var b2$1 = /*<>*/ caml_bytes_unsafe_get(b, i$5); /*<>*/ if(not_in_x80_to_xBF(b2$1)) - /*<>*/ return caml_call1(dec_invalid, 2) /*<>*/ ; + /*<>*/ return dec_invalid(2) /*<>*/ ; var i$6 = /*<>*/ i$5 + 1 | 0; /*<>*/ if(max < i$6) - /*<>*/ return caml_call1(dec_invalid, 3) /*<>*/ ; + /*<>*/ return dec_invalid(3) /*<>*/ ; var b3$1 = /*<>*/ caml_bytes_unsafe_get(b, i$6); /*<>*/ return not_in_x80_to_xBF(b3$1) - ? /*<>*/ caml_call1(dec_invalid, 3) + ? /*<>*/ dec_invalid(3) : /*<>*/ dec_ret (4, /*<>*/ utf_8_uchar_4(b0, b1$2, b2$1, b3$1)) /*<>*/ ; case 7: var i$10 = /*<>*/ i + 1 | 0; /*<>*/ if(max < i$10) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var b1$0 = /*<>*/ caml_bytes_unsafe_get(b, i$10); /*<>*/ if(not_in_x80_to_x8F(b1$0)) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var i$11 = /*<>*/ i$10 + 1 | 0; /*<>*/ if(max < i$11) - /*<>*/ return caml_call1(dec_invalid, 2) /*<>*/ ; + /*<>*/ return dec_invalid(2) /*<>*/ ; var b2 = /*<>*/ caml_bytes_unsafe_get(b, i$11); /*<>*/ if(not_in_x80_to_xBF(b2)) - /*<>*/ return caml_call1(dec_invalid, 2) /*<>*/ ; + /*<>*/ return dec_invalid(2) /*<>*/ ; var i$12 = /*<>*/ i$11 + 1 | 0; /*<>*/ if(max < i$12) - /*<>*/ return caml_call1(dec_invalid, 3) /*<>*/ ; + /*<>*/ return dec_invalid(3) /*<>*/ ; var b3 = /*<>*/ caml_bytes_unsafe_get(b, i$12); /*<>*/ return not_in_x80_to_xBF(b3) - ? /*<>*/ caml_call1(dec_invalid, 3) + ? /*<>*/ dec_invalid(3) : /*<>*/ dec_ret (4, /*<>*/ utf_8_uchar_4(b0, b1$0, b2, b3)) /*<>*/ ; @@ -5885,22 +5851,22 @@ default: var i$7 = /*<>*/ i + 1 | 0; /*<>*/ if(max < i$7) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var b1$1 = /*<>*/ caml_bytes_unsafe_get(b, i$7); /*<>*/ if(not_in_x80_to_xBF(b1$1)) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var i$8 = /*<>*/ i$7 + 1 | 0; /*<>*/ if(max < i$8) - /*<>*/ return caml_call1(dec_invalid, 2) /*<>*/ ; + /*<>*/ return dec_invalid(2) /*<>*/ ; var b2$0 = /*<>*/ caml_bytes_unsafe_get(b, i$8); /*<>*/ if(not_in_x80_to_xBF(b2$0)) - /*<>*/ return caml_call1(dec_invalid, 2) /*<>*/ ; + /*<>*/ return dec_invalid(2) /*<>*/ ; var i$9 = /*<>*/ i$8 + 1 | 0; /*<>*/ if(max < i$9) - /*<>*/ return caml_call1(dec_invalid, 3) /*<>*/ ; + /*<>*/ return dec_invalid(3) /*<>*/ ; var b3$0 = /*<>*/ caml_bytes_unsafe_get(b, i$9); /*<>*/ return not_in_x80_to_xBF(b3$0) - ? /*<>*/ caml_call1(dec_invalid, 3) + ? /*<>*/ dec_invalid(3) : /*<>*/ dec_ret (4, /*<>*/ utf_8_uchar_4(b0, b1$1, b2$0, b3$0)) /*<>*/ ; @@ -5909,31 +5875,31 @@ else if(225 > b0){ var i$13 = /*<>*/ i + 1 | 0; /*<>*/ if(max < i$13) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var b1$5 = /*<>*/ caml_bytes_unsafe_get(b, i$13); /*<>*/ if(not_in_xA0_to_xBF(b1$5)) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var i$14 = /*<>*/ i$13 + 1 | 0; /*<>*/ if(max < i$14) - /*<>*/ return caml_call1(dec_invalid, 2) /*<>*/ ; + /*<>*/ return dec_invalid(2) /*<>*/ ; var b2$4 = /*<>*/ caml_bytes_unsafe_get(b, i$14); /*<>*/ return not_in_x80_to_xBF(b2$4) - ? /*<>*/ caml_call1(dec_invalid, 2) + ? /*<>*/ dec_invalid(2) : /*<>*/ dec_ret (3, /*<>*/ utf_8_uchar_3(b0, b1$5, b2$4)) /*<>*/ ; } var i$2 = /*<>*/ i + 1 | 0; /*<>*/ if(max < i$2) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var b1$3 = /*<>*/ caml_bytes_unsafe_get(b, i$2); /*<>*/ if(not_in_x80_to_xBF(b1$3)) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var i$3 = /*<>*/ i$2 + 1 | 0; /*<>*/ if(max < i$3) - /*<>*/ return caml_call1(dec_invalid, 2) /*<>*/ ; + /*<>*/ return dec_invalid(2) /*<>*/ ; var b2$2 = /*<>*/ caml_bytes_unsafe_get(b, i$3); /*<>*/ return not_in_x80_to_xBF(b2$2) - ? /*<>*/ caml_call1(dec_invalid, 2) + ? /*<>*/ dec_invalid(2) : /*<>*/ dec_ret (3, /*<>*/ utf_8_uchar_3(b0, b1$3, b2$2)) /*<>*/ ; } @@ -5942,14 +5908,14 @@ /*<>*/ if(194 <= b0){ var i$15 = /*<>*/ i + 1 | 0; /*<>*/ if(max < i$15) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var b1 = /*<>*/ caml_bytes_unsafe_get(b, i$15); /*<>*/ return not_in_x80_to_xBF(b1) - ? /*<>*/ caml_call1(dec_invalid, 1) + ? /*<>*/ dec_invalid(1) : /*<>*/ dec_ret(2, (b0 & 31) << 6 | b1 & 63) /*<>*/ ; } } - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; } function set_utf_8_uchar(b, i, u){ function set(_h_, _g_, _f_){ @@ -5957,7 +5923,7 @@ } var max = /*<>*/ caml_ml_bytes_length(b) - 1 | 0, - u$0 = /*<>*/ caml_call1(Stdlib_Uchar[10], u); + u$0 = /*<>*/ Stdlib_Uchar[10].call(null, u); /*<>*/ if(0 > u$0) /*<>*/ throw caml_maybe_attach_backtrace ([0, Assert_failure, _b_], 1); @@ -6157,15 +6123,14 @@ var max = /*<>*/ caml_ml_bytes_length(b) - 1 | 0; /*<>*/ if(0 <= i && max >= i){ /*<>*/ if(i === max) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var hi = /*<>*/ unsafe_get_uint16_be(b, i); /*<>*/ if(55296 <= hi && 57343 >= hi){ /*<>*/ if(56319 < hi) - /*<>*/ return caml_call1(dec_invalid, 2) /*<>*/ ; + /*<>*/ return dec_invalid(2) /*<>*/ ; var last = /*<>*/ i + 3 | 0; /*<>*/ if(max < last) - /*<>*/ return caml_call1 - (dec_invalid, (max - i | 0) + 1 | 0) /*<>*/ ; + /*<>*/ return dec_invalid((max - i | 0) + 1 | 0) /*<>*/ ; var lo = /*<>*/ unsafe_get_uint16_be(b, i + 2 | 0); /*<>*/ if(56320 <= lo && 57343 >= lo){ var @@ -6173,17 +6138,17 @@ /*<>*/ ((hi & 1023) << 10 | lo & 1023) + 65536 | 0; /*<>*/ return dec_ret(4, u) /*<>*/ ; } - /*<>*/ return caml_call1(dec_invalid, 2) /*<>*/ ; + /*<>*/ return dec_invalid(2) /*<>*/ ; } /*<>*/ return dec_ret(2, hi) /*<>*/ ; } - /*<>*/ return caml_call1 - (Stdlib[1], cst_index_out_of_bounds) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_index_out_of_bounds) /*<>*/ ; } function set_utf_16be_uchar(b, i, u){ var max = /*<>*/ caml_ml_bytes_length(b) - 1 | 0; /*<>*/ if(0 <= i && max >= i){ - var u$0 = /*<>*/ caml_call1(Stdlib_Uchar[10], u); + var u$0 = /*<>*/ Stdlib_Uchar[10].call(null, u); /*<>*/ if(0 > u$0) /*<>*/ throw caml_maybe_attach_backtrace ([0, Assert_failure, _d_], 1); @@ -6206,8 +6171,8 @@ /*<>*/ unsafe_set_uint16_be(b, i + 2 | 0, lo); /*<>*/ return 4; } - /*<>*/ return caml_call1 - (Stdlib[1], cst_index_out_of_bounds$0) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_index_out_of_bounds$0) /*<>*/ ; } function is_valid_utf_16be(b){ var max = /*<>*/ caml_ml_bytes_length(b) - 1 | 0, i = 0; @@ -6237,15 +6202,14 @@ var max = /*<>*/ caml_ml_bytes_length(b) - 1 | 0; /*<>*/ if(0 <= i && max >= i){ /*<>*/ if(i === max) - /*<>*/ return caml_call1(dec_invalid, 1) /*<>*/ ; + /*<>*/ return dec_invalid(1) /*<>*/ ; var hi = /*<>*/ unsafe_get_uint16_le(b, i); /*<>*/ if(55296 <= hi && 57343 >= hi){ /*<>*/ if(56319 < hi) - /*<>*/ return caml_call1(dec_invalid, 2) /*<>*/ ; + /*<>*/ return dec_invalid(2) /*<>*/ ; var last = /*<>*/ i + 3 | 0; /*<>*/ if(max < last) - /*<>*/ return caml_call1 - (dec_invalid, (max - i | 0) + 1 | 0) /*<>*/ ; + /*<>*/ return dec_invalid((max - i | 0) + 1 | 0) /*<>*/ ; var lo = /*<>*/ unsafe_get_uint16_le(b, i + 2 | 0); /*<>*/ if(56320 <= lo && 57343 >= lo){ var @@ -6253,17 +6217,17 @@ /*<>*/ ((hi & 1023) << 10 | lo & 1023) + 65536 | 0; /*<>*/ return dec_ret(4, u) /*<>*/ ; } - /*<>*/ return caml_call1(dec_invalid, 2) /*<>*/ ; + /*<>*/ return dec_invalid(2) /*<>*/ ; } /*<>*/ return dec_ret(2, hi) /*<>*/ ; } - /*<>*/ return caml_call1 - (Stdlib[1], cst_index_out_of_bounds$1) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_index_out_of_bounds$1) /*<>*/ ; } function set_utf_16le_uchar(b, i, u){ var max = /*<>*/ caml_ml_bytes_length(b) - 1 | 0; /*<>*/ if(0 <= i && max >= i){ - var u$0 = /*<>*/ caml_call1(Stdlib_Uchar[10], u); + var u$0 = /*<>*/ Stdlib_Uchar[10].call(null, u); /*<>*/ if(0 > u$0) /*<>*/ throw caml_maybe_attach_backtrace ([0, Assert_failure, _f_], 1); @@ -6286,8 +6250,8 @@ /*<>*/ unsafe_set_uint16_le(b, i + 2 | 0, lo); /*<>*/ return 4; } - /*<>*/ return caml_call1 - (Stdlib[1], cst_index_out_of_bounds$2) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_index_out_of_bounds$2) /*<>*/ ; } function is_valid_utf_16le(b){ var max = /*<>*/ caml_ml_bytes_length(b) - 1 | 0, i = 0; @@ -6410,7 +6374,7 @@ //# unitInfo: Provides: Stdlib__String //# unitInfo: Requires: Stdlib, Stdlib__Bytes -//# shape: Stdlib__String:[F(2),F(2),N,F(1),F(1),F(5),F(2),F(2)*,F(2)*,F(2)*,F(2),F(2),F(3),F(3),F(2),F(3),F(2),F(2),F(2),F(3),F(3),F(2),F(2),F(1),F(1),F(1),F(1),F(1),F(1),F(2),F(2),F(3),F(3),F(3),F(3),F(2),F(2),F(2),F(2),F(1),F(1),F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(2)] +//# shape: Stdlib__String:[F(2),F(2),N,F(1),F(1),F(5),F(2),F(2)*,F(2)*,F(2)*,F(2),F(2),F(3),F(3),F(2),F(3),F(2),F(2),F(2),F(3),F(3),F(2),F(2),F(1),F(1),F(1),F(1),F(1),F(1),F(2),F(2),F(3),F(3),F(3),F(3),F(2),F(2),F(2),F(2),F(1)*,F(1)*,F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(2)] (function (globalThis){ "use strict"; @@ -6434,11 +6398,6 @@ ? f(a0, a1) : runtime.caml_call_gen(f, [a0, a1]); } - function caml_call3(f, a0, a1, a2){ - return (f.l >= 0 ? f.l : f.l = f.length) === 3 - ? f(a0, a1, a2) - : runtime.caml_call_gen(f, [a0, a1, a2]); - } var global_data = runtime.caml_get_global_data(), cst = cst$0, @@ -6448,20 +6407,18 @@ bts = Stdlib_Bytes[44], bos = Stdlib_Bytes[45]; function make(n, c){ - /*<>*/ return /*<>*/ caml_call1 - (bts, /*<>*/ caml_call2(Stdlib_Bytes[1], n, c)) /*<>*/ ; + /*<>*/ return /*<>*/ bts + ( /*<>*/ Stdlib_Bytes[1].call(null, n, c)) /*<>*/ ; } function init(n, f){ - /*<>*/ return /*<>*/ caml_call1 - (bts, /*<>*/ caml_call2(Stdlib_Bytes[2], n, f)) /*<>*/ ; + /*<>*/ return /*<>*/ bts + ( /*<>*/ Stdlib_Bytes[2].call(null, n, f)) /*<>*/ ; } var of_bytes = /*<>*/ Stdlib_Bytes[6], to_bytes = Stdlib_Bytes[5]; function sub(s, ofs, len){ - var _h_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return /*<>*/ caml_call1 - (bts, - /*<>*/ caml_call3 - (Stdlib_Bytes[7], _h_, ofs, len)) /*<>*/ ; + var _h_ = /*<>*/ bos(s); + /*<>*/ return /*<>*/ bts + ( /*<>*/ Stdlib_Bytes[7].call(null, _h_, ofs, len)) /*<>*/ ; } var blit = /*<>*/ Stdlib_Bytes[12], @@ -6487,7 +6444,7 @@ param = tl; } else{ - /*<>*/ acc = caml_call1(Stdlib[1], cst_String_concat); + /*<>*/ acc = Stdlib[1].call(null, cst_String_concat); param = tl; } } @@ -6522,7 +6479,7 @@ /*<>*/ caml_blit_string (hd$0, 0, dst, pos, caml_ml_string_length(hd$0)); } - /*<>*/ return caml_call1(bts, dst); + /*<>*/ return bts(dst); } } var @@ -6568,32 +6525,30 @@ /*<>*/ return 0; /*<>*/ } function map(f, s){ - var _d_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return /*<>*/ caml_call1 - (bts, - /*<>*/ caml_call2(Stdlib_Bytes[17], f, _d_)) /*<>*/ ; + var _d_ = /*<>*/ bos(s); + /*<>*/ return /*<>*/ bts + ( /*<>*/ Stdlib_Bytes[17].call(null, f, _d_)) /*<>*/ ; } function mapi(f, s){ - var _d_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return /*<>*/ caml_call1 - (bts, - /*<>*/ caml_call2(Stdlib_Bytes[18], f, _d_)) /*<>*/ ; + var _d_ = /*<>*/ bos(s); + /*<>*/ return /*<>*/ bts + ( /*<>*/ Stdlib_Bytes[18].call(null, f, _d_)) /*<>*/ ; } function fold_right(f, x, a){ - var _d_ = /*<>*/ caml_call1(bos, x); - /*<>*/ return caml_call3(Stdlib_Bytes[20], f, _d_, a) /*<>*/ ; + var _d_ = /*<>*/ bos(x); + /*<>*/ return Stdlib_Bytes[20].call(null, f, _d_, a) /*<>*/ ; } function fold_left(f, a, x){ - var _d_ = /*<>*/ caml_call1(bos, x); - /*<>*/ return caml_call3(Stdlib_Bytes[19], f, a, _d_); + var _d_ = /*<>*/ bos(x); + /*<>*/ return Stdlib_Bytes[19].call(null, f, a, _d_); } function exists(f, s){ - var _d_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[22], f, _d_); + var _d_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[22].call(null, f, _d_); } function for_all(f, s){ - var _d_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[21], f, _d_); + var _d_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[21].call(null, f, _d_); } function is_space(param){ var _d_ = /*<>*/ param - 9 | 0; @@ -6617,17 +6572,17 @@ ( /*<>*/ caml_string_unsafe_get (s, caml_ml_string_length(s) - 1 | 0))) /*<>*/ return s; - var _d_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return /*<>*/ caml_call1 - (bts, /*<>*/ caml_call1(Stdlib_Bytes[23], _d_)) /*<>*/ ; + var _d_ = /*<>*/ bos(s); + /*<>*/ return /*<>*/ bts + ( /*<>*/ Stdlib_Bytes[23].call(null, _d_)) /*<>*/ ; } function escaped(s){ var - b = /*<>*/ caml_call1(bos, s), - b$0 = /*<>*/ caml_call1(Stdlib_Bytes[87], b); + b = /*<>*/ bos(s), + b$0 = /*<>*/ Stdlib_Bytes[87].call(null, b); /*<>*/ return b === b$0 ? s - : /*<>*/ caml_call1(bts, b$0) /*<>*/ ; + : /*<>*/ bts(b$0) /*<>*/ ; } function index_rec(s, lim, i$1, c){ var i = /*<>*/ i$1; @@ -6663,15 +6618,15 @@ var l = /*<>*/ caml_ml_string_length(s); /*<>*/ if(0 <= i && l >= i) /*<>*/ return index_rec(s, l, i, c) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_index_from_Bytes_in) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_index_from_Bytes_in) /*<>*/ ; } function index_from_opt(s, i, c){ var l = /*<>*/ caml_ml_string_length(s); /*<>*/ if(0 <= i && l >= i) /*<>*/ return index_rec_opt(s, l, i, c) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_index_from_opt_Byte) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_index_from_opt_Byte) /*<>*/ ; } function rindex_rec(s, i$1, c){ var i = /*<>*/ i$1; @@ -6692,8 +6647,8 @@ function rindex_from(s, i, c){ /*<>*/ if(-1 <= i && caml_ml_string_length(s) > i) /*<>*/ return rindex_rec(s, i, c) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_rindex_from_Bytes_r) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_rindex_from_Bytes_r) /*<>*/ ; } function rindex_rec_opt(s, i$1, c){ var i = /*<>*/ i$1; @@ -6712,8 +6667,8 @@ function rindex_from_opt(s, i, c){ /*<>*/ if(-1 <= i && caml_ml_string_length(s) > i) /*<>*/ return rindex_rec_opt(s, i, c) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_rindex_from_opt_Byt) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_rindex_from_opt_Byt) /*<>*/ ; } function contains_from(s, i, c){ var l = /*<>*/ caml_ml_string_length(s); @@ -6728,8 +6683,8 @@ if(exn === Stdlib[8]) /*<>*/ return 0; /*<>*/ throw caml_maybe_attach_backtrace(exn, 0); } - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_contains_from_Bytes) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_contains_from_Bytes) /*<>*/ ; } function contains(s, c){ /*<>*/ return contains_from(s, 0, c) /*<>*/ ; @@ -6746,28 +6701,28 @@ if(exn === Stdlib[8]) /*<>*/ return 0; /*<>*/ throw caml_maybe_attach_backtrace(exn, 0); } - /*<>*/ return caml_call1 - (Stdlib[1], cst_String_rcontains_from_Byte) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_String_rcontains_from_Byte) /*<>*/ ; } function uppercase_ascii(s){ - var _d_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return /*<>*/ caml_call1 - (bts, /*<>*/ caml_call1(Stdlib_Bytes[36], _d_)) /*<>*/ ; + var _d_ = /*<>*/ bos(s); + /*<>*/ return /*<>*/ bts + ( /*<>*/ Stdlib_Bytes[36].call(null, _d_)) /*<>*/ ; } function lowercase_ascii(s){ - var _d_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return /*<>*/ caml_call1 - (bts, /*<>*/ caml_call1(Stdlib_Bytes[37], _d_)) /*<>*/ ; + var _d_ = /*<>*/ bos(s); + /*<>*/ return /*<>*/ bts + ( /*<>*/ Stdlib_Bytes[37].call(null, _d_)) /*<>*/ ; } function capitalize_ascii(s){ - var _d_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return /*<>*/ caml_call1 - (bts, /*<>*/ caml_call1(Stdlib_Bytes[38], _d_)) /*<>*/ ; + var _d_ = /*<>*/ bos(s); + /*<>*/ return /*<>*/ bts + ( /*<>*/ Stdlib_Bytes[38].call(null, _d_)) /*<>*/ ; } function uncapitalize_ascii(s){ - var _d_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return /*<>*/ caml_call1 - (bts, /*<>*/ caml_call1(Stdlib_Bytes[39], _d_)) /*<>*/ ; + var _d_ = /*<>*/ bos(s); + /*<>*/ return /*<>*/ bts + ( /*<>*/ Stdlib_Bytes[39].call(null, _d_)) /*<>*/ ; } function starts_with(prefix, s){ var @@ -6831,80 +6786,80 @@ /*<>*/ } var compare = /*<>*/ runtime.caml_string_compare; function to_seq(s){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call1(Stdlib_Bytes[47], _a_) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[47].call(null, _a_) /*<>*/ ; } function to_seqi(s){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call1(Stdlib_Bytes[48], _a_) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[48].call(null, _a_) /*<>*/ ; } function of_seq(g){ - /*<>*/ return /*<>*/ caml_call1 - (bts, /*<>*/ caml_call1(Stdlib_Bytes[49], g)) /*<>*/ ; + /*<>*/ return /*<>*/ bts + ( /*<>*/ Stdlib_Bytes[49].call(null, g)) /*<>*/ ; } function get_utf_8_uchar(s, i){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[50], _a_, i) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[50].call(null, _a_, i) /*<>*/ ; } function is_valid_utf_8(s){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call1(Stdlib_Bytes[52], _a_); + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[52].call(null, _a_); } function get_utf_16be_uchar(s, i){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[53], _a_, i) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[53].call(null, _a_, i) /*<>*/ ; } function is_valid_utf_16be(s){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call1(Stdlib_Bytes[55], _a_); + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[55].call(null, _a_); } function get_utf_16le_uchar(s, i){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[56], _a_, i) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[56].call(null, _a_, i) /*<>*/ ; } function is_valid_utf_16le(s){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call1(Stdlib_Bytes[58], _a_); + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[58].call(null, _a_); } function get_int8(s, i){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[60], _a_, i) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[60].call(null, _a_, i) /*<>*/ ; } function get_uint16_le(s, i){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[63], _a_, i) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[63].call(null, _a_, i) /*<>*/ ; } function get_uint16_be(s, i){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[62], _a_, i) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[62].call(null, _a_, i) /*<>*/ ; } function get_int16_ne(s, i){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[64], _a_, i) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[64].call(null, _a_, i) /*<>*/ ; } function get_int16_le(s, i){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[66], _a_, i) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[66].call(null, _a_, i) /*<>*/ ; } function get_int16_be(s, i){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[65], _a_, i) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[65].call(null, _a_, i) /*<>*/ ; } function get_int32_le(s, i){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[69], _a_, i) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[69].call(null, _a_, i) /*<>*/ ; } function get_int32_be(s, i){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[68], _a_, i) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[68].call(null, _a_, i) /*<>*/ ; } function get_int64_le(s, i){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[72], _a_, i) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[72].call(null, _a_, i) /*<>*/ ; } function get_int64_be(s, i){ - var _a_ = /*<>*/ caml_call1(bos, s); - /*<>*/ return caml_call2(Stdlib_Bytes[71], _a_, i) /*<>*/ ; + var _a_ = /*<>*/ bos(s); + /*<>*/ return Stdlib_Bytes[71].call(null, _a_, i) /*<>*/ ; } var Stdlib_String = @@ -7009,13 +6964,7 @@ runtime = globalThis.jsoo_runtime, cst_Marshal_from_bytes$1 = "Marshal.from_bytes", caml_marshal_data_size = runtime.caml_marshal_data_size, - caml_ml_bytes_length = runtime.caml_ml_bytes_length; - function caml_call1(f, a0){ - return (f.l >= 0 ? f.l : f.l = f.length) === 1 - ? f(a0) - : runtime.caml_call_gen(f, [a0]); - } - var + caml_ml_bytes_length = runtime.caml_ml_bytes_length, global_data = runtime.caml_get_global_data(), Stdlib_Bytes = global_data.Stdlib__Bytes, Stdlib = global_data.Stdlib, @@ -7026,8 +6975,8 @@ (0 <= ofs && 0 <= len && (caml_ml_bytes_length(buff) - len | 0) >= ofs) /*<>*/ return runtime.caml_output_value_to_buffer (buff, ofs, len, v, flags) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_Marshal_to_buffer_substrin) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Marshal_to_buffer_substrin) /*<>*/ ; } var cst_Marshal_data_size = /*<>*/ "Marshal.data_size", @@ -7037,8 +6986,8 @@ /*<>*/ if (0 <= ofs && (caml_ml_bytes_length(buff) - 16 | 0) >= ofs) /*<>*/ return caml_marshal_data_size(buff, ofs) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_Marshal_data_size) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Marshal_data_size) /*<>*/ ; } function total_size(buff, ofs){ /*<>*/ return 16 + data_size(buff, ofs) | 0 /*<>*/ ; @@ -7051,18 +7000,18 @@ - (16 + len | 0) | 0) < ofs - ? /*<>*/ caml_call1 - (Stdlib[1], cst_Marshal_from_bytes$0) + ? /*<>*/ Stdlib + [1].call + (null, cst_Marshal_from_bytes$0) : /*<>*/ runtime.caml_input_value_from_bytes (buff, ofs) /*<>*/ ; } - /*<>*/ return caml_call1 - (Stdlib[1], cst_Marshal_from_bytes) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Marshal_from_bytes) /*<>*/ ; } function from_string(buff, ofs){ /*<>*/ return /*<>*/ from_bytes - ( /*<>*/ caml_call1(Stdlib_Bytes[45], buff), - ofs) /*<>*/ ; + ( /*<>*/ Stdlib_Bytes[45].call(null, buff), ofs) /*<>*/ ; } var Stdlib_Marshal = @@ -7103,11 +7052,6 @@ ? f(a0, a1) : runtime.caml_call_gen(f, [a0, a1]); } - function caml_call3(f, a0, a1, a2){ - return (f.l >= 0 ? f.l : f.l = f.length) === 3 - ? f(a0, a1, a2) - : runtime.caml_call_gen(f, [a0, a1, a2]); - } var global_data = runtime.caml_get_global_data(), cst = "", @@ -7132,7 +7076,7 @@ function init(l, f){ /*<>*/ if(0 === l) /*<>*/ return [0]; /*<>*/ if(0 > l) - /*<>*/ return caml_call1(Stdlib[1], cst_Array_init) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Array_init) /*<>*/ ; var res = /*<>*/ /*<>*/ caml_array_make @@ -7152,7 +7096,7 @@ /*<>*/ } function make_matrix(sx, sy, init){ /*<>*/ if(sy < 0) - /*<>*/ caml_call1(Stdlib[1], cst_Array_make_matrix); + /*<>*/ Stdlib[1].call(null, cst_Array_make_matrix); var res = /*<>*/ caml_array_make(sx, [0]); /*<>*/ if(0 < sy){ var _ak_ = /*<>*/ sx - 1 | 0, _al_ = 0; @@ -7170,7 +7114,7 @@ /*<>*/ } function init_matrix(sx, sy, f){ /*<>*/ if(sy < 0) - /*<>*/ caml_call1(Stdlib[1], cst_Array_init_matrix); + /*<>*/ Stdlib[1].call(null, cst_Array_init_matrix); var res = /*<>*/ caml_array_make(sx, [0]); /*<>*/ if(0 < sy){ var _af_ = /*<>*/ sx - 1 | 0, _ah_ = 0; @@ -7220,13 +7164,13 @@ /*<>*/ if (0 <= ofs && 0 <= len && (a.length - 1 - len | 0) >= ofs) /*<>*/ return caml_array_sub(a, ofs, len) /*<>*/ ; - /*<>*/ return caml_call1(Stdlib[1], cst_Array_sub) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Array_sub) /*<>*/ ; } function fill(a, ofs, len, v){ /*<>*/ if (0 <= ofs && 0 <= len && (a.length - 1 - len | 0) >= ofs) /*<>*/ return runtime.caml_array_fill(a, ofs, len, v) /*<>*/ ; - /*<>*/ return caml_call1(Stdlib[1], cst_Array_fill) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Array_fill) /*<>*/ ; } function blit(a1, ofs1, a2, ofs2, len){ /*<>*/ if @@ -7238,7 +7182,7 @@ && 0 <= ofs2 && (a2.length - 1 - len | 0) >= ofs2) /*<>*/ return runtime.caml_array_blit (a1, ofs1, a2, ofs2, len) /*<>*/ ; - /*<>*/ return caml_call1(Stdlib[1], cst_Array_blit) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Array_blit) /*<>*/ ; } function iter(f, a){ var _ad_ = /*<>*/ a.length - 2 | 0, _ae_ = 0; @@ -7255,8 +7199,8 @@ /*<>*/ } function iter2(f, a, b){ /*<>*/ if(a.length - 1 !== b.length - 1) - /*<>*/ return caml_call1 - (Stdlib[1], cst_Array_iter2_arrays_must_ha) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Array_iter2_arrays_must_ha) /*<>*/ ; var _ab_ = /*<>*/ a.length - 2 | 0, _ac_ = 0; if(_ab_ >= 0){ var i = _ac_; @@ -7320,8 +7264,8 @@ la = /*<>*/ a.length - 1, lb = /*<>*/ b.length - 1; /*<>*/ if(la !== lb) - /*<>*/ return caml_call1 - (Stdlib[1], cst_Array_map2_arrays_must_hav) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Array_map2_arrays_must_hav) /*<>*/ ; /*<>*/ if(0 === la) /*<>*/ return [0]; var r = @@ -7499,7 +7443,7 @@ function for_all2(p, l1, l2){ var n1 = /*<>*/ l1.length - 1, n2 = l2.length - 1; /*<>*/ if(n1 !== n2) - /*<>*/ return caml_call1(Stdlib[1], cst_Array_for_all2) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Array_for_all2) /*<>*/ ; var i = /*<>*/ 0; for(;;){ /*<>*/ if(i === n1) /*<>*/ return 1; @@ -7512,7 +7456,7 @@ function exists2(p, l1, l2){ var n1 = /*<>*/ l1.length - 1, n2 = l2.length - 1; /*<>*/ if(n1 !== n2) - /*<>*/ return caml_call1(Stdlib[1], cst_Array_exists2) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Array_exists2) /*<>*/ ; var i = /*<>*/ 0; for(;;){ /*<>*/ if(i === n1) /*<>*/ return 0; @@ -7628,7 +7572,7 @@ na = /*<>*/ a.length - 1, nb = /*<>*/ b.length - 1; /*<>*/ if(na !== nb) - /*<>*/ caml_call1(Stdlib[1], cst_Array_combine); + /*<>*/ Stdlib[1].call(null, cst_Array_combine); /*<>*/ if(0 === na) /*<>*/ return [0]; var x = /*<>*/ caml_array_make(na, [0, a[1], b[1]]), @@ -7924,17 +7868,14 @@ _h_ = /*<>*/ [0, cst_out_of_expected_range_0, - [0, caml_call1(int$, i), _b_]], - _i_ = - /*<>*/ [0, - cst_returned, - [0, caml_call1(int$, j), _h_]], + [0, int$(i), _b_]], + _i_ = /*<>*/ [0, cst_returned, [0, int$(j), _h_]], _j_ = /*<>*/ [0, cst_Array_shuffle_rand, - [0, caml_call1(int$, i + 1 | 0), _i_]], - _k_ = /*<>*/ caml_call2(Stdlib_String[7], cst, _j_); - /*<>*/ caml_call1(Stdlib[1], _k_); + [0, int$(i + 1 | 0), _i_]], + _k_ = /*<>*/ Stdlib_String[7].call(null, cst, _j_); + /*<>*/ Stdlib[1].call(null, _k_); } var v = /*<>*/ a[i + 1]; /*<>*/ a[i + 1] = a[j + 1]; @@ -7979,8 +7920,8 @@ function of_seq(i$2){ var l = - /*<>*/ caml_call3 - (Stdlib_Seq[5], + /*<>*/ Stdlib_Seq[5].call + (null, function(acc, x){ /*<>*/ return [0, x, acc]; /*<>*/ }, @@ -8086,11 +8027,6 @@ ? f(a0, a1) : runtime.caml_call_gen(f, [a0, a1]); } - function caml_call3(f, a0, a1, a2){ - return (f.l >= 0 ? f.l : f.l = f.length) === 3 - ? f(a0, a1, a2) - : runtime.caml_call_gen(f, [a0, a1, a2]); - } var global_data = runtime.caml_get_global_data(), Stdlib_Seq = global_data.Stdlib__Seq, @@ -8227,7 +8163,7 @@ _ap_ = (ofs + len | 0) < 0 ? 1 : 0, _am_ = _ap_ || (a.length - 1 < (ofs + len | 0) ? 1 : 0); } - return _am_ ? /*<>*/ caml_call1(Stdlib[1], msg) : _am_ /*<>*/ ; + return _am_ ? /*<>*/ Stdlib[1].call(null, msg) : _am_ /*<>*/ ; } var empty = /*<>*/ caml_floatarray_create(0), @@ -8246,8 +8182,8 @@ "Float.Array.map2: arrays must have the same length"; function init(l, f){ /*<>*/ if(0 > l) - /*<>*/ return caml_call1 - (Stdlib[1], cst_Float_Array_init) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Float_Array_init) /*<>*/ ; var res = /*<>*/ caml_floatarray_create(l), _ak_ = /*<>*/ l - 1 | 0, @@ -8265,8 +8201,8 @@ /*<>*/ } function make_matrix(sx, sy, v){ /*<>*/ if(sy < 0) - /*<>*/ caml_call1 - (Stdlib[1], cst_Float_Array_make_matrix); + /*<>*/ Stdlib[1].call + (null, cst_Float_Array_make_matrix); var res = /*<>*/ /*<>*/ caml_array_make @@ -8287,8 +8223,8 @@ /*<>*/ } function init_matrix(sx, sy, f){ /*<>*/ if(sy < 0) - /*<>*/ caml_call1 - (Stdlib[1], cst_Float_Array_init_matrix); + /*<>*/ Stdlib[1].call + (null, cst_Float_Array_init_matrix); var res = /*<>*/ /*<>*/ caml_array_make @@ -8334,7 +8270,7 @@ } else{ /*<>*/ acc = - caml_call1(Stdlib[1], cst_Float_Array_concat); + Stdlib[1].call(null, cst_Float_Array_concat); param = tl; } } @@ -8390,8 +8326,8 @@ (src, sofs, dst, dofs, len) /*<>*/ ; } function to_list(a){ - /*<>*/ return caml_call2 - (Stdlib_List[11], + /*<>*/ return Stdlib_List[11].call + (null, a.length - 1, function(_ad_){ /*<>*/ return a[_ad_ + 1];}) /*<>*/ ; } @@ -8399,7 +8335,7 @@ var result = /*<>*/ /*<>*/ caml_floatarray_create - ( /*<>*/ caml_call1(Stdlib_List[1], l)), + ( /*<>*/ Stdlib_List[1].call(null, l)), i = /*<>*/ 0, l$0 = l; for(;;){ @@ -8426,8 +8362,8 @@ /*<>*/ } function iter2(f, a, b){ /*<>*/ if(a.length - 1 !== b.length - 1) - /*<>*/ return caml_call1 - (Stdlib[1], cst_Float_Array_iter2_arrays_m) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Float_Array_iter2_arrays_m) /*<>*/ ; var _$_ = /*<>*/ a.length - 2 | 0, _aa_ = 0; if(_$_ >= 0){ var i = _aa_; @@ -8475,8 +8411,8 @@ la = /*<>*/ a.length - 1, lb = /*<>*/ b.length - 1; /*<>*/ if(la !== lb) - /*<>*/ return caml_call1 - (Stdlib[1], cst_Float_Array_map2_arrays_mu) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Float_Array_map2_arrays_mu) /*<>*/ ; var r = /*<>*/ caml_floatarray_create(la), _V_ = /*<>*/ la - 1 | 0, @@ -8973,14 +8909,14 @@ function of_seq(i$2){ var l = - /*<>*/ caml_call3 - (Stdlib_Seq[5], + /*<>*/ Stdlib_Seq[5].call + (null, function(acc, x){ /*<>*/ return [0, x, acc]; /*<>*/ }, 0, i$2), - len = /*<>*/ caml_call1(Stdlib_List[1], l), + len = /*<>*/ Stdlib_List[1].call(null, l), a = /*<>*/ caml_floatarray_create(len), i$1 = /*<>*/ len - 1 | 0, i = i$1, @@ -9586,31 +9522,11 @@ caml_check_bound = runtime.caml_check_bound, caml_create_bytes = runtime.caml_create_bytes, caml_ml_bytes_length = runtime.caml_ml_bytes_length; - function caml_call1(f, a0){ - return (f.l >= 0 ? f.l : f.l = f.length) === 1 - ? f(a0) - : runtime.caml_call_gen(f, [a0]); - } function caml_call2(f, a0, a1){ return (f.l >= 0 ? f.l : f.l = f.length) === 2 ? f(a0, a1) : runtime.caml_call_gen(f, [a0, a1]); } - function caml_call3(f, a0, a1, a2){ - return (f.l >= 0 ? f.l : f.l = f.length) === 3 - ? f(a0, a1, a2) - : runtime.caml_call_gen(f, [a0, a1, a2]); - } - function caml_call4(f, a0, a1, a2, a3){ - return (f.l >= 0 ? f.l : f.l = f.length) === 4 - ? f(a0, a1, a2, a3) - : runtime.caml_call_gen(f, [a0, a1, a2, a3]); - } - function caml_call5(f, a0, a1, a2, a3, a4){ - return (f.l >= 0 ? f.l : f.l = f.length) === 5 - ? f(a0, a1, a2, a3, a4) - : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4]); - } var global_data = runtime.caml_get_global_data(), dummy_pos = [0, cst, 0, 0, -1], @@ -9666,8 +9582,8 @@ /*<>*/ if (((lexbuf[3] - lexbuf[5] | 0) + n | 0) <= caml_ml_bytes_length(lexbuf[2])) - /*<>*/ caml_call5 - (Stdlib_Bytes[11], + /*<>*/ Stdlib_Bytes[11].call + (null, lexbuf[2], lexbuf[5], lexbuf[2], @@ -9676,20 +9592,21 @@ else{ var newlen = - /*<>*/ /*<>*/ caml_call2 - (Stdlib_Int[10], + /*<>*/ /*<>*/ Stdlib_Int + [10].call + (null, 2 * /*<>*/ caml_ml_bytes_length(lexbuf[2]) | 0, Stdlib_Sys[12]); /*<>*/ if (newlen < ((lexbuf[3] - lexbuf[5] | 0) + n | 0)) - /*<>*/ caml_call1 - (Stdlib[2], cst_Lexing_lex_refill_cannot_g); + /*<>*/ Stdlib[2].call + (null, cst_Lexing_lex_refill_cannot_g); var newbuf = /*<>*/ caml_create_bytes(newlen); - /*<>*/ caml_call5 - (Stdlib_Bytes[11], + /*<>*/ Stdlib_Bytes[11].call + (null, lexbuf[2], lexbuf[5], newbuf, @@ -9720,8 +9637,8 @@ } } } - /*<>*/ caml_call5 - (Stdlib_Bytes[11], aux_buffer, 0, lexbuf[2], lexbuf[3], n); + /*<>*/ Stdlib_Bytes[11].call + (null, aux_buffer, 0, lexbuf[2], lexbuf[3], n); /*<>*/ lexbuf[3] = lexbuf[3] + n | 0; return 0; }, @@ -9741,14 +9658,14 @@ /*<>*/ return from_function (with_positions, function(buf, n){ - /*<>*/ return caml_call4 - (Stdlib[84], ic, buf, 0, n) /*<>*/ ; + /*<>*/ return Stdlib[84].call + (null, ic, buf, 0, n) /*<>*/ ; }) /*<>*/ ; } function from_string(opt, s){ var with_positions = /*<>*/ opt ? opt[1] : 1, - lex_buffer = /*<>*/ caml_call1(Stdlib_Bytes[5], s), + lex_buffer = /*<>*/ Stdlib_Bytes[5].call(null, s), _b_ = /*<>*/ with_positions ? zero_pos : dummy_pos, _c_ = with_positions ? zero_pos : dummy_pos; return [0, @@ -9784,19 +9701,19 @@ /*<>*/ } function lexeme(lexbuf){ var len = /*<>*/ lexbuf[6] - lexbuf[5] | 0; - /*<>*/ return caml_call3 - (Stdlib_Bytes[8], lexbuf[2], lexbuf[5], len) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[8].call + (null, lexbuf[2], lexbuf[5], len) /*<>*/ ; } function sub_lexeme(lexbuf, i1, i2){ var len = /*<>*/ i2 - i1 | 0; - /*<>*/ return caml_call3 - (Stdlib_Bytes[8], lexbuf[2], i1, len) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[8].call + (null, lexbuf[2], i1, len) /*<>*/ ; } function sub_lexeme_opt(lexbuf, i1, i2){ /*<>*/ if(0 > i1) /*<>*/ return 0; var len = /*<>*/ i2 - i1 | 0; /*<>*/ return [0, - caml_call3(Stdlib_Bytes[8], lexbuf[2], i1, len)] /*<>*/ ; + Stdlib_Bytes[8].call(null, lexbuf[2], i1, len)] /*<>*/ ; /*<>*/ } function sub_lexeme_char(lexbuf, i){ /*<>*/ return caml_bytes_get(lexbuf[2], i) /*<>*/ ; @@ -9889,16 +9806,6 @@ ? f(a0) : runtime.caml_call_gen(f, [a0]); } - function caml_call4(f, a0, a1, a2, a3){ - return (f.l >= 0 ? f.l : f.l = f.length) === 4 - ? f(a0, a1, a2, a3) - : runtime.caml_call_gen(f, [a0, a1, a2, a3]); - } - function caml_call5(f, a0, a1, a2, a3, a4){ - return (f.l >= 0 ? f.l : f.l = f.length) === 5 - ? f(a0, a1, a2, a3, a4) - : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4]); - } var global_data = runtime.caml_get_global_data(), Stdlib_Obj = global_data.Stdlib__Obj, @@ -9935,23 +9842,22 @@ /*<>*/ caml_array_make(newsize, Stdlib_Lexing[1]), new_end = /*<>*/ caml_array_make(newsize, Stdlib_Lexing[1]); - /*<>*/ caml_call5 - (Stdlib_Array[9], env[1], 0, new_s, 0, oldsize); + /*<>*/ Stdlib_Array[9].call + (null, env[1], 0, new_s, 0, oldsize); /*<>*/ env[1] = new_s; - /*<>*/ caml_call5 - (Stdlib_Array[9], env[2], 0, new_v, 0, oldsize); + /*<>*/ Stdlib_Array[9].call + (null, env[2], 0, new_v, 0, oldsize); /*<>*/ env[2] = new_v; - /*<>*/ caml_call5 - (Stdlib_Array[9], env[3], 0, new_start, 0, oldsize); + /*<>*/ Stdlib_Array[9].call + (null, env[3], 0, new_start, 0, oldsize); /*<>*/ env[3] = new_start; - /*<>*/ caml_call5 - (Stdlib_Array[9], env[4], 0, new_end, 0, oldsize); + /*<>*/ Stdlib_Array[9].call + (null, env[4], 0, new_end, 0, oldsize); /*<>*/ env[4] = new_end; /*<>*/ env[5] = newsize; /*<>*/ } function clear_parser(param){ - /*<>*/ caml_call4 - (Stdlib_Array[8], env[2], 0, env[5], 0); + /*<>*/ Stdlib_Array[8].call(null, env[2], 0, env[5], 0); /*<>*/ env[8] = 0; return 0; /*<>*/ } @@ -10038,7 +9944,7 @@ if(tag === YYexit){var v = exn$0[2]; /*<>*/ return v;} /*<>*/ current_lookahead_fun[1] = function(tok){ - /*<>*/ if(! caml_call1(Stdlib_Obj[1], tok)) + /*<>*/ if(! Stdlib_Obj[1].call(null, tok)) /*<>*/ return caml_check_bound(tables[2], tok) [tok + 1] === curr_char @@ -10150,11 +10056,6 @@ ? f(a0, a1) : runtime.caml_call_gen(f, [a0, a1]); } - function caml_call3(f, a0, a1, a2){ - return (f.l >= 0 ? f.l : f.l = f.length) === 3 - ? f(a0, a1, a2) - : runtime.caml_call_gen(f, [a0, a1, a2]); - } var global_data = runtime.caml_get_global_data(), Stdlib = global_data.Stdlib, @@ -10200,7 +10101,7 @@ var hr = /*<>*/ 0; /*<>*/ if((hr + 2 | 0) < hl){ /*<>*/ if(! l) - /*<>*/ return caml_call1(Stdlib[1], cst_Set_bal$0) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Set_bal$0) /*<>*/ ; var lr = /*<>*/ l[3], lv = l[2], @@ -10210,7 +10111,7 @@ /*<>*/ return /*<>*/ create (ll, lv, /*<>*/ create(lr, v, r)) /*<>*/ ; /*<>*/ if(! lr) - /*<>*/ return caml_call1(Stdlib[1], cst_Set_bal) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Set_bal) /*<>*/ ; var lrr = /*<>*/ lr[3], lrv = lr[2], @@ -10224,7 +10125,7 @@ return [0, l, v, r, _y_]; } /*<>*/ if(! r) - /*<>*/ return caml_call1(Stdlib[1], cst_Set_bal$2) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Set_bal$2) /*<>*/ ; var rr = /*<>*/ r[3], rv = r[2], @@ -10234,7 +10135,7 @@ /*<>*/ return /*<>*/ create ( /*<>*/ create(l, v, rl), rv, rr) /*<>*/ ; /*<>*/ if(! rl) - /*<>*/ return caml_call1(Stdlib[1], cst_Set_bal$1) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Set_bal$1) /*<>*/ ; var rlr = /*<>*/ rl[3], rlv = rl[2], @@ -10353,8 +10254,8 @@ /*<>*/ } function remove_min_elt(param){ /*<>*/ if(! param) - /*<>*/ return caml_call1 - (Stdlib[1], cst_Set_remove_min_elt) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Set_remove_min_elt) /*<>*/ ; var l = /*<>*/ param[1]; if(l){ var r = param[3], v = param[2]; @@ -10981,7 +10882,7 @@ (x1, /*<>*/ singleton(x0)))) /*<>*/ ; /*<>*/ if(match$2[2]){ var - l$0 = /*<>*/ caml_call2(Stdlib_List[66], Ord[1], l), + l$0 = /*<>*/ Stdlib_List[66].call(null, Ord[1], l), sub = /*<>*/ function(n, l){ /*<>*/ if(3 >= n >>> 0) @@ -11040,8 +10941,7 @@ /*<>*/ return [0, create(left, mid, right), l$2] /*<>*/ ; /*<>*/ }; /*<>*/ return /*<>*/ sub - ( /*<>*/ caml_call1(Stdlib_List[1], l$0), - l$0) + ( /*<>*/ Stdlib_List[1].call(null, l$0), l$0) [1] /*<>*/ ; } var x4 = /*<>*/ match$2[1]; @@ -11055,8 +10955,8 @@ (x1, /*<>*/ singleton(x0))))) /*<>*/ ; } function add_seq(i, m){ - /*<>*/ return caml_call3 - (Stdlib_Seq[5], + /*<>*/ return Stdlib_Seq[5].call + (null, function(s, x){ /*<>*/ return add(x, s) /*<>*/ ; }, @@ -11258,7 +11158,7 @@ var hr = /*<>*/ 0; /*<>*/ if((hr + 2 | 0) < hl){ /*<>*/ if(! l) - /*<>*/ return caml_call1(Stdlib[1], cst_Map_bal$0) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Map_bal$0) /*<>*/ ; var lr = /*<>*/ l[4], ld = l[3], @@ -11269,7 +11169,7 @@ /*<>*/ return /*<>*/ create (ll, lv, ld, /*<>*/ create(lr, x, d, r)) /*<>*/ ; /*<>*/ if(! lr) - /*<>*/ return caml_call1(Stdlib[1], cst_Map_bal) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Map_bal) /*<>*/ ; var lrr = /*<>*/ lr[4], lrd = lr[3], @@ -11287,7 +11187,7 @@ return [0, l, x, d, r, _w_]; } /*<>*/ if(! r) - /*<>*/ return caml_call1(Stdlib[1], cst_Map_bal$2) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Map_bal$2) /*<>*/ ; var rr = /*<>*/ r[4], rd = r[3], @@ -11298,7 +11198,7 @@ /*<>*/ return /*<>*/ create ( /*<>*/ create(l, x, d, rl), rv, rd, rr) /*<>*/ ; /*<>*/ if(! rl) - /*<>*/ return caml_call1(Stdlib[1], cst_Map_bal$1) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Map_bal$1) /*<>*/ ; var rlr = /*<>*/ rl[4], rld = rl[3], @@ -11566,8 +11466,8 @@ /*<>*/ } function remove_min_binding(param){ /*<>*/ if(! param) - /*<>*/ return caml_call1 - (Stdlib[1], cst_Map_remove_min_elt) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Map_remove_min_elt) /*<>*/ ; var l = /*<>*/ param[1]; if(l){ var r = param[4], d = param[3], v = param[2]; @@ -12084,8 +11984,8 @@ /*<>*/ return bindings_aux(0, s) /*<>*/ ; } function of_list(bs){ - /*<>*/ return caml_call3 - (Stdlib_List[26], + /*<>*/ return Stdlib_List[26].call + (null, function(m, param){ var v = /*<>*/ param[2], k = param[1]; /*<>*/ return add(k, v, m) /*<>*/ ; @@ -12094,8 +11994,8 @@ bs) /*<>*/ ; } function add_seq(i, m){ - /*<>*/ return caml_call3 - (Stdlib_Seq[5], + /*<>*/ return Stdlib_Seq[5].call + (null, function(m, param){ var v = /*<>*/ param[2], k = param[1]; /*<>*/ return add(k, v, m) /*<>*/ ; @@ -12236,29 +12136,13 @@ //# unitInfo: Provides: Stdlib__Stack //# unitInfo: Requires: Stdlib__List, Stdlib__Seq -//# shape: Stdlib__Stack:[N,F(1)*,F(2),F(1),F(1),F(1),F(1),F(1)*,F(1),F(1)*,F(1)*,F(1)*,F(2),F(3),F(1),F(2),F(1)] +//# shape: Stdlib__Stack:[N,F(1)*,F(2),F(1),F(1),F(1),F(1),F(1)*,F(1),F(1)*,F(1)*,F(1)*,F(2),F(3),F(1)*,F(2),F(1)] (function (globalThis){ "use strict"; var runtime = globalThis.jsoo_runtime, - caml_maybe_attach_backtrace = runtime.caml_maybe_attach_backtrace; - function caml_call1(f, a0){ - return (f.l >= 0 ? f.l : f.l = f.length) === 1 - ? f(a0) - : runtime.caml_call_gen(f, [a0]); - } - function caml_call2(f, a0, a1){ - return (f.l >= 0 ? f.l : f.l = f.length) === 2 - ? f(a0, a1) - : runtime.caml_call_gen(f, [a0, a1]); - } - function caml_call3(f, a0, a1, a2){ - return (f.l >= 0 ? f.l : f.l = f.length) === 3 - ? f(a0, a1, a2) - : runtime.caml_call_gen(f, [a0, a1, a2]); - } - var + caml_maybe_attach_backtrace = runtime.caml_maybe_attach_backtrace, global_data = runtime.caml_get_global_data(), Stdlib_Seq = global_data.Stdlib__Seq, Stdlib_List = global_data.Stdlib__List, @@ -12325,17 +12209,17 @@ /*<>*/ return s[2]; /*<>*/ } function iter(f, s){ - /*<>*/ return caml_call2(Stdlib_List[18], f, s[1]) /*<>*/ ; + /*<>*/ return Stdlib_List[18].call(null, f, s[1]) /*<>*/ ; } function fold(f, acc, s){ - /*<>*/ return caml_call3(Stdlib_List[26], f, acc, s[1]) /*<>*/ ; + /*<>*/ return Stdlib_List[26].call(null, f, acc, s[1]) /*<>*/ ; } function to_seq(s){ - /*<>*/ return caml_call1(Stdlib_List[68], s[1]) /*<>*/ ; + /*<>*/ return Stdlib_List[68].call(null, s[1]) /*<>*/ ; } function add_seq(q, i){ - /*<>*/ return caml_call2 - (Stdlib_Seq[4], + /*<>*/ return Stdlib_Seq[4].call + (null, function(x){ /*<>*/ return push(x, q) /*<>*/ ; }, @@ -12547,8 +12431,8 @@ /*<>*/ return aux(_a_, _b_);} /*<>*/ ; /*<>*/ } function add_seq(q, i){ - /*<>*/ return caml_call2 - (Stdlib_Seq[4], + /*<>*/ return Stdlib_Seq[4].call + (null, function(x){ /*<>*/ return add(x, q) /*<>*/ ; }, @@ -12616,26 +12500,6 @@ ? f(a0) : runtime.caml_call_gen(f, [a0]); } - function caml_call2(f, a0, a1){ - return (f.l >= 0 ? f.l : f.l = f.length) === 2 - ? f(a0, a1) - : runtime.caml_call_gen(f, [a0, a1]); - } - function caml_call3(f, a0, a1, a2){ - return (f.l >= 0 ? f.l : f.l = f.length) === 3 - ? f(a0, a1, a2) - : runtime.caml_call_gen(f, [a0, a1, a2]); - } - function caml_call4(f, a0, a1, a2, a3){ - return (f.l >= 0 ? f.l : f.l = f.length) === 4 - ? f(a0, a1, a2, a3) - : runtime.caml_call_gen(f, [a0, a1, a2, a3]); - } - function caml_call5(f, a0, a1, a2, a3, a4){ - return (f.l >= 0 ? f.l : f.l = f.length) === 5 - ? f(a0, a1, a2, a3, a4) - : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4]); - } var global_data = runtime.caml_get_global_data(), Stdlib_Bytes = global_data.Stdlib__Bytes, @@ -12657,19 +12521,19 @@ /*<>*/ return [0, [0, s, n$1], 0, s]; /*<>*/ } function contents(b){ - /*<>*/ return caml_call3 - (Stdlib_Bytes[8], b[1][1], 0, b[2]) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[8].call + (null, b[1][1], 0, b[2]) /*<>*/ ; } function to_bytes(b){ - /*<>*/ return caml_call3 - (Stdlib_Bytes[7], b[1][1], 0, b[2]) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[7].call + (null, b[1][1], 0, b[2]) /*<>*/ ; } function sub(b, ofs, len){ /*<>*/ if (0 <= ofs && 0 <= len && (b[2] - len | 0) >= ofs) - /*<>*/ return caml_call3 - (Stdlib_Bytes[8], b[1][1], ofs, len) /*<>*/ ; - /*<>*/ return caml_call1(Stdlib[1], cst_Buffer_sub) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[8].call + (null, b[1][1], ofs, len) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Buffer_sub) /*<>*/ ; } function blit(src, srcoff, dst, dstoff, len){ /*<>*/ if @@ -12679,9 +12543,9 @@ && (src[2] - len | 0) >= srcoff && 0 <= dstoff && (caml_ml_bytes_length(dst) - len | 0) >= dstoff) - /*<>*/ return caml_call5 - (Stdlib_Bytes[11], src[1][1], srcoff, dst, dstoff, len) /*<>*/ ; - /*<>*/ return caml_call1(Stdlib[1], cst_Buffer_blit) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[11].call + (null, src[1][1], srcoff, dst, dstoff, len) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Buffer_blit) /*<>*/ ; } function nth(b, ofs){ var @@ -12692,7 +12556,7 @@ /*<>*/ if (0 <= ofs && position > ofs && length >= position) /*<>*/ return runtime.caml_bytes_unsafe_get(buffer, ofs) /*<>*/ ; - /*<>*/ return caml_call1(Stdlib[1], cst_Buffer_nth) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Buffer_nth) /*<>*/ ; } function length(b){ /*<>*/ return b[2]; @@ -12720,11 +12584,11 @@ /*<>*/ if((old_pos + more | 0) <= Stdlib_Sys[12]) /*<>*/ new_len[1] = Stdlib_Sys[12]; else - /*<>*/ caml_call1 - (Stdlib[2], cst_Buffer_add_cannot_grow_buf); + /*<>*/ Stdlib[2].call + (null, cst_Buffer_add_cannot_grow_buf); var new_buffer = /*<>*/ caml_create_bytes(new_len[1]); - /*<>*/ caml_call5 - (Stdlib_Bytes[11], b[1][1], 0, new_buffer, 0, b[2]); + /*<>*/ Stdlib_Bytes[11].call + (null, b[1][1], 0, new_buffer, 0, b[2]); /*<>*/ b[1] = [0, new_buffer, new_len[1]]; /*<>*/ } function add_char(b, c){ @@ -12757,8 +12621,7 @@ /*<>*/ resize(b, uchar_utf_8_byte_length_max); var n = - /*<>*/ caml_call3 - (Stdlib_Bytes[51], b[1][1], pos, u); + /*<>*/ Stdlib_Bytes[51].call(null, b[1][1], pos, u); /*<>*/ if(0 !== n){ /*<>*/ b[2] = pos + n | 0; return 0; @@ -12773,8 +12636,7 @@ /*<>*/ resize(b, uchar_utf_16_byte_length_max); var n = - /*<>*/ caml_call3 - (Stdlib_Bytes[54], b[1][1], pos, u); + /*<>*/ Stdlib_Bytes[54].call(null, b[1][1], pos, u); /*<>*/ if(0 !== n){ /*<>*/ b[2] = pos + n | 0; return 0; @@ -12789,8 +12651,7 @@ /*<>*/ resize(b, uchar_utf_16_byte_length_max); var n = - /*<>*/ caml_call3 - (Stdlib_Bytes[57], b[1][1], pos, u); + /*<>*/ Stdlib_Bytes[57].call(null, b[1][1], pos, u); /*<>*/ if(0 !== n){ /*<>*/ b[2] = pos + n | 0; return 0; @@ -12807,7 +12668,7 @@ _j_ = len < 0 ? 1 : 0, _i_ = _j_ || ((caml_ml_string_length(s) - len | 0) < offset ? 1 : 0); if(_i_) - /*<>*/ caml_call1(Stdlib[1], cst_Buffer_add_substring); + /*<>*/ Stdlib[1].call(null, cst_Buffer_add_substring); var position = /*<>*/ b[2], match = /*<>*/ b[1], @@ -12816,8 +12677,8 @@ new_position = /*<>*/ position + len | 0; /*<>*/ if(length < new_position){ /*<>*/ resize(b, len); - /*<>*/ caml_call5 - (Stdlib_Bytes[12], s, offset, b[1][1], b[2], len); + /*<>*/ Stdlib_Bytes[12].call + (null, s, offset, b[1][1], b[2], len); } else /*<>*/ runtime.caml_blit_string @@ -12834,7 +12695,7 @@ _h_ = len < 0 ? 1 : 0, _g_ = _h_ || ((caml_ml_bytes_length(bytes) - len | 0) < offset ? 1 : 0); if(_g_) - /*<>*/ caml_call1(Stdlib[1], cst_Buffer_add_subbytes); + /*<>*/ Stdlib[1].call(null, cst_Buffer_add_subbytes); var position = /*<>*/ b[2], match = /*<>*/ b[1], @@ -12843,8 +12704,8 @@ new_position = /*<>*/ position + len | 0; /*<>*/ if(length < new_position){ /*<>*/ resize(b, len); - /*<>*/ caml_call5 - (Stdlib_Bytes[11], bytes, offset, b[1][1], b[2], len); + /*<>*/ Stdlib_Bytes[11].call + (null, bytes, offset, b[1][1], b[2], len); } else /*<>*/ runtime.caml_blit_bytes @@ -12868,7 +12729,7 @@ _e_ = /*<>*/ to_read$1 < 0 ? 1 : 0, _f_ = _e_ || (Stdlib_Sys[12] < to_read$1 ? 1 : 0); if(_f_) - /*<>*/ caml_call1(Stdlib[1], cst_Buffer_add_channel); + /*<>*/ Stdlib[1].call(null, cst_Buffer_add_channel); /*<>*/ if(b[1][2] < (b[2] + to_read$1 | 0)) /*<>*/ resize(b, to_read$1); var @@ -12881,8 +12742,8 @@ /*<>*/ if(0 !== to_read){ var r = - /*<>*/ caml_call4 - (Stdlib[84], ic, buf, ofs, to_read); + /*<>*/ Stdlib[84].call + (null, ic, buf, ofs, to_read); /*<>*/ if(0 !== r){ var already_read$0 = /*<>*/ already_read + r | 0, @@ -12902,8 +12763,8 @@ } /*<>*/ } function output_buffer(oc, b){ - /*<>*/ return caml_call4 - (Stdlib[68], oc, b[1][1], 0, b[2]) /*<>*/ ; + /*<>*/ return Stdlib[68].call + (null, oc, b[1][1], 0, b[2]) /*<>*/ ; } function add_substitute(b, f, s){ var @@ -12962,8 +12823,8 @@ var val = /*<>*/ [0, - /*<>*/ caml_call3 - (Stdlib_String[16], s, start, stop$0 - start | 0), + /*<>*/ Stdlib_String[16].call + (null, s, start, stop$0 - start | 0), stop$0]; break a; } @@ -13003,8 +12864,8 @@ var val = /*<>*/ [0, - /*<>*/ caml_call3 - (Stdlib_String[16], s, new_start, (stop - start | 0) - 1 | 0), + /*<>*/ Stdlib_String[16].call + (null, s, new_start, (stop - start | 0) - 1 | 0), stop + 1 | 0]; } } @@ -13038,7 +12899,7 @@ /*<>*/ b[2] = len; return 0; } - /*<>*/ return caml_call1(Stdlib[1], cst_Buffer_truncate) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Buffer_truncate) /*<>*/ ; } function to_seq(b){ function aux(i, param){ @@ -13071,8 +12932,8 @@ /*<>*/ return aux(_a_, _b_);} /*<>*/ ; /*<>*/ } function add_seq(b, seq){ - /*<>*/ return caml_call2 - (Stdlib_Seq[4], + /*<>*/ return Stdlib_Seq[4].call + (null, function(_a_){ /*<>*/ return add_char(b, _a_);}, seq) /*<>*/ ; } @@ -13309,18 +13170,7 @@ "use strict"; var runtime = globalThis.jsoo_runtime, - caml_maybe_attach_backtrace = runtime.caml_maybe_attach_backtrace; - function caml_call1(f, a0){ - return (f.l >= 0 ? f.l : f.l = f.length) === 1 - ? f(a0) - : runtime.caml_call_gen(f, [a0]); - } - function caml_call2(f, a0, a1){ - return (f.l >= 0 ? f.l : f.l = f.length) === 2 - ? f(a0, a1) - : runtime.caml_call_gen(f, [a0, a1]); - } - var + caml_maybe_attach_backtrace = runtime.caml_maybe_attach_backtrace, global_data = runtime.caml_get_global_data(), Stdlib_Mutex = global_data.Stdlib__Mutex, Stdlib_Condition = global_data.Stdlib__Condition, @@ -13330,41 +13180,41 @@ cst_Semaphore_Counting_release = "Semaphore.Counting.release: overflow"; function make(v){ /*<>*/ if(v < 0) - /*<>*/ caml_call1 - (Stdlib[1], cst_Semaphore_Counting_init_wr); - var _b_ = /*<>*/ caml_call1(Stdlib_Condition[1], 0); + /*<>*/ Stdlib[1].call + (null, cst_Semaphore_Counting_init_wr); + var _b_ = /*<>*/ Stdlib_Condition[1].call(null, 0); /*<>*/ return [0, - caml_call1(Stdlib_Mutex[1], 0), + Stdlib_Mutex[1].call(null, 0), v, _b_] /*<>*/ ; /*<>*/ } function release(s){ - /*<>*/ caml_call1(Stdlib_Mutex[2], s[1]); + /*<>*/ Stdlib_Mutex[2].call(null, s[1]); /*<>*/ if(s[2] < Stdlib[19]){ /*<>*/ s[2] = s[2] + 1 | 0; - /*<>*/ caml_call1(Stdlib_Condition[3], s[3]); - /*<>*/ return caml_call1(Stdlib_Mutex[4], s[1]) /*<>*/ ; + /*<>*/ Stdlib_Condition[3].call(null, s[3]); + /*<>*/ return Stdlib_Mutex[4].call(null, s[1]) /*<>*/ ; } - /*<>*/ caml_call1(Stdlib_Mutex[4], s[1]); + /*<>*/ Stdlib_Mutex[4].call(null, s[1]); /*<>*/ throw caml_maybe_attach_backtrace ([0, Stdlib[11], cst_Semaphore_Counting_release], 1); /*<>*/ } function acquire(s){ - /*<>*/ caml_call1(Stdlib_Mutex[2], s[1]); + /*<>*/ Stdlib_Mutex[2].call(null, s[1]); /*<>*/ for(;;){ if(0 !== s[2]){ /*<>*/ s[2] = s[2] - 1 | 0; - /*<>*/ return caml_call1(Stdlib_Mutex[4], s[1]) /*<>*/ ; + /*<>*/ return Stdlib_Mutex[4].call(null, s[1]) /*<>*/ ; } - /*<>*/ caml_call2(Stdlib_Condition[2], s[3], s[1]); + /*<>*/ Stdlib_Condition[2].call(null, s[3], s[1]); } /*<>*/ } function try_acquire(s){ - /*<>*/ caml_call1(Stdlib_Mutex[2], s[1]); + /*<>*/ Stdlib_Mutex[2].call(null, s[1]); var ret = /*<>*/ 0 === s[2] ? 0 : (s[2] = s[2] - 1 | 0, 1); - /*<>*/ caml_call1(Stdlib_Mutex[4], s[1]); + /*<>*/ Stdlib_Mutex[4].call(null, s[1]); /*<>*/ return ret; /*<>*/ } function get_value(s){ @@ -13374,33 +13224,33 @@ Counting = /*<>*/ [0, make, release, acquire, try_acquire, get_value]; function make$0(b){ var - _a_ = /*<>*/ caml_call1(Stdlib_Condition[1], 0), + _a_ = /*<>*/ Stdlib_Condition[1].call(null, 0), _b_ = /*<>*/ b ? 1 : 0; /*<>*/ return [0, - caml_call1(Stdlib_Mutex[1], 0), + Stdlib_Mutex[1].call(null, 0), _b_, _a_] /*<>*/ ; /*<>*/ } function release$0(s){ - /*<>*/ caml_call1(Stdlib_Mutex[2], s[1]); + /*<>*/ Stdlib_Mutex[2].call(null, s[1]); /*<>*/ s[2] = 1; - /*<>*/ caml_call1(Stdlib_Condition[3], s[3]); - /*<>*/ return caml_call1(Stdlib_Mutex[4], s[1]) /*<>*/ ; + /*<>*/ Stdlib_Condition[3].call(null, s[3]); + /*<>*/ return Stdlib_Mutex[4].call(null, s[1]) /*<>*/ ; } function acquire$0(s){ - /*<>*/ caml_call1(Stdlib_Mutex[2], s[1]); + /*<>*/ Stdlib_Mutex[2].call(null, s[1]); /*<>*/ for(;;){ if(0 !== s[2]){ /*<>*/ s[2] = 0; - /*<>*/ return caml_call1(Stdlib_Mutex[4], s[1]) /*<>*/ ; + /*<>*/ return Stdlib_Mutex[4].call(null, s[1]) /*<>*/ ; } - /*<>*/ caml_call2(Stdlib_Condition[2], s[3], s[1]); + /*<>*/ Stdlib_Condition[2].call(null, s[3], s[1]); } /*<>*/ } function try_acquire$0(s){ - /*<>*/ caml_call1(Stdlib_Mutex[2], s[1]); + /*<>*/ Stdlib_Mutex[2].call(null, s[1]); var ret = /*<>*/ 0 === s[2] ? 0 : (s[2] = 0, 1); - /*<>*/ caml_call1(Stdlib_Mutex[4], s[1]); + /*<>*/ Stdlib_Mutex[4].call(null, s[1]); /*<>*/ return ret; /*<>*/ } var @@ -13430,21 +13280,6 @@ ? f(a0) : runtime.caml_call_gen(f, [a0]); } - function caml_call2(f, a0, a1){ - return (f.l >= 0 ? f.l : f.l = f.length) === 2 - ? f(a0, a1) - : runtime.caml_call_gen(f, [a0, a1]); - } - function caml_call3(f, a0, a1, a2){ - return (f.l >= 0 ? f.l : f.l = f.length) === 3 - ? f(a0, a1, a2) - : runtime.caml_call_gen(f, [a0, a1, a2]); - } - function caml_call5(f, a0, a1, a2, a3, a4){ - return (f.l >= 0 ? f.l : f.l = f.length) === 5 - ? f(a0, a1, a2, a3, a4) - : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4]); - } var dummy = 0, global_data = runtime.caml_get_global_data(), @@ -13465,13 +13300,13 @@ /*<>*/ } /*<>*/ create_dls(0); var - key_counter = /*<>*/ caml_call1(Stdlib_Atomic[1], 0), - parent_keys = /*<>*/ caml_call1(Stdlib_Atomic[1], 0), + key_counter = /*<>*/ Stdlib_Atomic[1].call(null, 0), + parent_keys = /*<>*/ Stdlib_Atomic[1].call(null, 0), _a_ = /*<>*/ [0, "domain.ml", 184, 13]; function new_key(split_from_parent, init_orphan){ var idx = - /*<>*/ caml_call2(Stdlib_Atomic[7], key_counter, 1), + /*<>*/ Stdlib_Atomic[7].call(null, key_counter, 1), k = /*<>*/ [0, idx, init_orphan]; /*<>*/ if(split_from_parent){ var @@ -13479,9 +13314,9 @@ ki = /*<>*/ [0, k, split]; /*<>*/ for(;;){ var - l = /*<>*/ caml_call1(Stdlib_Atomic[3], parent_keys); + l = /*<>*/ Stdlib_Atomic[3].call(null, parent_keys); /*<>*/ if - (! (1 - caml_call3(Stdlib_Atomic[6], parent_keys, l, [0, ki, l]))) + (! (1 - Stdlib_Atomic[6].call(null, parent_keys, l, [0, ki, l]))) break; } } @@ -13501,8 +13336,7 @@ new_sz = s; } var new_st = /*<>*/ caml_array_make(new_sz, none); - /*<>*/ caml_call5 - (Stdlib_Array[9], st, 0, new_st, 0, sz); + /*<>*/ Stdlib_Array[9].call(null, st, 0, new_st, 0, sz); /*<>*/ if (runtime.caml_domain_dls_compare_and_set(st, new_st)) /*<>*/ return new_st; @@ -13542,8 +13376,8 @@ ([0, Assert_failure, _a_], 1); /*<>*/ } function set_initial_keys(l){ - /*<>*/ return caml_call2 - (Stdlib_List[18], + /*<>*/ return Stdlib_List[18].call + (null, function(param){ var v = /*<>*/ param[2], k = param[1]; /*<>*/ return set(k, v) /*<>*/ ; @@ -13562,7 +13396,7 @@ /*<>*/ } var first_domain_spawned = - /*<>*/ caml_call1(Stdlib_Atomic[1], 0), + /*<>*/ Stdlib_Atomic[1].call(null, 0), first_spawn_function = /*<>*/ [0, function(param){ /*<>*/ }], @@ -13570,7 +13404,7 @@ /*<>*/ "first domain already spawned"; function before_first_spawn(f){ /*<>*/ if - (caml_call1(Stdlib_Atomic[3], first_domain_spawned)) + (Stdlib_Atomic[3].call(null, first_domain_spawned)) /*<>*/ throw caml_maybe_attach_backtrace ([0, Stdlib[6], cst_first_domain_already_spawn], 1); var old_f = /*<>*/ first_spawn_function[1]; @@ -13604,9 +13438,9 @@ /*<>*/ Stdlib[104][1] = do_at_exit; function spawn(f){ /*<>*/ if - (1 - caml_call1(Stdlib_Atomic[3], first_domain_spawned)){ - /*<>*/ caml_call2 - (Stdlib_Atomic[4], first_domain_spawned, 1); + (1 - Stdlib_Atomic[3].call(null, first_domain_spawned)){ + /*<>*/ Stdlib_Atomic[4].call + (null, first_domain_spawned, 1); /*<>*/ caml_call1(first_spawn_function[1], 0); /*<>*/ first_spawn_function[1] = function(param){ @@ -13614,10 +13448,10 @@ /*<>*/ }; } var - _a_ = /*<>*/ caml_call1(Stdlib_Atomic[3], parent_keys), + _a_ = /*<>*/ Stdlib_Atomic[3].call(null, parent_keys), pk = - /*<>*/ caml_call2 - (Stdlib_List[20], + /*<>*/ Stdlib_List[20].call + (null, function(param){ var split = /*<>*/ param[2], k = param[1]; /*<>*/ return [0, @@ -13626,9 +13460,9 @@ (split, /*<>*/ get(k))] /*<>*/ ; /*<>*/ }, _a_), - _b_ = /*<>*/ caml_call1(Stdlib_Condition[1], 0), + _b_ = /*<>*/ Stdlib_Condition[1].call(null, 0), term_sync = - /*<>*/ [0, 0, caml_call1(Stdlib_Mutex[1], 0), _b_]; + /*<>*/ [0, 0, Stdlib_Mutex[1].call(null, 0), _b_]; function body(param){ /*<>*/ try{ /*<>*/ create_dls(0); @@ -13654,14 +13488,13 @@ /*<>*/ for(;;){ var match = term_sync[1]; if(match){var res = match[1]; /*<>*/ return res;} - /*<>*/ caml_call2 - (Stdlib_Condition[2], term_sync[3], term_sync[2]); + /*<>*/ Stdlib_Condition[2].call + (null, term_sync[3], term_sync[2]); } /*<>*/ } var match = - /*<>*/ caml_call2 - (Stdlib_Mutex[5], term_sync[2], loop); + /*<>*/ Stdlib_Mutex[5].call(null, term_sync[2], loop); /*<>*/ if(0 === match[0]){ var x = match[1]; /*<>*/ return x; @@ -13855,8 +13688,8 @@ _p_ = [0, cst_camlinternalFormat_ml, 826, 22], _q_ = [0, cst_camlinternalFormat_ml, 831, 30]; function create_char_set(param){ - /*<>*/ return caml_call2 - (Stdlib_Bytes[1], 32, 0) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[1].call + (null, 32, 0) /*<>*/ ; } function add_in_char_set(char_set, c){ var @@ -13869,11 +13702,11 @@ /*<>*/ return /*<>*/ caml_bytes_set (char_set, str_ind, - /*<>*/ caml_call1(Stdlib[29], _a7_)) /*<>*/ ; + /*<>*/ Stdlib[29].call(null, _a7_)) /*<>*/ ; } function freeze_char_set(char_set){ - /*<>*/ return caml_call1 - (Stdlib_Bytes[6], char_set) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[6].call + (null, char_set) /*<>*/ ; } function rev_char_set(char_set){ var @@ -13887,11 +13720,11 @@ /*<>*/ /*<>*/ caml_bytes_set (char_set$0, i, - /*<>*/ caml_call1(Stdlib[29], _a6_)); + /*<>*/ Stdlib[29].call(null, _a6_)); var _a7_ = /*<>*/ i + 1 | 0; if(31 === i) - /*<>*/ return caml_call1 - (Stdlib_Bytes[44], char_set$0) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[44].call + (null, char_set$0) /*<>*/ ; /*<>*/ i = _a7_; } /*<>*/ } @@ -14010,12 +13843,12 @@ /*<>*/ if(len < min_len){ var new_len = - /*<>*/ caml_call2 - (Stdlib_Int[11], len * 2 | 0, min_len), + /*<>*/ Stdlib_Int[11].call + (null, len * 2 | 0, min_len), new_str = /*<>*/ caml_create_bytes(new_len); - /*<>*/ caml_call5 - (Stdlib_Bytes[11], buf[2], 0, new_str, 0, len); + /*<>*/ Stdlib_Bytes[11].call + (null, buf[2], 0, new_str, 0, len); /*<>*/ buf[2] = new_str; } /*<>*/ } @@ -14028,13 +13861,13 @@ var str_len = /*<>*/ caml_ml_string_length(s); /*<>*/ buffer_check_size(buf, str_len); - /*<>*/ caml_call5 - (Stdlib_String[6], s, 0, buf[2], buf[1], str_len); + /*<>*/ Stdlib_String[6].call + (null, s, 0, buf[2], buf[1], str_len); /*<>*/ buf[1] = buf[1] + str_len | 0; /*<>*/ } function buffer_contents(buf){ - /*<>*/ return caml_call3 - (Stdlib_Bytes[8], buf[2], 0, buf[1]) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[8].call + (null, buf[2], 0, buf[1]) /*<>*/ ; } function char_of_iconv(iconv){ /*<>*/ switch(iconv){ @@ -14082,7 +13915,7 @@ /*<>*/ } function bprint_char_set(buf, char_set){ function print_char(buf, i){ - var c = /*<>*/ caml_call1(Stdlib[29], i); + var c = /*<>*/ Stdlib[29].call(null, i); /*<>*/ return 37 === c ? ( /*<>*/ buffer_add_char (buf, 37), @@ -14106,11 +13939,11 @@ function is_alone(c){ var after = - /*<>*/ caml_call1 - (Stdlib_Char[1], c + 1 | 0), + /*<>*/ Stdlib_Char[1].call + (null, c + 1 | 0), before = - /*<>*/ caml_call1 - (Stdlib_Char[1], c - 1 | 0), + /*<>*/ Stdlib_Char[1].call + (null, c - 1 | 0), _a3_ = /*<>*/ is_in_char_set(set, c); /*<>*/ if(_a3_) var @@ -14134,15 +13967,14 @@ /*<>*/ if (! /*<>*/ is_in_char_set - (set, - /*<>*/ caml_call1(Stdlib[29], i))){ + (set, /*<>*/ Stdlib[29].call(null, i))){ var i$0 = /*<>*/ i + 1 | 0; i = i$0; continue; } var switcher = - /*<>*/ caml_call1(Stdlib[29], i) - 45 + /*<>*/ Stdlib[29].call(null, i) - 45 | 0; /*<>*/ if(48 < switcher >>> 0){ if(210 <= switcher){ @@ -14160,7 +13992,7 @@ (! /*<>*/ is_in_char_set (set, - /*<>*/ caml_call1(Stdlib[29], i$1))){ + /*<>*/ Stdlib[29].call(null, i$1))){ /*<>*/ print_char(buf, i$1 - 1 | 0); var i$6 = /*<>*/ i$1 + 1 | 0; i = i$6; @@ -14168,8 +14000,7 @@ } var switcher$0 = - /*<>*/ caml_call1(Stdlib[29], i$1) - - 45 + /*<>*/ Stdlib[29].call(null, i$1) - 45 | 0; /*<>*/ if(48 < switcher$0 >>> 0){ if(210 <= switcher$0){ @@ -14184,8 +14015,8 @@ ! /*<>*/ is_in_char_set (set, - /*<>*/ caml_call1 - (Stdlib[29], i$1 + 1 | 0))){ + /*<>*/ Stdlib[29].call + (null, i$1 + 1 | 0))){ /*<>*/ print_char(buf, i$1 - 1 | 0); var i$5 = /*<>*/ i$1 + 1 | 0; i = i$5; @@ -14195,8 +14026,8 @@ (! /*<>*/ is_in_char_set (set, - /*<>*/ caml_call1 - (Stdlib[29], i$1 + 1 | 0))){ + /*<>*/ Stdlib[29].call + (null, i$1 + 1 | 0))){ /*<>*/ print_char(buf, i$1 - 1 | 0); /*<>*/ print_char(buf, i$1); var i$4 = /*<>*/ i$1 + 2 | 0; @@ -14213,7 +14044,7 @@ (! /*<>*/ is_in_char_set (set, - /*<>*/ caml_call1(Stdlib[29], j$0))) + /*<>*/ Stdlib[29].call(null, j$0))) break; var j$1 = /*<>*/ j$0 + 1 | 0; j$0 = j$1; @@ -14253,8 +14084,8 @@ var width = /*<>*/ pad_opt[1]; /*<>*/ return /*<>*/ buffer_add_string (buf, - /*<>*/ caml_call1 - (Stdlib_Int[12], width)) /*<>*/ ; + /*<>*/ Stdlib_Int[12].call + (null, width)) /*<>*/ ; } function bprint_padding(buf, pad){ /*<>*/ if(typeof pad === "number") @@ -14264,8 +14095,8 @@ /*<>*/ bprint_padty(buf, padty); /*<>*/ return /*<>*/ buffer_add_string (buf, - /*<>*/ caml_call1 - (Stdlib_Int[12], n)) /*<>*/ ; + /*<>*/ Stdlib_Int[12].call + (null, n)) /*<>*/ ; } var padty$0 = /*<>*/ pad[1]; /*<>*/ bprint_padty(buf, padty$0); @@ -14277,8 +14108,8 @@ /*<>*/ buffer_add_char(buf, 46); /*<>*/ return /*<>*/ buffer_add_string (buf, - /*<>*/ caml_call1 - (Stdlib_Int[12], n)) /*<>*/ ; + /*<>*/ Stdlib_Int[12].call + (null, n)) /*<>*/ ; } /*<>*/ if(prec) /*<>*/ return buffer_add_string(buf, cst) /*<>*/ ; @@ -14350,10 +14181,10 @@ var c = /*<>*/ formatting_lit[1], _a3_ = - /*<>*/ caml_call2 - (Stdlib_String[1], 1, c); - /*<>*/ return caml_call2 - (Stdlib[28], cst$7, _a3_); + /*<>*/ Stdlib_String[1].call + (null, 1, c); + /*<>*/ return Stdlib[28].call + (null, cst$7, _a3_); } } function bprint_char_literal(buf, chr){ @@ -15619,8 +15450,9 @@ var fmt$0 = /*<>*/ formatting_gen[1][1], _aW_ = /*<>*/ fmtty_of_fmt(fmt$0); - /*<>*/ return caml_call2 - (CamlinternalFormatBasics[1], _aW_, _aX_) /*<>*/ ; + /*<>*/ return CamlinternalFormatBasics + [1].call + (null, _aW_, _aX_) /*<>*/ ; case 19: var rest$14 = /*<>*/ fmtty[1]; /*<>*/ return [13, @@ -15652,8 +15484,9 @@ var fmtty$5 = ign[2], _aY_ = /*<>*/ fmtty_of_fmt(fmtty$4); - /*<>*/ return caml_call2 - (CamlinternalFormatBasics[1], fmtty$5, _aY_) /*<>*/ ; + /*<>*/ return CamlinternalFormatBasics + [1].call + (null, fmtty$5, _aY_) /*<>*/ ; } /*<>*/ fmtty = fmtty$4; } @@ -16252,12 +16085,13 @@ pad_opt$0 = fmt[1], _aW_ = /*<>*/ [0, - caml_call1(CamlinternalFormatBasics[2], sub_fmtty1)]; + CamlinternalFormatBasics[2].call(null, sub_fmtty1)]; /*<>*/ if ( /*<>*/ caml_notequal ([0, - /*<>*/ caml_call1 - (CamlinternalFormatBasics[2], sub_fmtty$1)], + /*<>*/ CamlinternalFormatBasics + [2].call + (null, sub_fmtty$1)], _aW_)) /*<>*/ throw caml_maybe_attach_backtrace (Type_mismatch, 1); @@ -16265,8 +16099,9 @@ match$29 = /*<>*/ /*<>*/ type_format_gen (fmt_rest$13, - /*<>*/ caml_call1 - (CamlinternalFormatBasics[2], fmtty_rest$10)), + /*<>*/ CamlinternalFormatBasics + [2].call + (null, fmtty_rest$10)), fmtty$13 = /*<>*/ match$29[2], fmt$14 = match$29[1]; /*<>*/ return [0, @@ -16673,24 +16508,26 @@ sub1_fmtty$0 = sub_fmtty[1], _aU_ = /*<>*/ [0, - caml_call1(CamlinternalFormatBasics[2], sub1_fmtty)]; + CamlinternalFormatBasics[2].call(null, sub1_fmtty)]; /*<>*/ if ( /*<>*/ caml_notequal ([0, - /*<>*/ caml_call1 - (CamlinternalFormatBasics[2], sub1_fmtty$0)], + /*<>*/ CamlinternalFormatBasics + [2].call + (null, sub1_fmtty$0)], _aU_)) /*<>*/ throw caml_maybe_attach_backtrace (Type_mismatch, 1); var _aV_ = /*<>*/ [0, - caml_call1(CamlinternalFormatBasics[2], sub2_fmtty$1)]; + CamlinternalFormatBasics[2].call(null, sub2_fmtty$1)]; /*<>*/ if ( /*<>*/ caml_notequal ([0, - /*<>*/ caml_call1 - (CamlinternalFormatBasics[2], sub2_fmtty$2)], + /*<>*/ CamlinternalFormatBasics + [2].call + (null, sub2_fmtty$2)], _aV_)) /*<>*/ throw caml_maybe_attach_backtrace (Type_mismatch, 1); @@ -16708,8 +16545,9 @@ var match$9 = /*<>*/ /*<>*/ type_ignored_format_substituti - ( /*<>*/ caml_call1 - (CamlinternalFormatBasics[2], sub_fmtty_rest$17), + ( /*<>*/ CamlinternalFormatBasics + [2].call + (null, sub_fmtty_rest$17), fmt, fmtty_rest$8), fmt$9 = /*<>*/ match$9[2], @@ -16791,30 +16629,31 @@ var _aU_ = /*<>*/ symm(fmtty); /*<>*/ return /*<>*/ type_format (fmt, - /*<>*/ caml_call1 - (CamlinternalFormatBasics[2], _aU_)) /*<>*/ ; + /*<>*/ CamlinternalFormatBasics + [2].call + (null, _aU_)) /*<>*/ ; } function fix_padding(padty, width, str){ var len = /*<>*/ caml_ml_string_length(str), padty$0 = /*<>*/ 0 <= width ? padty : 0, width$0 = - /*<>*/ caml_call1(Stdlib[18], width); + /*<>*/ Stdlib[18].call(null, width); /*<>*/ if(width$0 <= len) /*<>*/ return str; var _aU_ = /*<>*/ 2 === padty$0 ? 48 : 32, res = - /*<>*/ caml_call2 - (Stdlib_Bytes[1], width$0, _aU_); + /*<>*/ Stdlib_Bytes[1].call + (null, width$0, _aU_); /*<>*/ switch(padty$0){ case 0: - /*<>*/ caml_call5 - (Stdlib_String[6], str, 0, res, 0, len); + /*<>*/ Stdlib_String[6].call + (null, str, 0, res, 0, len); break; case 1: - /*<>*/ caml_call5 - (Stdlib_String[6], str, 0, res, width$0 - len | 0, len); + /*<>*/ Stdlib_String[6].call + (null, str, 0, res, width$0 - len | 0, len); break; default: a: @@ -16832,13 +16671,8 @@ (res, 0, /*<>*/ caml_string_get(str, 0)); - /*<>*/ caml_call5 - (Stdlib_String[6], - str, - 1, - res, - (width$0 - len | 0) + 1 | 0, - len - 1 | 0); + /*<>*/ Stdlib_String[6].call + (null, str, 1, res, (width$0 - len | 0) + 1 | 0, len - 1 | 0); break; } a: @@ -16857,25 +16691,20 @@ (res, 1, /*<>*/ caml_string_get(str, 1)); - /*<>*/ caml_call5 - (Stdlib_String[6], - str, - 2, - res, - (width$0 - len | 0) + 2 | 0, - len - 2 | 0); + /*<>*/ Stdlib_String[6].call + (null, str, 2, res, (width$0 - len | 0) + 2 | 0, len - 2 | 0); break; } - /*<>*/ caml_call5 - (Stdlib_String[6], str, 0, res, width$0 - len | 0, len); + /*<>*/ Stdlib_String[6].call + (null, str, 0, res, width$0 - len | 0, len); } - /*<>*/ return caml_call1 - (Stdlib_Bytes[44], res) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[44].call + (null, res) /*<>*/ ; } function fix_int_precision(prec, str){ var prec$0 = - /*<>*/ caml_call1(Stdlib[18], prec), + /*<>*/ Stdlib[18].call(null, prec), len = /*<>*/ caml_ml_string_length(str), c = /*<>*/ caml_string_get(str, 0); a: @@ -16899,21 +16728,16 @@ break b; var res$1 = - /*<>*/ caml_call2 - (Stdlib_Bytes[1], prec$0 + 2 | 0, 48); + /*<>*/ Stdlib_Bytes[1].call + (null, prec$0 + 2 | 0, 48); /*<>*/ /*<>*/ caml_bytes_set (res$1, 1, /*<>*/ caml_string_get(str, 1)); - /*<>*/ caml_call5 - (Stdlib_String[6], - str, - 2, - res$1, - (prec$0 - len | 0) + 4 | 0, - len - 2 | 0); - /*<>*/ return caml_call1 - (Stdlib_Bytes[44], res$1) /*<>*/ ; + /*<>*/ Stdlib_String[6].call + (null, str, 2, res$1, (prec$0 - len | 0) + 4 | 0, len - 2 | 0); + /*<>*/ return Stdlib_Bytes[44].call + (null, res$1) /*<>*/ ; case 0: case 2: break; case 1: @@ -16927,18 +16751,13 @@ break a; var res$0 = - /*<>*/ caml_call2 - (Stdlib_Bytes[1], prec$0 + 1 | 0, 48); + /*<>*/ Stdlib_Bytes[1].call + (null, prec$0 + 1 | 0, 48); /*<>*/ caml_bytes_set(res$0, 0, c); - /*<>*/ caml_call5 - (Stdlib_String[6], - str, - 1, - res$0, - (prec$0 - len | 0) + 2 | 0, - len - 1 | 0); - /*<>*/ return caml_call1 - (Stdlib_Bytes[44], res$0) /*<>*/ ; + /*<>*/ Stdlib_String[6].call + (null, str, 1, res$0, (prec$0 - len | 0) + 2 | 0, len - 1 | 0); + /*<>*/ return Stdlib_Bytes[44].call + (null, res$0) /*<>*/ ; } /*<>*/ if(71 <= c){ if(5 < c - 97 >>> 0) break a; @@ -16948,12 +16767,12 @@ /*<>*/ if(len < prec$0){ var res = - /*<>*/ caml_call2 - (Stdlib_Bytes[1], prec$0, 48); - /*<>*/ caml_call5 - (Stdlib_String[6], str, 0, res, prec$0 - len | 0, len); - /*<>*/ return caml_call1 - (Stdlib_Bytes[44], res) /*<>*/ ; + /*<>*/ Stdlib_Bytes[1].call + (null, prec$0, 48); + /*<>*/ Stdlib_String[6].call + (null, str, 0, res, prec$0 - len | 0, len); + /*<>*/ return Stdlib_Bytes[44].call + (null, res) /*<>*/ ; } } /*<>*/ return str; @@ -16961,21 +16780,21 @@ function string_to_caml_string(str){ var str$0 = - /*<>*/ caml_call1 - (Stdlib_String[25], str), + /*<>*/ Stdlib_String[25].call + (null, str), l = /*<>*/ caml_ml_string_length(str$0), res = - /*<>*/ caml_call2 - (Stdlib_Bytes[1], l + 2 | 0, 34); + /*<>*/ Stdlib_Bytes[1].call + (null, l + 2 | 0, 34); /*<>*/ caml_blit_string (str$0, 0, res, 1, l); - /*<>*/ return caml_call1 - (Stdlib_Bytes[44], res) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[44].call + (null, res) /*<>*/ ; } function format_of_fconv(fconv, prec){ var prec$0 = - /*<>*/ caml_call1(Stdlib[18], prec), + /*<>*/ Stdlib[18].call(null, prec), symb = /*<>*/ char_of_fconv(_r_, fconv), buf = /*<>*/ buffer_create(16); /*<>*/ buffer_add_char(buf, 37); @@ -16983,8 +16802,7 @@ /*<>*/ buffer_add_char(buf, 46); /*<>*/ /*<>*/ buffer_add_string (buf, - /*<>*/ caml_call1 - (Stdlib_Int[12], prec$0)); + /*<>*/ Stdlib_Int[12].call(null, prec$0)); /*<>*/ buffer_add_char(buf, symb); /*<>*/ return buffer_contents(buf) /*<>*/ ; } @@ -17046,8 +16864,8 @@ i = _aT_; } } - /*<>*/ return caml_call1 - (Stdlib_Bytes[44], buf) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[44].call + (null, buf) /*<>*/ ; } function convert_int(iconv, n){ /*<>*/ switch(iconv){ @@ -17244,16 +17062,17 @@ _aO_ = /*<>*/ _aN_ ? str - : /*<>*/ caml_call2 - (Stdlib[28], str, cst$17); + : /*<>*/ Stdlib + [28].call + (null, str, cst$17); /*<>*/ return caml_special_val(_aO_) /*<>*/ ; } case 6: /*<>*/ return hex(0) /*<>*/ ; case 7: var _aP_ = /*<>*/ hex(0); - /*<>*/ return caml_call1 - (Stdlib_String[26], _aP_) /*<>*/ ; + /*<>*/ return Stdlib_String[26].call + (null, _aP_) /*<>*/ ; case 8: /*<>*/ return /*<>*/ caml_special_val ( /*<>*/ hex(0)) /*<>*/ ; @@ -17289,19 +17108,19 @@ /*<>*/ return function(c){ var str = - /*<>*/ caml_call1 - (Stdlib_Char[2], c), + /*<>*/ Stdlib_Char[2].call + (null, c), l = /*<>*/ caml_ml_string_length(str), res = - /*<>*/ caml_call2 - (Stdlib_Bytes[1], l + 2 | 0, 39); + /*<>*/ Stdlib_Bytes[1].call + (null, l + 2 | 0, 39); /*<>*/ caml_blit_string (str, 0, res, 1, l); var new_acc = /*<>*/ [4, acc, - caml_call1(Stdlib_Bytes[44], res)]; + Stdlib_Bytes[44].call(null, res)]; /*<>*/ return make_printf (k, new_acc, rest$0) /*<>*/ ;} /*<>*/ ; case 2: @@ -17525,8 +17344,9 @@ /*<>*/ return /*<>*/ make_printf (k, acc, - /*<>*/ caml_call2 - (CamlinternalFormatBasics[3], _aM_, rest$13)) /*<>*/ ;} /*<>*/ ; + /*<>*/ CamlinternalFormatBasics + [3].call + (null, _aM_, rest$13)) /*<>*/ ;} /*<>*/ ; case 15: var rest$14 = /*<>*/ fmt[1]; /*<>*/ return function(f, x){ @@ -17807,8 +17627,9 @@ /*<>*/ return /*<>*/ make_from_fmtty (k, acc, - /*<>*/ caml_call2 - (CamlinternalFormatBasics[1], ty, rest$8), + /*<>*/ CamlinternalFormatBasics + [1].call + (null, ty, rest$8), fmt) /*<>*/ ;} /*<>*/ ; case 10: var rest$9 = /*<>*/ fmtty[1]; @@ -18197,8 +18018,9 @@ /*<>*/ return /*<>*/ make_iprintf (k, o, - /*<>*/ caml_call2 - (CamlinternalFormatBasics[3], _aL_, rest$19)) /*<>*/ ;} /*<>*/ ; + /*<>*/ CamlinternalFormatBasics + [3].call + (null, _aL_, rest$19)) /*<>*/ ;} /*<>*/ ; case 15: var rest$20 = /*<>*/ fmt[1], @@ -18409,8 +18231,8 @@ /*<>*/ string_of_formatting_lit (fmting_lit); /*<>*/ output_acc(o, p); - /*<>*/ return caml_call2 - (Stdlib[66], o, s) /*<>*/ ; + /*<>*/ return Stdlib[66].call + (null, o, s) /*<>*/ ; case 1: var match = /*<>*/ acc[2], @@ -18418,15 +18240,15 @@ if(0 === match[0]){ var acc$0 = match[1]; /*<>*/ output_acc(o, p$0); - /*<>*/ caml_call2 - (Stdlib[66], o, cst$18); + /*<>*/ Stdlib[66].call + (null, o, cst$18); /*<>*/ acc = acc$0; } else{ var acc$1 = /*<>*/ match[1]; /*<>*/ output_acc(o, p$0); - /*<>*/ caml_call2 - (Stdlib[66], o, cst$19); + /*<>*/ Stdlib[66].call + (null, o, cst$19); /*<>*/ acc = acc$1; } break; @@ -18437,24 +18259,23 @@ case 7: var p$4 = /*<>*/ acc[1]; /*<>*/ output_acc(o, p$4); - /*<>*/ return caml_call1 - (Stdlib[63], o) /*<>*/ ; + /*<>*/ return Stdlib[63].call(null, o) /*<>*/ ; case 8: var msg = /*<>*/ acc[2], p$5 = acc[1]; /*<>*/ output_acc(o, p$5); - /*<>*/ return caml_call1 - (Stdlib[1], msg) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, msg) /*<>*/ ; case 2: case 4: var s$0 = /*<>*/ acc[2], p$1 = acc[1]; /*<>*/ output_acc(o, p$1); - /*<>*/ return caml_call2 - (Stdlib[66], o, s$0) /*<>*/ ; + /*<>*/ return Stdlib[66].call + (null, o, s$0) /*<>*/ ; default: var c = /*<>*/ acc[2], p$2 = acc[1]; /*<>*/ output_acc(o, p$2); - /*<>*/ return caml_call2 - (Stdlib[65], o, c) /*<>*/ ; + /*<>*/ return Stdlib[65].call + (null, o, c) /*<>*/ ; } } } @@ -18472,8 +18293,8 @@ /*<>*/ string_of_formatting_lit (fmting_lit); /*<>*/ bufput_acc(b, p); - /*<>*/ return caml_call2 - (Stdlib_Buffer[16], b, s) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[16].call + (null, b, s) /*<>*/ ; case 1: var match = /*<>*/ acc[2], @@ -18481,15 +18302,15 @@ if(0 === match[0]){ var acc$0 = match[1]; /*<>*/ bufput_acc(b, p$0); - /*<>*/ caml_call2 - (Stdlib_Buffer[16], b, cst$20); + /*<>*/ Stdlib_Buffer[16].call + (null, b, cst$20); /*<>*/ acc = acc$0; } else{ var acc$1 = /*<>*/ match[1]; /*<>*/ bufput_acc(b, p$0); - /*<>*/ caml_call2 - (Stdlib_Buffer[16], b, cst$21); + /*<>*/ Stdlib_Buffer[16].call + (null, b, cst$21); /*<>*/ acc = acc$1; } break; @@ -18504,19 +18325,19 @@ case 8: var msg = /*<>*/ acc[2], p$4 = acc[1]; /*<>*/ bufput_acc(b, p$4); - /*<>*/ return caml_call1 - (Stdlib[1], msg) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, msg) /*<>*/ ; case 2: case 4: var s$0 = /*<>*/ acc[2], p$1 = acc[1]; /*<>*/ bufput_acc(b, p$1); - /*<>*/ return caml_call2 - (Stdlib_Buffer[16], b, s$0) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[16].call + (null, b, s$0) /*<>*/ ; default: var c = /*<>*/ acc[2], p$2 = acc[1]; /*<>*/ bufput_acc(b, p$2); - /*<>*/ return caml_call2 - (Stdlib_Buffer[12], b, c) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[12].call + (null, b, c) /*<>*/ ; } } } @@ -18534,8 +18355,8 @@ /*<>*/ string_of_formatting_lit (fmting_lit); /*<>*/ strput_acc(b, p); - /*<>*/ return caml_call2 - (Stdlib_Buffer[16], b, s) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[16].call + (null, b, s) /*<>*/ ; case 1: var match = /*<>*/ acc[2], @@ -18543,15 +18364,15 @@ if(0 === match[0]){ var acc$0 = match[1]; /*<>*/ strput_acc(b, p$0); - /*<>*/ caml_call2 - (Stdlib_Buffer[16], b, cst$22); + /*<>*/ Stdlib_Buffer[16].call + (null, b, cst$22); /*<>*/ acc = acc$0; } else{ var acc$1 = /*<>*/ match[1]; /*<>*/ strput_acc(b, p$0); - /*<>*/ caml_call2 - (Stdlib_Buffer[16], b, cst$23); + /*<>*/ Stdlib_Buffer[16].call + (null, b, cst$23); /*<>*/ acc = acc$1; } break; @@ -18559,8 +18380,8 @@ var f = /*<>*/ acc[2], p$3 = acc[1]; /*<>*/ strput_acc(b, p$3); var _aL_ = /*<>*/ caml_call1(f, 0); - /*<>*/ return caml_call2 - (Stdlib_Buffer[16], b, _aL_) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[16].call + (null, b, _aL_) /*<>*/ ; case 7: var acc$2 = /*<>*/ acc[1]; /*<>*/ acc = acc$2; @@ -18568,19 +18389,19 @@ case 8: var msg = /*<>*/ acc[2], p$4 = acc[1]; /*<>*/ strput_acc(b, p$4); - /*<>*/ return caml_call1 - (Stdlib[1], msg) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, msg) /*<>*/ ; case 2: case 4: var s$0 = /*<>*/ acc[2], p$1 = acc[1]; /*<>*/ strput_acc(b, p$1); - /*<>*/ return caml_call2 - (Stdlib_Buffer[16], b, s$0) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[16].call + (null, b, s$0) /*<>*/ ; default: var c = /*<>*/ acc[2], p$2 = acc[1]; /*<>*/ strput_acc(b, p$2); - /*<>*/ return caml_call2 - (Stdlib_Buffer[12], b, c) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[12].call + (null, b, c) /*<>*/ ; } } } @@ -18588,15 +18409,14 @@ var fmt = /*<>*/ param[1], buf = - /*<>*/ caml_call1 - (Stdlib_Buffer[1], 256); + /*<>*/ Stdlib_Buffer[1].call(null, 256); function k(acc){ /*<>*/ strput_acc(buf, acc); var _aL_ = - /*<>*/ caml_call1 - (Stdlib_Buffer[2], buf); - /*<>*/ return caml_call1(Stdlib[2], _aL_); + /*<>*/ Stdlib_Buffer[2].call + (null, buf); + /*<>*/ return Stdlib[2].call(null, _aL_); } /*<>*/ return make_printf(k, 0, fmt) /*<>*/ ; } @@ -18634,8 +18454,8 @@ } var box_name = - /*<>*/ caml_call3 - (Stdlib_String[16], str, wstart, wend - wstart | 0), + /*<>*/ Stdlib_String[16].call + (null, str, wstart, wend - wstart | 0), nstart = /*<>*/ parse_spaces(wend), nend = /*<>*/ nstart; for(;;){ @@ -18657,8 +18477,8 @@ var _aL_ = /*<>*/ /*<>*/ runtime.caml_int_of_string - ( /*<>*/ caml_call3 - (Stdlib_String[16], str, nstart, nend - nstart | 0)), + ( /*<>*/ Stdlib_String[16].call + (null, str, nstart, nend - nstart | 0)), indent = _aL_; } catch(exn$0){ @@ -20056,8 +19876,8 @@ if(17 === switcher$0){ var s = - /*<>*/ caml_call3 - (Stdlib_String[16], + /*<>*/ Stdlib_String[16].call + (null, str, str_ind$0 - 2 | 0, (str_ind_3 - str_ind$0 | 0) + 3 | 0), @@ -20084,8 +19904,8 @@ (Stdlib[8], 1); var s$0 = - /*<>*/ caml_call3 - (Stdlib_String[16], + /*<>*/ Stdlib_String[16].call + (null, str, str_ind$0 - 2 | 0, (str_ind_5 - str_ind$0 | 0) + 3 | 0), @@ -20152,8 +19972,8 @@ (Stdlib[8], 1); var s$1 = - /*<>*/ caml_call3 - (Stdlib_String[16], + /*<>*/ Stdlib_String[16].call + (null, str, str_ind$1 - 2 | 0, (str_ind_3$0 - str_ind$1 | 0) + 3 | 0), @@ -20225,15 +20045,15 @@ (Stdlib[8], 1); var ind = - /*<>*/ caml_call3 - (Stdlib_String[32], str, str_ind + 1 | 0, 62); + /*<>*/ Stdlib_String[32].call + (null, str, str_ind + 1 | 0, 62); /*<>*/ if(end_ind <= ind) /*<>*/ throw caml_maybe_attach_backtrace (Stdlib[8], 1); var sub_str = - /*<>*/ caml_call3 - (Stdlib_String[16], str, str_ind, (ind - str_ind | 0) + 1 | 0), + /*<>*/ Stdlib_String[16].call + (null, str, str_ind, (ind - str_ind | 0) + 1 | 0), fmt_rest$0 = /*<>*/ parse(ind + 1 | 0, end_ind)[1], sub_fmt = @@ -20274,7 +20094,7 @@ for(;;){ /*<>*/ /*<>*/ add_in_char_set (char_set, - /*<>*/ caml_call1(Stdlib[29], i)); + /*<>*/ Stdlib[29].call(null, i)); var _ac_ = /*<>*/ i + 1 | 0; if(c === i) break; i = _ac_; @@ -20514,8 +20334,8 @@ fmt]] : [0, [11, - /*<>*/ caml_call3 - (Stdlib_String[16], str, lit_start, size), + /*<>*/ Stdlib_String[16].call + (null, str, lit_start, size), fmt]] /*<>*/ ; } function search_subformat_end(str_ind$7, end_ind, c){ @@ -20726,8 +20546,8 @@ function incompatible_flag(pct_ind, str_ind, symb, option){ var subfmt = - /*<>*/ caml_call3 - (Stdlib_String[16], str, pct_ind, str_ind - pct_ind | 0); + /*<>*/ Stdlib_String[16].call + (null, str, pct_ind, str_ind - pct_ind | 0); /*<>*/ return caml_call5 (failwith_message(_Y_), str, pct_ind, option, symb, subfmt) /*<>*/ ; } @@ -20819,16 +20639,6 @@ ? f(a0) : runtime.caml_call_gen(f, [a0]); } - function caml_call2(f, a0, a1){ - return (f.l >= 0 ? f.l : f.l = f.length) === 2 - ? f(a0, a1) - : runtime.caml_call_gen(f, [a0, a1]); - } - function caml_call3(f, a0, a1, a2){ - return (f.l >= 0 ? f.l : f.l = f.length) === 3 - ? f(a0, a1, a2) - : runtime.caml_call_gen(f, [a0, a1, a2]); - } var global_data = runtime.caml_get_global_data(), Stdlib_Buffer = global_data.Stdlib__Buffer, @@ -20836,11 +20646,11 @@ Stdlib = global_data.Stdlib; function kfprintf(k, o, param){ var fmt = /*<>*/ param[1]; - /*<>*/ return caml_call3 - (CamlinternalFormat[7], + /*<>*/ return CamlinternalFormat[7].call + (null, function(acc){ - /*<>*/ caml_call2 - (CamlinternalFormat[9], o, acc); + /*<>*/ CamlinternalFormat[9].call + (null, o, acc); /*<>*/ return caml_call1(k, o) /*<>*/ ; }, 0, @@ -20848,11 +20658,11 @@ } function kbprintf(k, b, param){ var fmt = /*<>*/ param[1]; - /*<>*/ return caml_call3 - (CamlinternalFormat[7], + /*<>*/ return CamlinternalFormat[7].call + (null, function(acc){ - /*<>*/ caml_call2 - (CamlinternalFormat[10], b, acc); + /*<>*/ CamlinternalFormat[10].call + (null, b, acc); /*<>*/ return caml_call1(k, b) /*<>*/ ; }, 0, @@ -20860,8 +20670,8 @@ } function ikfprintf(k, oc, param){ var fmt = /*<>*/ param[1]; - /*<>*/ return caml_call3 - (CamlinternalFormat[8], k, oc, fmt) /*<>*/ ; + /*<>*/ return CamlinternalFormat[8].call + (null, k, oc, fmt) /*<>*/ ; } function fprintf(oc, fmt){ /*<>*/ return kfprintf @@ -20888,13 +20698,13 @@ function ksprintf(k, param){ var fmt = /*<>*/ param[1]; function k$0(acc){ - var buf = /*<>*/ caml_call1(Stdlib_Buffer[1], 64); - /*<>*/ caml_call2(CamlinternalFormat[11], buf, acc); + var buf = /*<>*/ Stdlib_Buffer[1].call(null, 64); + /*<>*/ CamlinternalFormat[11].call(null, buf, acc); /*<>*/ return /*<>*/ caml_call1 - (k, /*<>*/ caml_call1(Stdlib_Buffer[2], buf)) /*<>*/ ; + (k, /*<>*/ Stdlib_Buffer[2].call(null, buf)) /*<>*/ ; } - /*<>*/ return caml_call3 - (CamlinternalFormat[7], k$0, 0, fmt) /*<>*/ ; + /*<>*/ return CamlinternalFormat[7].call + (null, k$0, 0, fmt) /*<>*/ ; } function sprintf(fmt){ /*<>*/ return ksprintf @@ -20969,16 +20779,6 @@ ? f(a0, a1, a2, a3) : runtime.caml_call_gen(f, [a0, a1, a2, a3]); } - function caml_call5(f, a0, a1, a2, a3, a4){ - return (f.l >= 0 ? f.l : f.l = f.length) === 5 - ? f(a0, a1, a2, a3, a4) - : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4]); - } - function caml_call6(f, a0, a1, a2, a3, a4, a5){ - return (f.l >= 0 ? f.l : f.l = f.length) === 6 - ? f(a0, a1, a2, a3, a4, a5) - : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4, a5]); - } var global_data = runtime.caml_get_global_data(), cst$7 = "\n", @@ -21033,17 +20833,17 @@ var t = /*<>*/ l[2], h = l[1], - _N_ = /*<>*/ caml_call2(Stdlib[28], prefix, h), + _N_ = /*<>*/ Stdlib[28].call(null, prefix, h), _O_ = - /*<>*/ caml_call3 - (Stdlib_List[26], + /*<>*/ Stdlib_List[26].call + (null, function(x, y){ - var _O_ = /*<>*/ caml_call2(Stdlib[28], sep, y); - /*<>*/ return caml_call2(Stdlib[28], x, _O_); + var _O_ = /*<>*/ Stdlib[28].call(null, sep, y); + /*<>*/ return Stdlib[28].call(null, x, _O_); }, _N_, t); - /*<>*/ return caml_call2(Stdlib[28], _O_, suffix) /*<>*/ ; + /*<>*/ return Stdlib[28].call(null, _O_, suffix) /*<>*/ ; } function help_action(param){ /*<>*/ throw caml_maybe_attach_backtrace([0, Stop, _c_], 1); @@ -21075,14 +20875,15 @@ [0, cst_help$0, [0, help_action], cst_Display_this_list_of_optio$0], 0]; } - var _L_ = /*<>*/ caml_call2(Stdlib[37], add1, add2); - /*<>*/ return caml_call2(Stdlib[37], speclist, _L_); + var _L_ = /*<>*/ Stdlib[37].call(null, add1, add2); + /*<>*/ return Stdlib[37].call(null, speclist, _L_); } function usage_b(buf, speclist, errmsg){ - /*<>*/ caml_call3(Stdlib_Printf[5], buf, _d_, errmsg); + /*<>*/ caml_call1 + (Stdlib_Printf[5].call(null, buf, _d_), errmsg); var _K_ = /*<>*/ add_help(speclist); - /*<>*/ return caml_call2 - (Stdlib_List[18], + /*<>*/ return Stdlib_List[18].call + (null, function(param){ var doc = /*<>*/ param[3], @@ -21092,24 +20893,25 @@ /*<>*/ 0 < caml_ml_string_length(doc) ? 1 : 0; if(! _K_) return _K_; /*<>*/ if(11 !== spec[0]) - /*<>*/ return caml_call4 - (Stdlib_Printf[5], buf, _a_, key, doc); + /*<>*/ return caml_call2 + (Stdlib_Printf[5].call(null, buf, _a_), key, doc); var l = /*<>*/ spec[1], _L_ = /*<>*/ make_symlist(cst$1, cst$0, cst, l); - /*<>*/ return caml_call5 - (Stdlib_Printf[5], buf, _b_, key, _L_, doc); + /*<>*/ return caml_call3 + (Stdlib_Printf[5].call(null, buf, _b_), key, _L_, doc); }, _K_) /*<>*/ ; } function usage_string(speclist, errmsg){ - var b = /*<>*/ caml_call1(Stdlib_Buffer[1], 200); + var b = /*<>*/ Stdlib_Buffer[1].call(null, 200); /*<>*/ usage_b(b, speclist, errmsg); - /*<>*/ return caml_call1(Stdlib_Buffer[2], b) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[2].call(null, b) /*<>*/ ; } function usage(speclist, errmsg){ var _K_ = /*<>*/ usage_string(speclist, errmsg); - /*<>*/ return caml_call2(Stdlib_Printf[3], _e_, _K_); + /*<>*/ return caml_call1 + (Stdlib_Printf[3].call(null, _e_), _K_); } var current = /*<>*/ [0, 0], @@ -21179,7 +20981,7 @@ var initpos = /*<>*/ current[1]; function convert_error(error){ var - b = /*<>*/ caml_call1(Stdlib_Buffer[1], 200), + b = /*<>*/ Stdlib_Buffer[1].call(null, 200), progname = /*<>*/ initpos < argv[1].length - 1 ? /*<>*/ caml_check_bound @@ -21190,34 +20992,34 @@ case 0: var s = error[1]; if(s !== cst_help$4 && s !== cst_help$3) - /*<>*/ caml_call4 - (Stdlib_Printf[5], b, _f_, progname, s); + /*<>*/ caml_call2 + (Stdlib_Printf[5].call(null, b, _f_), progname, s); break; case 1: var expected = /*<>*/ error[3], arg = error[2], opt = error[1]; - /*<>*/ caml_call6 - (Stdlib_Printf[5], b, _i_, progname, arg, opt, expected); + /*<>*/ caml_call4 + (Stdlib_Printf[5].call(null, b, _i_), progname, arg, opt, expected); break; case 2: var s$0 = /*<>*/ error[1]; - /*<>*/ caml_call4 - (Stdlib_Printf[5], b, _j_, progname, s$0); + /*<>*/ caml_call2 + (Stdlib_Printf[5].call(null, b, _j_), progname, s$0); break; default: var s$1 = /*<>*/ error[1]; - /*<>*/ caml_call4 - (Stdlib_Printf[5], b, _k_, progname, s$1); + /*<>*/ caml_call2 + (Stdlib_Printf[5].call(null, b, _k_), progname, s$1); } /*<>*/ usage_b(b, speclist[1], errmsg); /*<>*/ if (! caml_equal(error, _g_) && ! /*<>*/ caml_equal(error, _h_)) - /*<>*/ return [0, Bad, caml_call1(Stdlib_Buffer[2], b)] /*<>*/ ; - /*<>*/ return [0, Help, caml_call1(Stdlib_Buffer[2], b)] /*<>*/ ; + /*<>*/ return [0, Bad, Stdlib_Buffer[2].call(null, b)] /*<>*/ ; + /*<>*/ return [0, Help, Stdlib_Buffer[2].call(null, b)] /*<>*/ ; /*<>*/ } /*<>*/ current[1]++; /*<>*/ for(;;){ @@ -21226,7 +21028,7 @@ var _E_ = current[1], s = /*<>*/ caml_check_bound(argv[1], _E_)[_E_ + 1]; - /*<>*/ if(caml_call2(Stdlib_String[11], cst$3, s)){ + /*<>*/ if(Stdlib_String[11].call(null, cst$3, s)){ /*<>*/ try{ var follow$1 = /*<>*/ 0, @@ -21239,13 +21041,12 @@ if(exn$0 !== Stdlib[8]) throw caml_maybe_attach_backtrace(exn$0, 0); try{ var - i = /*<>*/ caml_call2(Stdlib_String[36], s, 61), + i = /*<>*/ Stdlib_String[36].call(null, s, 61), len = /*<>*/ caml_ml_string_length(s), arg = - /*<>*/ caml_call3 - (Stdlib_String[16], s, i + 1 | 0, len - (i + 1 | 0) | 0), - keyword = - /*<>*/ caml_call3(Stdlib_String[16], s, 0, i), + /*<>*/ Stdlib_String[16].call + (null, s, i + 1 | 0, len - (i + 1 | 0) | 0), + keyword = /*<>*/ Stdlib_String[16].call(null, s, 0, i), follow = /*<>*/ [0, arg], _F_ = assoc3(keyword, speclist[1]), follow$0 = follow, @@ -21299,7 +21100,7 @@ arg = /*<>*/ get_arg$0(0); /*<>*/ try{ var - _I_ = /*<>*/ [0, caml_call1(Stdlib[32], arg)], + _I_ = /*<>*/ [0, Stdlib[32].call(null, arg)], match = _I_; } catch(exn$0){ @@ -21381,15 +21182,15 @@ case 10: var specs = /*<>*/ param[1]; /*<>*/ no_arg$0(0); - /*<>*/ return caml_call2 - (Stdlib_List[18], treat_action$0, specs) /*<>*/ ; + /*<>*/ return Stdlib_List[18].call + (null, treat_action$0, specs) /*<>*/ ; case 11: var f$4 = /*<>*/ param[2], symb = param[1], arg$5 = /*<>*/ get_arg$0(0); /*<>*/ if - (caml_call2(Stdlib_List[37], arg$5, symb)){ + (Stdlib_List[37].call(null, arg$5, symb)){ /*<>*/ caml_call1(f$4, arg$5); /*<>*/ return consume_arg$0(0) /*<>*/ ; } @@ -21400,7 +21201,7 @@ /*<>*/ throw caml_maybe_attach_backtrace ([0, Stop, - [1, s$0, arg$5, caml_call2(Stdlib[28], cst_one_of, _J_)]], + [1, s$0, arg$5, Stdlib[28].call(null, cst_one_of, _J_)]], 1); case 12: var f$5 = /*<>*/ param[1]; @@ -21423,7 +21224,7 @@ if(current[1] >= (argv[1].length - 2 | 0)) /*<>*/ return /*<>*/ caml_call1 (f$6, - /*<>*/ caml_call1(Stdlib_List[10], acc[1])) /*<>*/ ; + /*<>*/ Stdlib_List[10].call(null, acc[1])) /*<>*/ ; var _H_ = /*<>*/ current[1] + 1 | 0, _K_ = /*<>*/ acc[1]; @@ -21442,17 +21243,17 @@ /*<>*/ consume_arg$0(0); var before = - /*<>*/ caml_call3 - (Stdlib_Array[6], argv[1], 0, current[1] + 1 | 0), + /*<>*/ Stdlib_Array[6].call + (null, argv[1], 0, current[1] + 1 | 0), after = - /*<>*/ caml_call3 - (Stdlib_Array[6], + /*<>*/ Stdlib_Array[6].call + (null, argv[1], current[1] + 1 | 0, (argv[1].length - 1 - current[1] | 0) - 1 | 0); /*<>*/ argv[1] = - caml_call1 - (Stdlib_Array[5], [0, before, [0, newarg, [0, after, 0]]]); + Stdlib_Array[5].call + (null, [0, before, [0, newarg, [0, after, 0]]]); /*<>*/ return 0; } /*<>*/ }; @@ -21507,14 +21308,16 @@ var exn = /*<>*/ caml_wrap_exception(exn$0), tag = exn[1]; if(tag === Bad){ var msg$0 = exn[2]; - /*<>*/ caml_call2(Stdlib_Printf[3], _l_, msg$0); - /*<>*/ return caml_call1(Stdlib[99], 2) /*<>*/ ; + /*<>*/ caml_call1 + (Stdlib_Printf[3].call(null, _l_), msg$0); + /*<>*/ return Stdlib[99].call(null, 2) /*<>*/ ; } var tag$0 = /*<>*/ exn[1]; if(tag$0 !== Help) throw caml_maybe_attach_backtrace(exn, 0); var msg$1 = exn[2]; - /*<>*/ caml_call2(Stdlib_Printf[2], _m_, msg$1); - /*<>*/ return caml_call1(Stdlib[99], 0) /*<>*/ ; + /*<>*/ caml_call1 + (Stdlib_Printf[2].call(null, _m_), msg$1); + /*<>*/ return Stdlib[99].call(null, 0) /*<>*/ ; } } function parse_dynamic(l, f, msg){ @@ -21529,14 +21332,16 @@ var exn = /*<>*/ caml_wrap_exception(exn$0), tag = exn[1]; if(tag === Bad){ var msg$0 = exn[2]; - /*<>*/ caml_call2(Stdlib_Printf[3], _n_, msg$0); - /*<>*/ return caml_call1(Stdlib[99], 2) /*<>*/ ; + /*<>*/ caml_call1 + (Stdlib_Printf[3].call(null, _n_), msg$0); + /*<>*/ return Stdlib[99].call(null, 2) /*<>*/ ; } var tag$0 = /*<>*/ exn[1]; if(tag$0 !== Help) throw caml_maybe_attach_backtrace(exn, 0); var msg$1 = exn[2]; - /*<>*/ caml_call2(Stdlib_Printf[2], _o_, msg$1); - /*<>*/ return caml_call1(Stdlib[99], 0) /*<>*/ ; + /*<>*/ caml_call1 + (Stdlib_Printf[2].call(null, _o_), msg$1); + /*<>*/ return Stdlib[99].call(null, 0) /*<>*/ ; } } function parse_expand(l, f, msg){ @@ -21554,14 +21359,16 @@ var exn = /*<>*/ caml_wrap_exception(exn$0), tag = exn[1]; if(tag === Bad){ var msg$0 = exn[2]; - /*<>*/ caml_call2(Stdlib_Printf[3], _p_, msg$0); - /*<>*/ return caml_call1(Stdlib[99], 2) /*<>*/ ; + /*<>*/ caml_call1 + (Stdlib_Printf[3].call(null, _p_), msg$0); + /*<>*/ return Stdlib[99].call(null, 2) /*<>*/ ; } var tag$0 = /*<>*/ exn[1]; if(tag$0 !== Help) throw caml_maybe_attach_backtrace(exn, 0); var msg$1 = exn[2]; - /*<>*/ caml_call2(Stdlib_Printf[2], _q_, msg$1); - /*<>*/ return caml_call1(Stdlib[99], 0) /*<>*/ ; + /*<>*/ caml_call1 + (Stdlib_Printf[2].call(null, _q_), msg$1); + /*<>*/ return Stdlib[99].call(null, 0) /*<>*/ ; } } function second_word(s){ @@ -21577,12 +21384,12 @@ } /*<>*/ } /*<>*/ try{ - var n$0 = /*<>*/ caml_call2(Stdlib_String[36], s, 9); + var n$0 = /*<>*/ Stdlib_String[36].call(null, s, 9); } catch(exn$1){ var exn = /*<>*/ caml_wrap_exception(exn$1); if(exn !== Stdlib[8]) throw caml_maybe_attach_backtrace(exn, 0); - try{var n = /*<>*/ caml_call2(Stdlib_String[36], s, 32);} + try{var n = /*<>*/ Stdlib_String[36].call(null, s, 32);} catch(exn){ var exn$0 = /*<>*/ caml_wrap_exception(exn); if(exn$0 === Stdlib[8]) /*<>*/ return len; @@ -21598,19 +21405,19 @@ spec = param[2], kwd = param[1]; /*<>*/ if(11 === spec[0]) - /*<>*/ return caml_call2 - (Stdlib_Int[11], cur, caml_ml_string_length(kwd)) /*<>*/ ; + /*<>*/ return Stdlib_Int[11].call + (null, cur, caml_ml_string_length(kwd)) /*<>*/ ; var _E_ = /*<>*/ caml_ml_string_length(kwd) + /*<>*/ second_word(doc) | 0; - /*<>*/ return caml_call2(Stdlib_Int[11], cur, _E_) /*<>*/ ; + /*<>*/ return Stdlib_Int[11].call(null, cur, _E_) /*<>*/ ; } function replace_leading_tab(s){ var seen = /*<>*/ [0, 0]; - /*<>*/ return caml_call2 - (Stdlib_String[18], + /*<>*/ return Stdlib_String[18].call + (null, function(c){ /*<>*/ if(9 === c && ! seen[1]){ /*<>*/ seen[1] = 1; @@ -21625,11 +21432,11 @@ limit = /*<>*/ opt ? opt[1] : Stdlib[19], completed = /*<>*/ add_help(speclist), len = - /*<>*/ caml_call3 - (Stdlib_List[26], max_arg_len, 0, completed), - len$0 = /*<>*/ caml_call2(Stdlib_Int[10], len, limit); - /*<>*/ return caml_call2 - (Stdlib_List[20], + /*<>*/ Stdlib_List[26].call + (null, max_arg_len, 0, completed), + len$0 = /*<>*/ Stdlib_Int[10].call(null, len, limit); + /*<>*/ return Stdlib_List[20].call + (null, function(ksd){ var kwd = /*<>*/ ksd[1], spec = ksd[2]; if(ksd[3] === cst$8) /*<>*/ return ksd; @@ -21638,19 +21445,19 @@ msg$0 = ksd[3], cutcol$0 = /*<>*/ second_word(msg$0), _C_ = - /*<>*/ caml_call2 - (Stdlib_Int[11], 0, len$0 - cutcol$0 | 0) + /*<>*/ Stdlib_Int[11].call + (null, 0, len$0 - cutcol$0 | 0) + 3 | 0, spaces$0 = - /*<>*/ caml_call2(Stdlib_String[1], _C_, 32), + /*<>*/ Stdlib_String[1].call(null, _C_, 32), _D_ = /*<>*/ replace_leading_tab(msg$0), _E_ = - /*<>*/ caml_call2(Stdlib[28], spaces$0, _D_); + /*<>*/ Stdlib[28].call(null, spaces$0, _D_); /*<>*/ return [0, kwd, spec, - caml_call2(Stdlib[28], cst$7, _E_)] /*<>*/ ; + Stdlib[28].call(null, cst$7, _E_)] /*<>*/ ; } var msg = /*<>*/ ksd[3], @@ -21665,34 +21472,35 @@ replace_leading_tab(msg)] /*<>*/ ; var spaces = - /*<>*/ caml_call2(Stdlib_String[1], diff, 32), + /*<>*/ Stdlib_String[1].call(null, diff, 32), _A_ = /*<>*/ replace_leading_tab(msg), prefix = - /*<>*/ caml_call3 - (Stdlib_String[16], _A_, 0, cutcol), + /*<>*/ Stdlib_String[16].call + (null, _A_, 0, cutcol), suffix = - /*<>*/ /*<>*/ caml_call3 - (Stdlib_String[16], + /*<>*/ /*<>*/ Stdlib_String + [16].call + (null, msg, cutcol, /*<>*/ caml_ml_string_length(msg) - cutcol | 0), _B_ = - /*<>*/ caml_call2(Stdlib[28], spaces, suffix); + /*<>*/ Stdlib[28].call(null, spaces, suffix); /*<>*/ return [0, kwd, spec$0, - caml_call2(Stdlib[28], prefix, _B_)] /*<>*/ ; + Stdlib[28].call(null, prefix, _B_)] /*<>*/ ; }, completed) /*<>*/ ; } function read_aux(trim, sep, file){ var - ic = /*<>*/ caml_call1(Stdlib[80], file), - buf = /*<>*/ caml_call1(Stdlib_Buffer[1], 200), + ic = /*<>*/ Stdlib[80].call(null, file), + buf = /*<>*/ Stdlib_Buffer[1].call(null, 200), words = /*<>*/ [0, 0]; function stash(param){ - var word = /*<>*/ caml_call1(Stdlib_Buffer[2], buf); + var word = /*<>*/ Stdlib_Buffer[2].call(null, buf); /*<>*/ if(trim) var len = /*<>*/ caml_ml_string_length(word), @@ -21700,32 +21508,33 @@ /*<>*/ 0 < len ? 13 === /*<>*/ caml_string_get(word, len - 1 | 0) - ? /*<>*/ caml_call3 - (Stdlib_String[16], word, 0, len - 1 | 0) + ? /*<>*/ Stdlib_String + [16].call + (null, word, 0, len - 1 | 0) : word : word; else var word$0 = /*<>*/ word; /*<>*/ words[1] = [0, word$0, words[1]]; - /*<>*/ return caml_call1(Stdlib_Buffer[8], buf) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[8].call(null, buf) /*<>*/ ; } /*<>*/ try{ for(;;){ - var c = /*<>*/ caml_call1(Stdlib[82], ic); + var c = /*<>*/ Stdlib[82].call(null, ic); /*<>*/ if(c === sep) /*<>*/ stash(0); else - /*<>*/ caml_call2(Stdlib_Buffer[12], buf, c); + /*<>*/ Stdlib_Buffer[12].call(null, buf, c); } } catch(exn$0){ var exn = /*<>*/ caml_wrap_exception(exn$0); if(exn !== Stdlib[12]) throw caml_maybe_attach_backtrace(exn, 0); - /*<>*/ if(0 < caml_call1(Stdlib_Buffer[7], buf)) + /*<>*/ if(0 < Stdlib_Buffer[7].call(null, buf)) /*<>*/ stash(0); - /*<>*/ caml_call1(Stdlib[93], ic); - var _A_ = /*<>*/ caml_call1(Stdlib_List[10], words[1]); - /*<>*/ return caml_call1(Stdlib_Array[11], _A_); + /*<>*/ Stdlib[93].call(null, ic); + var _A_ = /*<>*/ Stdlib_List[10].call(null, words[1]); + /*<>*/ return Stdlib_Array[11].call(null, _A_); } } var _r_ = /*<>*/ 10, _s_ = 1; @@ -21738,15 +21547,15 @@ /*<>*/ return read_aux(_u_, _t_, _A_); } function write_aux(sep, file, args){ - var oc = /*<>*/ caml_call1(Stdlib[61], file); - /*<>*/ caml_call2 - (Stdlib_Array[12], + var oc = /*<>*/ Stdlib[61].call(null, file); + /*<>*/ Stdlib_Array[12].call + (null, function(s){ - /*<>*/ return caml_call4 - (Stdlib_Printf[1], oc, _v_, s, sep) /*<>*/ ; + /*<>*/ return caml_call2 + (Stdlib_Printf[1].call(null, oc, _v_), s, sep) /*<>*/ ; }, args); - /*<>*/ return caml_call1(Stdlib[76], oc) /*<>*/ ; + /*<>*/ return Stdlib[76].call(null, oc) /*<>*/ ; } var _w_ = /*<>*/ 10; function write_arg(_z_, _A_){return write_aux(_w_, _z_, _A_);} @@ -21808,20 +21617,15 @@ ? f(a0, a1) : runtime.caml_call_gen(f, [a0, a1]); } - function caml_call3(f, a0, a1, a2){ - return (f.l >= 0 ? f.l : f.l = f.length) === 3 - ? f(a0, a1, a2) - : runtime.caml_call_gen(f, [a0, a1, a2]); - } - function caml_call6(f, a0, a1, a2, a3, a4, a5){ - return (f.l >= 0 ? f.l : f.l = f.length) === 6 - ? f(a0, a1, a2, a3, a4, a5) - : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4, a5]); + function caml_call5(f, a0, a1, a2, a3, a4){ + return (f.l >= 0 ? f.l : f.l = f.length) === 5 + ? f(a0, a1, a2, a3, a4) + : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4]); } - function caml_call8(f, a0, a1, a2, a3, a4, a5, a6, a7){ - return (f.l >= 0 ? f.l : f.l = f.length) === 8 - ? f(a0, a1, a2, a3, a4, a5, a6, a7) - : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4, a5, a6, a7]); + function caml_call7(f, a0, a1, a2, a3, a4, a5, a6){ + return (f.l >= 0 ? f.l : f.l = f.length) === 7 + ? f(a0, a1, a2, a3, a4, a5, a6) + : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4, a5, a6]); } var global_data = runtime.caml_get_global_data(), @@ -21852,7 +21656,7 @@ Stdlib = global_data.Stdlib, Stdlib_Buffer = global_data.Stdlib__Buffer, Stdlib_Obj = global_data.Stdlib__Obj, - printers = /*<>*/ caml_call1(Stdlib_Atomic[1], 0), + printers = /*<>*/ Stdlib_Atomic[1].call(null, 0), _a_ = /*<>*/ [0, [3, 0, 0], "%S"], _b_ = [0, [4, 0, 0, 0, 0], "%d"], _c_ = [0, [11, ", ", [2, 0, [2, 0, 0]]], ", %s%s"], @@ -21904,30 +21708,32 @@ cst_Program_not_linked_with_g_ = cst_Program_not_linked_with_g_$0; function field(x, i){ var f = /*<>*/ x[i + 1]; - /*<>*/ if(! caml_call1(Stdlib_Obj[1], f)) - /*<>*/ return caml_call2(Stdlib_Printf[4], _b_, f) /*<>*/ ; - var _O_ = /*<>*/ Stdlib_Obj[15]; - if(caml_obj_tag(f) === _O_) - /*<>*/ return caml_call2(Stdlib_Printf[4], _a_, f) /*<>*/ ; - var _P_ = /*<>*/ Stdlib_Obj[16]; - return caml_obj_tag(f) === _P_ - ? /*<>*/ caml_call1(Stdlib[35], f) + /*<>*/ if(! Stdlib_Obj[1].call(null, f)) + /*<>*/ return caml_call1 + (Stdlib_Printf[4].call(null, _b_), f) /*<>*/ ; + var _R_ = /*<>*/ Stdlib_Obj[15]; + if(caml_obj_tag(f) === _R_) + /*<>*/ return caml_call1 + (Stdlib_Printf[4].call(null, _a_), f) /*<>*/ ; + var _S_ = /*<>*/ Stdlib_Obj[16]; + return caml_obj_tag(f) === _S_ + ? /*<>*/ Stdlib[35].call(null, f) : cst /*<>*/ ; } function other_fields(x, i){ /*<>*/ if(x.length - 1 <= i) /*<>*/ return cst$0; var - _N_ = /*<>*/ other_fields(x, i + 1 | 0), - _O_ = /*<>*/ field(x, i); - /*<>*/ return caml_call3 - (Stdlib_Printf[4], _c_, _O_, _N_) /*<>*/ ; + _Q_ = /*<>*/ other_fields(x, i + 1 | 0), + _R_ = /*<>*/ field(x, i); + /*<>*/ return caml_call2 + (Stdlib_Printf[4].call(null, _c_), _R_, _Q_) /*<>*/ ; } function use_printers(x){ var param = - /*<>*/ /*<>*/ caml_call1 - (Stdlib_Atomic[3], printers); + /*<>*/ /*<>*/ Stdlib_Atomic[3].call + (null, printers); /*<>*/ for(;;){ /*<>*/ if(! param) /*<>*/ return 0; @@ -21935,7 +21741,7 @@ /*<>*/ try{ var val = /*<>*/ caml_call1(hd, x); } - catch(_N_){ /*<>*/ param = tl; continue;} + catch(_Q_){ /*<>*/ param = tl; continue;} /*<>*/ if(val){ var s = val[1]; /*<>*/ return [0, s]; @@ -21950,24 +21756,25 @@ match = /*<>*/ t.length - 1; if(2 < match >>> 0) var - _L_ = /*<>*/ other_fields(t, 2), - _M_ = /*<>*/ field(t, 1), - _K_ = - /*<>*/ caml_call3 - (Stdlib_Printf[4], _d_, _M_, _L_); + _O_ = /*<>*/ other_fields(t, 2), + _P_ = /*<>*/ field(t, 1), + _N_ = + /*<>*/ caml_call2 + (Stdlib_Printf[4].call(null, _d_), _P_, _O_); else /*<>*/ switch(match){ case 2: var - _N_ = /*<>*/ field(t, 1), - _K_ = - /*<>*/ caml_call2(Stdlib_Printf[4], _e_, _N_); + _Q_ = /*<>*/ field(t, 1), + _N_ = + /*<>*/ caml_call1 + (Stdlib_Printf[4].call(null, _e_), _Q_); break; case 0: - var _K_ = /*<>*/ cst$1; break; - default: var _K_ = cst$2; + var _N_ = /*<>*/ cst$1; break; + default: var _N_ = cst$2; } - var match$0 = /*<>*/ [0, constructor, [0, _K_]]; + var match$0 = /*<>*/ [0, constructor, [0, _N_]]; } else var match$0 = /*<>*/ [0, t[1], 0]; @@ -21977,7 +21784,7 @@ /*<>*/ if(! fields_opt) /*<>*/ return constructor$0; var f = /*<>*/ fields_opt[1]; - /*<>*/ return caml_call2(Stdlib[28], constructor$0, f) /*<>*/ ; + /*<>*/ return Stdlib[28].call(null, constructor$0, f) /*<>*/ ; } function to_string_default(x){ /*<>*/ if(x === Stdlib[9]) @@ -21987,9 +21794,8 @@ var tag = /*<>*/ x[1]; if(tag === Stdlib[4]){ var match = x[2], char$ = match[3], line = match[2], file = match[1]; - /*<>*/ return caml_call6 - (Stdlib_Printf[4], - locfmt, + /*<>*/ return caml_call5 + (Stdlib_Printf[4].call(null, locfmt), file, line, char$, @@ -22003,9 +21809,8 @@ char$0 = match$0[3], line$0 = match$0[2], file$0 = match$0[1]; - /*<>*/ return caml_call6 - (Stdlib_Printf[4], - locfmt, + /*<>*/ return caml_call5 + (Stdlib_Printf[4].call(null, locfmt), file$0, line$0, char$0, @@ -22020,9 +21825,8 @@ char$1 = match$1[3], line$1 = match$1[2], file$1 = match$1[1]; - /*<>*/ return caml_call6 - (Stdlib_Printf[4], - locfmt, + /*<>*/ return caml_call5 + (Stdlib_Printf[4].call(null, locfmt), file$1, line$1, char$1, @@ -22038,29 +21842,31 @@ /*<>*/ } function print(fct, arg){ /*<>*/ try{ - var _K_ = /*<>*/ caml_call1(fct, arg); - return _K_; + var _N_ = /*<>*/ caml_call1(fct, arg); + return _N_; } catch(x$0){ var x = /*<>*/ caml_wrap_exception(x$0), - _J_ = /*<>*/ to_string(x); - /*<>*/ caml_call2(Stdlib_Printf[3], _f_, _J_); - /*<>*/ caml_call1(Stdlib[63], Stdlib[40]); + _M_ = /*<>*/ to_string(x); + /*<>*/ caml_call1 + (Stdlib_Printf[3].call(null, _f_), _M_); + /*<>*/ Stdlib[63].call(null, Stdlib[40]); /*<>*/ throw caml_maybe_attach_backtrace(x, 0); } /*<>*/ } function catch$(fct, arg){ /*<>*/ try{ - var _J_ = /*<>*/ caml_call1(fct, arg); - return _J_; + var _M_ = /*<>*/ caml_call1(fct, arg); + return _M_; } catch(x$0){ var x = /*<>*/ caml_wrap_exception(x$0); - /*<>*/ caml_call1(Stdlib[63], Stdlib[39]); - var _I_ = /*<>*/ to_string(x); - /*<>*/ caml_call2(Stdlib_Printf[3], _g_, _I_); - /*<>*/ return caml_call1(Stdlib[99], 2) /*<>*/ ; + /*<>*/ Stdlib[63].call(null, Stdlib[39]); + var _L_ = /*<>*/ to_string(x); + /*<>*/ caml_call1 + (Stdlib_Printf[3].call(null, _g_), _L_); + /*<>*/ return Stdlib[99].call(null, 2) /*<>*/ ; } } function raw_backtrace_entries(bt){ @@ -22076,37 +21882,51 @@ ? 0 === pos ? cst_Raised_at : cst_Re_raised_at : 0 === pos ? cst_Raised_by_primitive_operat : cst_Called_from /*<>*/ ; } - /*<>*/ if(0 === slot[0]){ + /*<>*/ if(0 !== slot[0]){ + /*<>*/ if(slot[1]) + /*<>*/ return 0; + var _L_ = /*<>*/ info(0); + /*<>*/ return [0, + caml_call1(Stdlib_Printf[4].call(null, _k_), _L_)] /*<>*/ ; + } + /*<>*/ if(slot[3] === slot[6]) + var + _C_ = /*<>*/ slot[3], + lines = + /*<>*/ /*<>*/ caml_call1 + (Stdlib_Printf[4].call(null, _h_), _C_); + else var + _J_ = /*<>*/ slot[6], + _K_ = slot[3], lines = - /*<>*/ slot[3] === slot[6] - ? /*<>*/ caml_call2 - (Stdlib_Printf[4], _h_, slot[3]) - : /*<>*/ caml_call3 - (Stdlib_Printf[4], _j_, slot[3], slot[6]), - _C_ = /*<>*/ slot[7], - _D_ = slot[4], - _E_ = slot[8] ? cst_inlined : cst$3, - _F_ = /*<>*/ slot[2], - _G_ = slot[9], - _H_ = info(slot[1]); - /*<>*/ return [0, - caml_call8 - (Stdlib_Printf[4], _i_, _H_, _G_, _F_, _E_, lines, _D_, _C_)] /*<>*/ ; - } - /*<>*/ if(slot[1]) - /*<>*/ return 0; - var _I_ = /*<>*/ info(0); - /*<>*/ return [0, - caml_call2(Stdlib_Printf[4], _k_, _I_)] /*<>*/ ; - /*<>*/ } + /*<>*/ /*<>*/ caml_call2 + (Stdlib_Printf[4].call(null, _j_), _K_, _J_); + var + _D_ = /*<>*/ slot[7], + _E_ = slot[4], + _F_ = slot[8] ? cst_inlined : cst$3, + _G_ = /*<>*/ slot[2], + _H_ = slot[9], + _I_ = info(slot[1]); + /*<>*/ return [0, + caml_call7 + (Stdlib_Printf[4].call(null, _i_), + _I_, + _H_, + _G_, + _F_, + lines, + _E_, + _D_)] /*<>*/ ; + } function print_raw_backtrace(outchan, raw_backtrace){ var backtrace = /*<>*/ convert_raw_backtrace(raw_backtrace); /*<>*/ if(! backtrace) - /*<>*/ return caml_call2 - (Stdlib_Printf[1], outchan, _m_) /*<>*/ ; + /*<>*/ return Stdlib_Printf[1].call + (null, outchan, _m_) /*<>*/ ; var a = /*<>*/ backtrace[1], _A_ = /*<>*/ a.length - 2 | 0, @@ -22120,8 +21940,8 @@ (i, /*<>*/ caml_check_bound(a, i)[i + 1]); /*<>*/ if(match){ var str = match[1]; - /*<>*/ caml_call3 - (Stdlib_Printf[1], outchan, _l_, str); + /*<>*/ caml_call1 + (Stdlib_Printf[1].call(null, outchan, _l_), str); } var _C_ = /*<>*/ i + 1 | 0; if(_A_ === i) break; @@ -22143,7 +21963,7 @@ /*<>*/ return cst_Program_not_linked_with_g_; var a = /*<>*/ backtrace[1], - b = /*<>*/ caml_call1(Stdlib_Buffer[1], 1024), + b = /*<>*/ Stdlib_Buffer[1].call(null, 1024), _y_ = /*<>*/ a.length - 2 | 0, _z_ = 0; if(_y_ >= 0){ @@ -22155,14 +21975,15 @@ (i, /*<>*/ caml_check_bound(a, i)[i + 1]); /*<>*/ if(match){ var str = match[1]; - /*<>*/ caml_call3(Stdlib_Printf[5], b, _n_, str); + /*<>*/ caml_call1 + (Stdlib_Printf[5].call(null, b, _n_), str); } var _A_ = /*<>*/ i + 1 | 0; if(_y_ === i) break; i = _A_; } } - /*<>*/ return caml_call1(Stdlib_Buffer[2], b) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[2].call(null, b) /*<>*/ ; } function backtrace_slot_is_raise(param){ /*<>*/ return 0 === param[0] ? param[1] : param[1] /*<>*/ ; @@ -22224,11 +22045,11 @@ /*<>*/ for(;;){ var old_printers = - /*<>*/ caml_call1(Stdlib_Atomic[3], printers), + /*<>*/ Stdlib_Atomic[3].call(null, printers), new_printers = /*<>*/ [0, fn, old_printers], success = - /*<>*/ caml_call3 - (Stdlib_Atomic[6], printers, old_printers, new_printers), + /*<>*/ Stdlib_Atomic[6].call + (null, printers, old_printers, new_printers), _x_ = /*<>*/ 1 - success; if(! _x_) return _x_; } @@ -22259,17 +22080,18 @@ cst_Fatal_error_exception_s]; function default_uncaught_exception_han(exn, raw_backtrace){ var _w_ = /*<>*/ to_string(exn); - /*<>*/ caml_call2(Stdlib_Printf[3], _o_, _w_); + /*<>*/ caml_call1 + (Stdlib_Printf[3].call(null, _o_), _w_); /*<>*/ print_raw_backtrace(Stdlib[40], raw_backtrace); var status = /*<>*/ runtime.caml_ml_debug_info_status(0); /*<>*/ if(status < 0){ var - _v_ = /*<>*/ caml_call1(Stdlib[18], status), + _v_ = /*<>*/ Stdlib[18].call(null, status), _x_ = /*<>*/ caml_check_bound(errors, _v_)[_v_ + 1]; - /*<>*/ caml_call1(Stdlib[53], _x_); + /*<>*/ Stdlib[53].call(null, _x_); } - /*<>*/ return caml_call1(Stdlib[63], Stdlib[40]) /*<>*/ ; + /*<>*/ return Stdlib[63].call(null, Stdlib[40]) /*<>*/ ; } var uncaught_exception_handler = @@ -22301,7 +22123,7 @@ ? empty_backtrace : /*<>*/ caml_get_exception_raw_backtra(0); /*<>*/ try{ - /*<>*/ caml_call1(Stdlib[103], 0); + /*<>*/ Stdlib[103].call(null, 0); } catch(exn){} /*<>*/ try{ @@ -22317,17 +22139,19 @@ raw_backtrace$0 = /*<>*/ caml_get_exception_raw_backtra(0), _t_ = /*<>*/ to_string(exn$1); - /*<>*/ caml_call2(Stdlib_Printf[3], _p_, _t_); + /*<>*/ caml_call1 + (Stdlib_Printf[3].call(null, _p_), _t_); /*<>*/ print_raw_backtrace (Stdlib[40], raw_backtrace); var _u_ = /*<>*/ to_string(exn$0); - /*<>*/ caml_call2(Stdlib_Printf[3], _q_, _u_); + /*<>*/ caml_call1 + (Stdlib_Printf[3].call(null, _q_), _u_); /*<>*/ print_raw_backtrace (Stdlib[40], raw_backtrace$0); var _r_ = - /*<>*/ /*<>*/ caml_call1 - (Stdlib[63], Stdlib[40]); + /*<>*/ /*<>*/ Stdlib[63].call + (null, Stdlib[40]); } var _s_ = _r_; } @@ -22336,8 +22160,8 @@ if(exn !== Stdlib[9]) throw caml_maybe_attach_backtrace(exn, 0); var _s_ = - /*<>*/ caml_call1 - (Stdlib[53], cst_Fatal_error_out_of_memory_); + /*<>*/ Stdlib[53].call + (null, cst_Fatal_error_out_of_memory_); } return _s_; } @@ -22429,16 +22253,16 @@ "Stdlib.Fun.Finally_raised", runtime.caml_fresh_oo_id(0)], cst_Fun_Finally_raised = "Fun.Finally_raised: "; - /*<>*/ caml_call1 - (Stdlib_Printexc[9], + /*<>*/ Stdlib_Printexc[9].call + (null, function(param){ var tag = /*<>*/ param[1]; if(tag !== Finally_raised) /*<>*/ return 0; var exn = /*<>*/ param[2], - _a_ = /*<>*/ caml_call1(Stdlib_Printexc[1], exn); + _a_ = /*<>*/ Stdlib_Printexc[1].call(null, exn); /*<>*/ return [0, - caml_call2(Stdlib[28], cst_Fun_Finally_raised, _a_)] /*<>*/ ; + Stdlib[28].call(null, cst_Fun_Finally_raised, _a_)] /*<>*/ ; /*<>*/ }); var dummy = 0; function protect(finally$, work){ @@ -22450,7 +22274,7 @@ catch(e$0){ var e = /*<>*/ caml_wrap_exception(e$0), - bt = /*<>*/ caml_call1(Stdlib_Printexc[12], 0), + bt = /*<>*/ Stdlib_Printexc[12].call(null, 0), exn = /*<>*/ [0, Finally_raised, e]; caml_restore_raw_backtrace(exn, bt); throw caml_maybe_attach_backtrace(exn, 0); @@ -22462,7 +22286,7 @@ catch(work_exn$0){ var work_exn = /*<>*/ caml_wrap_exception(work_exn$0), - work_bt = /*<>*/ caml_call1(Stdlib_Printexc[12], 0); + work_bt = /*<>*/ Stdlib_Printexc[12].call(null, 0); /*<>*/ finally_no_exn(0); /*<>*/ caml_restore_raw_backtrace(work_exn, work_bt); throw caml_maybe_attach_backtrace(work_exn, 0); @@ -22504,16 +22328,6 @@ ? f(a0, a1) : runtime.caml_call_gen(f, [a0, a1]); } - function caml_call3(f, a0, a1, a2){ - return (f.l >= 0 ? f.l : f.l = f.length) === 3 - ? f(a0, a1, a2) - : runtime.caml_call_gen(f, [a0, a1, a2]); - } - function caml_call4(f, a0, a1, a2, a3){ - return (f.l >= 0 ? f.l : f.l = f.length) === 4 - ? f(a0, a1, a2, a3) - : runtime.caml_call_gen(f, [a0, a1, a2, a3]); - } var global_data = runtime.caml_get_global_data(), Stdlib_Atomic = global_data.Stdlib__Atomic; @@ -22598,34 +22412,55 @@ function eventlog_resume(param){ /*<>*/ return 0; /*<>*/ } function print_stat(c){ - var st = /*<>*/ runtime.caml_gc_stat(0); - /*<>*/ caml_call3(Stdlib_Printf[1], c, _a_, st[4]); - /*<>*/ caml_call3(Stdlib_Printf[1], c, _b_, st[5]); - /*<>*/ caml_call3(Stdlib_Printf[1], c, _c_, st[14]); - /*<>*/ caml_call3(Stdlib_Printf[1], c, _d_, st[17]); - /*<>*/ caml_call2(Stdlib_Printf[1], c, _e_); var + st = /*<>*/ runtime.caml_gc_stat(0), + _v_ = /*<>*/ st[4]; + caml_call1(Stdlib_Printf[1].call(null, c, _a_), _v_); + var _w_ = /*<>*/ st[5]; + caml_call1(Stdlib_Printf[1].call(null, c, _b_), _w_); + var _x_ = /*<>*/ st[14]; + caml_call1(Stdlib_Printf[1].call(null, c, _c_), _x_); + var _y_ = /*<>*/ st[17]; + caml_call1(Stdlib_Printf[1].call(null, c, _d_), _y_); + /*<>*/ Stdlib_Printf[1].call(null, c, _e_); + var + _z_ = /*<>*/ st[1], l1 = - /*<>*/ /*<>*/ caml_ml_string_length - ( /*<>*/ caml_call2(Stdlib_Printf[4], _f_, st[1])); - /*<>*/ caml_call4(Stdlib_Printf[1], c, _g_, l1, st[1]); - /*<>*/ caml_call4(Stdlib_Printf[1], c, _h_, l1, st[2]); - /*<>*/ caml_call4(Stdlib_Printf[1], c, _i_, l1, st[3]); - /*<>*/ caml_call2(Stdlib_Printf[1], c, _j_); - var + /*<>*/ caml_ml_string_length + ( /*<>*/ caml_call1 + (Stdlib_Printf[4].call(null, _f_), _z_)), + _A_ = /*<>*/ st[1]; + caml_call2(Stdlib_Printf[1].call(null, c, _g_), l1, _A_); + var _B_ = /*<>*/ st[2]; + caml_call2(Stdlib_Printf[1].call(null, c, _h_), l1, _B_); + var _C_ = /*<>*/ st[3]; + caml_call2(Stdlib_Printf[1].call(null, c, _i_), l1, _C_); + /*<>*/ Stdlib_Printf[1].call(null, c, _j_); + var + _D_ = /*<>*/ st[15], l2 = - /*<>*/ /*<>*/ caml_ml_string_length - ( /*<>*/ caml_call2(Stdlib_Printf[4], _k_, st[15])); - /*<>*/ caml_call4(Stdlib_Printf[1], c, _l_, l2, st[15]); - /*<>*/ caml_call4(Stdlib_Printf[1], c, _m_, l2, st[6]); - /*<>*/ caml_call4(Stdlib_Printf[1], c, _n_, l2, st[8]); - /*<>*/ caml_call4(Stdlib_Printf[1], c, _o_, l2, st[10]); - /*<>*/ caml_call4(Stdlib_Printf[1], c, _p_, l2, st[12]); - /*<>*/ caml_call4(Stdlib_Printf[1], c, _q_, l2, st[13]); - /*<>*/ caml_call2(Stdlib_Printf[1], c, _r_); - /*<>*/ caml_call3(Stdlib_Printf[1], c, _s_, st[9]); - /*<>*/ caml_call3(Stdlib_Printf[1], c, _t_, st[11]); - /*<>*/ return caml_call3(Stdlib_Printf[1], c, _u_, st[7]) /*<>*/ ; + /*<>*/ caml_ml_string_length + ( /*<>*/ caml_call1 + (Stdlib_Printf[4].call(null, _k_), _D_)), + _E_ = /*<>*/ st[15]; + caml_call2(Stdlib_Printf[1].call(null, c, _l_), l2, _E_); + var _F_ = /*<>*/ st[6]; + caml_call2(Stdlib_Printf[1].call(null, c, _m_), l2, _F_); + var _G_ = /*<>*/ st[8]; + caml_call2(Stdlib_Printf[1].call(null, c, _n_), l2, _G_); + var _H_ = /*<>*/ st[10]; + caml_call2(Stdlib_Printf[1].call(null, c, _o_), l2, _H_); + var _I_ = /*<>*/ st[12]; + caml_call2(Stdlib_Printf[1].call(null, c, _p_), l2, _I_); + var _J_ = /*<>*/ st[13]; + caml_call2(Stdlib_Printf[1].call(null, c, _q_), l2, _J_); + /*<>*/ Stdlib_Printf[1].call(null, c, _r_); + var _K_ = /*<>*/ st[9]; + caml_call1(Stdlib_Printf[1].call(null, c, _s_), _K_); + var _L_ = /*<>*/ st[11]; + caml_call1(Stdlib_Printf[1].call(null, c, _t_), _L_); + var _M_ = /*<>*/ st[7]; + return caml_call1(Stdlib_Printf[1].call(null, c, _u_), _M_) /*<>*/ ; } function allocated_bytes(param){ var @@ -22636,12 +22471,12 @@ /*<>*/ return (mi + ma - pro) * (Stdlib_Sys[9] / 8 | 0); } function delete_alarm(a){ - /*<>*/ return caml_call2(Stdlib_Atomic[4], a, 0) /*<>*/ ; + /*<>*/ return Stdlib_Atomic[4].call(null, a, 0) /*<>*/ ; } function create_alarm(f){ - var alarm = /*<>*/ caml_call1(Stdlib_Atomic[1], 1); - /*<>*/ caml_call1 - (Stdlib_Domain[6], + var alarm = /*<>*/ Stdlib_Atomic[1].call(null, 1); + /*<>*/ Stdlib_Domain[6].call + (null, function(param){ /*<>*/ return delete_alarm(alarm) /*<>*/ ; }); @@ -22706,21 +22541,6 @@ ? f(a0, a1) : runtime.caml_call_gen(f, [a0, a1]); } - function caml_call3(f, a0, a1, a2){ - return (f.l >= 0 ? f.l : f.l = f.length) === 3 - ? f(a0, a1, a2) - : runtime.caml_call_gen(f, [a0, a1, a2]); - } - function caml_call4(f, a0, a1, a2, a3){ - return (f.l >= 0 ? f.l : f.l = f.length) === 4 - ? f(a0, a1, a2, a3) - : runtime.caml_call_gen(f, [a0, a1, a2, a3]); - } - function caml_call5(f, a0, a1, a2, a3, a4){ - return (f.l >= 0 ? f.l : f.l = f.length) === 5 - ? f(a0, a1, a2, a3, a4) - : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4]); - } var global_data = runtime.caml_get_global_data(), Stdlib = global_data.Stdlib, @@ -22733,10 +22553,10 @@ open_gen = Stdlib[81]; function with_open(openfun, s, f){ var ic = /*<>*/ caml_call1(openfun, s); - /*<>*/ return caml_call2 - (Stdlib_Fun[5], + /*<>*/ return Stdlib_Fun[5].call + (null, function(param){ - /*<>*/ return caml_call1(Stdlib[94], ic) /*<>*/ ; + /*<>*/ return Stdlib[94].call(null, ic) /*<>*/ ; }, function(param){ /*<>*/ return caml_call1(f, ic) /*<>*/ ; @@ -22749,8 +22569,11 @@ /*<>*/ return with_open(Stdlib[79], s, f) /*<>*/ ; } function with_open_gen(flags, perm, s, f){ - /*<>*/ return /*<>*/ with_open - ( /*<>*/ caml_call2(Stdlib[81], flags, perm), + var _c_ = /*<>*/ Stdlib[81]; + /*<>*/ return with_open + (function(_d_){ + /*<>*/ return _c_(flags, perm, _d_); + }, s, f) /*<>*/ ; } @@ -22762,7 +22585,7 @@ close_noerr = Stdlib[94]; function input_char(ic){ /*<>*/ try{ - var c = /*<>*/ caml_call1(Stdlib[82], ic); + var c = /*<>*/ Stdlib[82].call(null, ic); } catch(exn$0){ var exn = /*<>*/ caml_wrap_exception(exn$0); @@ -22773,7 +22596,7 @@ /*<>*/ } function input_byte(ic){ /*<>*/ try{ - var n = /*<>*/ caml_call1(Stdlib[87], ic); + var n = /*<>*/ Stdlib[87].call(null, ic); } catch(exn$0){ var exn = /*<>*/ caml_wrap_exception(exn$0); @@ -22784,7 +22607,7 @@ /*<>*/ } function input_line(ic){ /*<>*/ try{ - var s = /*<>*/ caml_call1(Stdlib[83], ic); + var s = /*<>*/ Stdlib[83].call(null, ic); } catch(exn$0){ var exn = /*<>*/ caml_wrap_exception(exn$0); @@ -22809,12 +22632,12 @@ && ( /*<>*/ caml_ba_dim_1(buf) - len | 0) >= ofs) /*<>*/ return caml_ml_input_bigarray (ic, buf, ofs, len) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_input_bigarray) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_input_bigarray) /*<>*/ ; } function really_input(ic, buf, pos, len){ /*<>*/ try{ - /*<>*/ caml_call4(Stdlib[85], ic, buf, pos, len); + /*<>*/ Stdlib[85].call(null, ic, buf, pos, len); /*<>*/ return _a_; } catch(exn$0){ @@ -22847,12 +22670,12 @@ len = len$0; } } - /*<>*/ return caml_call1 - (Stdlib[1], cst_really_input_bigarray) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_really_input_bigarray) /*<>*/ ; } function really_input_string(ic, len){ /*<>*/ try{ - var s = /*<>*/ caml_call2(Stdlib[86], ic, len); + var s = /*<>*/ Stdlib[86].call(null, ic, len); } catch(exn$0){ var exn = /*<>*/ caml_wrap_exception(exn$0); @@ -22867,8 +22690,8 @@ /*<>*/ if(0 !== len$0){ var r = - /*<>*/ caml_call4 - (Stdlib[84], ic, buf, ofs$0, len$0); + /*<>*/ Stdlib[84].call + (null, ic, buf, ofs$0, len$0); /*<>*/ if(0 !== r){ var len$1 = /*<>*/ len$0 - r | 0, @@ -22898,19 +22721,20 @@ : ofs < Stdlib_Sys[12] ? Stdlib_Sys[12] - : /*<>*/ caml_call1 - (Stdlib[2], cst_In_channel_input_all_chann), + : /*<>*/ Stdlib + [2].call + (null, cst_In_channel_input_all_chann), new_buf = /*<>*/ caml_create_bytes(new_len$1); - /*<>*/ caml_call5 - (Stdlib_Bytes[11], buf, 0, new_buf, 0, ofs); + /*<>*/ Stdlib_Bytes[11].call + (null, buf, 0, new_buf, 0, ofs); /*<>*/ return new_buf; /*<>*/ } function input_all(ic){ var chunk_size = /*<>*/ 65536; /*<>*/ try{ var - _b_ = /*<>*/ caml_call1(Stdlib[91], ic), - _c_ = /*<>*/ caml_call1(Stdlib[92], ic) - _b_ | 0, + _b_ = /*<>*/ Stdlib[91].call(null, ic), + _c_ = /*<>*/ Stdlib[92].call(null, ic) - _b_ | 0, initial_size = _c_; } catch(exn$0){ @@ -22931,15 +22755,15 @@ nread = /*<>*/ read_upto(ic, buf, 0, initial_size$1); /*<>*/ if(nread < initial_size$1) - /*<>*/ return caml_call3 - (Stdlib_Bytes[8], buf, 0, nread) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[8].call + (null, buf, 0, nread) /*<>*/ ; /*<>*/ try{ - var c = /*<>*/ caml_call1(Stdlib[82], ic); + var c = /*<>*/ Stdlib[82].call(null, ic); } catch(exn){ var exn$0 = /*<>*/ caml_wrap_exception(exn); if(exn$0 === Stdlib[12]) - /*<>*/ return caml_call1(Stdlib_Bytes[44], buf) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[44].call(null, buf) /*<>*/ ; /*<>*/ throw caml_maybe_attach_backtrace(exn$0, 0); } var buf$2 = /*<>*/ ensure(buf, nread, 65537); @@ -22955,8 +22779,8 @@ /*<>*/ caml_ml_bytes_length(buf$1) - ofs | 0, r = /*<>*/ read_upto(ic, buf$1, ofs, rem); /*<>*/ if(r < rem) - /*<>*/ return caml_call3 - (Stdlib_Bytes[8], buf$1, 0, ofs + r | 0) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[8].call + (null, buf$1, 0, ofs + r | 0) /*<>*/ ; var ofs$0 = /*<>*/ ofs + rem | 0; buf$0 = buf$1; ofs = ofs$0; @@ -22964,7 +22788,7 @@ /*<>*/ } function input_lines(ic){ /*<>*/ try{ - var line = /*<>*/ caml_call1(Stdlib[83], ic); + var line = /*<>*/ Stdlib[83].call(null, ic); } catch(exn$0){ var exn = /*<>*/ caml_wrap_exception(exn$0); @@ -22977,7 +22801,7 @@ offset = 1; for(;;){ /*<>*/ try{ - var line$0 = /*<>*/ caml_call1(Stdlib[83], ic); + var line$0 = /*<>*/ Stdlib[83].call(null, ic); } catch(exn){ var exn$0 = /*<>*/ caml_wrap_exception(exn); @@ -22994,7 +22818,7 @@ function fold_lines(f, accu$1, ic){ var accu = /*<>*/ accu$1; for(;;){ - try{var line = /*<>*/ caml_call1(Stdlib[83], ic);} + try{var line = /*<>*/ Stdlib[83].call(null, ic);} catch(exn$0){ var exn = /*<>*/ caml_wrap_exception(exn$0); if(exn === Stdlib[12]) /*<>*/ return accu; @@ -23051,11 +22875,6 @@ ? f(a0) : runtime.caml_call_gen(f, [a0]); } - function caml_call2(f, a0, a1){ - return (f.l >= 0 ? f.l : f.l = f.length) === 2 - ? f(a0, a1) - : runtime.caml_call_gen(f, [a0, a1]); - } var global_data = runtime.caml_get_global_data(), Stdlib = global_data.Stdlib, @@ -23067,10 +22886,10 @@ open_gen = Stdlib[62]; function with_open(openfun, s, f){ var oc = /*<>*/ caml_call1(openfun, s); - /*<>*/ return caml_call2 - (Stdlib_Fun[5], + /*<>*/ return Stdlib_Fun[5].call + (null, function(param){ - /*<>*/ return caml_call1(Stdlib[77], oc) /*<>*/ ; + /*<>*/ return Stdlib[77].call(null, oc) /*<>*/ ; }, function(param){ /*<>*/ return caml_call1(f, oc) /*<>*/ ; @@ -23083,8 +22902,11 @@ /*<>*/ return with_open(Stdlib[60], s, f) /*<>*/ ; } function with_open_gen(flags, perm, s, f){ - /*<>*/ return /*<>*/ with_open - ( /*<>*/ caml_call2(Stdlib[62], flags, perm), + var _a_ = /*<>*/ Stdlib[62]; + /*<>*/ return with_open + (function(_b_){ + /*<>*/ return _a_(flags, perm, _b_); + }, s, f) /*<>*/ ; } @@ -23113,8 +22935,8 @@ >= ofs) /*<>*/ return runtime.caml_ml_output_bigarray (oc, buf, ofs, len) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_output_bigarray) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_output_bigarray) /*<>*/ ; } var set_binary_mode = /*<>*/ Stdlib[78], @@ -23177,23 +22999,7 @@ caml_md5_string = runtime.caml_md5_string, caml_ml_bytes_length = runtime.caml_ml_bytes_length, caml_ml_string_length = runtime.caml_ml_string_length, - caml_string_get = runtime.caml_string_get; - function caml_call1(f, a0){ - return (f.l >= 0 ? f.l : f.l = f.length) === 1 - ? f(a0) - : runtime.caml_call_gen(f, [a0]); - } - function caml_call2(f, a0, a1){ - return (f.l >= 0 ? f.l : f.l = f.length) === 2 - ? f(a0, a1) - : runtime.caml_call_gen(f, [a0, a1]); - } - function caml_call4(f, a0, a1, a2, a3){ - return (f.l >= 0 ? f.l : f.l = f.length) === 4 - ? f(a0, a1, a2, a3) - : runtime.caml_call_gen(f, [a0, a1, a2, a3]); - } - var + caml_string_get = runtime.caml_string_get, global_data = runtime.caml_get_global_data(), Stdlib = global_data.Stdlib, Stdlib_In_channel = global_data.Stdlib__In_channel, @@ -23212,7 +23018,7 @@ var _i_ = /*<>*/ 10 <= n ? (97 + n | 0) - 10 | 0 : 48 + n | 0; - return caml_call1(Stdlib_Char[1], _i_) /*<>*/ ; + return Stdlib_Char[1].call(null, _i_) /*<>*/ ; } var len = /*<>*/ caml_ml_string_length(d), @@ -23234,7 +23040,7 @@ i = _i_; } } - /*<>*/ return caml_call1(Stdlib_Bytes[44], result) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[44].call(null, result) /*<>*/ ; } function string_of_hex(s){ function digit(c){ @@ -23245,10 +23051,10 @@ else if(71 > c) /*<>*/ return (c - 65 | 0) + 10 | 0; } else if(9 >= c - 48 >>> 0) /*<>*/ return c - 48 | 0; - /*<>*/ return caml_call1(Stdlib[1], cst_Digest_of_hex) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Digest_of_hex) /*<>*/ ; } - /*<>*/ return caml_call2 - (Stdlib_String[2], + /*<>*/ return Stdlib_String[2].call + (null, caml_ml_string_length(s) / 2 | 0, function(i){ var @@ -23262,14 +23068,14 @@ << 4) + _f_ | 0; - /*<>*/ return caml_call1(Stdlib_Char[1], _g_); + /*<>*/ return Stdlib_Char[1].call(null, _g_); }) /*<>*/ ; } function BLAKE2(X){ var _a_ = /*<>*/ X[1] < 1 ? 1 : 0, _b_ = _a_ || (64 < X[1] ? 1 : 0); if(_b_) - /*<>*/ caml_call1 - (Stdlib[1], cst_Digest_BLAKE2_wrong_hash_s); + /*<>*/ Stdlib[1].call + (null, cst_Digest_BLAKE2_wrong_hash_s); var hash_length = /*<>*/ X[1], compare = Stdlib_String[10], @@ -23291,7 +23097,7 @@ _f_ = len < 0 ? 1 : 0, _e_ = _f_ || ((caml_ml_string_length(str) - len | 0) < ofs ? 1 : 0); if(_e_) - /*<>*/ caml_call1(Stdlib[1], cst_Digest_substring); + /*<>*/ Stdlib[1].call(null, cst_Digest_substring); /*<>*/ return caml_blake2_string (hash_length, cst, str, ofs, len) /*<>*/ ; } @@ -23304,7 +23110,7 @@ _d_ = len < 0 ? 1 : 0, _c_ = _d_ || ((caml_ml_bytes_length(b) - len | 0) < ofs ? 1 : 0); if(_c_) - /*<>*/ caml_call1(Stdlib[1], cst_Digest_subbytes); + /*<>*/ Stdlib[1].call(null, cst_Digest_subbytes); /*<>*/ return caml_blake2_bytes (hash_length, cst, b, ofs, len) /*<>*/ ; } @@ -23321,11 +23127,11 @@ /*<>*/ return caml_blake2_final(ctx, hash_length) /*<>*/ ; var _b_ = - /*<>*/ caml_call2 - (Stdlib_Int[10], buf_size, toread$0), + /*<>*/ Stdlib_Int[10].call + (null, buf_size, toread$0), n = - /*<>*/ caml_call4 - (Stdlib_In_channel[16], ic, buf, 0, _b_); + /*<>*/ Stdlib_In_channel[16].call + (null, ic, buf, 0, _b_); /*<>*/ if(0 === n) /*<>*/ throw caml_maybe_attach_backtrace (Stdlib[12], 1); @@ -23338,37 +23144,36 @@ /*<>*/ for(;;){ var n$0 = - /*<>*/ caml_call4 - (Stdlib_In_channel[16], ic, buf, 0, buf_size); + /*<>*/ Stdlib_In_channel[16].call + (null, ic, buf, 0, buf_size); /*<>*/ if(0 === n$0) /*<>*/ return caml_blake2_final(ctx, hash_length) /*<>*/ ; /*<>*/ caml_blake2_update(ctx, buf, 0, n$0); } /*<>*/ } function file(filename){ - /*<>*/ return caml_call2 - (Stdlib_In_channel[5], + /*<>*/ return Stdlib_In_channel[5].call + (null, filename, function(ic){ /*<>*/ return channel(ic, -1) /*<>*/ ; }) /*<>*/ ; } function output(chan, digest){ - /*<>*/ return caml_call2(Stdlib[66], chan, digest) /*<>*/ ; + /*<>*/ return Stdlib[66].call(null, chan, digest) /*<>*/ ; } function input(chan){ - /*<>*/ return caml_call2 - (Stdlib[86], chan, hash_length) /*<>*/ ; + /*<>*/ return Stdlib[86].call(null, chan, hash_length) /*<>*/ ; } function to_hex(d){ /*<>*/ if(caml_ml_string_length(d) !== hash_length) - /*<>*/ caml_call1(Stdlib[1], cst_Digest_to_hex); + /*<>*/ Stdlib[1].call(null, cst_Digest_to_hex); /*<>*/ return hex_of_string(d) /*<>*/ ; } function of_hex(s){ /*<>*/ if (caml_ml_string_length(s) !== (hash_length * 2 | 0)) - /*<>*/ caml_call1(Stdlib[1], cst_Digest_of_hex$0); + /*<>*/ Stdlib[1].call(null, cst_Digest_of_hex$0); /*<>*/ return string_of_hex(s) /*<>*/ ; } /*<>*/ return [0, @@ -23408,38 +23213,38 @@ /*<>*/ if (0 <= ofs && 0 <= len && (caml_ml_string_length(str) - len | 0) >= ofs) /*<>*/ return caml_md5_string(str, ofs, len) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_Digest_substring$0) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Digest_substring$0) /*<>*/ ; } function subbytes(b, ofs, len){ /*<>*/ if (0 <= ofs && 0 <= len && (caml_ml_bytes_length(b) - len | 0) >= ofs) /*<>*/ return caml_md5_bytes(b, ofs, len) /*<>*/ ; - /*<>*/ return caml_call1 - (Stdlib[1], cst_Digest_subbytes$0) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Digest_subbytes$0) /*<>*/ ; } function file(filename){ - /*<>*/ return caml_call2 - (Stdlib_In_channel[5], + /*<>*/ return Stdlib_In_channel[5].call + (null, filename, function(ic){ /*<>*/ return caml_md5_chan(ic, -1) /*<>*/ ; }) /*<>*/ ; } function output(chan, digest){ - /*<>*/ return caml_call2(Stdlib[66], chan, digest) /*<>*/ ; + /*<>*/ return Stdlib[66].call(null, chan, digest) /*<>*/ ; } function input(chan){ - /*<>*/ return caml_call2(Stdlib[86], chan, 16) /*<>*/ ; + /*<>*/ return Stdlib[86].call(null, chan, 16) /*<>*/ ; } function to_hex(d){ /*<>*/ if(16 !== caml_ml_string_length(d)) - /*<>*/ caml_call1(Stdlib[1], cst_Digest_to_hex$0); + /*<>*/ Stdlib[1].call(null, cst_Digest_to_hex$0); /*<>*/ return hex_of_string(d) /*<>*/ ; } function of_hex(s){ /*<>*/ if(32 !== caml_ml_string_length(s)) - /*<>*/ caml_call1(Stdlib[1], cst_Digest_from_hex); + /*<>*/ Stdlib[1].call(null, cst_Digest_from_hex); /*<>*/ return string_of_hex(s) /*<>*/ ; } var @@ -23649,8 +23454,8 @@ var _U_ = /*<>*/ dims(arr), _V_ = - /*<>*/ caml_call3 - (Stdlib_Array[18], caml_mul, 1, _U_); + /*<>*/ Stdlib_Array[18].call + (null, caml_mul, 1, _U_); /*<>*/ return /*<>*/ caml_mul ( /*<>*/ kind_size_in_bytes ( /*<>*/ caml_ba_kind(arr)), @@ -23824,8 +23629,8 @@ for(;;){ var row = /*<>*/ caml_check_bound(data, i)[i + 1]; /*<>*/ if(row.length - 1 !== dim2) - /*<>*/ caml_call1 - (Stdlib[1], cst_Bigarray_Array2_of_array_n); + /*<>*/ Stdlib[1].call + (null, cst_Bigarray_Array2_of_array_n); var _z_ = /*<>*/ dim2 - 1 | 0, _B_ = 0; if(_z_ >= 0){ var j = _B_; @@ -23971,16 +23776,16 @@ for(;;){ var row = /*<>*/ caml_check_bound(data, i)[i + 1]; /*<>*/ if(row.length - 1 !== dim2) - /*<>*/ caml_call1 - (Stdlib[1], cst_Bigarray_Array3_of_array_n); + /*<>*/ Stdlib[1].call + (null, cst_Bigarray_Array3_of_array_n); var _b_ = /*<>*/ dim2 - 1 | 0, _e_ = 0; if(_b_ >= 0){ var j = _e_; for(;;){ var col = /*<>*/ caml_check_bound(row, j)[j + 1]; /*<>*/ if(col.length - 1 !== dim3) - /*<>*/ caml_call1 - (Stdlib[1], cst_Bigarray_Array3_of_array_n$0); + /*<>*/ Stdlib[1].call + (null, cst_Bigarray_Array3_of_array_n$0); var _c_ = /*<>*/ dim3 - 1 | 0, _g_ = 0; if(_c_ >= 0){ var k = _g_; @@ -24011,26 +23816,30 @@ function array0_of_genarray(a){ /*<>*/ return 0 === caml_ba_num_dims(a) ? a - : /*<>*/ caml_call1 - (Stdlib[1], cst_Bigarray_array0_of_genarra) /*<>*/ ; + : /*<>*/ Stdlib + [1].call + (null, cst_Bigarray_array0_of_genarra) /*<>*/ ; } function array1_of_genarray(a){ /*<>*/ return 1 === caml_ba_num_dims(a) ? a - : /*<>*/ caml_call1 - (Stdlib[1], cst_Bigarray_array1_of_genarra) /*<>*/ ; + : /*<>*/ Stdlib + [1].call + (null, cst_Bigarray_array1_of_genarra) /*<>*/ ; } function array2_of_genarray(a){ /*<>*/ return 2 === caml_ba_num_dims(a) ? a - : /*<>*/ caml_call1 - (Stdlib[1], cst_Bigarray_array2_of_genarra) /*<>*/ ; + : /*<>*/ Stdlib + [1].call + (null, cst_Bigarray_array2_of_genarra) /*<>*/ ; } function array3_of_genarray(a){ /*<>*/ return 3 === caml_ba_num_dims(a) ? a - : /*<>*/ caml_call1 - (Stdlib[1], cst_Bigarray_array3_of_genarra) /*<>*/ ; + : /*<>*/ Stdlib + [1].call + (null, cst_Bigarray_array3_of_genarra) /*<>*/ ; } function reshape_0(a){ /*<>*/ return caml_ba_reshape(a, [0]) /*<>*/ ; @@ -24153,11 +23962,6 @@ ? f(a0, a1, a2) : runtime.caml_call_gen(f, [a0, a1, a2]); } - function caml_call5(f, a0, a1, a2, a3, a4){ - return (f.l >= 0 ? f.l : f.l = f.length) === 5 - ? f(a0, a1, a2, a3, a4) - : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4]); - } var global_data = runtime.caml_get_global_data(), serialization_prefix = "lxm1:", @@ -24199,21 +24003,16 @@ "Random.State.of_binary_string: expected a format compatible with OCaml "; function to_binary_string(s){ var buf = /*<>*/ caml_create_bytes(37); - /*<>*/ caml_call5 - (Stdlib_Bytes[12], - serialization_prefix, - 0, - buf, - 0, - serialization_prefix_len); + /*<>*/ Stdlib_Bytes[12].call + (null, serialization_prefix, 0, buf, 0, serialization_prefix_len); var i = /*<>*/ 0; for(;;){ var _u_ = /*<>*/ runtime.caml_ba_get_1(s, i); - /*<>*/ caml_call3 - (Stdlib_Bytes[86], buf, 5 + (i * 8 | 0) | 0, _u_); + /*<>*/ Stdlib_Bytes[86].call + (null, buf, 5 + (i * 8 | 0) | 0, _u_); var _v_ = /*<>*/ i + 1 | 0; if(3 === i) - /*<>*/ return caml_call1(Stdlib_Bytes[44], buf) /*<>*/ ; + /*<>*/ return Stdlib_Bytes[44].call(null, buf) /*<>*/ ; /*<>*/ i = _v_; } /*<>*/ } @@ -24228,20 +24027,20 @@ || 1 - - /*<>*/ caml_call2 - (Stdlib_String[11], serialization_prefix, buf); + /*<>*/ Stdlib_String[11].call + (null, serialization_prefix, buf); /*<>*/ if(_t_){ var _u_ = - /*<>*/ caml_call2 - (Stdlib[28], cst_Random_State_of_binary_str, Stdlib_Sys[46]); - /*<>*/ caml_call1(Stdlib[2], _u_); + /*<>*/ Stdlib[28].call + (null, cst_Random_State_of_binary_str, Stdlib_Sys[46]); + /*<>*/ Stdlib[2].call(null, _u_); } var - i1 = /*<>*/ caml_call2(Stdlib_String[64], buf, 5), - i2 = /*<>*/ caml_call2(Stdlib_String[64], buf, 13), - i3 = /*<>*/ caml_call2(Stdlib_String[64], buf, 21), - i4 = /*<>*/ caml_call2(Stdlib_String[64], buf, 29); + i1 = /*<>*/ Stdlib_String[64].call(null, buf, 5), + i2 = /*<>*/ Stdlib_String[64].call(null, buf, 13), + i3 = /*<>*/ Stdlib_String[64].call(null, buf, 21), + i4 = /*<>*/ Stdlib_String[64].call(null, buf, 29); /*<>*/ return mk(i1, i2, i3, i4) /*<>*/ ; } function copy(src){ @@ -24262,23 +24061,23 @@ _r_ = /*<>*/ /*<>*/ caml_int64_of_int32 ( /*<>*/ runtime.caml_check_bound(seed, i)[i + 1]); - /*<>*/ caml_call3(Stdlib_Bytes[86], b, i * 8 | 0, _r_); + /*<>*/ Stdlib_Bytes[86].call(null, b, i * 8 | 0, _r_); var _s_ = /*<>*/ i + 1 | 0; if(_m_ === i) break; i = _s_; } } /*<>*/ caml_bytes_set(b, n * 8 | 0, 1); - var d1 = /*<>*/ caml_call1(Stdlib_Digest[4], b); + var d1 = /*<>*/ Stdlib_Digest[4].call(null, b); /*<>*/ caml_bytes_set(b, n * 8 | 0, 2); var - d2 = /*<>*/ caml_call1(Stdlib_Digest[4], b), - _o_ = /*<>*/ caml_call2(Stdlib_String[64], d2, 8), - _p_ = /*<>*/ caml_call2(Stdlib_String[64], d2, 0), - _q_ = /*<>*/ caml_call2(Stdlib_String[64], d1, 8); + d2 = /*<>*/ Stdlib_Digest[4].call(null, b), + _o_ = /*<>*/ Stdlib_String[64].call(null, d2, 8), + _p_ = /*<>*/ Stdlib_String[64].call(null, d2, 0), + _q_ = /*<>*/ Stdlib_String[64].call(null, d1, 8); /*<>*/ return /*<>*/ set (s, - /*<>*/ caml_call2(Stdlib_String[64], d1, 0), + /*<>*/ Stdlib_String[64].call(null, d1, 0), _q_, _p_, _o_) /*<>*/ ; @@ -24320,12 +24119,11 @@ function int$(s, bound){ /*<>*/ if(1073741823 >= bound && 0 < bound) /*<>*/ return int_aux(s, bound, max_int31) /*<>*/ ; - /*<>*/ return caml_call1(Stdlib[1], cst_Random_int) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Random_int) /*<>*/ ; } function full_int(s, bound){ /*<>*/ if(0 >= bound) - /*<>*/ return caml_call1 - (Stdlib[1], cst_Random_full_int) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Random_full_int) /*<>*/ ; var _m_ = /*<>*/ bound <= 1073741823 @@ -24351,7 +24149,7 @@ /*<>*/ } function int_in_range(s, min, max){ /*<>*/ if(max < min) - /*<>*/ caml_call1(Stdlib[1], cst_Random_int_in_range); + /*<>*/ Stdlib[1].call(null, cst_Random_int_in_range); /*<>*/ if(-1073741824 <= min && max <= 1073741823) /*<>*/ return int_in_range_aux (s, min, max, max_int31, 31) /*<>*/ ; @@ -24377,16 +24175,16 @@ /*<>*/ } function int32(s, bound){ /*<>*/ return caml_lessequal(bound, 0) - ? /*<>*/ caml_call1(Stdlib[1], cst_Random_int32) + ? /*<>*/ Stdlib[1].call(null, cst_Random_int32) : /*<>*/ int32aux(s, bound) /*<>*/ ; } function int32_in_range(s, min, max){ /*<>*/ if(caml_greaterthan(min, max)) - /*<>*/ return caml_call1 - (Stdlib[1], cst_Random_int32_in_range) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Random_int32_in_range) /*<>*/ ; var span = - /*<>*/ caml_call1(Stdlib_Int32[6], max - min | 0); + /*<>*/ Stdlib_Int32[6].call(null, max - min | 0); /*<>*/ if(! caml_lessequal(span, Stdlib_Int32[1])) /*<>*/ return min + int32aux(s, span) | 0 /*<>*/ ; /*<>*/ for(;;){ @@ -24425,17 +24223,17 @@ /*<>*/ } function int64(s, bound){ /*<>*/ return caml_lessequal(bound, _g_) - ? /*<>*/ caml_call1(Stdlib[1], cst_Random_int64) + ? /*<>*/ Stdlib[1].call(null, cst_Random_int64) : /*<>*/ int64aux(s, bound) /*<>*/ ; } function int64_in_range(s, min, max){ /*<>*/ if(caml_greaterthan(min, max)) - /*<>*/ return caml_call1 - (Stdlib[1], cst_Random_int64_in_range) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_Random_int64_in_range) /*<>*/ ; var span = - /*<>*/ /*<>*/ caml_call1 - (Stdlib_Int64[6], /*<>*/ caml_int64_sub(max, min)); + /*<>*/ /*<>*/ Stdlib_Int64[6].call + (null, /*<>*/ caml_int64_sub(max, min)); /*<>*/ if(! caml_lessequal(span, Stdlib_Int64[1])) /*<>*/ return /*<>*/ caml_int64_add (min, /*<>*/ int64aux(s, span)) /*<>*/ ; @@ -24693,7 +24491,7 @@ //# unitInfo: Provides: Stdlib__Hashtbl //# unitInfo: Requires: Stdlib, Stdlib__Array, Stdlib__Atomic, Stdlib__Domain, Stdlib__Int, Stdlib__Random, Stdlib__Seq, Stdlib__String, Stdlib__Sys -//# shape: Stdlib__Hashtbl:[F(2),F(1),F(1),F(1),F(3),F(2),F(2),F(2),F(2),F(2),F(3),F(2),F(2),F(3),F(1)*,F(1),F(1),F(2),F(1),F(1)*->F(1),F(1),F(1),F(2),F(2),F(1),F(1)*,F(1)*,F(1)*,F(2)*,F(3)*,F(4)*] +//# shape: Stdlib__Hashtbl:[F(2),F(1),F(1),F(1),F(3),F(2),F(2),F(2),F(2),F(2),F(3),F(2),F(2),F(3),F(1)*,F(1),F(1),F(2),F(1),F(1)*->F(1),F(1)*->F(1),F(1)*->F(1),F(2),F(2),F(1),F(1)*,F(1)*,F(1)*,F(2)*,F(3)*,F(4)*] (function (globalThis){ "use strict"; @@ -24721,11 +24519,6 @@ ? f(a0, a1, a2) : runtime.caml_call_gen(f, [a0, a1, a2]); } - function caml_call4(f, a0, a1, a2, a3){ - return (f.l >= 0 ? f.l : f.l = f.length) === 4 - ? f(a0, a1, a2, a3) - : runtime.caml_call_gen(f, [a0, a1, a2, a3]); - } var global_data = runtime.caml_get_global_data(), _a_ = [0, 0], @@ -24742,9 +24535,9 @@ var Stdlib_String = global_data.Stdlib__String; function ongoing_traversal(h){ var - _E_ = /*<>*/ h.length - 1 < 4 ? 1 : 0, - _F_ = _E_ || (h[4] < 0 ? 1 : 0); - return _F_; + _K_ = /*<>*/ h.length - 1 < 4 ? 1 : 0, + _L_ = _K_ || (h[4] < 0 ? 1 : 0); + return _L_; /*<>*/ } function flip_ongoing_traversal(h){ /*<>*/ h[4] = - h[4] | 0; @@ -24774,16 +24567,16 @@ } var randomized_default = - /*<>*/ caml_call2(Stdlib_String[15], params, 82), + /*<>*/ Stdlib_String[15].call(null, params, 82), randomized = - /*<>*/ caml_call1 - (Stdlib_Atomic[1], randomized_default); + /*<>*/ Stdlib_Atomic[1].call + (null, randomized_default); function randomize(param){ - /*<>*/ return caml_call2 - (Stdlib_Atomic[4], randomized, 1) /*<>*/ ; + /*<>*/ return Stdlib_Atomic[4].call + (null, randomized, 1) /*<>*/ ; } function is_randomized(param){ - /*<>*/ return caml_call1(Stdlib_Atomic[3], randomized) /*<>*/ ; + /*<>*/ return Stdlib_Atomic[3].call(null, randomized) /*<>*/ ; } var prng_key = @@ -24804,38 +24597,38 @@ random = /*<>*/ opt ? opt[1] - : /*<>*/ caml_call1(Stdlib_Atomic[3], randomized), + : /*<>*/ Stdlib_Atomic[3].call(null, randomized), s = /*<>*/ power_2_above(16, initial_size); /*<>*/ if(random) var - _E_ = + _K_ = /*<>*/ caml_call1(Stdlib_Domain[11][2], prng_key), seed = /*<>*/ /*<>*/ caml_call1 - (Stdlib_Random[19][4], _E_); + (Stdlib_Random[19][4], _K_); else var seed = /*<>*/ 0; /*<>*/ return [0, 0, caml_array_make(s, 0), seed, s] /*<>*/ ; /*<>*/ } function clear(h){ - var _E_ = /*<>*/ 0 < h[1] ? 1 : 0; - return _E_ + var _K_ = /*<>*/ 0 < h[1] ? 1 : 0; + return _K_ ? (h [1] = 0, - /*<>*/ caml_call4 - (Stdlib_Array[8], h[2], 0, h[2].length - 1, 0)) - : _E_ /*<>*/ ; + /*<>*/ Stdlib_Array[8].call + (null, h[2], 0, h[2].length - 1, 0)) + : _K_ /*<>*/ ; } function reset(h){ var len = /*<>*/ h[2].length - 1; /*<>*/ if (4 <= h.length - 1 - && len !== /*<>*/ caml_call1(Stdlib[18], h[4])){ + && len !== /*<>*/ Stdlib[18].call(null, h[4])){ /*<>*/ h[1] = 0; /*<>*/ h[2] = /*<>*/ caml_array_make - ( /*<>*/ caml_call1(Stdlib[18], h[4]), 0); + ( /*<>*/ Stdlib[18].call(null, h[4]), 0); /*<>*/ return 0; } /*<>*/ return clear(h) /*<>*/ ; @@ -24864,10 +24657,10 @@ /*<>*/ } function copy(h){ var - _C_ = /*<>*/ h[4], - _D_ = h[3], - _E_ = caml_call2(Stdlib_Array[14], copy_bucketlist, h[2]); - /*<>*/ return [0, h[1], _E_, _D_, _C_]; + _I_ = /*<>*/ h[4], + _J_ = h[3], + _K_ = Stdlib_Array[14].call(null, copy_bucketlist, h[2]); + /*<>*/ return [0, h[1], _K_, _J_, _I_]; /*<>*/ } function length(h){ /*<>*/ return h[1]; @@ -24876,10 +24669,10 @@ var nsize = /*<>*/ ndata.length - 1, ndata_tail = /*<>*/ caml_array_make(nsize, 0), - _w_ = /*<>*/ odata.length - 2 | 0, - _z_ = 0; - if(_w_ >= 0){ - var i$0 = _z_; + _C_ = /*<>*/ odata.length - 2 | 0, + _F_ = 0; + if(_C_ >= 0){ + var i$0 = _F_; for(;;){ var cell$1 = @@ -24904,39 +24697,39 @@ = cell$0; /*<>*/ cell = next; } - var _C_ = /*<>*/ i$0 + 1 | 0; - if(_w_ === i$0) break; - i$0 = _C_; + var _I_ = /*<>*/ i$0 + 1 | 0; + if(_C_ === i$0) break; + i$0 = _I_; } } /*<>*/ if(inplace){ - var _x_ = /*<>*/ nsize - 1 | 0, _A_ = 0; - if(_x_ >= 0){ - var i = _A_; + var _D_ = /*<>*/ nsize - 1 | 0, _G_ = 0; + if(_D_ >= 0){ + var i = _G_; for(;;){ var match$0 = /*<>*/ caml_check_bound(ndata_tail, i)[i + 1]; /*<>*/ if(match$0) /*<>*/ match$0[3] = 0; - var _B_ = /*<>*/ i + 1 | 0; - if(_x_ === i) break; - i = _B_; + var _H_ = /*<>*/ i + 1 | 0; + if(_D_ === i) break; + i = _H_; } } - var _y_ = /*<>*/ 0; + var _E_ = /*<>*/ 0; } else - var _y_ = /*<>*/ inplace; - return _y_; + var _E_ = /*<>*/ inplace; + return _E_; /*<>*/ } function resize(indexfun, h){ var odata = /*<>*/ h[2], osize = /*<>*/ odata.length - 1, nsize = /*<>*/ osize * 2 | 0, - _w_ = /*<>*/ nsize < Stdlib_Sys[13] ? 1 : 0; - if(! _w_) return _w_; + _C_ = /*<>*/ nsize < Stdlib_Sys[13] ? 1 : 0; + if(! _C_) return _C_; var ndata = /*<>*/ caml_array_make(nsize, 0), inplace = /*<>*/ 1 - ongoing_traversal(h); @@ -24952,9 +24745,9 @@ /*<>*/ if(1 - old_trav) /*<>*/ flip_ongoing_traversal(h); /*<>*/ try{ - var d = h[2], _s_ = /*<>*/ d.length - 2 | 0, _u_ = 0; - if(_s_ >= 0){ - var i = _u_; + var d = h[2], _y_ = /*<>*/ d.length - 2 | 0, _A_ = 0; + if(_y_ >= 0){ + var i = _A_; for(;;){ var param = @@ -24967,15 +24760,15 @@ /*<>*/ caml_call2(f, key, data); /*<>*/ param = next; } - var _w_ = /*<>*/ i + 1 | 0; - if(_s_ === i) break; - i = _w_; + var _C_ = /*<>*/ i + 1 | 0; + if(_y_ === i) break; + i = _C_; } } var - _t_ = /*<>*/ 1 - old_trav, - _v_ = _t_ ? /*<>*/ flip_ongoing_traversal(h) : _t_; - return _v_; + _z_ = /*<>*/ 1 - old_trav, + _B_ = _z_ ? /*<>*/ flip_ongoing_traversal(h) : _z_; + return _B_; } catch(exn$0){ var exn = /*<>*/ caml_wrap_exception(exn$0); @@ -24992,9 +24785,9 @@ /*<>*/ if(1 - old_trav) /*<>*/ flip_ongoing_traversal(h); /*<>*/ try{ - var _o_ = d.length - 2 | 0, _q_ = 0; - if(_o_ >= 0){ - var i = _q_; + var _u_ = d.length - 2 | 0, _w_ = 0; + if(_u_ >= 0){ + var i = _w_; for(;;){ var slot$0 = /*<>*/ caml_check_bound(h[2], i)[i + 1], @@ -25026,15 +24819,15 @@ /*<>*/ prec[3] = 0; else /*<>*/ caml_check_bound(h[2], i)[i + 1] = 0; - var _s_ = /*<>*/ i + 1 | 0; - if(_o_ === i) break; - i = _s_; + var _y_ = /*<>*/ i + 1 | 0; + if(_u_ === i) break; + i = _y_; } } var - _p_ = /*<>*/ 1 - old_trav, - _r_ = _p_ ? /*<>*/ flip_ongoing_traversal(h) : _p_; - return _r_; + _v_ = /*<>*/ 1 - old_trav, + _x_ = _v_ ? /*<>*/ flip_ongoing_traversal(h) : _v_; + return _x_; } catch(exn$0){ var exn = /*<>*/ caml_wrap_exception(exn$0); @@ -25052,10 +24845,10 @@ var d = h[2], accu$1 = /*<>*/ [0, init], - _l_ = /*<>*/ d.length - 2 | 0, - _m_ = 0; - if(_l_ >= 0){ - var i = _m_; + _r_ = /*<>*/ d.length - 2 | 0, + _s_ = 0; + if(_r_ >= 0){ + var i = _s_; for(;;){ var accu$2 = /*<>*/ accu$1[1], @@ -25073,15 +24866,15 @@ accu = accu$0; } /*<>*/ accu$1[1] = accu; - var _o_ = i + 1 | 0; - if(_l_ === i) break; - i = _o_; + var _u_ = i + 1 | 0; + if(_r_ === i) break; + i = _u_; } } /*<>*/ if(1 - old_trav) /*<>*/ flip_ongoing_traversal(h); - var _n_ = /*<>*/ accu$1[1]; - return _n_; + var _t_ = /*<>*/ accu$1[1]; + return _t_; } catch(exn$0){ var exn = /*<>*/ caml_wrap_exception(exn$0); @@ -25105,17 +24898,17 @@ function stats(h){ var mbl = - /*<>*/ caml_call3 - (Stdlib_Array[18], + /*<>*/ Stdlib_Array[18].call + (null, function(m, b){ - var _l_ = /*<>*/ bucket_length(0, b); - /*<>*/ return caml_call2(Stdlib_Int[11], m, _l_); + var _r_ = /*<>*/ bucket_length(0, b); + /*<>*/ return Stdlib_Int[11].call(null, m, _r_); }, 0, h[2]), histo = /*<>*/ caml_array_make(mbl + 1 | 0, 0); - /*<>*/ caml_call2 - (Stdlib_Array[12], + /*<>*/ Stdlib_Array[12].call + (null, function(b){ var l = /*<>*/ bucket_length(0, b); /*<>*/ histo[l + 1] = @@ -25134,8 +24927,8 @@ var key = buck[1], data = buck[2], next = buck[3]; /*<>*/ return [0, [0, key, data], - function(_l_){ - /*<>*/ return aux(i, next, _l_); + function(_r_){ + /*<>*/ return aux(i, next, _r_); }] /*<>*/ ; } /*<>*/ if(i === tbl_data.length - 1) @@ -25148,19 +24941,23 @@ buck = buck$0; } /*<>*/ } - var _j_ = /*<>*/ 0, _k_ = 0; - return function(_l_){ - /*<>*/ return aux(_k_, _j_, _l_);} /*<>*/ ; + var _p_ = /*<>*/ 0, _q_ = 0; + return function(_r_){ + /*<>*/ return aux(_q_, _p_, _r_);} /*<>*/ ; /*<>*/ } function to_seq_keys(m){ - var _j_ = /*<>*/ to_seq(m); - /*<>*/ return caml_call2 - (Stdlib_Seq[29], function(_j_){ /*<>*/ return _j_[1];}, _j_) /*<>*/ ; + var _m_ = /*<>*/ to_seq(m); + function _n_(_p_){ /*<>*/ return _p_[1];} + var _o_ = /*<>*/ Stdlib_Seq[29]; + return function(_p_){ + /*<>*/ return _o_(_n_, _m_, _p_);} /*<>*/ ; } function to_seq_values(m){ var _j_ = /*<>*/ to_seq(m); - /*<>*/ return caml_call2 - (Stdlib_Seq[29], function(_j_){ /*<>*/ return _j_[2];}, _j_) /*<>*/ ; + function _k_(_m_){ /*<>*/ return _m_[2];} + var _l_ = /*<>*/ Stdlib_Seq[29]; + return function(_m_){ + /*<>*/ return _l_(_k_, _j_, _m_);} /*<>*/ ; } function MakeSeeded(H){ function key_index(h, key){ @@ -25383,8 +25180,8 @@ } /*<>*/ } function add_seq(tbl, i){ - /*<>*/ return caml_call2 - (Stdlib_Seq[4], + /*<>*/ return Stdlib_Seq[4].call + (null, function(param){ var v = /*<>*/ param[2], k = param[1]; /*<>*/ return add(tbl, k, v) /*<>*/ ; @@ -25392,8 +25189,8 @@ i) /*<>*/ ; } function replace_seq(tbl, i){ - /*<>*/ return caml_call2 - (Stdlib_Seq[4], + /*<>*/ return Stdlib_Seq[4].call + (null, function(param){ var v = /*<>*/ param[2], k = param[1]; /*<>*/ return replace(tbl, k, v) /*<>*/ ; @@ -25503,8 +25300,9 @@ ? /*<>*/ caml_hash (10, 100, h[3], key) & (h[2].length - 2 | 0) - : /*<>*/ caml_call1 - (Stdlib[1], cst_Hashtbl_unsupported_hash_t) /*<>*/ ; + : /*<>*/ Stdlib + [1].call + (null, cst_Hashtbl_unsupported_hash_t) /*<>*/ ; } function add(h, key, data){ var @@ -25719,8 +25517,8 @@ } /*<>*/ } function add_seq(tbl, i){ - /*<>*/ return caml_call2 - (Stdlib_Seq[4], + /*<>*/ return Stdlib_Seq[4].call + (null, function(param){ var v = /*<>*/ param[2], k = param[1]; /*<>*/ return add(tbl, k, v) /*<>*/ ; @@ -25728,8 +25526,8 @@ i) /*<>*/ ; } function replace_seq(tbl, i){ - /*<>*/ return caml_call2 - (Stdlib_Seq[4], + /*<>*/ return Stdlib_Seq[4].call + (null, function(param){ var v = /*<>*/ param[2], k = param[1]; /*<>*/ return replace(tbl, k, v) /*<>*/ ; @@ -25746,7 +25544,7 @@ random = /*<>*/ opt ? opt[1] - : /*<>*/ caml_call1(Stdlib_Atomic[3], randomized), + : /*<>*/ Stdlib_Atomic[3].call(null, randomized), s = /*<>*/ power_2_above(16, h[2].length - 1); /*<>*/ if(random) var @@ -25839,11 +25637,6 @@ ? f(a0, a1, a2, a3) : runtime.caml_call_gen(f, [a0, a1, a2, a3]); } - function caml_call5(f, a0, a1, a2, a3, a4){ - return (f.l >= 0 ? f.l : f.l = f.length) === 5 - ? f(a0, a1, a2, a3, a4) - : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4]); - } var global_data = runtime.caml_get_global_data(), Stdlib = global_data.Stdlib, @@ -25863,7 +25656,7 @@ var _A_ = /*<>*/ 0 <= l ? 1 : 0, _B_ = _A_ ? l <= Stdlib_Obj[23][15] ? 1 : 0 : _A_; - if(1 - _B_) /*<>*/ caml_call1(Stdlib[1], cst_Weak_create); + if(1 - _B_) /*<>*/ Stdlib[1].call(null, cst_Weak_create); /*<>*/ return runtime.caml_weak_create(l) /*<>*/ ; } function length(x){ @@ -25874,7 +25667,7 @@ _y_ = /*<>*/ 0 <= o ? 1 : 0, _A_ = _y_ ? o < /*<>*/ length(e) ? 1 : 0 : _y_, _z_ = /*<>*/ 1 - _A_; - return _z_ ? /*<>*/ caml_call1(Stdlib[1], msg) : _z_ /*<>*/ ; + return _z_ ? /*<>*/ Stdlib[1].call(null, msg) : _z_ /*<>*/ ; } function set(e, o, x){ /*<>*/ raise_if_invalid_offset(e, o, cst_Weak_set); @@ -25912,7 +25705,7 @@ : _x_; /*<>*/ return _y_; } - /*<>*/ return caml_call1(Stdlib[1], cst_Weak_blit) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, cst_Weak_blit) /*<>*/ ; } function fill(ar, ofs, len, x){ /*<>*/ if @@ -25969,8 +25762,8 @@ /*<>*/ } function fold(f, t, init){ var i = /*<>*/ 0; - /*<>*/ return caml_call3 - (Stdlib_Array[20], + /*<>*/ return Stdlib_Array[20].call + (null, function(b, accu$1){ var i$0 = /*<>*/ i, accu = accu$1; for(;;){ @@ -25994,8 +25787,8 @@ } function iter(f, t){ var i = /*<>*/ 0; - /*<>*/ return caml_call2 - (Stdlib_Array[12], + /*<>*/ return Stdlib_Array[12].call + (null, function(b){ var i$0 = /*<>*/ i; for(;;){ @@ -26016,8 +25809,8 @@ } function iter_weak(f, t){ var i = /*<>*/ 0; - /*<>*/ return caml_call2 - (Stdlib_Array[13], + /*<>*/ return Stdlib_Array[13].call + (null, function(j, b){ var i$0 = /*<>*/ i; for(;;){ @@ -26052,8 +25845,8 @@ /*<>*/ } function count(t){ var _s_ = /*<>*/ 0; - /*<>*/ return caml_call3 - (Stdlib_Array[20], + /*<>*/ return Stdlib_Array[20].call + (null, function(_t_, _u_){ /*<>*/ return count_bucket(_s_, _t_, _u_); }, @@ -26064,8 +25857,8 @@ var oldlen = /*<>*/ t[1].length - 1, newlen = - /*<>*/ caml_call2 - (Stdlib_Int[10], ((3 * oldlen | 0) / 2 | 0) + 3 | 0, Stdlib_Sys[13]); + /*<>*/ Stdlib_Int[10].call + (null, ((3 * oldlen | 0) / 2 | 0) + 3 | 0, Stdlib_Sys[13]); /*<>*/ if(oldlen < newlen){ var newt = /*<>*/ create$0(newlen), @@ -26107,19 +25900,17 @@ if(sz <= i$2){ var newsz = - /*<>*/ caml_call2 - (Stdlib_Int[10], - ((3 * sz | 0) / 2 | 0) + 3 | 0, - Stdlib_Sys[13] - 2 | 0); + /*<>*/ Stdlib_Int[10].call + (null, ((3 * sz | 0) / 2 | 0) + 3 | 0, Stdlib_Sys[13] - 2 | 0); /*<>*/ if(newsz <= sz) - /*<>*/ caml_call1 - (Stdlib[2], cst_Weak_Make_hash_bucket_cann); + /*<>*/ Stdlib[2].call + (null, cst_Weak_Make_hash_bucket_cann); var newbucket$0 = /*<>*/ create(newsz), newhashes = /*<>*/ caml_array_make(newsz, 0); /*<>*/ blit(bucket, 0, newbucket$0, 0, sz); - /*<>*/ caml_call5 - (Stdlib_Array[9], hashes, 0, newhashes, 0, sz); + /*<>*/ Stdlib_Array[9].call + (null, hashes, 0, newhashes, 0, sz); /*<>*/ caml_call3(setter, newbucket$0, sz, d); /*<>*/ caml_check_bound(newhashes, sz)[sz + 1] = h; /*<>*/ caml_check_bound(t[1], index)[index + 1] = newbucket$0; @@ -26178,8 +25969,8 @@ /*<>*/ caml_check_bound(t[1], _k_)[_k_ + 1] = newbucket; var _q_ = - /*<>*/ caml_call3 - (Stdlib_Array[6], hbucket, 0, prev_len), + /*<>*/ Stdlib_Array[6].call + (null, hbucket, 0, prev_len), _l_ = /*<>*/ t[5]; /*<>*/ caml_check_bound(t[2], _l_)[_l_ + 1] = _q_; } @@ -26332,17 +26123,13 @@ function stats(t){ var len = /*<>*/ t[1].length - 1, - lens = - /*<>*/ caml_call2(Stdlib_Array[14], length, t[1]); - /*<>*/ caml_call2 - (Stdlib_Array[35], runtime.caml_int_compare, lens); + lens = /*<>*/ Stdlib_Array[14].call(null, length, t[1]); + /*<>*/ Stdlib_Array[35].call + (null, runtime.caml_int_compare, lens); var totlen = - /*<>*/ caml_call3 - (Stdlib_Array[18], - function(_f_, _e_){ /*<>*/ return _f_ + _e_ | 0;}, - 0, - lens), + /*<>*/ Stdlib_Array[18].call + (null, function(_f_, _e_){ /*<>*/ return _f_ + _e_ | 0;}, 0, lens), _a_ = /*<>*/ len - 1 | 0, _b_ = /*<>*/ len / 2 | 0, _c_ = /*<>*/ caml_check_bound(lens, _a_)[_a_ + 1], @@ -26409,11 +26196,6 @@ ? f(a0, a1, a2) : runtime.caml_call_gen(f, [a0, a1, a2]); } - function caml_call4(f, a0, a1, a2, a3){ - return (f.l >= 0 ? f.l : f.l = f.length) === 4 - ? f(a0, a1, a2, a3) - : runtime.caml_call_gen(f, [a0, a1, a2, a3]); - } var dummy = 0, global_data = runtime.caml_get_global_data(), @@ -26454,8 +26236,8 @@ [248, "Stdlib.Format.String_tag", runtime.caml_fresh_oo_id(0)]; function pp_enqueue(state, token){ /*<>*/ state[13] = state[13] + token[3] | 0; - /*<>*/ return caml_call2 - (Stdlib_Queue[3], token, state[28]) /*<>*/ ; + /*<>*/ return Stdlib_Queue[3].call + (null, token, state[28]) /*<>*/ ; } var pp_infinity = /*<>*/ 1000000010, @@ -26478,11 +26260,11 @@ /*<>*/ state[11] = 0; /*<>*/ } function format_string(state, s){ - var _U_ = /*<>*/ s !== cst$16 ? 1 : 0; - /*<>*/ return _U_ + var _ah_ = /*<>*/ s !== cst$16 ? 1 : 0; + /*<>*/ return _ah_ ? /*<>*/ format_pp_text (state, caml_ml_string_length(s), s) - : _U_ /*<>*/ ; + : _ah_ /*<>*/ ; } function break_new_line(state, param, width){ var @@ -26495,7 +26277,7 @@ var indent = /*<>*/ (state[6] - width | 0) + offset | 0, real_indent = - /*<>*/ caml_call2(Stdlib_Int[10], state[8], indent); + /*<>*/ Stdlib_Int[10].call(null, state[8], indent); /*<>*/ state[10] = real_indent; /*<>*/ state[9] = state[6] - state[10] | 0; var n = /*<>*/ state[10]; @@ -26518,7 +26300,7 @@ case 0: var match$3 = - /*<>*/ caml_call1(Stdlib_Stack[8], state[3]); + /*<>*/ Stdlib_Stack[8].call(null, state[3]); /*<>*/ if(! match$3) /*<>*/ return; var @@ -26536,29 +26318,29 @@ add_tab(state[6] - state[9] | 0, tabs[1]); /*<>*/ return; case 1: - /*<>*/ caml_call1(Stdlib_Stack[5], state[2]); + /*<>*/ Stdlib_Stack[5].call(null, state[2]); /*<>*/ return; case 2: - /*<>*/ caml_call1(Stdlib_Stack[5], state[3]); + /*<>*/ Stdlib_Stack[5].call(null, state[3]); /*<>*/ return; case 3: var match$4 = - /*<>*/ caml_call1(Stdlib_Stack[8], state[2]); + /*<>*/ Stdlib_Stack[8].call(null, state[2]); /*<>*/ if(! match$4) /*<>*/ return pp_output_newline(state) /*<>*/ ; var width$0 = /*<>*/ match$4[1][2]; /*<>*/ return break_new_line(state, _a_, width$0) /*<>*/ ; case 4: var - _U_ = + _ah_ = /*<>*/ state[10] !== (state[6] - state[9] | 0) ? 1 : 0; - if(! _U_) return _U_; + if(! _ah_) return _ah_; var match$1 = - /*<>*/ caml_call1(Stdlib_Queue[6], state[28]); + /*<>*/ Stdlib_Queue[6].call(null, state[28]); /*<>*/ if(! match$1) /*<>*/ return; var @@ -26571,7 +26353,7 @@ default: var match$5 = - /*<>*/ caml_call1(Stdlib_Stack[5], state[5]); + /*<>*/ Stdlib_Stack[5].call(null, state[5]); /*<>*/ if(! match$5) /*<>*/ return; var @@ -26599,7 +26381,7 @@ off = /*<>*/ breaks[2], before = breaks[1], match$6 = - /*<>*/ caml_call1(Stdlib_Stack[8], state[2]); + /*<>*/ Stdlib_Stack[8].call(null, state[2]); /*<>*/ if(! match$6) /*<>*/ return; var @@ -26651,7 +26433,7 @@ n = param[1], insertion_point = /*<>*/ state[6] - state[9] | 0, match$8 = - /*<>*/ caml_call1(Stdlib_Stack[8], state[3]); + /*<>*/ Stdlib_Stack[8].call(null, state[3]); /*<>*/ if(! match$8) /*<>*/ return; var @@ -26681,8 +26463,7 @@ insertion_point$0 = /*<>*/ state[6] - state[9] | 0; /*<>*/ if(state[8] < insertion_point$0){ var - match = - /*<>*/ caml_call1(Stdlib_Stack[8], state[2]); + match = /*<>*/ Stdlib_Stack[8].call(null, state[2]); /*<>*/ if(match){ var match$0 = match[1], width = match$0[2], box_type = match$0[1]; /*<>*/ if @@ -26696,25 +26477,25 @@ width$2 = /*<>*/ state[9] - off$1 | 0, box_type$1 = /*<>*/ 1 === ty ? 1 : state[9] < size$0 ? ty : 5; - /*<>*/ return caml_call2 - (Stdlib_Stack[3], [0, box_type$1, width$2], state[2]) /*<>*/ ; + /*<>*/ return Stdlib_Stack[3].call + (null, [0, box_type$1, width$2], state[2]) /*<>*/ ; case 5: var tbox = /*<>*/ param[1]; - /*<>*/ return caml_call2 - (Stdlib_Stack[3], tbox, state[3]) /*<>*/ ; + /*<>*/ return Stdlib_Stack[3].call + (null, tbox, state[3]) /*<>*/ ; default: var tag_name$0 = /*<>*/ param[1], marker$0 = /*<>*/ caml_call1(state[24], tag_name$0); /*<>*/ pp_output_string(state, marker$0); - /*<>*/ return caml_call2 - (Stdlib_Stack[3], tag_name$0, state[5]) /*<>*/ ; + /*<>*/ return Stdlib_Stack[3].call + (null, tag_name$0, state[5]) /*<>*/ ; } } function advance_left(state){ /*<>*/ for(;;){ var - match = /*<>*/ caml_call1(Stdlib_Queue[9], state[28]); + match = /*<>*/ Stdlib_Queue[9].call(null, state[28]); /*<>*/ if(! match) /*<>*/ return 0; var match$0 = /*<>*/ match[1], @@ -26722,11 +26503,11 @@ length = match$0[3], token = match$0[2], pending_count = /*<>*/ state[13] - state[12] | 0, - _U_ = /*<>*/ 0 <= size ? 1 : 0, - _T_ = - /*<>*/ _U_ || (state[9] <= pending_count ? 1 : 0); - if(! _T_) return _T_; - /*<>*/ caml_call1(Stdlib_Queue[5], state[28]); + _ah_ = /*<>*/ 0 <= size ? 1 : 0, + _ag_ = + /*<>*/ _ah_ || (state[9] <= pending_count ? 1 : 0); + if(! _ag_) return _ag_; + /*<>*/ Stdlib_Queue[5].call(null, state[28]); var size$0 = /*<>*/ 0 <= size ? size : pp_infinity; /*<>*/ format_pp_token(state, size$0, token); /*<>*/ state[12] = length + state[12] | 0; @@ -26741,14 +26522,13 @@ (state, [0, size, [0, s], size]) /*<>*/ ; } function initialize_scan_stack(stack){ - /*<>*/ caml_call1(Stdlib_Stack[9], stack); + /*<>*/ Stdlib_Stack[9].call(null, stack); var queue_elem = /*<>*/ [0, unknown, _b_, 0]; - /*<>*/ return caml_call2 - (Stdlib_Stack[3], [0, -1, queue_elem], stack) /*<>*/ ; + /*<>*/ return Stdlib_Stack[3].call + (null, [0, -1, queue_elem], stack) /*<>*/ ; } function set_size(state, ty){ - var - match = /*<>*/ caml_call1(Stdlib_Stack[8], state[1]); + var match = /*<>*/ Stdlib_Stack[8].call(null, state[1]); /*<>*/ if(! match) /*<>*/ return; var match$0 = /*<>*/ match[1], @@ -26764,7 +26544,7 @@ /*<>*/ if(1 - ty){ var x$0 = /*<>*/ state[13] + size | 0; /*<>*/ queue_elem[1] = x$0; - /*<>*/ caml_call1(Stdlib_Stack[5], state[1]); + /*<>*/ Stdlib_Stack[5].call(null, state[1]); } /*<>*/ return; case 2: @@ -26772,7 +26552,7 @@ /*<>*/ if(ty){ var x = /*<>*/ state[13] + size | 0; /*<>*/ queue_elem[1] = x; - /*<>*/ caml_call1(Stdlib_Stack[5], state[1]); + /*<>*/ Stdlib_Stack[5].call(null, state[1]); } /*<>*/ return; } @@ -26782,8 +26562,7 @@ /*<>*/ if(b) /*<>*/ set_size(state, 1); var elem = /*<>*/ [0, state[13], token]; - /*<>*/ return caml_call2 - (Stdlib_Stack[3], elem, state[1]) /*<>*/ ; + /*<>*/ return Stdlib_Stack[3].call(null, elem, state[1]) /*<>*/ ; } function pp_open_box_gen(state, indent, br_ty){ /*<>*/ state[14] = state[14] + 1 | 0; @@ -26793,54 +26572,54 @@ elem = /*<>*/ [0, size, [4, indent, br_ty], 0]; /*<>*/ return scan_push(state, 0, elem) /*<>*/ ; } - var _T_ = /*<>*/ state[14] === state[15] ? 1 : 0; - if(! _T_) return _T_; + var _ag_ = /*<>*/ state[14] === state[15] ? 1 : 0; + if(! _ag_) return _ag_; var s = /*<>*/ state[16], x = /*<>*/ caml_ml_string_length(s); /*<>*/ return enqueue_string_as(state, x, s) /*<>*/ ; } function pp_close_box(state, param){ - var _S_ = /*<>*/ 1 < state[14] ? 1 : 0; - if(_S_){ + var _af_ = /*<>*/ 1 < state[14] ? 1 : 0; + if(_af_){ /*<>*/ if(state[14] < state[15]){ /*<>*/ pp_enqueue(state, [0, zero, 1, 0]); /*<>*/ set_size(state, 1); /*<>*/ set_size(state, 0); } /*<>*/ state[14] = state[14] - 1 | 0; - var _T_ = 0; + var _ag_ = 0; } else - var _T_ = /*<>*/ _S_; - return _T_; + var _ag_ = /*<>*/ _af_; + return _ag_; /*<>*/ } function pp_open_stag(state, tag_name){ /*<>*/ if(state[22]){ - /*<>*/ caml_call2(Stdlib_Stack[3], tag_name, state[4]); + /*<>*/ Stdlib_Stack[3].call(null, tag_name, state[4]); /*<>*/ caml_call1(state[26], tag_name); } - var _S_ = /*<>*/ state[23]; - if(! _S_) return _S_; + var _af_ = /*<>*/ state[23]; + if(! _af_) return _af_; var token = /*<>*/ [6, tag_name]; /*<>*/ return pp_enqueue(state, [0, zero, token, 0]) /*<>*/ ; } function pp_close_stag(state, param){ /*<>*/ if(state[23]) /*<>*/ pp_enqueue(state, [0, zero, 5, 0]); - var _R_ = /*<>*/ state[22]; - if(_R_){ + var _ae_ = /*<>*/ state[22]; + if(_ae_){ var - match = /*<>*/ caml_call1(Stdlib_Stack[5], state[4]); + match = /*<>*/ Stdlib_Stack[5].call(null, state[4]); /*<>*/ if(match){ var tag_name = match[1]; /*<>*/ return caml_call1(state[27], tag_name) /*<>*/ ; } - var _S_ = /*<>*/ 0; + var _af_ = /*<>*/ 0; } else - var _S_ = /*<>*/ _R_; - return _S_; + var _af_ = /*<>*/ _ae_; + return _af_; /*<>*/ } function pp_set_print_tags(state, b){ /*<>*/ state[22] = b; @@ -26882,20 +26661,20 @@ function pp_rinit(state){ /*<>*/ state[12] = 1; /*<>*/ state[13] = 1; - /*<>*/ caml_call1(Stdlib_Queue[12], state[28]); + /*<>*/ Stdlib_Queue[12].call(null, state[28]); /*<>*/ initialize_scan_stack(state[1]); - /*<>*/ caml_call1(Stdlib_Stack[9], state[2]); - /*<>*/ caml_call1(Stdlib_Stack[9], state[3]); - /*<>*/ caml_call1(Stdlib_Stack[9], state[4]); - /*<>*/ caml_call1(Stdlib_Stack[9], state[5]); + /*<>*/ Stdlib_Stack[9].call(null, state[2]); + /*<>*/ Stdlib_Stack[9].call(null, state[3]); + /*<>*/ Stdlib_Stack[9].call(null, state[4]); + /*<>*/ Stdlib_Stack[9].call(null, state[5]); /*<>*/ state[10] = 0; /*<>*/ state[14] = 0; /*<>*/ state[9] = state[6]; /*<>*/ return pp_open_box_gen(state, 0, 3) /*<>*/ ; } function pp_flush_queue(state, end_with_newline){ - /*<>*/ caml_call2 - (Stdlib_Stack[13], + /*<>*/ Stdlib_Stack[13].call + (null, function(param){ /*<>*/ return pp_close_stag(state, 0) /*<>*/ ; }, @@ -26912,10 +26691,10 @@ } /*<>*/ } function pp_print_as_size(state, size, s){ - var _R_ = /*<>*/ state[14] < state[15] ? 1 : 0; - return _R_ + var _ae_ = /*<>*/ state[14] < state[15] ? 1 : 0; + return _ae_ ? /*<>*/ enqueue_string_as(state, size, s) - : _R_ /*<>*/ ; + : _ae_ /*<>*/ ; } function pp_print_as(state, isize, s){ /*<>*/ return pp_print_as_size(state, isize, s) /*<>*/ ; @@ -26925,8 +26704,8 @@ /*<>*/ return pp_print_as_size(state, isize, s) /*<>*/ ; } function pp_print_substring_as(pos, len, state, size, source){ - var _R_ = /*<>*/ state[14] < state[15] ? 1 : 0; - if(! _R_) return _R_; + var _ae_ = /*<>*/ state[14] < state[15] ? 1 : 0; + if(! _ae_) return _ae_; var token = /*<>*/ [1, source, pos, len]; /*<>*/ return enqueue_advance (state, [0, size, token, size]) /*<>*/ ; @@ -26937,24 +26716,24 @@ } function pp_print_bytes(state, s){ var - s$0 = /*<>*/ caml_call1(Stdlib_Bytes[6], s), + s$0 = /*<>*/ Stdlib_Bytes[6].call(null, s), isize = /*<>*/ runtime.caml_ml_bytes_length(s); /*<>*/ return pp_print_as_size(state, isize, s$0) /*<>*/ ; } function pp_print_int(state, i){ /*<>*/ return /*<>*/ pp_print_string - (state, /*<>*/ caml_call1(Stdlib_Int[12], i)) /*<>*/ ; + (state, /*<>*/ Stdlib_Int[12].call(null, i)) /*<>*/ ; } function pp_print_float(state, f){ /*<>*/ return /*<>*/ pp_print_string - (state, /*<>*/ caml_call1(Stdlib[35], f)) /*<>*/ ; + (state, /*<>*/ Stdlib[35].call(null, f)) /*<>*/ ; } function pp_print_bool(state, b){ /*<>*/ return /*<>*/ pp_print_string - (state, /*<>*/ caml_call1(Stdlib[30], b)) /*<>*/ ; + (state, /*<>*/ Stdlib[30].call(null, b)) /*<>*/ ; } function pp_print_char(state, c){ - var s = /*<>*/ caml_call2(Stdlib_String[1], 1, c); + var s = /*<>*/ Stdlib_String[1].call(null, 1, c); /*<>*/ return pp_print_as_size(state, 1, s) /*<>*/ ; } function pp_print_nothing(state, param){ /*<>*/ return 0; @@ -26983,24 +26762,24 @@ /*<>*/ return caml_call1(state[18], 0) /*<>*/ ; } function pp_force_newline(state, param){ - var _R_ = /*<>*/ state[14] < state[15] ? 1 : 0; - return _R_ + var _ae_ = /*<>*/ state[14] < state[15] ? 1 : 0; + return _ae_ ? /*<>*/ enqueue_advance(state, [0, zero, 3, 0]) - : _R_ /*<>*/ ; + : _ae_ /*<>*/ ; } function pp_print_if_newline(state, param){ - var _R_ = /*<>*/ state[14] < state[15] ? 1 : 0; - return _R_ + var _ae_ = /*<>*/ state[14] < state[15] ? 1 : 0; + return _ae_ ? /*<>*/ enqueue_advance(state, [0, zero, 4, 0]) - : _R_ /*<>*/ ; + : _ae_ /*<>*/ ; } function pp_print_custom_break(state, fits, breaks){ var after = /*<>*/ fits[3], width = fits[2], before = fits[1], - _R_ = /*<>*/ state[14] < state[15] ? 1 : 0; - if(! _R_) return _R_; + _ae_ = /*<>*/ state[14] < state[15] ? 1 : 0; + if(! _ae_) return _ae_; var size = /*<>*/ - state[13] | 0, token = /*<>*/ [2, fits, breaks], @@ -27023,31 +26802,31 @@ } function pp_open_tbox(state, param){ /*<>*/ state[14] = state[14] + 1 | 0; - var _R_ = /*<>*/ state[14] < state[15] ? 1 : 0; - if(! _R_) return _R_; + var _ae_ = /*<>*/ state[14] < state[15] ? 1 : 0; + if(! _ae_) return _ae_; var elem = /*<>*/ [0, zero, [5, [0, [0, 0]]], 0]; /*<>*/ return enqueue_advance(state, elem) /*<>*/ ; } function pp_close_tbox(state, param){ - var _Q_ = /*<>*/ 1 < state[14] ? 1 : 0; - if(_Q_){ - var _R_ = /*<>*/ state[14] < state[15] ? 1 : 0; - if(_R_){ + var _ad_ = /*<>*/ 1 < state[14] ? 1 : 0; + if(_ad_){ + var _ae_ = /*<>*/ state[14] < state[15] ? 1 : 0; + if(_ae_){ var elem = /*<>*/ [0, zero, 2, 0]; /*<>*/ enqueue_advance(state, elem); /*<>*/ state[14] = state[14] - 1 | 0; - var _P_ = 0; + var _ac_ = 0; } else - var _P_ = /*<>*/ _R_; + var _ac_ = /*<>*/ _ae_; } else - var _P_ = /*<>*/ _Q_; - return _P_; + var _ac_ = /*<>*/ _ad_; + return _ac_; /*<>*/ } function pp_print_tbreak(state, width, offset){ - var _P_ = /*<>*/ state[14] < state[15] ? 1 : 0; - if(! _P_) return _P_; + var _ac_ = /*<>*/ state[14] < state[15] ? 1 : 0; + if(! _ac_) return _ac_; var size = /*<>*/ - state[13] | 0, elem = /*<>*/ [0, size, [3, width, offset], width]; @@ -27057,16 +26836,16 @@ /*<>*/ return pp_print_tbreak(state, 0, 0) /*<>*/ ; } function pp_set_tab(state, param){ - var _P_ = /*<>*/ state[14] < state[15] ? 1 : 0; - if(! _P_) return _P_; + var _ac_ = /*<>*/ state[14] < state[15] ? 1 : 0; + if(! _ac_) return _ac_; var elem = /*<>*/ [0, zero, 0, 0]; /*<>*/ return enqueue_advance(state, elem) /*<>*/ ; } function pp_set_max_boxes(state, n){ var - _O_ = /*<>*/ 1 < n ? 1 : 0, - _P_ = _O_ ? (state[15] = n, 0) : _O_; - return _P_; + _ab_ = /*<>*/ 1 < n ? 1 : 0, + _ac_ = _ab_ ? (state[15] = n, 0) : _ab_; + return _ac_; /*<>*/ } function pp_get_max_boxes(state, param){ /*<>*/ return state[15]; @@ -27085,12 +26864,12 @@ /*<>*/ return n < 1000000010 ? n : 1000000009 /*<>*/ ; } function pp_set_max_indent(state, n$0){ - var _O_ = /*<>*/ 1 < n$0 ? 1 : 0; - if(! _O_) return _O_; + var _ab_ = /*<>*/ 1 < n$0 ? 1 : 0; + if(! _ab_) return _ab_; var n$1 = /*<>*/ state[6] - n$0 | 0, - _N_ = /*<>*/ 1 <= n$1 ? 1 : 0; - if(! _N_) return _N_; + _aa_ = /*<>*/ 1 <= n$1 ? 1 : 0; + if(! _aa_) return _aa_; var n = /*<>*/ pp_limit(n$1); /*<>*/ state[7] = n; /*<>*/ state[8] = state[6] - state[7] | 0; @@ -27100,20 +26879,20 @@ /*<>*/ return state[8]; /*<>*/ } function pp_set_margin(state, n){ - var _M_ = /*<>*/ 1 <= n ? 1 : 0; - if(! _M_) return _M_; + var _$_ = /*<>*/ 1 <= n ? 1 : 0; + if(! _$_) return _$_; var n$0 = /*<>*/ pp_limit(n); /*<>*/ state[6] = n$0; /*<>*/ if(state[8] <= state[6]) var new_max_indent = /*<>*/ state[8]; else var - _N_ = - /*<>*/ caml_call2 - (Stdlib_Int[11], state[6] - state[7] | 0, state[6] / 2 | 0), + _aa_ = + /*<>*/ Stdlib_Int[11].call + (null, state[6] - state[7] | 0, state[6] / 2 | 0), new_max_indent = - /*<>*/ /*<>*/ caml_call2 - (Stdlib_Int[11], _N_, 1); + /*<>*/ /*<>*/ Stdlib_Int[11].call + (null, _aa_, 1); /*<>*/ return pp_set_max_indent(state, new_max_indent) /*<>*/ ; } function validate_geometry(param){ @@ -27144,11 +26923,11 @@ /*<>*/ return pp_set_full_geometry(state, geometry) /*<>*/ ; var msg = /*<>*/ match[1], - _M_ = - /*<>*/ caml_call2 - (Stdlib[28], cst_Format_pp_set_geometry, msg); + _$_ = + /*<>*/ Stdlib[28].call + (null, cst_Format_pp_set_geometry, msg); /*<>*/ throw caml_maybe_attach_backtrace - ([0, Stdlib[6], _M_], 1); + ([0, Stdlib[6], _$_], 1); /*<>*/ } function pp_safe_set_geometry(state, max_indent, margin){ var geometry = /*<>*/ [0, max_indent, margin]; @@ -27198,14 +26977,13 @@ /*<>*/ return caml_call3(state[17], cst$7, 0, 1) /*<>*/ ; } var - blank_line = - /*<>*/ caml_call2(Stdlib_String[1], 80, 32), + blank_line = /*<>*/ Stdlib_String[1].call(null, 80, 32), _g_ = /*<>*/ [4, 0, 3]; function display_blanks(state, n$1){ var n = /*<>*/ n$1; for(;;){ - var _M_ = 0 < n ? 1 : 0; - if(! _M_) return _M_; + var _$_ = 0 < n ? 1 : 0; + if(! _$_) return _$_; /*<>*/ if(80 >= n) /*<>*/ return caml_call3(state[17], blank_line, 0, n) /*<>*/ ; /*<>*/ caml_call3(state[17], blank_line, 0, 80); @@ -27214,22 +26992,26 @@ } /*<>*/ } function pp_set_formatter_out_channel(state, oc){ - /*<>*/ state[17] = caml_call1(Stdlib[69], oc); + var _Y_ = /*<>*/ Stdlib[69]; + /*<>*/ state[17] = + function(_Z_, ___, _$_){ + /*<>*/ return _Y_(oc, _Z_, ___, _$_); + }; /*<>*/ state[18] = function(param){ - /*<>*/ return caml_call1(Stdlib[63], oc) /*<>*/ ; + /*<>*/ return Stdlib[63].call(null, oc) /*<>*/ ; }; /*<>*/ state[19] = - function(_M_){ - /*<>*/ return display_newline(state, _M_); + function(_Y_){ + /*<>*/ return display_newline(state, _Y_); }; /*<>*/ state[20] = - function(_M_){ - /*<>*/ return display_blanks(state, _M_); + function(_Y_){ + /*<>*/ return display_blanks(state, _Y_); }; /*<>*/ state[21] = - function(_M_){ - /*<>*/ return display_blanks(state, _M_); + function(_Y_){ + /*<>*/ return display_blanks(state, _Y_); }; /*<>*/ return 0; } @@ -27238,40 +27020,40 @@ if(tag !== String_tag) /*<>*/ return cst$10; var s = /*<>*/ param[2], - _M_ = /*<>*/ caml_call2(Stdlib[28], s, cst$8); - /*<>*/ return caml_call2(Stdlib[28], cst$9, _M_) /*<>*/ ; + _Y_ = /*<>*/ Stdlib[28].call(null, s, cst$8); + /*<>*/ return Stdlib[28].call(null, cst$9, _Y_) /*<>*/ ; } function default_pp_mark_close_tag(param){ var tag = /*<>*/ param[1]; if(tag !== String_tag) /*<>*/ return cst$13; var s = /*<>*/ param[2], - _M_ = /*<>*/ caml_call2(Stdlib[28], s, cst$11); - /*<>*/ return caml_call2(Stdlib[28], cst$12, _M_) /*<>*/ ; + _Y_ = /*<>*/ Stdlib[28].call(null, s, cst$11); + /*<>*/ return Stdlib[28].call(null, cst$12, _Y_) /*<>*/ ; } - function default_pp_print_open_tag(_M_){ /*<>*/ return 0;} - function default_pp_print_close_tag(_M_){return 0;} + function default_pp_print_open_tag(_Y_){ /*<>*/ return 0;} + function default_pp_print_close_tag(_Y_){return 0;} function pp_make_formatter(f, g, h, i, j){ var - pp_queue = /*<>*/ caml_call1(Stdlib_Queue[2], 0), + pp_queue = /*<>*/ Stdlib_Queue[2].call(null, 0), sys_tok = /*<>*/ [0, unknown, _g_, 0]; - /*<>*/ caml_call2(Stdlib_Queue[3], sys_tok, pp_queue); - var scan_stack = /*<>*/ caml_call1(Stdlib_Stack[2], 0); + /*<>*/ Stdlib_Queue[3].call(null, sys_tok, pp_queue); + var scan_stack = /*<>*/ Stdlib_Stack[2].call(null, 0); /*<>*/ initialize_scan_stack(scan_stack); - /*<>*/ caml_call2 - (Stdlib_Stack[3], [0, 1, sys_tok], scan_stack); + /*<>*/ Stdlib_Stack[3].call + (null, [0, 1, sys_tok], scan_stack); var pp_margin = /*<>*/ 78, - _J_ = /*<>*/ Stdlib[19], - _K_ = caml_call1(Stdlib_Stack[2], 0), - _L_ = /*<>*/ caml_call1(Stdlib_Stack[2], 0), - _M_ = /*<>*/ caml_call1(Stdlib_Stack[2], 0); + _V_ = /*<>*/ Stdlib[19], + _W_ = Stdlib_Stack[2].call(null, 0), + _X_ = /*<>*/ Stdlib_Stack[2].call(null, 0), + _Y_ = /*<>*/ Stdlib_Stack[2].call(null, 0); /*<>*/ return [0, scan_stack, - caml_call1(Stdlib_Stack[2], 0), - _M_, - _L_, - _K_, + Stdlib_Stack[2].call(null, 0), + _Y_, + _X_, + _W_, pp_margin, 10, 68, @@ -27281,7 +27063,7 @@ 1, 1, 1, - _J_, + _V_, cst$14, f, g, @@ -27306,39 +27088,45 @@ /*<>*/ pp_make_formatter (output, flush, - function(_J_){ /*<>*/ return 0;}, - function(_J_){return 0;}, - function(_J_){return 0;}); + function(_V_){ /*<>*/ return 0;}, + function(_V_){return 0;}, + function(_V_){return 0;}); /*<>*/ ppf[19] = - function(_J_){ - /*<>*/ return display_newline(ppf, _J_); + function(_V_){ + /*<>*/ return display_newline(ppf, _V_); }; /*<>*/ ppf[20] = - function(_J_){ - /*<>*/ return display_blanks(ppf, _J_); + function(_V_){ + /*<>*/ return display_blanks(ppf, _V_); }; /*<>*/ ppf[21] = - function(_J_){ - /*<>*/ return display_blanks(ppf, _J_); + function(_V_){ + /*<>*/ return display_blanks(ppf, _V_); }; /*<>*/ return ppf; /*<>*/ } function formatter_of_out_channel(oc){ - /*<>*/ return /*<>*/ make_formatter - ( /*<>*/ caml_call1(Stdlib[69], oc), + var _S_ = /*<>*/ Stdlib[69]; + /*<>*/ return make_formatter + (function(_T_, _U_, _V_){ + /*<>*/ return _S_(oc, _T_, _U_, _V_); + }, function(param){ - /*<>*/ return caml_call1(Stdlib[63], oc) /*<>*/ ; + /*<>*/ return Stdlib[63].call(null, oc) /*<>*/ ; }) /*<>*/ ; } function formatter_of_buffer(b){ - /*<>*/ return /*<>*/ make_formatter - ( /*<>*/ caml_call1(Stdlib_Buffer[18], b), - function(_J_){ /*<>*/ return 0;}) /*<>*/ ; + var _P_ = /*<>*/ Stdlib_Buffer[18]; + /*<>*/ return make_formatter + (function(_Q_, _R_, _S_){ + /*<>*/ return _P_(b, _Q_, _R_, _S_); + }, + function(_P_){ /*<>*/ return 0;}) /*<>*/ ; } var pp_buffer_size = /*<>*/ 512; function pp_make_buffer(param){ - /*<>*/ return caml_call1 - (Stdlib_Buffer[1], pp_buffer_size) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[1].call + (null, pp_buffer_size) /*<>*/ ; } var stdbuf = /*<>*/ pp_make_buffer(0), @@ -27366,18 +27154,18 @@ (Stdlib_Domain[11][3], str_formatter_key, str_formatter); function buffered_out_string(key, str, ofs, len){ var - _J_ = /*<>*/ caml_call1(Stdlib_Domain[11][2], key); - /*<>*/ return caml_call4 - (Stdlib_Buffer[18], _J_, str, ofs, len) /*<>*/ ; + _P_ = /*<>*/ caml_call1(Stdlib_Domain[11][2], key); + /*<>*/ return Stdlib_Buffer[18].call + (null, _P_, str, ofs, len) /*<>*/ ; } function buffered_out_flush(oc, key, param){ var buf = /*<>*/ caml_call1(Stdlib_Domain[11][2], key), - len = /*<>*/ caml_call1(Stdlib_Buffer[7], buf), - str = /*<>*/ caml_call1(Stdlib_Buffer[2], buf); - /*<>*/ caml_call4(Stdlib[69], oc, str, 0, len); - /*<>*/ caml_call1(Stdlib[63], oc); - /*<>*/ return caml_call1(Stdlib_Buffer[8], buf) /*<>*/ ; + len = /*<>*/ Stdlib_Buffer[7].call(null, buf), + str = /*<>*/ Stdlib_Buffer[2].call(null, buf); + /*<>*/ Stdlib[69].call(null, oc, str, 0, len); + /*<>*/ Stdlib[63].call(null, oc); + /*<>*/ return Stdlib_Buffer[8].call(null, buf) /*<>*/ ; } var std_buf_key = @@ -27385,16 +27173,16 @@ (Stdlib_Domain[11][1], 0, function(param){ - /*<>*/ return caml_call1 - (Stdlib_Buffer[1], pp_buffer_size) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[1].call + (null, pp_buffer_size) /*<>*/ ; }), err_buf_key = /*<>*/ caml_call2 (Stdlib_Domain[11][1], 0, function(param){ - /*<>*/ return caml_call1 - (Stdlib_Buffer[1], pp_buffer_size) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[1].call + (null, pp_buffer_size) /*<>*/ ; }), std_formatter_key = /*<>*/ caml_call2 @@ -27402,36 +27190,36 @@ 0, function(param){ var - _G_ = /*<>*/ Stdlib[39], + _M_ = /*<>*/ Stdlib[39], ppf = /*<>*/ pp_make_formatter - (function(_H_, _I_, _J_){ + (function(_N_, _O_, _P_){ /*<>*/ return buffered_out_string - (std_buf_key, _H_, _I_, _J_); + (std_buf_key, _N_, _O_, _P_); }, - function(_H_){ + function(_N_){ /*<>*/ return buffered_out_flush - (_G_, std_buf_key, _H_); + (_M_, std_buf_key, _N_); }, - function(_G_){ /*<>*/ return 0;}, - function(_G_){return 0;}, - function(_G_){return 0;}); + function(_M_){ /*<>*/ return 0;}, + function(_M_){return 0;}, + function(_M_){return 0;}); /*<>*/ ppf[19] = - function(_G_){ - /*<>*/ return display_newline(ppf, _G_); + function(_M_){ + /*<>*/ return display_newline(ppf, _M_); }; /*<>*/ ppf[20] = - function(_G_){ - /*<>*/ return display_blanks(ppf, _G_); + function(_M_){ + /*<>*/ return display_blanks(ppf, _M_); }; /*<>*/ ppf[21] = - function(_G_){ - /*<>*/ return display_blanks(ppf, _G_); + function(_M_){ + /*<>*/ return display_blanks(ppf, _M_); }; - /*<>*/ caml_call1 - (Stdlib_Domain[6], - function(_G_){ - /*<>*/ return pp_print_flush(ppf, _G_); + /*<>*/ Stdlib_Domain[6].call + (null, + function(_M_){ + /*<>*/ return pp_print_flush(ppf, _M_); }); /*<>*/ return ppf; /*<>*/ }); @@ -27444,36 +27232,36 @@ 0, function(param){ var - _D_ = /*<>*/ Stdlib[40], + _J_ = /*<>*/ Stdlib[40], ppf = /*<>*/ pp_make_formatter - (function(_E_, _F_, _G_){ + (function(_K_, _L_, _M_){ /*<>*/ return buffered_out_string - (err_buf_key, _E_, _F_, _G_); + (err_buf_key, _K_, _L_, _M_); }, - function(_E_){ + function(_K_){ /*<>*/ return buffered_out_flush - (_D_, err_buf_key, _E_); + (_J_, err_buf_key, _K_); }, - function(_D_){ /*<>*/ return 0;}, - function(_D_){return 0;}, - function(_D_){return 0;}); + function(_J_){ /*<>*/ return 0;}, + function(_J_){return 0;}, + function(_J_){return 0;}); /*<>*/ ppf[19] = - function(_D_){ - /*<>*/ return display_newline(ppf, _D_); + function(_J_){ + /*<>*/ return display_newline(ppf, _J_); }; /*<>*/ ppf[20] = - function(_D_){ - /*<>*/ return display_blanks(ppf, _D_); + function(_J_){ + /*<>*/ return display_blanks(ppf, _J_); }; /*<>*/ ppf[21] = - function(_D_){ - /*<>*/ return display_blanks(ppf, _D_); + function(_J_){ + /*<>*/ return display_blanks(ppf, _J_); }; - /*<>*/ caml_call1 - (Stdlib_Domain[6], - function(_D_){ - /*<>*/ return pp_print_flush(ppf, _D_); + /*<>*/ Stdlib_Domain[6].call + (null, + function(_J_){ + /*<>*/ return pp_print_flush(ppf, _J_); }); /*<>*/ return ppf; /*<>*/ }); @@ -27497,8 +27285,8 @@ } function flush_buffer_formatter(buf, ppf){ /*<>*/ pp_flush_queue(ppf, 0); - var s = /*<>*/ caml_call1(Stdlib_Buffer[2], buf); - /*<>*/ caml_call1(Stdlib_Buffer[9], buf); + var s = /*<>*/ Stdlib_Buffer[2].call(null, buf); + /*<>*/ Stdlib_Buffer[9].call(null, buf); /*<>*/ return s; /*<>*/ } function flush_str_formatter(param){ @@ -27518,20 +27306,22 @@ function(param){ var buf = - /*<>*/ caml_call1 - (Stdlib_Buffer[1], pp_buffer_size), - output$0 = - /*<>*/ caml_call1(Stdlib_Buffer[18], buf); + /*<>*/ Stdlib_Buffer[1].call + (null, pp_buffer_size), + _G_ = /*<>*/ Stdlib_Buffer[18]; + function output$0(_H_, _I_, _J_){ + /*<>*/ return _G_(buf, _H_, _I_, _J_); + } function flush$0(param){ var - _D_ = - /*<>*/ caml_call1(Stdlib_Buffer[7], buf); + _G_ = + /*<>*/ Stdlib_Buffer[7].call(null, buf); /*<>*/ /*<>*/ caml_call3 (output, - /*<>*/ caml_call1(Stdlib_Buffer[2], buf), + /*<>*/ Stdlib_Buffer[2].call(null, buf), 0, - _D_); - /*<>*/ caml_call1(Stdlib_Buffer[8], buf); + _G_); + /*<>*/ Stdlib_Buffer[8].call(null, buf); /*<>*/ return caml_call1(flush, 0) /*<>*/ ; } /*<>*/ return make_formatter @@ -27539,10 +27329,13 @@ }) /*<>*/ ; } function synchronized_formatter_of_out_(oc){ - /*<>*/ return /*<>*/ make_synchronized_formatter - ( /*<>*/ caml_call1(Stdlib[69], oc), + var _D_ = /*<>*/ Stdlib[69]; + /*<>*/ return make_synchronized_formatter + (function(_E_, _F_, _G_){ + /*<>*/ return _D_(oc, _E_, _F_, _G_); + }, function(param){ - /*<>*/ return caml_call1(Stdlib[63], oc) /*<>*/ ; + /*<>*/ return Stdlib[63].call(null, oc) /*<>*/ ; }) /*<>*/ ; } function make_symbolic_output_buffer(param){ /*<>*/ return [0, 0]; @@ -27552,7 +27345,7 @@ return 0; /*<>*/ } function get_symbolic_output_buffer(sob){ - /*<>*/ return caml_call1(Stdlib_List[10], sob[1]) /*<>*/ ; + /*<>*/ return Stdlib_List[10].call(null, sob[1]) /*<>*/ ; } function flush_symbolic_output_buffer(sob){ var items = /*<>*/ get_symbolic_output_buffer(sob); @@ -27568,8 +27361,8 @@ /*<>*/ return /*<>*/ add_symbolic_output_item (sob, [0, - /*<>*/ caml_call3 - (Stdlib_String[16], s, i, n)]) /*<>*/ ; + /*<>*/ Stdlib_String[16].call + (null, s, i, n)]) /*<>*/ ; } function g(param){ /*<>*/ return add_symbolic_output_item(sob, 0); @@ -28019,15 +27812,16 @@ } function compute_tag(output, tag_acc){ var - buf = /*<>*/ caml_call1(Stdlib_Buffer[1], 16), + buf = /*<>*/ Stdlib_Buffer[1].call(null, 16), ppf = /*<>*/ formatter_of_buffer(buf); /*<>*/ caml_call2(output, ppf, tag_acc); /*<>*/ pp_print_flush(ppf, 0); - var len = /*<>*/ caml_call1(Stdlib_Buffer[7], buf); + var len = /*<>*/ Stdlib_Buffer[7].call(null, buf); /*<>*/ return 2 <= len - ? /*<>*/ caml_call3 - (Stdlib_Buffer[4], buf, 1, len - 2 | 0) - : /*<>*/ caml_call1(Stdlib_Buffer[2], buf) /*<>*/ ; + ? /*<>*/ Stdlib_Buffer + [4].call + (null, buf, 1, len - 2 | 0) + : /*<>*/ Stdlib_Buffer[2].call(null, buf) /*<>*/ ; } function output_formatting_lit(ppf, fmting_lit){ /*<>*/ if(typeof fmting_lit === "number") @@ -28089,8 +27883,7 @@ var _D_ = /*<>*/ compute_tag(output_acc, acc$1), match$0 = - /*<>*/ caml_call1 - (CamlinternalFormat[20], _D_), + /*<>*/ CamlinternalFormat[20].call(null, _D_), bty = /*<>*/ match$0[2], indent = match$0[1]; /*<>*/ return pp_open_box_gen(ppf, indent, bty) /*<>*/ ; @@ -28149,7 +27942,7 @@ default: var msg = /*<>*/ acc[2], p$7 = acc[1]; /*<>*/ output_acc(ppf, p$7); - /*<>*/ return caml_call1(Stdlib[1], msg) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, msg) /*<>*/ ; } /*<>*/ output_acc(ppf, p$3); /*<>*/ return pp_print_char(ppf, c) /*<>*/ ; @@ -28158,7 +27951,7 @@ /*<>*/ return /*<>*/ pp_print_as_size (ppf, size$0, - /*<>*/ caml_call2(Stdlib_String[1], 1, c$0)) /*<>*/ ; + /*<>*/ Stdlib_String[1].call(null, 1, c$0)) /*<>*/ ; } /*<>*/ output_acc(ppf, p$1); /*<>*/ return pp_print_string(ppf, s) /*<>*/ ; @@ -28196,8 +27989,7 @@ var _v_ = /*<>*/ compute_tag(strput_acc, acc$1), match$0 = - /*<>*/ caml_call1 - (CamlinternalFormat[20], _v_), + /*<>*/ CamlinternalFormat[20].call(null, _v_), bty = /*<>*/ match$0[2], indent = match$0[1]; /*<>*/ return pp_open_box_gen(ppf, indent, bty) /*<>*/ ; @@ -28267,7 +28059,7 @@ default: var msg = /*<>*/ acc[2], p$8 = acc[1]; /*<>*/ strput_acc(ppf, p$8); - /*<>*/ return caml_call1(Stdlib[1], msg) /*<>*/ ; + /*<>*/ return Stdlib[1].call(null, msg) /*<>*/ ; } /*<>*/ strput_acc(ppf, p$3); /*<>*/ return pp_print_char(ppf, c) /*<>*/ ; @@ -28276,7 +28068,7 @@ /*<>*/ return /*<>*/ pp_print_as_size (ppf, size$0, - /*<>*/ caml_call2(Stdlib_String[1], 1, c$0)) /*<>*/ ; + /*<>*/ Stdlib_String[1].call(null, 1, c$0)) /*<>*/ ; } /*<>*/ strput_acc(ppf, p$1); /*<>*/ return pp_print_string(ppf, s) /*<>*/ ; @@ -28286,8 +28078,8 @@ } function kfprintf(k, ppf, param){ var fmt = /*<>*/ param[1]; - /*<>*/ return caml_call3 - (CamlinternalFormat[7], + /*<>*/ return CamlinternalFormat[7].call + (null, function(acc){ /*<>*/ output_acc(ppf, acc); /*<>*/ return caml_call1(k, ppf) /*<>*/ ; @@ -28297,16 +28089,13 @@ } function ikfprintf(k, ppf, param){ var fmt = /*<>*/ param[1]; - /*<>*/ return caml_call3 - (CamlinternalFormat[8], k, ppf, fmt) /*<>*/ ; + /*<>*/ return CamlinternalFormat[8].call + (null, k, ppf, fmt) /*<>*/ ; } function ifprintf(ppf, param){ var fmt = /*<>*/ param[1]; - /*<>*/ return caml_call3 - (CamlinternalFormat[8], - function(_n_){ /*<>*/ return 0;}, - 0, - fmt) /*<>*/ ; + /*<>*/ return CamlinternalFormat[8].call + (null, function(_n_){ /*<>*/ return 0;}, 0, fmt) /*<>*/ ; } function fprintf(ppf){ function _m_(_n_){ /*<>*/ return 0;} @@ -28315,8 +28104,8 @@ /*<>*/ } function printf(param){ var fmt = /*<>*/ param[1]; - /*<>*/ return caml_call3 - (CamlinternalFormat[7], + /*<>*/ return CamlinternalFormat[7].call + (null, function(acc){ /*<>*/ return /*<>*/ output_acc ( /*<>*/ caml_call1 @@ -28328,8 +28117,8 @@ } function eprintf(param){ var fmt = /*<>*/ param[1]; - /*<>*/ return caml_call3 - (CamlinternalFormat[7], + /*<>*/ return CamlinternalFormat[7].call + (null, function(acc){ /*<>*/ return /*<>*/ output_acc ( /*<>*/ caml_call1 @@ -28341,8 +28130,8 @@ } function kdprintf(k, param){ var fmt = /*<>*/ param[1]; - /*<>*/ return caml_call3 - (CamlinternalFormat[7], + /*<>*/ return CamlinternalFormat[7].call + (null, function(acc){ /*<>*/ return caml_call1 (k, @@ -28370,8 +28159,8 @@ /*<>*/ return /*<>*/ caml_call1 (k, /*<>*/ flush_buffer_formatter(b, ppf)) /*<>*/ ; } - /*<>*/ return caml_call3 - (CamlinternalFormat[7], k$0, 0, fmt) /*<>*/ ; + /*<>*/ return CamlinternalFormat[7].call + (null, k$0, 0, fmt) /*<>*/ ; } function sprintf(fmt){ /*<>*/ return ksprintf(id, fmt) /*<>*/ ; @@ -28386,8 +28175,8 @@ /*<>*/ return /*<>*/ caml_call1 (k, /*<>*/ flush_buffer_formatter(b, ppf)) /*<>*/ ; } - /*<>*/ return caml_call3 - (CamlinternalFormat[7], k$0, 0, fmt) /*<>*/ ; + /*<>*/ return CamlinternalFormat[7].call + (null, k$0, 0, fmt) /*<>*/ ; } function asprintf(fmt){ /*<>*/ return kasprintf(id, fmt) /*<>*/ ; @@ -28402,10 +28191,9 @@ (Stdlib_Domain[11][2], err_formatter_key), 0) /*<>*/ ; } - /*<>*/ caml_call1 - (Stdlib[100], flush_standard_formatters); - /*<>*/ caml_call1 - (Stdlib_Domain[5], + /*<>*/ Stdlib[100].call(null, flush_standard_formatters); + /*<>*/ Stdlib_Domain[5].call + (null, function(param){ /*<>*/ flush_standard_formatters(0); var @@ -28646,11 +28434,6 @@ ? f(a0, a1, a2) : runtime.caml_call_gen(f, [a0, a1, a2]); } - function caml_call4(f, a0, a1, a2, a3){ - return (f.l >= 0 ? f.l : f.l = f.length) === 4 - ? f(a0, a1, a2, a3) - : runtime.caml_call_gen(f, [a0, a1, a2, a3]); - } var global_data = runtime.caml_get_global_data(), cst$3 = cst$5, @@ -28736,8 +28519,8 @@ function token_string(ib){ var token_buffer = /*<>*/ ib[8], - tok = /*<>*/ caml_call1(Stdlib_Buffer[2], token_buffer); - /*<>*/ caml_call1(Stdlib_Buffer[8], token_buffer); + tok = /*<>*/ Stdlib_Buffer[2].call(null, token_buffer); + /*<>*/ Stdlib_Buffer[8].call(null, token_buffer); /*<>*/ ib[6] = ib[6] + 1 | 0; /*<>*/ return tok; /*<>*/ } @@ -28747,7 +28530,7 @@ /*<>*/ return width$0; /*<>*/ } function store_char(width, ib, c){ - /*<>*/ caml_call2(Stdlib_Buffer[12], ib[8], c); + /*<>*/ Stdlib_Buffer[12].call(null, ib[8], c); /*<>*/ return ignore_char(width, ib) /*<>*/ ; } var default_token_buffer_size = /*<>*/ 1024; @@ -28760,7 +28543,7 @@ 0, 0, next, - caml_call1(Stdlib_Buffer[1], default_token_buffer_size), + Stdlib_Buffer[1].call(null, default_token_buffer_size), iname] /*<>*/ ; /*<>*/ } function from_string(s){ @@ -28781,7 +28564,7 @@ function from_function(_aw_){return create(_a_, _aw_);} var len = /*<>*/ 1024; function scan_close_at_end(ic){ - /*<>*/ caml_call1(Stdlib[93], ic); + /*<>*/ Stdlib[93].call(null, ic); /*<>*/ throw caml_maybe_attach_backtrace(Stdlib[12], 1); /*<>*/ } function scan_raise_at_end(ic){ @@ -28802,7 +28585,7 @@ /*<>*/ if(eof[1]) /*<>*/ throw caml_maybe_attach_backtrace (Stdlib[12], 1); - /*<>*/ lim[1] = caml_call4(Stdlib[84], ic, buf, 0, len); + /*<>*/ lim[1] = Stdlib[84].call(null, ic, buf, 0, len); /*<>*/ return 0 === lim[1] ? (eof [1] @@ -28837,10 +28620,10 @@ if(typeof match === "number") /*<>*/ return 0; /*<>*/ if(0 === match[0]){ var ic = match[1]; - /*<>*/ return caml_call1(Stdlib[93], ic) /*<>*/ ; + /*<>*/ return Stdlib[93].call(null, ic) /*<>*/ ; } var ic$0 = /*<>*/ match[2]; - /*<>*/ return caml_call1(Stdlib[93], ic$0) /*<>*/ ; + /*<>*/ return Stdlib[93].call(null, ic$0) /*<>*/ ; } var Scan_failure = @@ -28937,19 +28720,21 @@ /*<>*/ } function bad_input_escape(c){ /*<>*/ return /*<>*/ bad_input - ( /*<>*/ caml_call2(Stdlib_Printf[4], _d_, c)) /*<>*/ ; + ( /*<>*/ caml_call1 + (Stdlib_Printf[4].call(null, _d_), c)) /*<>*/ ; } function bad_token_length(message){ /*<>*/ return /*<>*/ bad_input - ( /*<>*/ caml_call2 - (Stdlib_Printf[4], _e_, message)) /*<>*/ ; + ( /*<>*/ caml_call1 + (Stdlib_Printf[4].call(null, _e_), message)) /*<>*/ ; } function bad_hex_float(param){ /*<>*/ return bad_input(cst_not_a_valid_float_in_hexad) /*<>*/ ; } function character_mismatch(c, ci){ /*<>*/ return /*<>*/ bad_input - ( /*<>*/ caml_call3(Stdlib_Printf[4], _g_, c, ci)) /*<>*/ ; + ( /*<>*/ caml_call2 + (Stdlib_Printf[4].call(null, _g_), c, ci)) /*<>*/ ; } function check_char(ib, c$0){ /*<>*/ if(10 === c$0){ @@ -28998,7 +28783,8 @@ ? s !== "true" ? /*<>*/ bad_input - ( /*<>*/ caml_call2(Stdlib_Printf[4], _h_, s)) + ( /*<>*/ caml_call1 + (Stdlib_Printf[4].call(null, _h_), s)) : 1 : 0 /*<>*/ ; } @@ -29029,29 +28815,29 @@ var _as_ = /*<>*/ token_string(ib), tok = - /*<>*/ /*<>*/ caml_call2 - (Stdlib[28], cst_0b, _as_); + /*<>*/ /*<>*/ Stdlib[28].call + (null, cst_0b, _as_); break; case 3: var _at_ = /*<>*/ token_string(ib), tok = - /*<>*/ /*<>*/ caml_call2 - (Stdlib[28], cst_0o, _at_); + /*<>*/ /*<>*/ Stdlib[28].call + (null, cst_0o, _at_); break; case 4: var _au_ = /*<>*/ token_string(ib), tok = - /*<>*/ /*<>*/ caml_call2 - (Stdlib[28], cst_0u, _au_); + /*<>*/ /*<>*/ Stdlib[28].call + (null, cst_0u, _au_); break; case 5: var _av_ = /*<>*/ token_string(ib), tok = - /*<>*/ /*<>*/ caml_call2 - (Stdlib[28], cst_0x, _av_); + /*<>*/ /*<>*/ Stdlib[28].call + (null, cst_0x, _av_); break; default: var @@ -29061,8 +28847,8 @@ var l = /*<>*/ caml_ml_string_length(tok); /*<>*/ if (0 !== l && 43 === /*<>*/ caml_string_get(tok, 0)) - /*<>*/ return caml_call3 - (Stdlib_String[16], tok, 1, l - 1 | 0) /*<>*/ ; + /*<>*/ return Stdlib_String[16].call + (null, tok, 1, l - 1 | 0) /*<>*/ ; /*<>*/ return tok; /*<>*/ } function token_float(ib){ @@ -29096,7 +28882,8 @@ var c = /*<>*/ checked_peek_char(ib); /*<>*/ if(9 < c - 48 >>> 0) /*<>*/ return /*<>*/ bad_input - ( /*<>*/ caml_call2(Stdlib_Printf[4], _j_, c)) /*<>*/ ; + ( /*<>*/ caml_call1 + (Stdlib_Printf[4].call(null, _j_), c)) /*<>*/ ; var width$0 = /*<>*/ store_char(width, ib, c); /*<>*/ return scan_decimal_digit_star(width$0, ib) /*<>*/ ; } @@ -29106,8 +28893,8 @@ var c$0 = /*<>*/ checked_peek_char(ib); /*<>*/ if(! caml_call1(digitp, c$0)) /*<>*/ return /*<>*/ bad_input - ( /*<>*/ caml_call3 - (Stdlib_Printf[4], _k_, c$0, basis)) /*<>*/ ; + ( /*<>*/ caml_call2 + (Stdlib_Printf[4].call(null, _k_), c$0, basis)) /*<>*/ ; var width$3 = /*<>*/ store_char(width$2, ib, c$0), width = /*<>*/ width$3; @@ -29258,7 +29045,7 @@ var width$2 = /*<>*/ store_char(width$0, ib, c), precision$0 = - /*<>*/ caml_call2(Stdlib_Int[10], width$2, precision), + /*<>*/ Stdlib_Int[10].call(null, width$2, precision), width$3 = /*<>*/ width$2 - (precision$0 - scan_fractional_part(precision$0, ib) | 0) @@ -29271,8 +29058,9 @@ function lowercase(c){ /*<>*/ return 25 < c - 65 >>> 0 ? c - : /*<>*/ caml_call1 - (Stdlib[29], (c - 65 | 0) + 97 | 0) /*<>*/ ; + : /*<>*/ Stdlib + [29].call + (null, (c - 65 | 0) + 97 | 0) /*<>*/ ; } var len = /*<>*/ caml_ml_string_length(str), @@ -29371,8 +29159,8 @@ else var precision$0 = - /*<>*/ caml_call2 - (Stdlib_Int[10], width$6, precision), + /*<>*/ Stdlib_Int[10].call + (null, width$6, precision), width$7 = /*<>*/ width$6 - @@ -29439,8 +29227,8 @@ var width$1 = /*<>*/ store_char(width$0, ib, c), precision$0 = - /*<>*/ caml_call2 - (Stdlib_Int[10], width$1, precision), + /*<>*/ Stdlib_Int[10].call + (null, width$1, precision), width_precision = /*<>*/ scan_fractional_part(precision$0, ib), frac_width = /*<>*/ precision$0 - width_precision | 0, @@ -29526,8 +29314,8 @@ if(112 === match){var width$5 = width$4; break a;} var precision$0 = - /*<>*/ caml_call2 - (Stdlib_Int[10], width$4, precision), + /*<>*/ Stdlib_Int[10].call + (null, width$4, precision), width$5 = /*<>*/ width$4 - @@ -29610,8 +29398,8 @@ var c = /*<>*/ peek_char(ib); /*<>*/ return ib[1] ? /*<>*/ bad_input - ( /*<>*/ caml_call2 - (Stdlib_Printf[4], _f_, message)) + ( /*<>*/ caml_call1 + (Stdlib_Printf[4].call(null, _f_), message)) : c /*<>*/ ; } function scan_backslash_char(width, ib){ @@ -29640,14 +29428,14 @@ b: { /*<>*/ if(0 <= c && 255 >= c){ - var _O_ = /*<>*/ caml_call1(Stdlib[29], c); + var _O_ = /*<>*/ Stdlib[29].call(null, c); break b; } var _O_ = /*<>*/ bad_input - ( /*<>*/ caml_call4 - (Stdlib_Printf[4], _l_, c0, c1$0, c2$0)); + ( /*<>*/ caml_call3 + (Stdlib_Printf[4].call(null, _l_), c0, c1$0, c2$0)); } /*<>*/ return store_char(width - 2 | 0, ib, _O_) /*<>*/ ; } @@ -29681,14 +29469,14 @@ b: { /*<>*/ if(0 <= c$0 && 255 >= c$0){ - var _N_ = /*<>*/ caml_call1(Stdlib[29], c$0); + var _N_ = /*<>*/ Stdlib[29].call(null, c$0); break b; } var _N_ = /*<>*/ bad_input - ( /*<>*/ caml_call3 - (Stdlib_Printf[4], _m_, c1, c2)); + ( /*<>*/ caml_call2 + (Stdlib_Printf[4].call(null, _m_), c1, c2)); } /*<>*/ return store_char(width - 2 | 0, ib, _N_) /*<>*/ ; case 0: @@ -29796,8 +29584,8 @@ if(_K_) var _L_ = - /*<>*/ caml_call2 - (CamlinternalFormat[1], char_set, c), + /*<>*/ CamlinternalFormat[1].call + (null, char_set, c), _I_ = /*<>*/ _L_ ? c !== stp ? 1 : 0 : _L_; else var _I_ = /*<>*/ _K_; @@ -29832,7 +29620,8 @@ } var i = /*<>*/ char_count(ib); /*<>*/ return /*<>*/ bad_input - ( /*<>*/ caml_call3(Stdlib_Printf[4], _o_, i, s)) /*<>*/ ; + ( /*<>*/ caml_call2 + (Stdlib_Printf[4].call(null, _o_), i, s)) /*<>*/ ; } function width_of_pad_opt(pad_opt){ /*<>*/ if(! pad_opt) @@ -29844,12 +29633,11 @@ /*<>*/ if(6 === fmting) /*<>*/ return _p_; var - str = - /*<>*/ caml_call1(CamlinternalFormat[17], fmting), + str = /*<>*/ CamlinternalFormat[17].call(null, fmting), stp = /*<>*/ caml_string_get(str, 1), sub_str = - /*<>*/ /*<>*/ caml_call3 - (Stdlib_String[16], + /*<>*/ /*<>*/ Stdlib_String[16].call + (null, str, 2, /*<>*/ caml_ml_string_length(str) - 2 | 0); @@ -29923,11 +29711,10 @@ rest$13 = /*<>*/ fmt[3], fmtty = fmt[2], _I_ = - /*<>*/ caml_call1 - (CamlinternalFormat[21], fmtty), + /*<>*/ CamlinternalFormat[21].call(null, fmtty), _H_ = - /*<>*/ caml_call1 - (CamlinternalFormatBasics[2], _I_); + /*<>*/ CamlinternalFormatBasics[2].call + (null, _I_); /*<>*/ if(counter >= 50) return caml_trampoline_return (take_fmtty_format_readers$0, [0, k, _H_, rest$13]) /*<>*/ ; @@ -29952,8 +29739,8 @@ rest$17 = fmt[2], fmt$0 = _G_[1][1], fmt$1 = - /*<>*/ caml_call2 - (CamlinternalFormatBasics[3], fmt$0, rest$17); + /*<>*/ CamlinternalFormatBasics[3].call + (null, fmt$0, rest$17); /*<>*/ fmt = fmt$1; } else{ @@ -29961,8 +29748,8 @@ rest$18 = /*<>*/ fmt[2], fmt$2 = _G_[1][1], fmt$3 = - /*<>*/ caml_call2 - (CamlinternalFormatBasics[3], fmt$2, rest$18); + /*<>*/ CamlinternalFormatBasics[3].call + (null, fmt$2, rest$18); /*<>*/ fmt = fmt$3; } break; @@ -30074,13 +29861,13 @@ ty2 = fmtty[2], ty1 = fmtty[1], _G_ = - /*<>*/ caml_call1(CamlinternalFormat[21], ty1), + /*<>*/ CamlinternalFormat[21].call(null, ty1), ty = - /*<>*/ caml_call2 - (CamlinternalFormat[22], _G_, ty2), + /*<>*/ CamlinternalFormat[22].call + (null, _G_, ty2), fmtty$9 = - /*<>*/ caml_call2 - (CamlinternalFormatBasics[1], ty, rest); + /*<>*/ CamlinternalFormatBasics[1].call + (null, ty, rest); /*<>*/ fmtty = fmtty$9; break; case 10: @@ -30200,8 +29987,8 @@ }; /*<>*/ return /*<>*/ pad_prec_scanf (ib, - /*<>*/ caml_call2 - (CamlinternalFormatBasics[3], fmt$0, rest$3), + /*<>*/ CamlinternalFormatBasics[3].call + (null, fmt$0, rest$3), readers, pad, 0, @@ -30217,8 +30004,8 @@ }; /*<>*/ return /*<>*/ pad_prec_scanf (ib, - /*<>*/ caml_call2 - (CamlinternalFormatBasics[3], fmt$1, rest$4), + /*<>*/ CamlinternalFormatBasics[3].call + (null, fmt$1, rest$4), readers, pad, 0, @@ -30251,8 +30038,8 @@ iconv = fmt[1], conv = /*<>*/ /*<>*/ integer_conversion_of_char - ( /*<>*/ caml_call1 - (CamlinternalFormat[16], iconv)), + ( /*<>*/ CamlinternalFormat[16].call + (null, iconv)), scan$4 = /*<>*/ function(width, param, ib){ /*<>*/ return scan_int_conversion @@ -30277,8 +30064,8 @@ iconv$0 = fmt[1], conv$0 = /*<>*/ /*<>*/ integer_conversion_of_char - ( /*<>*/ caml_call1 - (CamlinternalFormat[16], iconv$0)), + ( /*<>*/ CamlinternalFormat[16].call + (null, iconv$0)), scan$5 = /*<>*/ function(width, param, ib){ /*<>*/ return scan_int_conversion @@ -30303,8 +30090,8 @@ iconv$1 = fmt[1], conv$1 = /*<>*/ /*<>*/ integer_conversion_of_char - ( /*<>*/ caml_call1 - (CamlinternalFormat[16], iconv$1)), + ( /*<>*/ CamlinternalFormat[16].call + (null, iconv$1)), scan$6 = /*<>*/ function(width, param, ib){ /*<>*/ return scan_int_conversion @@ -30329,8 +30116,8 @@ iconv$2 = fmt[1], conv$2 = /*<>*/ /*<>*/ integer_conversion_of_char - ( /*<>*/ caml_call1 - (CamlinternalFormat[16], iconv$2)), + ( /*<>*/ CamlinternalFormat[16].call + (null, iconv$2)), scan$7 = /*<>*/ function(width, param, ib){ /*<>*/ return scan_int_conversion @@ -30403,8 +30190,8 @@ === c ? 4 : /*<>*/ bad_input - ( /*<>*/ caml_call2 - (Stdlib_Printf[4], _n_, c)); + ( /*<>*/ caml_call1 + (Stdlib_Printf[4].call(null, _n_), c)); /*<>*/ return scan_string(0, m, ib) /*<>*/ ; }; /*<>*/ return pad_prec_scanf @@ -30417,8 +30204,8 @@ break; case 11: var rest$15 = /*<>*/ fmt[2], str$0 = fmt[1]; - /*<>*/ caml_call2 - (Stdlib_String[30], + /*<>*/ Stdlib_String[30].call + (null, function(_G_){ /*<>*/ return check_char(ib, _G_);}, str$0); /*<>*/ fmt = rest$15; @@ -30439,8 +30226,8 @@ /*<>*/ try{ var _B_ = - /*<>*/ caml_call2 - (CamlinternalFormat[14], s, fmtty), + /*<>*/ CamlinternalFormat[14].call + (null, s, fmtty), fmt$2 = _B_; } catch(exn$0){ @@ -30465,28 +30252,28 @@ /*<>*/ try{ var fmt$5 = - /*<>*/ caml_call2 - (CamlinternalFormat[13], 0, s$0) + /*<>*/ CamlinternalFormat[13].call + (null, 0, s$0) [1], fmt$6 = - /*<>*/ caml_call2 - (CamlinternalFormat[13], 0, s$0) + /*<>*/ CamlinternalFormat[13].call + (null, 0, s$0) [1], _C_ = - /*<>*/ caml_call1 - (CamlinternalFormat[21], fmtty$0), + /*<>*/ CamlinternalFormat[21].call + (null, fmtty$0), _D_ = - /*<>*/ caml_call1 - (CamlinternalFormatBasics[2], _C_), + /*<>*/ CamlinternalFormatBasics[2].call + (null, _C_), fmt$7 = - /*<>*/ caml_call2 - (CamlinternalFormat[12], fmt$6, _D_), + /*<>*/ CamlinternalFormat[12].call + (null, fmt$6, _D_), _E_ = - /*<>*/ caml_call1 - (CamlinternalFormatBasics[2], fmtty$0), + /*<>*/ CamlinternalFormatBasics[2].call + (null, fmtty$0), _F_ = - /*<>*/ caml_call2 - (CamlinternalFormat[12], fmt$5, _E_), + /*<>*/ CamlinternalFormat[12].call + (null, fmt$5, _E_), fmt$4 = fmt$7, fmt$3 = _F_; } @@ -30503,24 +30290,24 @@ [0, fmt$3, s$0], /*<>*/ make_scanf (ib, - /*<>*/ caml_call2 - (CamlinternalFormatBasics[3], fmt$4, rest$18), + /*<>*/ CamlinternalFormatBasics[3].call + (null, fmt$4, rest$18), readers)] /*<>*/ ; case 15: - /*<>*/ return caml_call1 - (Stdlib[1], cst_scanf_bad_conversion_a) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_scanf_bad_conversion_a) /*<>*/ ; case 16: - /*<>*/ return caml_call1 - (Stdlib[1], cst_scanf_bad_conversion_t) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_scanf_bad_conversion_t) /*<>*/ ; case 17: var rest$19 = /*<>*/ fmt[2], formatting_lit = fmt[1], _G_ = - /*<>*/ caml_call1 - (CamlinternalFormat[17], formatting_lit); - /*<>*/ caml_call2 - (Stdlib_String[30], + /*<>*/ CamlinternalFormat[17].call + (null, formatting_lit); + /*<>*/ Stdlib_String[30].call + (null, function(_G_){ /*<>*/ return check_char(ib, _G_);}, _G_); /*<>*/ fmt = rest$19; @@ -30533,8 +30320,8 @@ /*<>*/ check_char(ib, 123); var fmt$9 = - /*<>*/ caml_call2 - (CamlinternalFormatBasics[3], fmt$8, rest$20); + /*<>*/ CamlinternalFormatBasics[3].call + (null, fmt$8, rest$20); /*<>*/ fmt = fmt$9; } else{ @@ -30543,16 +30330,16 @@ /*<>*/ check_char(ib, 91); var fmt$11 = - /*<>*/ caml_call2 - (CamlinternalFormatBasics[3], fmt$10, rest$21); + /*<>*/ CamlinternalFormatBasics[3].call + (null, fmt$10, rest$21); /*<>*/ fmt = fmt$11; } break; case 19: var fmt_rest = /*<>*/ fmt[1]; /*<>*/ if(! readers) - /*<>*/ return caml_call1 - (Stdlib[1], cst_scanf_missing_reader) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_scanf_missing_reader) /*<>*/ ; var readers_rest = /*<>*/ readers[2], reader = readers[1], @@ -30615,8 +30402,8 @@ rest$26 = /*<>*/ fmt[2], ign = fmt[1], fmt$12 = - /*<>*/ caml_call2 - (CamlinternalFormat[6], ign, rest$26) + /*<>*/ CamlinternalFormat[6].call + (null, ign, rest$26) [1], match$3 = /*<>*/ make_scanf(ib, fmt$12, readers); /*<>*/ if(! match$3) @@ -30625,8 +30412,8 @@ var arg_rest = /*<>*/ match$3[2]; /*<>*/ return arg_rest; default: - /*<>*/ return caml_call1 - (Stdlib[1], cst_scanf_bad_conversion_custo) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_scanf_bad_conversion_custo) /*<>*/ ; } } } @@ -30639,18 +30426,18 @@ /*<>*/ return [0, x$0, make_scanf(ib, fmt, readers)] /*<>*/ ; } /*<>*/ if(prec) - /*<>*/ return caml_call1 - (Stdlib[1], cst_scanf_bad_conversion) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_scanf_bad_conversion) /*<>*/ ; /*<>*/ caml_call3(scan, Stdlib[19], Stdlib[19], ib); var x = /*<>*/ caml_call1(token, ib); /*<>*/ return [0, x, make_scanf(ib, fmt, readers)] /*<>*/ ; } /*<>*/ if(0 !== pad[0]) - /*<>*/ return caml_call1 - (Stdlib[1], cst_scanf_bad_conversion$2) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_scanf_bad_conversion$2) /*<>*/ ; /*<>*/ if(! pad[1]) - /*<>*/ return caml_call1 - (Stdlib[1], cst_scanf_bad_conversion$1) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_scanf_bad_conversion$1) /*<>*/ ; var w = /*<>*/ pad[2]; if(typeof prec !== "number"){ var p$0 = prec[1]; @@ -30659,8 +30446,8 @@ /*<>*/ return [0, x$2, make_scanf(ib, fmt, readers)] /*<>*/ ; } /*<>*/ if(prec) - /*<>*/ return caml_call1 - (Stdlib[1], cst_scanf_bad_conversion$0) /*<>*/ ; + /*<>*/ return Stdlib[1].call + (null, cst_scanf_bad_conversion$0) /*<>*/ ; /*<>*/ caml_call3(scan, w, Stdlib[19], ib); var x$1 = /*<>*/ caml_call1(token, ib); /*<>*/ return [0, x$1, make_scanf(ib, fmt, readers)] /*<>*/ ; @@ -30668,7 +30455,7 @@ function kscanf_gen(ib, ef, af, param){ var str = /*<>*/ param[2], fmt = param[1]; function k(readers, f$1){ - /*<>*/ caml_call1(Stdlib_Buffer[9], ib[8]); + /*<>*/ Stdlib_Buffer[9].call(null, ib[8]); /*<>*/ try{ var args$1 = /*<>*/ make_scanf(ib, fmt, readers), @@ -30683,12 +30470,12 @@ if(tag !== Stdlib[6]) throw caml_maybe_attach_backtrace(exc, 0); var msg = exc[2], - _v_ = /*<>*/ caml_call1(Stdlib_String[25], str), - _w_ = caml_call2(Stdlib[28], _v_, cst$0), + _v_ = /*<>*/ Stdlib_String[25].call(null, str), + _w_ = Stdlib[28].call(null, _v_, cst$0), _x_ = - /*<>*/ caml_call2(Stdlib[28], cst_in_format, _w_), - _y_ = /*<>*/ caml_call2(Stdlib[28], msg, _x_); - /*<>*/ return caml_call1(Stdlib[1], _y_) /*<>*/ ; + /*<>*/ Stdlib[28].call(null, cst_in_format, _w_), + _y_ = /*<>*/ Stdlib[28].call(null, msg, _x_); + /*<>*/ return Stdlib[1].call(null, _y_) /*<>*/ ; } /*<>*/ return caml_call2(ef, ib, exc) /*<>*/ ; } @@ -30755,8 +30542,8 @@ /*<>*/ try{ var _v_ = - /*<>*/ caml_call2 - (CamlinternalFormat[15], str, format), + /*<>*/ CamlinternalFormat[15].call + (null, str, format), fmt = _v_; } catch(exn$0){ @@ -30774,20 +30561,20 @@ } function format_from_string(s, fmt){ var - _u_ = /*<>*/ caml_call1(Stdlib_String[25], s), - _v_ = caml_call2(Stdlib[28], _u_, cst$1); + _u_ = /*<>*/ Stdlib_String[25].call(null, s), + _v_ = Stdlib[28].call(null, _u_, cst$1); /*<>*/ return /*<>*/ sscanf_format - ( /*<>*/ caml_call2(Stdlib[28], cst$2, _v_), + ( /*<>*/ Stdlib[28].call(null, cst$2, _v_), fmt, function(x){ /*<>*/ return x; /*<>*/ }) /*<>*/ ; } function unescaped(s){ - var _u_ = /*<>*/ caml_call2(Stdlib[28], s, cst$3); + var _u_ = /*<>*/ Stdlib[28].call(null, s, cst$3); /*<>*/ return /*<>*/ caml_call1 (sscanf - ( /*<>*/ caml_call2(Stdlib[28], cst$4, _u_), + ( /*<>*/ Stdlib[28].call(null, cst$4, _u_), _t_), function(x){ /*<>*/ return x; @@ -30884,11 +30671,6 @@ ? f(a0, a1, a2) : runtime.caml_call_gen(f, [a0, a1, a2]); } - function caml_call5(f, a0, a1, a2, a3, a4){ - return (f.l >= 0 ? f.l : f.l = f.length) === 5 - ? f(a0, a1, a2, a3, a4) - : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4]); - } var global_data = runtime.caml_get_global_data(), Assert_failure = global_data.Assert_failure, @@ -30931,11 +30713,11 @@ /*<>*/ } var compare = /*<>*/ caml_string_compare, - Vars = caml_call1(Stdlib_Map[1], [0, compare]), + Vars = Stdlib_Map[1].call(null, [0, compare]), compare$0 = caml_string_compare, - Meths = caml_call1(Stdlib_Map[1], [0, compare$0]), + Meths = Stdlib_Map[1].call(null, [0, compare$0]), compare$1 = runtime.caml_int_compare, - Labs = caml_call1(Stdlib_Map[1], [0, compare$1]), + Labs = Stdlib_Map[1].call(null, [0, compare$1]), dummy_table = [0, 0, [0, 0], Meths[1], Labs[1], 0, 0, Vars[1], 0], table_count = [0, 0], dummy_met = /*<>*/ caml_obj_block(0, 0), @@ -31001,8 +30783,8 @@ var new_buck = /*<>*/ caml_array_make(new_size, dummy_met); - /*<>*/ caml_call5 - (Stdlib_Array[9], array[2], 0, new_buck, 0, old_size); + /*<>*/ Stdlib_Array[9].call + (null, array[2], 0, new_buck, 0, old_size); /*<>*/ array[2] = new_buck; var _w_ = 0; } @@ -31044,8 +30826,8 @@ } /*<>*/ } function get_method_labels(table, names){ - /*<>*/ return caml_call2 - (Stdlib_Array[14], + /*<>*/ return Stdlib_Array[14].call + (null, function(_v_){ /*<>*/ return get_method_label (table, _v_); @@ -31069,8 +30851,8 @@ /*<>*/ try{ var _v_ = - /*<>*/ caml_call2 - (Stdlib_List[53], label, table[6]); + /*<>*/ Stdlib_List[53].call + (null, label, table[6]); return _v_; } catch(exn$0){ @@ -31085,8 +30867,9 @@ function to_list(arr){ /*<>*/ return 0 === arr ? 0 - : /*<>*/ caml_call1 - (Stdlib_Array[10], arr) /*<>*/ ; + : /*<>*/ Stdlib_Array + [10].call + (null, arr) /*<>*/ ; } function narrow(table, vars, virt_meths, concr_meths){ var @@ -31094,16 +30877,16 @@ virt_meths$0 = /*<>*/ to_list(virt_meths), concr_meths$0 = /*<>*/ to_list(concr_meths), virt_meth_labs = - /*<>*/ caml_call2 - (Stdlib_List[20], + /*<>*/ Stdlib_List[20].call + (null, function(_v_){ /*<>*/ return get_method_label (table, _v_); }, virt_meths$0), concr_meth_labs = - /*<>*/ caml_call2 - (Stdlib_List[20], + /*<>*/ Stdlib_List[20].call + (null, function(_v_){ /*<>*/ return get_method_label (table, _v_); @@ -31117,8 +30900,8 @@ caml_call3 (Vars[24], function(lab, info, tvars){ - /*<>*/ return caml_call2 - (Stdlib_List[37], lab, vars$0) + /*<>*/ return Stdlib_List[37].call + (null, lab, vars$0) ? /*<>*/ caml_call3 (Vars[2], lab, info, tvars) : tvars /*<>*/ ; @@ -31128,8 +30911,8 @@ var by_name = /*<>*/ [0, Meths[1]], by_label = /*<>*/ [0, Labs[1]]; - /*<>*/ caml_call3 - (Stdlib_List[28], + /*<>*/ Stdlib_List[28].call + (null, function(met, label){ /*<>*/ by_name[1] = caml_call3(Meths[2], met, label, by_name[1]); @@ -31152,8 +30935,8 @@ }, concr_meths$0, concr_meth_labs); - /*<>*/ caml_call3 - (Stdlib_List[28], + /*<>*/ Stdlib_List[28].call + (null, function(met, label){ /*<>*/ by_name[1] = caml_call3(Meths[2], met, label, by_name[1]); @@ -31166,12 +30949,12 @@ /*<>*/ table[3] = by_name[1]; /*<>*/ table[4] = by_label[1]; /*<>*/ table[6] = - caml_call3 - (Stdlib_List[27], + Stdlib_List[27].call + (null, function(met, hm){ var lab = /*<>*/ met[1]; - /*<>*/ return caml_call2 - (Stdlib_List[37], lab, virt_meth_labs) + /*<>*/ return Stdlib_List[37].call + (null, lab, virt_meth_labs) ? hm : [0, met, hm] /*<>*/ ; }, @@ -31182,7 +30965,7 @@ function widen(table){ var match = - /*<>*/ caml_call1(Stdlib_List[6], table[5]), + /*<>*/ Stdlib_List[6].call(null, table[5]), vars = /*<>*/ match[6], virt_meths = match[5], saved_vars = match[4], @@ -31190,10 +30973,10 @@ by_label = match[2], by_name = match[1]; /*<>*/ table[5] = - caml_call1(Stdlib_List[7], table[5]); + Stdlib_List[7].call(null, table[5]); /*<>*/ table[7] = - caml_call3 - (Stdlib_List[26], + Stdlib_List[26].call + (null, function(s, v){ var _t_ = @@ -31206,12 +30989,12 @@ /*<>*/ table[3] = by_name; /*<>*/ table[4] = by_label; /*<>*/ table[6] = - caml_call3 - (Stdlib_List[27], + Stdlib_List[27].call + (null, function(met, hm){ var lab = /*<>*/ met[1]; - /*<>*/ return caml_call2 - (Stdlib_List[37], lab, virt_meths) + /*<>*/ return Stdlib_List[37].call + (null, lab, virt_meths) ? hm : [0, met, hm] /*<>*/ ; }, @@ -31301,8 +31084,8 @@ } /*<>*/ } function get_variables(table, names){ - /*<>*/ return caml_call2 - (Stdlib_Array[14], + /*<>*/ return Stdlib_Array[14].call + (null, function(_l_){ /*<>*/ return get_variable (table, _l_); @@ -31318,11 +31101,11 @@ /*<>*/ return new_table([0]) /*<>*/ ; var tags = - /*<>*/ caml_call2 - (Stdlib_Array[14], public_method_label, public_methods), + /*<>*/ Stdlib_Array[14].call + (null, public_method_label, public_methods), table = /*<>*/ new_table(tags); - /*<>*/ caml_call2 - (Stdlib_Array[13], + /*<>*/ Stdlib_Array[13].call + (null, function(i, met){ var lab = /*<>*/ (i * 2 | 0) + 2 | 0; /*<>*/ table[3] = @@ -31338,7 +31121,7 @@ /*<>*/ inst_var_count[1] = (inst_var_count[1] + table[1] | 0) - 1 | 0; /*<>*/ table[8] = - caml_call1(Stdlib_List[10], table[8]); + Stdlib_List[10].call(null, table[8]); var _l_ = /*<>*/ Stdlib_Sys[9]; return /*<>*/ resize (table, @@ -31367,8 +31150,8 @@ _i_ = /*<>*/ to_array(concr_meths), _j_ = /*<>*/ [0, - caml_call2 - (Stdlib_Array[14], + Stdlib_Array[14].call + (null, function(nm){ /*<>*/ return /*<>*/ get_method (cla, @@ -31381,14 +31164,14 @@ /*<>*/ [0, [0, init], [0, - caml_call2 - (Stdlib_Array[14], + Stdlib_Array[14].call + (null, function(_l_){ /*<>*/ return get_variable(cla, _l_); }, _k_), _j_]]; - /*<>*/ return caml_call1(Stdlib_Array[5], _l_) /*<>*/ ; + /*<>*/ return Stdlib_Array[5].call(null, _l_) /*<>*/ ; } function make_class(pub_meths, class_init){ var @@ -31910,15 +31693,16 @@ var _h_ = /*<>*/ caml_obj_tag(l); if(250 === _h_) return l[1]; if(246 !== _h_ && 244 !== _h_) return l; - return caml_call1(CamlinternalLazy[2], l); + return CamlinternalLazy[2].call(null, l); }]); var init = /*<>*/ l; break; default: var init = - /*<>*/ /*<>*/ caml_call1 - (CamlinternalOO[21], loc); + /*<>*/ /*<>*/ CamlinternalOO + [21].call + (null, loc); } else if(0 === shape[0]) var @@ -31944,8 +31728,8 @@ var comps = shape[1]; /*<>*/ return init_mod_block(loc, comps) /*<>*/ ; } - /*<>*/ return caml_call1 - (Stdlib[2], cst_CamlinternalMod_init_mod_n) /*<>*/ ; + /*<>*/ return Stdlib[2].call + (null, cst_CamlinternalMod_init_mod_n) /*<>*/ ; } function update_mod_block(comps$0, modu, n){ /*<>*/ if @@ -32002,8 +31786,8 @@ var comps = shape[1]; /*<>*/ return update_mod_block(comps, o, n) /*<>*/ ; } - /*<>*/ return caml_call1 - (Stdlib[2], cst_CamlinternalMod_update_mod) /*<>*/ ; + /*<>*/ return Stdlib[2].call + (null, cst_CamlinternalMod_update_mod) /*<>*/ ; } var CamlinternalMod = /*<>*/ [0, init_mod, update_mod]; runtime.caml_register_global(8, CamlinternalMod, "CamlinternalMod"); @@ -32049,16 +31833,6 @@ ? f(a0, a1, a2) : runtime.caml_call_gen(f, [a0, a1, a2]); } - function caml_call4(f, a0, a1, a2, a3){ - return (f.l >= 0 ? f.l : f.l = f.length) === 4 - ? f(a0, a1, a2, a3) - : runtime.caml_call_gen(f, [a0, a1, a2, a3]); - } - function caml_call5(f, a0, a1, a2, a3, a4){ - return (f.l >= 0 ? f.l : f.l = f.length) === 5 - ? f(a0, a1, a2, a3, a4) - : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4]); - } var global_data = runtime.caml_get_global_data(), f$1 = cst_ensure_capacity$0, @@ -32076,35 +31850,35 @@ CamlinternalOO = global_data.CamlinternalOO, _a_ = [0, 0]; function copy(a, dummy){ - var _ae_ = /*<>*/ Stdlib_Obj[17]; - if(caml_obj_tag(a) !== _ae_) - /*<>*/ return caml_call1(Stdlib_Array[7], a) /*<>*/ ; + var _af_ = /*<>*/ Stdlib_Obj[17]; + if(caml_obj_tag(a) !== _af_) + /*<>*/ return Stdlib_Array[7].call(null, a) /*<>*/ ; var n = /*<>*/ a.length - 1, arr = /*<>*/ caml_array_make(n, dummy), - _ad_ = /*<>*/ n - 1 | 0, - _af_ = 0; - if(_ad_ >= 0){ - var i = _af_; + _ae_ = /*<>*/ n - 1 | 0, + _ag_ = 0; + if(_ae_ >= 0){ + var i = _ag_; for(;;){ var v = /*<>*/ a[i + 1]; /*<>*/ arr[i + 1] = v; - var _ag_ = /*<>*/ i + 1 | 0; - if(_ad_ === i) break; - i = _ag_; + var _ah_ = /*<>*/ i + 1 | 0; + if(_ae_ === i) break; + i = _ah_; } } /*<>*/ return arr; /*<>*/ } function prefix(arr, n){ - /*<>*/ return caml_call3(Stdlib_Array[6], arr, 0, n) /*<>*/ ; + /*<>*/ return Stdlib_Array[6].call(null, arr, 0, n) /*<>*/ ; } function extend(arr, length, dummy, new_capacity){ var new_arr = /*<>*/ caml_array_make(new_capacity, dummy); - /*<>*/ caml_call5 - (Stdlib_Array[9], arr, 0, new_arr, 0, length); + /*<>*/ Stdlib_Array[9].call + (null, arr, 0, new_arr, 0, length); /*<>*/ return new_arr; /*<>*/ } var @@ -32269,38 +32043,39 @@ cst_x = "x"; if(! _a_[1]){ var - _b_ = caml_call1(CamlinternalOO[16], 0), - _c_ = caml_call2(CamlinternalOO[3], _b_, cst_x); - caml_call1(CamlinternalOO[17], _b_); + _b_ = CamlinternalOO[16].call(null, 0), + _c_ = CamlinternalOO[3].call(null, _b_, cst_x); + CamlinternalOO[17].call(null, _b_); _a_[1] = - function(_ad_){ - var _ac_ = /*<>*/ caml_call2(CamlinternalOO[24], 0, _b_); - _ac_[_c_ + 1] = _ad_[2]; - return _ac_; + function(_ae_){ + var _ad_ = /*<>*/ CamlinternalOO[24].call(null, 0, _b_); + _ad_[_c_ + 1] = _ae_[2]; + return _ad_; }; } var dummy = /*<>*/ caml_call1(_a_[1], [0, 0, r]); /*<>*/ r[1] = [0, dummy]; function index_out_of_bounds(f, i, length){ /*<>*/ return 0 === length - ? /*<>*/ caml_call4 - (Stdlib_Printf[10], Stdlib[1], _f_, f, i) - : /*<>*/ caml_call5 - (Stdlib_Printf[10], Stdlib[1], _g_, f, i, length - 1 | 0) /*<>*/ ; + ? /*<>*/ caml_call2 + (Stdlib_Printf[10].call(null, Stdlib[1], _f_), f, i) + : /*<>*/ caml_call3 + (Stdlib_Printf[10].call(null, Stdlib[1], _g_), + f, + i, + length - 1 | 0) /*<>*/ ; } function negative_length_requested(f, n){ - /*<>*/ return caml_call4 - (Stdlib_Printf[10], Stdlib[1], _h_, f, n) /*<>*/ ; + /*<>*/ return caml_call2 + (Stdlib_Printf[10].call(null, Stdlib[1], _h_), f, n) /*<>*/ ; } function negative_capacity_requested(f, n){ - /*<>*/ return caml_call4 - (Stdlib_Printf[10], Stdlib[1], _i_, f, n) /*<>*/ ; + /*<>*/ return caml_call2 + (Stdlib_Printf[10].call(null, Stdlib[1], _i_), f, n) /*<>*/ ; } function missing_element(i, length){ - /*<>*/ return caml_call5 - (Stdlib_Printf[10], - Stdlib[1], - _k_, + /*<>*/ return caml_call3 + (Stdlib_Printf[10].call(null, Stdlib[1], _k_), invalid_state_description, i, length) /*<>*/ ; @@ -32308,25 +32083,26 @@ function check_same_length(f, param, expected){ var length_a = /*<>*/ param[1], - _ac_ = /*<>*/ expected !== length_a ? 1 : 0; - return _ac_ - ? /*<>*/ caml_call5 - (Stdlib_Printf[10], Stdlib[1], _m_, f, expected, length_a) - : _ac_ /*<>*/ ; + _ad_ = /*<>*/ expected !== length_a ? 1 : 0; + return _ad_ + ? /*<>*/ caml_call3 + (Stdlib_Printf[10].call(null, Stdlib[1], _m_), + f, + expected, + length_a) + : _ad_ /*<>*/ ; } function check_valid_length(length, arr){ var capacity = /*<>*/ arr.length - 1, - _ac_ = /*<>*/ capacity < length ? 1 : 0; - return _ac_ - ? /*<>*/ caml_call5 - (Stdlib_Printf[10], - Stdlib[1], - _l_, + _ad_ = /*<>*/ capacity < length ? 1 : 0; + return _ad_ + ? /*<>*/ caml_call3 + (Stdlib_Printf[10].call(null, Stdlib[1], _l_), invalid_state_description, length, capacity) - : _ac_ /*<>*/ ; + : _ad_ /*<>*/ ; } function unsafe_get(arr, dummy, i, length){ var v = /*<>*/ arr[i + 1]; @@ -32340,15 +32116,15 @@ function make(n, x){ /*<>*/ if(n < 0) /*<>*/ negative_length_requested(cst_make, n); - var _ac_ = /*<>*/ Stdlib_Obj[16]; - if(caml_obj_tag(x) !== _ac_) + var _ad_ = /*<>*/ Stdlib_Obj[16]; + if(caml_obj_tag(x) !== _ad_) var arr$0 = /*<>*/ /*<>*/ caml_array_make (n, x); else{ var arr = /*<>*/ caml_array_make(n, dummy); - /*<>*/ caml_call4(Stdlib_Array[8], arr, 0, n, x); + /*<>*/ Stdlib_Array[8].call(null, arr, 0, n, x); var arr$0 = /*<>*/ arr; } /*<>*/ return [0, n, arr$0, dummy]; @@ -32358,16 +32134,16 @@ /*<>*/ negative_length_requested(cst_init, n); var arr = /*<>*/ caml_array_make(n, dummy), - _aa_ = /*<>*/ n - 1 | 0, - _ab_ = 0; - if(_aa_ >= 0){ - var i = _ab_; + _ab_ = /*<>*/ n - 1 | 0, + _ac_ = 0; + if(_ab_ >= 0){ + var i = _ac_; for(;;){ var v = /*<>*/ caml_call1(f, i); /*<>*/ arr[i + 1] = v; - var _ac_ = /*<>*/ i + 1 | 0; - if(_aa_ === i) break; - i = _ac_; + var _ad_ = /*<>*/ i + 1 | 0; + if(_ab_ === i) break; + i = _ad_; } } /*<>*/ return [0, n, arr, dummy]; @@ -32413,8 +32189,8 @@ var length = /*<>*/ a[1], arr = a[2], dummy = a[3]; /*<>*/ check_valid_length(length, arr); /*<>*/ if(0 === length) - /*<>*/ caml_call3 - (Stdlib_Printf[10], Stdlib[1], _n_, f$0); + /*<>*/ caml_call1 + (Stdlib_Printf[10].call(null, Stdlib[1], _n_), f$0); /*<>*/ return unsafe_get (arr, dummy, length - 1 | 0, length) /*<>*/ ; } @@ -32460,16 +32236,16 @@ function remove_last(a){ var last = /*<>*/ a[1] - 1 | 0, - _$_ = /*<>*/ 0 <= last ? 1 : 0; - if(_$_){ + _aa_ = /*<>*/ 0 <= last ? 1 : 0; + if(_aa_){ /*<>*/ a[1] = last; var dummy = /*<>*/ a[3]; caml_check_bound(a[2], last)[last + 1] = dummy; - var _aa_ = /*<>*/ 0; + var _ab_ = /*<>*/ 0; } else - var _aa_ = /*<>*/ _$_; - return _aa_; + var _ab_ = /*<>*/ _aa_; + return _ab_; /*<>*/ } function truncate(a, n){ /*<>*/ if(n < 0) @@ -32480,8 +32256,8 @@ : (a [1] = n, - /*<>*/ caml_call4 - (Stdlib_Array[8], arr, n, length - n | 0, dummy)) /*<>*/ ; + /*<>*/ Stdlib_Array[8].call + (null, arr, n, length - n | 0, dummy)) /*<>*/ ; } function clear(a){ /*<>*/ return truncate(a, 0) /*<>*/ ; @@ -32498,25 +32274,25 @@ (cst_ensure_capacity, capacity_request) /*<>*/ ; /*<>*/ if(capacity_request <= cur_capacity) /*<>*/ return 0; - /*<>*/ if(Stdlib_Sys[13] < capacity_request) - /*<>*/ caml_call5 - (Stdlib_Printf[10], - Stdlib[1], - _j_, + /*<>*/ if(Stdlib_Sys[13] < capacity_request){ + var _Z_ = /*<>*/ Stdlib_Sys[13]; + caml_call3 + (Stdlib_Printf[10].call(null, Stdlib[1], _j_), f$1, capacity_request, - Stdlib_Sys[13]); + _Z_); + } var n = /*<>*/ 512 < cur_capacity ? cur_capacity + (cur_capacity / 2 | 0) | 0 : cur_capacity * 2 | 0, - _Z_ = /*<>*/ Stdlib_Sys[13], - ___ = caml_call2(Stdlib[17], 8, n), - _$_ = /*<>*/ caml_call2(Stdlib[16], ___, _Z_), + ___ = /*<>*/ Stdlib_Sys[13], + _$_ = Stdlib[17].call(null, 8, n), + _aa_ = /*<>*/ Stdlib[16].call(null, _$_, ___), new_capacity = - /*<>*/ caml_call2 - (Stdlib[17], _$_, capacity_request); + /*<>*/ Stdlib[17].call + (null, _aa_, capacity_request); /*<>*/ if(0 >= new_capacity) throw caml_maybe_attach_backtrace([0, Assert_failure, _q_], 1); var @@ -32549,7 +32325,7 @@ arr = /*<>*/ a[2], cur_capacity = /*<>*/ arr.length - 1; /*<>*/ if(n < cur_capacity){ - /*<>*/ a[1] = caml_call2(Stdlib[16], a[1], n); + /*<>*/ a[1] = Stdlib[16].call(null, a[1], n); /*<>*/ a[2] = prefix(arr, n); /*<>*/ return 0; } @@ -32599,8 +32375,8 @@ b) /*<>*/ ; } function append_seq(a, seq){ - /*<>*/ return caml_call2 - (Stdlib_Seq[4], + /*<>*/ return Stdlib_Seq[4].call + (null, function(x){ /*<>*/ return add_last(a, x) /*<>*/ ; }, @@ -32617,13 +32393,8 @@ /*<>*/ dst[1] = dst_pos + blit_length | 0; var dst_dummy = /*<>*/ dst[3], src_dummy = src[3]; /*<>*/ if(src_dummy === dst_dummy) - /*<>*/ return caml_call5 - (Stdlib_Array[9], - src_arr, - src_pos, - dst_arr, - dst_pos, - blit_length) /*<>*/ ; + /*<>*/ return Stdlib_Array[9].call + (null, src_arr, src_pos, dst_arr, dst_pos, blit_length) /*<>*/ ; var _Q_ = /*<>*/ blit_length < 0 ? 1 : 0; if(_Q_) var _P_ = _Q_; @@ -32672,16 +32443,14 @@ function blit(src, src_pos, dst, dst_pos, len){ var src_length = /*<>*/ src[1], dst_length = dst[1]; /*<>*/ if(len < 0) - /*<>*/ caml_call3 - (Stdlib_Printf[10], Stdlib[1], _r_, len); + /*<>*/ caml_call1 + (Stdlib_Printf[10].call(null, Stdlib[1], _r_), len); var _M_ = /*<>*/ src_pos < 0 ? 1 : 0, _N_ = _M_ || (src_length < (src_pos + len | 0) ? 1 : 0); if(_N_) - /*<>*/ caml_call5 - (Stdlib_Printf[10], - Stdlib[1], - _s_, + /*<>*/ caml_call3 + (Stdlib_Printf[10].call(null, Stdlib[1], _s_), src_pos, src_pos + len | 0, src_length); @@ -32689,10 +32458,8 @@ _O_ = /*<>*/ dst_pos < 0 ? 1 : 0, _P_ = _O_ || (dst_length < dst_pos ? 1 : 0); if(_P_) - /*<>*/ caml_call5 - (Stdlib_Printf[10], - Stdlib[1], - _t_, + /*<>*/ caml_call3 + (Stdlib_Printf[10].call(null, Stdlib[1], _t_), dst_pos, dst_pos + len | 0, dst_length); @@ -32710,8 +32477,8 @@ /*<>*/ param[1] = length_a + length_b | 0; var _K_ = /*<>*/ Stdlib_Obj[17], src_pos = 0; if(caml_obj_tag(src) !== _K_) - /*<>*/ caml_call5 - (Stdlib_Array[9], src, src_pos, arr, length_a, length_b); + /*<>*/ Stdlib_Array[9].call + (null, src, src_pos, arr, length_a, length_b); else{ var _H_ = /*<>*/ length_b - 1 | 0, _L_ = 0; if(_H_ >= 0){ @@ -33172,8 +32939,8 @@ /*<>*/ check_valid_length(length, arr); var res = - /*<>*/ caml_call2 - (Stdlib_Array[1], + /*<>*/ Stdlib_Array[1].call + (null, length, function(i){ /*<>*/ return unsafe_get(arr, dummy, i, length) /*<>*/ ; @@ -33183,7 +32950,7 @@ /*<>*/ } function of_list(li){ var - a = /*<>*/ caml_call1(Stdlib_Array[11], li), + a = /*<>*/ Stdlib_Array[11].call(null, li), length = /*<>*/ a.length - 1, _v_ = /*<>*/ Stdlib_Obj[17], arr = @@ -33378,7 +33145,7 @@ random = /*<>*/ opt ? opt[1] - : /*<>*/ caml_call1(Stdlib_Hashtbl[17], 0), + : /*<>*/ Stdlib_Hashtbl[17].call(null, 0), x = /*<>*/ 16; for(;;){ /*<>*/ if(initial_size <= x) break; @@ -33393,7 +33160,7 @@ var _H_ = prng[1]; else{ if(246 !== _G_ && 244 !== _G_){var _H_ = prng; break a;} - var _H_ = caml_call1(CamlinternalLazy[2], prng); + var _H_ = CamlinternalLazy[2].call(null, prng); } var seed = @@ -33439,7 +33206,7 @@ var _C_ = /*<>*/ h[4], _D_ = h[3], - _E_ = caml_call1(Stdlib_Array[7], h[2]); + _E_ = Stdlib_Array[7].call(null, h[2]); /*<>*/ return [0, h[1], _E_, _D_, _C_]; /*<>*/ } function key_index(h, hkey){ @@ -33755,18 +33522,18 @@ function stats(h){ var mbl = - /*<>*/ caml_call3 - (Stdlib_Array[18], + /*<>*/ Stdlib_Array[18].call + (null, function(m, b){ var _u_ = /*<>*/ bucket_length(0, b); - /*<>*/ return caml_call2 - (Stdlib_Int[11], m, _u_); + /*<>*/ return Stdlib_Int[11].call + (null, m, _u_); }, 0, h[2]), histo = /*<>*/ caml_array_make(mbl + 1 | 0, 0); - /*<>*/ caml_call2 - (Stdlib_Array[12], + /*<>*/ Stdlib_Array[12].call + (null, function(b){ var l = /*<>*/ bucket_length(0, b); /*<>*/ histo[l + 1] = @@ -33800,18 +33567,18 @@ var size = /*<>*/ [0, 0], mbl = - /*<>*/ caml_call3 - (Stdlib_Array[18], + /*<>*/ Stdlib_Array[18].call + (null, function(m, b){ var _u_ = /*<>*/ bucket_length_alive(0, b); - /*<>*/ return caml_call2 - (Stdlib_Int[11], m, _u_); + /*<>*/ return Stdlib_Int[11].call + (null, m, _u_); }, 0, h[2]), histo = /*<>*/ caml_array_make(mbl + 1 | 0, 0); - /*<>*/ caml_call2 - (Stdlib_Array[12], + /*<>*/ Stdlib_Array[12].call + (null, function(b){ var l = /*<>*/ bucket_length_alive(0, b); /*<>*/ size[1] = size[1] + l | 0; @@ -33827,8 +33594,8 @@ histo]; /*<>*/ } function add_seq(tbl, i){ - /*<>*/ return caml_call2 - (Stdlib_Seq[4], + /*<>*/ return Stdlib_Seq[4].call + (null, function(param){ var v = /*<>*/ param[2], k = param[1]; /*<>*/ return add(tbl, k, v) /*<>*/ ; @@ -33836,8 +33603,8 @@ i) /*<>*/ ; } function replace_seq(tbl, i){ - /*<>*/ return caml_call2 - (Stdlib_Seq[4], + /*<>*/ return Stdlib_Seq[4].call + (null, function(param){ var v = /*<>*/ param[2], k = param[1]; /*<>*/ return replace(tbl, k, v) /*<>*/ ; @@ -34009,7 +33776,7 @@ /*<>*/ return 0; var h = /*<>*/ l[1], t = l[2]; /*<>*/ if(test_key(k, h)){ - /*<>*/ b[1] = caml_call2(Stdlib_List[13], acc, t); + /*<>*/ b[1] = Stdlib_List[13].call(null, acc, t); /*<>*/ return 0; } var @@ -34022,8 +33789,8 @@ function find(b, k){ var match = - /*<>*/ caml_call2 - (Stdlib_List[40], + /*<>*/ Stdlib_List[40].call + (null, function(_u_){ /*<>*/ return test_key(k, _u_);}, b[1]); /*<>*/ if(! match) @@ -34032,7 +33799,7 @@ /*<>*/ return get_data(e) /*<>*/ ; } function length(b){ - /*<>*/ return caml_call1(Stdlib_List[1], b[1]) /*<>*/ ; + /*<>*/ return Stdlib_List[1].call(null, b[1]) /*<>*/ ; } function clear(b){ /*<>*/ b[1] = 0; @@ -34227,7 +33994,7 @@ /*<>*/ return 0; var h = /*<>*/ l[1], t = l[2]; /*<>*/ if(test_keys(k1, k2, h)){ - /*<>*/ b[1] = caml_call2(Stdlib_List[13], acc, t); + /*<>*/ b[1] = Stdlib_List[13].call(null, acc, t); /*<>*/ return 0; } var @@ -34240,8 +34007,8 @@ function find$0(b, k1, k2){ var match = - /*<>*/ caml_call2 - (Stdlib_List[40], + /*<>*/ Stdlib_List[40].call + (null, function(_u_){ /*<>*/ return test_keys(k1, k2, _u_); }, @@ -34252,7 +34019,7 @@ /*<>*/ return get_data$0(e) /*<>*/ ; } function length$0(b){ - /*<>*/ return caml_call1(Stdlib_List[1], b[1]) /*<>*/ ; + /*<>*/ return Stdlib_List[1].call(null, b[1]) /*<>*/ ; } function clear$0(b){ /*<>*/ b[1] = 0; @@ -34531,7 +34298,7 @@ /*<>*/ return 0; var h = /*<>*/ l[1], t = l[2]; /*<>*/ if(test_keys$0(k, h)){ - /*<>*/ b[1] = caml_call2(Stdlib_List[13], acc, t); + /*<>*/ b[1] = Stdlib_List[13].call(null, acc, t); /*<>*/ return 0; } var @@ -34544,8 +34311,8 @@ function find$1(b, k){ var match = - /*<>*/ caml_call2 - (Stdlib_List[40], + /*<>*/ Stdlib_List[40].call + (null, function(_c_){ /*<>*/ return test_keys$0(k, _c_); }, @@ -34556,7 +34323,7 @@ /*<>*/ return get_data$1(e) /*<>*/ ; } function length$2(b){ - /*<>*/ return caml_call1(Stdlib_List[1], b[1]) /*<>*/ ; + /*<>*/ return Stdlib_List[1].call(null, b[1]) /*<>*/ ; } function clear$1(b){ /*<>*/ b[1] = 0; @@ -34632,11 +34399,6 @@ ? f(a0, a1, a2) : runtime.caml_call_gen(f, [a0, a1, a2]); } - function caml_call4(f, a0, a1, a2, a3){ - return (f.l >= 0 ? f.l : f.l = f.length) === 4 - ? f(a0, a1, a2, a3) - : runtime.caml_call_gen(f, [a0, a1, a2, a3]); - } var global_data = runtime.caml_get_global_data(), cst$18 = cst$19, @@ -34688,8 +34450,8 @@ n = n$3; for(;;){ /*<>*/ if(0 > n) - /*<>*/ return caml_call3 - (Stdlib_String[16], name, 0, 1) /*<>*/ ; + /*<>*/ return Stdlib_String[16].call + (null, name, 0, 1) /*<>*/ ; /*<>*/ if(! caml_call2(is_dir_sep, name, n)) break; var n$0 = /*<>*/ n - 1 | 0; n = n$0; @@ -34697,11 +34459,11 @@ var p = /*<>*/ n + 1 | 0, n$1 = n; for(;;){ /*<>*/ if(0 > n$1) - /*<>*/ return caml_call3 - (Stdlib_String[16], name, 0, p) /*<>*/ ; + /*<>*/ return Stdlib_String[16].call + (null, name, 0, p) /*<>*/ ; /*<>*/ if(caml_call2(is_dir_sep, name, n$1)) - /*<>*/ return caml_call3 - (Stdlib_String[16], name, n$1 + 1 | 0, (p - n$1 | 0) - 1 | 0) /*<>*/ ; + /*<>*/ return Stdlib_String[16].call + (null, name, n$1 + 1 | 0, (p - n$1 | 0) - 1 | 0) /*<>*/ ; var n$2 = /*<>*/ n$1 - 1 | 0; n$1 = n$2; } @@ -34714,8 +34476,8 @@ n = n$5; for(;;){ /*<>*/ if(0 > n) - /*<>*/ return caml_call3 - (Stdlib_String[16], name, 0, 1) /*<>*/ ; + /*<>*/ return Stdlib_String[16].call + (null, name, 0, 1) /*<>*/ ; /*<>*/ if(! caml_call2(is_dir_sep, name, n)){ var n$1 = /*<>*/ n; break; @@ -34735,11 +34497,11 @@ } /*<>*/ for(;;){ /*<>*/ if(0 > n$3) - /*<>*/ return caml_call3 - (Stdlib_String[16], name, 0, 1) /*<>*/ ; + /*<>*/ return Stdlib_String[16].call + (null, name, 0, 1) /*<>*/ ; /*<>*/ if(! caml_call2(is_dir_sep, name, n$3)) - /*<>*/ return caml_call3 - (Stdlib_String[16], name, 0, n$3 + 1 | 0) /*<>*/ ; + /*<>*/ return Stdlib_String[16].call + (null, name, 0, n$3 + 1 | 0) /*<>*/ ; var n$4 = /*<>*/ n$3 - 1 | 0; n$3 = n$4; } @@ -34763,7 +34525,7 @@ _aa_ = _ab_ || - ( /*<>*/ caml_call3(Stdlib_String[16], n, 0, 2) + ( /*<>*/ Stdlib_String[16].call(null, n, 0, 2) !== cst$27 ? 1 : 0); @@ -34773,7 +34535,7 @@ ___ = _ac_ || - ( /*<>*/ caml_call3(Stdlib_String[16], n, 0, 3) + ( /*<>*/ Stdlib_String[16].call(null, n, 0, 3) !== cst$28 ? 1 : 0); @@ -34785,8 +34547,7 @@ return ___; /*<>*/ } function check_suffix(name, suff){ - /*<>*/ return caml_call2 - (Stdlib_String[12], suff, name) /*<>*/ ; + /*<>*/ return Stdlib_String[12].call(null, suff, name) /*<>*/ ; } function chop_suffix_opt(suffix, filename){ var @@ -34796,12 +34557,12 @@ /*<>*/ return 0; var r = - /*<>*/ caml_call3 - (Stdlib_String[16], filename, len_f - len_s | 0, len_s); + /*<>*/ Stdlib_String[16].call + (null, filename, len_f - len_s | 0, len_s); /*<>*/ return r === suffix ? [0, - /*<>*/ caml_call3 - (Stdlib_String[16], filename, 0, len_f - len_s | 0)] + /*<>*/ Stdlib_String[16].call + (null, filename, 0, len_f - len_s | 0)] : 0 /*<>*/ ; } var @@ -34832,25 +34593,25 @@ function quote(s){ var l = /*<>*/ caml_ml_string_length(s), - b = /*<>*/ caml_call1(Stdlib_Buffer[1], l + 20 | 0); - /*<>*/ caml_call2(Stdlib_Buffer[12], b, 39); + b = /*<>*/ Stdlib_Buffer[1].call(null, l + 20 | 0); + /*<>*/ Stdlib_Buffer[12].call(null, b, 39); var _X_ = /*<>*/ l - 1 | 0, _Y_ = 0; if(_X_ >= 0){ var i = _Y_; for(;;){ /*<>*/ if(39 === caml_string_get(s, i)) - /*<>*/ caml_call2(Stdlib_Buffer[16], b, quotequote); + /*<>*/ Stdlib_Buffer[16].call(null, b, quotequote); else{ var ___ = /*<>*/ caml_string_get(s, i); - /*<>*/ caml_call2(Stdlib_Buffer[12], b, ___); + /*<>*/ Stdlib_Buffer[12].call(null, b, ___); } var _Z_ = /*<>*/ i + 1 | 0; if(_X_ === i) break; i = _Z_; } } - /*<>*/ caml_call2(Stdlib_Buffer[12], b, 39); - /*<>*/ return caml_call1(Stdlib_Buffer[2], b); + /*<>*/ Stdlib_Buffer[12].call(null, b, 39); + /*<>*/ return Stdlib_Buffer[2].call(null, b); } function quote_command(cmd, stdin, stdout, stderr, args){ /*<>*/ if(stderr){ @@ -34861,8 +34622,8 @@ var _X_ = /*<>*/ quote(f), _O_ = - /*<>*/ /*<>*/ caml_call2 - (Stdlib[28], cst_2, _X_); + /*<>*/ /*<>*/ Stdlib[28].call + (null, cst_2, _X_); } else var _O_ = /*<>*/ cst$4; @@ -34871,27 +34632,27 @@ f$0 = stdout[1], _R_ = /*<>*/ quote(f$0), _P_ = - /*<>*/ /*<>*/ caml_call2 - (Stdlib[28], cst, _R_); + /*<>*/ /*<>*/ Stdlib[28].call + (null, cst, _R_); else var _P_ = /*<>*/ cst$3; - var _S_ = /*<>*/ caml_call2(Stdlib[28], _P_, _O_); + var _S_ = /*<>*/ Stdlib[28].call(null, _P_, _O_); /*<>*/ if(stdin) var f$1 = stdin[1], _T_ = /*<>*/ quote(f$1), _Q_ = - /*<>*/ /*<>*/ caml_call2 - (Stdlib[28], cst$0, _T_); + /*<>*/ /*<>*/ Stdlib[28].call + (null, cst$0, _T_); else var _Q_ = /*<>*/ cst$2; var - _U_ = /*<>*/ caml_call2(Stdlib[28], _Q_, _S_), + _U_ = /*<>*/ Stdlib[28].call(null, _Q_, _S_), _V_ = - /*<>*/ caml_call2 - (Stdlib_List[20], quote, [0, cmd, args]), - _W_ = /*<>*/ caml_call2(Stdlib_String[7], cst$1, _V_); - /*<>*/ return caml_call2(Stdlib[28], _W_, _U_) /*<>*/ ; + /*<>*/ Stdlib_List[20].call + (null, quote, [0, cmd, args]), + _W_ = /*<>*/ Stdlib_String[7].call(null, cst$1, _V_); + /*<>*/ return Stdlib[28].call(null, _W_, _U_) /*<>*/ ; } function basename(_O_){ /*<>*/ return generic_basename @@ -34961,7 +34722,7 @@ _B_ = _E_ || - ( /*<>*/ caml_call3(Stdlib_String[16], n, 0, 2) + ( /*<>*/ Stdlib_String[16].call(null, n, 0, 2) !== cst$27 ? 1 : 0); @@ -34971,7 +34732,7 @@ _C_ = _F_ || - ( /*<>*/ caml_call3(Stdlib_String[16], n, 0, 2) + ( /*<>*/ Stdlib_String[16].call(null, n, 0, 2) !== ".\\" ? 1 : 0); @@ -34981,7 +34742,7 @@ _D_ = _G_ || - ( /*<>*/ caml_call3(Stdlib_String[16], n, 0, 3) + ( /*<>*/ Stdlib_String[16].call(null, n, 0, 3) !== cst$28 ? 1 : 0); @@ -34991,8 +34752,7 @@ _z_ = _H_ || - ( /*<>*/ caml_call3 - (Stdlib_String[16], n, 0, 3) + ( /*<>*/ Stdlib_String[16].call(null, n, 0, 3) !== "..\\" ? 1 : 0); @@ -35019,17 +34779,18 @@ if(_x_) var s = - /*<>*/ caml_call3 - (Stdlib_String[16], + /*<>*/ Stdlib_String[16].call + (null, name, /*<>*/ caml_ml_string_length(name) - caml_ml_string_length(suff) | 0, caml_ml_string_length(suff)), - _z_ = /*<>*/ caml_call1(Stdlib_String[27], suff), + _z_ = /*<>*/ Stdlib_String[27].call(null, suff), _y_ = - /*<>*/ /*<>*/ caml_call1 - (Stdlib_String[27], s) + /*<>*/ /*<>*/ Stdlib_String + [27].call + (null, s) === _z_ ? 1 : 0; @@ -35045,13 +34806,13 @@ /*<>*/ return 0; var r = - /*<>*/ caml_call3 - (Stdlib_String[16], filename, len_f - len_s | 0, len_s), - _x_ = /*<>*/ caml_call1(Stdlib_String[27], suffix); - /*<>*/ return caml_call1(Stdlib_String[27], r) === _x_ + /*<>*/ Stdlib_String[16].call + (null, filename, len_f - len_s | 0, len_s), + _x_ = /*<>*/ Stdlib_String[27].call(null, suffix); + /*<>*/ return Stdlib_String[27].call(null, r) === _x_ ? [0, - /*<>*/ caml_call3 - (Stdlib_String[16], filename, 0, len_f - len_s | 0)] + /*<>*/ Stdlib_String[16].call + (null, filename, 0, len_f - len_s | 0)] : 0 /*<>*/ ; } /*<>*/ try{ @@ -35067,13 +34828,13 @@ function quote$0(s){ var l = /*<>*/ caml_ml_string_length(s), - b = /*<>*/ caml_call1(Stdlib_Buffer[1], l + 20 | 0); - /*<>*/ caml_call2(Stdlib_Buffer[12], b, 34); + b = /*<>*/ Stdlib_Buffer[1].call(null, l + 20 | 0); + /*<>*/ Stdlib_Buffer[12].call(null, b, 34); function loop$0(counter, i$1){ var i = /*<>*/ i$1; for(;;){ if(i === l) - /*<>*/ return caml_call2(Stdlib_Buffer[12], b, 34) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[12].call(null, b, 34) /*<>*/ ; var c = /*<>*/ caml_string_get(s, i); /*<>*/ if(34 === c){ var _w_ = /*<>*/ 0; @@ -35089,7 +34850,7 @@ var counter$0 = /*<>*/ counter + 1 | 0; return loop_bs(counter$0, _x_, i) /*<>*/ ; } - /*<>*/ caml_call2(Stdlib_Buffer[12], b, c); + /*<>*/ Stdlib_Buffer[12].call(null, b, c); var i$0 = /*<>*/ i + 1 | 0; i = i$0; } @@ -35102,13 +34863,13 @@ var n = /*<>*/ n$1, i = i$1; for(;;){ if(i === l){ - /*<>*/ caml_call2(Stdlib_Buffer[12], b, 34); + /*<>*/ Stdlib_Buffer[12].call(null, b, 34); /*<>*/ return add_bs(n) /*<>*/ ; } var match = /*<>*/ caml_string_get(s, i); /*<>*/ if(34 === match){ /*<>*/ add_bs((2 * n | 0) + 1 | 0); - /*<>*/ caml_call2(Stdlib_Buffer[12], b, 34); + /*<>*/ Stdlib_Buffer[12].call(null, b, 34); var _w_ = /*<>*/ i + 1 | 0; if(counter >= 50) return caml_trampoline_return(loop$0, [0, _w_]) /*<>*/ ; @@ -35132,7 +34893,7 @@ if(n >= 1){ var j = _v_; for(;;){ - /*<>*/ caml_call2(Stdlib_Buffer[12], b, 92); + /*<>*/ Stdlib_Buffer[12].call(null, b, 92); var _w_ = /*<>*/ j + 1 | 0; if(n === j) break; j = _w_; @@ -35140,14 +34901,15 @@ } /*<>*/ } /*<>*/ loop(0); - /*<>*/ return caml_call1(Stdlib_Buffer[2], b) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[2].call(null, b) /*<>*/ ; } function quote_cmd_filename(f){ var f$0 = - /*<>*/ caml_call2(Stdlib_String[15], f, 47) - ? /*<>*/ caml_call2 - (Stdlib_String[18], + /*<>*/ Stdlib_String[15].call(null, f, 47) + ? /*<>*/ Stdlib_String + [18].call + (null, function(c){ /*<>*/ return 47 === c ? 92 : c /*<>*/ ; }, @@ -35155,23 +34917,24 @@ : f; /*<>*/ if (! - caml_call2 - (Stdlib_String[23], + Stdlib_String[23].call + (null, function(param){ /*<>*/ if(34 !== param && 37 !== param) /*<>*/ return 0; /*<>*/ return 1; /*<>*/ }, f$0)) - /*<>*/ return caml_call2(Stdlib_String[15], f$0, 32) - ? /*<>*/ caml_call2 - (Stdlib_String[7], cst$7, [0, cst$6, [0, f$0, _a_]]) + /*<>*/ return Stdlib_String[15].call(null, f$0, 32) + ? /*<>*/ Stdlib_String + [7].call + (null, cst$7, [0, cst$6, [0, f$0, _a_]]) : f$0 /*<>*/ ; var _v_ = - /*<>*/ caml_call2 - (Stdlib[28], cst_Filename_quote_command_bad, f$0); - /*<>*/ return caml_call1(Stdlib[2], _v_) /*<>*/ ; + /*<>*/ Stdlib[28].call + (null, cst_Filename_quote_command_bad, f$0); + /*<>*/ return Stdlib[2].call(null, _v_) /*<>*/ ; } function quote_command$0(cmd, stdin, stdout, stderr, args){ /*<>*/ if(stderr){ @@ -35182,8 +34945,8 @@ var _v_ = /*<>*/ quote_cmd_filename(f), _l_ = - /*<>*/ /*<>*/ caml_call2 - (Stdlib[28], cst_2$0, _v_); + /*<>*/ /*<>*/ Stdlib[28].call + (null, cst_2$0, _v_); } else var _l_ = /*<>*/ cst$16; @@ -35193,8 +34956,8 @@ f$0 = stdout[1], _p_ = /*<>*/ quote_cmd_filename(f$0), _m_ = - /*<>*/ /*<>*/ caml_call2 - (Stdlib[28], cst$8, _p_); + /*<>*/ /*<>*/ Stdlib[28].call + (null, cst$8, _p_); else var _m_ = /*<>*/ cst$15; var _q_ = [0, _m_, _o_]; @@ -35203,20 +34966,19 @@ f$1 = stdin[1], _r_ = /*<>*/ quote_cmd_filename(f$1), _n_ = - /*<>*/ /*<>*/ caml_call2 - (Stdlib[28], cst$9, _r_); + /*<>*/ /*<>*/ Stdlib[28].call + (null, cst$9, _r_); else var _n_ = /*<>*/ cst$14; var _s_ = - /*<>*/ caml_call2(Stdlib_List[20], quote$0, args), - s = /*<>*/ caml_call2(Stdlib_String[7], cst$10, _s_), + /*<>*/ Stdlib_List[20].call(null, quote$0, args), + s = /*<>*/ Stdlib_String[7].call(null, cst$10, _s_), b = - /*<>*/ /*<>*/ caml_call1 - (Stdlib_Buffer[1], - /*<>*/ caml_ml_string_length(s) + 20 | 0); - /*<>*/ caml_call2 - (Stdlib_String[30], + /*<>*/ /*<>*/ Stdlib_Buffer[1].call + (null, /*<>*/ caml_ml_string_length(s) + 20 | 0); + /*<>*/ Stdlib_String[30].call + (null, function(c){ a: { @@ -35236,23 +34998,23 @@ switch(c - 33 | 0){case 2:case 3:case 6: break a; } } - /*<>*/ caml_call2(Stdlib_Buffer[12], b, 94); - /*<>*/ return caml_call2(Stdlib_Buffer[12], b, c) /*<>*/ ; + /*<>*/ Stdlib_Buffer[12].call(null, b, 94); + /*<>*/ return Stdlib_Buffer[12].call(null, b, c) /*<>*/ ; } - /*<>*/ return caml_call2(Stdlib_Buffer[12], b, c) /*<>*/ ; + /*<>*/ return Stdlib_Buffer[12].call(null, b, c) /*<>*/ ; }, s); var _t_ = /*<>*/ [0, cst$11, - [0, caml_call1(Stdlib_Buffer[2], b), [0, _n_, _q_]]], + [0, Stdlib_Buffer[2].call(null, b), [0, _n_, _q_]]], _u_ = /*<>*/ [0, cst$12, [0, quote_cmd_filename(cmd), _t_]]; - /*<>*/ return caml_call2 - (Stdlib_String[7], cst$13, _u_) /*<>*/ ; + /*<>*/ return Stdlib_String[7].call + (null, cst$13, _u_) /*<>*/ ; } function drive_and_path(s){ var @@ -35284,13 +35046,14 @@ /*<>*/ return [0, cst$17, s]; var _l_ = - /*<>*/ /*<>*/ caml_call3 - (Stdlib_String[16], + /*<>*/ /*<>*/ Stdlib_String + [16].call + (null, s, 2, /*<>*/ caml_ml_string_length(s) - 2 | 0); /*<>*/ return [0, - caml_call3(Stdlib_String[16], s, 0, 2), + Stdlib_String[16].call(null, s, 0, 2), _l_] /*<>*/ ; /*<>*/ } function dirname$0(s){ @@ -35301,7 +35064,7 @@ dir = /*<>*/ generic_dirname (is_dir_sep$0, current_dir_name$0, path); - /*<>*/ return caml_call2(Stdlib[28], drive, dir) /*<>*/ ; + /*<>*/ return Stdlib[28].call(null, drive, dir) /*<>*/ ; } function basename$0(s){ var path = /*<>*/ drive_and_path(s)[2]; @@ -35373,22 +35136,22 @@ && ! /*<>*/ is_dir_sep$1(dirname, l - 1 | 0)){ var _i_ = - /*<>*/ caml_call2 - (Stdlib[28], dir_sep$2, filename); - /*<>*/ return caml_call2(Stdlib[28], dirname, _i_); + /*<>*/ Stdlib[28].call(null, dir_sep$2, filename); + /*<>*/ return Stdlib[28].call(null, dirname, _i_); } - /*<>*/ return caml_call2 - (Stdlib[28], dirname, filename) /*<>*/ ; + /*<>*/ return Stdlib[28].call(null, dirname, filename) /*<>*/ ; } function chop_suffix(name, suff){ /*<>*/ return check_suffix$1(name, suff) - ? /*<>*/ caml_call3 - (Stdlib_String[16], + ? /*<>*/ Stdlib_String + [16].call + (null, name, 0, caml_ml_string_length(name) - caml_ml_string_length(suff) | 0) - : /*<>*/ caml_call1 - (Stdlib[1], cst_Filename_chop_suffix) /*<>*/ ; + : /*<>*/ Stdlib + [1].call + (null, cst_Filename_chop_suffix) /*<>*/ ; } function extension_len(name){ var @@ -35421,32 +35184,27 @@ var l = /*<>*/ extension_len(name); /*<>*/ return 0 === l ? cst$18 - : /*<>*/ caml_call3 - (Stdlib_String[16], - name, - caml_ml_string_length(name) - l | 0, - l) /*<>*/ ; + : /*<>*/ Stdlib_String + [16].call + (null, name, caml_ml_string_length(name) - l | 0, l) /*<>*/ ; } function chop_extension(name){ var l = /*<>*/ extension_len(name); /*<>*/ return 0 === l - ? /*<>*/ caml_call1 - (Stdlib[1], cst_Filename_chop_extension) - : /*<>*/ caml_call3 - (Stdlib_String[16], - name, - 0, - caml_ml_string_length(name) - l | 0) /*<>*/ ; + ? /*<>*/ Stdlib + [1].call + (null, cst_Filename_chop_extension) + : /*<>*/ Stdlib_String + [16].call + (null, name, 0, caml_ml_string_length(name) - l | 0) /*<>*/ ; } function remove_extension(name){ var l = /*<>*/ extension_len(name); /*<>*/ return 0 === l ? name - : /*<>*/ caml_call3 - (Stdlib_String[16], - name, - 0, - caml_ml_string_length(name) - l | 0) /*<>*/ ; + : /*<>*/ Stdlib_String + [16].call + (null, name, 0, caml_ml_string_length(name) - l | 0) /*<>*/ ; } var prng_key = @@ -35462,8 +35220,8 @@ & 16777215; /*<>*/ return /*<>*/ concat (temp_dir, - /*<>*/ caml_call4 - (Stdlib_Printf[4], _c_, prefix, rnd, suffix)) /*<>*/ ; + /*<>*/ caml_call3 + (Stdlib_Printf[4].call(null, _c_), prefix, rnd, suffix)) /*<>*/ ; } var current_temp_dir_name = @@ -35527,7 +35285,7 @@ _i_ = /*<>*/ [0, name, - caml_call3(Stdlib[62], [0, 1, [0, 3, [0, 5, mode]]], perms, name)]; + Stdlib[62].call(null, [0, 1, [0, 3, [0, 5, mode]]], perms, name)]; return _i_; } catch(e$0){ @@ -36185,7 +35943,7 @@ //# unitInfo: Provides: Stdlib__StringLabels //# unitInfo: Requires: Stdlib__String -//# shape: Stdlib__StringLabels:[F(2),F(2),N,F(1),F(1),F(5),F(2),F(2)*,F(2)*,F(2)*,F(2),F(2),F(3),F(3),F(2),F(3),F(2),F(2),F(2),F(3),F(3),F(2),F(2),F(1),F(1),F(1),F(1),F(1),F(1),F(2),F(2),F(3),F(3),F(3),F(3),F(2),F(2),F(2),F(2),F(1),F(1),F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(2)] +//# shape: Stdlib__StringLabels:[F(2),F(2),N,F(1),F(1),F(5),F(2),F(2)*,F(2)*,F(2)*,F(2),F(2),F(3),F(3),F(2),F(3),F(2),F(2),F(2),F(3),F(3),F(2),F(2),F(1),F(1),F(1),F(1),F(1),F(1),F(2),F(2),F(3),F(3),F(3),F(3),F(2),F(2),F(2),F(2),F(1)*,F(1)*,F(1),F(2),F(1),F(2),F(1),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(2),F(1),F(2),F(2),F(2),F(2),F(2),F(2)] (function (globalThis){ "use strict"; @@ -36331,7 +36089,7 @@ //# unitInfo: Provides: Stdlib__MoreLabels //# unitInfo: Requires: Stdlib__Hashtbl, Stdlib__Map, Stdlib__Set -//# shape: Stdlib__MoreLabels:[[F(2),F(1),F(1),F(1),F(3),F(2),F(2),F(2),F(2),F(2),F(3),F(2),F(2),F(3),F(1)*,F(1),F(1),F(2),F(1),F(1)*->F(1),F(1),F(1),F(2),F(2),F(1),F(1)*,F(1)*,F(1)*,F(2)*,F(3)*,F(4)*],[F(1)*],[F(1)*]] +//# shape: Stdlib__MoreLabels:[[F(2),F(1),F(1),F(1),F(3),F(2),F(2),F(2),F(2),F(2),F(3),F(2),F(2),F(3),F(1)*,F(1),F(1),F(2),F(1),F(1)*->F(1),F(1)*->F(1),F(1)*->F(1),F(2),F(2),F(1),F(1)*,F(1)*,F(1)*,F(2)*,F(3)*,F(4)*],[F(1)*],[F(1)*]] (function (globalThis){ "use strict"; @@ -36379,11 +36137,6 @@ ? f(a0) : runtime.caml_call_gen(f, [a0]); } - function caml_call2(f, a0, a1){ - return (f.l >= 0 ? f.l : f.l = f.length) === 2 - ? f(a0, a1) - : runtime.caml_call_gen(f, [a0, a1]); - } var global_data = runtime.caml_get_global_data(), Stdlib = global_data.Stdlib, @@ -36402,22 +36155,22 @@ if(tag !== Unhandled) /*<>*/ return 0; var x = /*<>*/ param[2], - _h_ = /*<>*/ caml_call1(Stdlib_Printexc[26], x), - msg = /*<>*/ caml_call2(Stdlib_Printf[4], _a_, _h_); + _h_ = /*<>*/ Stdlib_Printexc[26].call(null, x), + msg = + /*<>*/ caml_call1 + (Stdlib_Printf[4].call(null, _a_), _h_); /*<>*/ return [0, msg]; /*<>*/ } - /*<>*/ caml_call1(Stdlib_Printexc[9], printer); + /*<>*/ Stdlib_Printexc[9].call(null, printer); var Should_not_see_this = /*<>*/ [248, "Stdlib.Effect.Should_not_see_this__", caml_fresh_oo_id(0)]; - /*<>*/ caml_call2 - (Stdlib_Callback[2], - "Effect.Unhandled", - [0, Unhandled, Should_not_see_this]); - /*<>*/ caml_call2 - (Stdlib_Callback[2], + /*<>*/ Stdlib_Callback[2].call + (null, "Effect.Unhandled", [0, Unhandled, Should_not_see_this]); + /*<>*/ Stdlib_Callback[2].call + (null, "Effect.Continuation_already_resumed", Continuation_already_resumed); function continue$(k, v){ @@ -36504,7 +36257,7 @@ (f, /*<>*/ jsoo_effect_not_supported()) /*<>*/ ; } function error(param){ - /*<>*/ return caml_call1(Stdlib[2], cst_impossible) /*<>*/ ; + /*<>*/ return Stdlib[2].call(null, cst_impossible) /*<>*/ ; } function effc(eff, k, last_fiber){ /*<>*/ if(eff === Initial_setup) From ffab80e375ec4cfa7539c66fa67d21c4816a0d3c Mon Sep 17 00:00:00 2001 From: Hugo Heuzard Date: Thu, 5 Dec 2024 08:34:47 +0100 Subject: [PATCH 05/13] Changes --- CHANGES.md | 1 + 1 file changed, 1 insertion(+) diff --git a/CHANGES.md b/CHANGES.md index f08cfdd244..2d1903832d 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -48,6 +48,7 @@ * Compiler/wasm: use type analysis to remove some unnecessary uses of JavasScript strict equality (#2040) * Compiler/wasm: use more precise environment types (#2041) * Compiler/wasm: optimize calls to statically known function (#2044) +* Compiler: Propagate arity between compilation units (#1594) ## Bug fixes * Compiler: fix stack overflow issues with double translation (#1869) From 35334d1c9d6943287d7dc71658a2bafdb7b7c77a Mon Sep 17 00:00:00 2001 From: Hugo Heuzard Date: Tue, 20 May 2025 20:52:00 +0200 Subject: [PATCH 06/13] Compiler: propagate information during optcall optimiastion. --- compiler/lib/driver.ml | 6 +++++- compiler/lib/global_flow.ml | 4 ++++ compiler/lib/global_flow.mli | 2 ++ compiler/lib/specialize.ml | 18 ++++++++++-------- compiler/lib/specialize.mli | 6 +++++- 5 files changed, 26 insertions(+), 10 deletions(-) diff --git a/compiler/lib/driver.ml b/compiler/lib/driver.ml index c237302744..2957d8cc97 100644 --- a/compiler/lib/driver.ml +++ b/compiler/lib/driver.ml @@ -68,6 +68,7 @@ let specialize_1 (p, info) = let return_values = Code.Var.Map.empty in Specialize.f ~function_arity:(fun f -> Specialize.function_arity ~return_values info f) + ~update_def:(fun x expr -> Flow.Info.update_def info x expr) p let specialize_js (p, info) = @@ -177,7 +178,10 @@ let effects_and_exact_calls p, trampolined_calls, in_cps, None, shapes | `Disabled | `Jspi -> let p = - Specialize.f ~function_arity:(fun f -> Global_flow.function_arity info f) p + Specialize.f + ~function_arity:(fun f -> Global_flow.function_arity info f) + ~update_def:(fun x expr -> Global_flow.update_def info x expr) + p in let shapes = collects_shapes ~shapes p in ( p diff --git a/compiler/lib/global_flow.ml b/compiler/lib/global_flow.ml index d3eeb8f929..b4dcdbc98f 100644 --- a/compiler/lib/global_flow.ml +++ b/compiler/lib/global_flow.ml @@ -804,6 +804,10 @@ let get_unique_closure info f = | None -> None | Some kind -> kind) +let update_def info x expr = + let idx = Code.Var.idx x in + info.info_defs.(idx) <- Expr expr + let function_arity info f = match Var.Tbl.get info.info_approximation f with | Top | Values { others = true; _ } -> None diff --git a/compiler/lib/global_flow.mli b/compiler/lib/global_flow.mli index 3d78b4373e..1eca38e567 100644 --- a/compiler/lib/global_flow.mli +++ b/compiler/lib/global_flow.mli @@ -80,6 +80,8 @@ type state = val f : fast:bool -> Code.program -> state * info +val update_def : info -> Code.Var.t -> Code.expr -> unit + val exact_call : info -> Var.t -> int -> bool val get_unique_closure : info -> Var.t -> Var.t option diff --git a/compiler/lib/specialize.ml b/compiler/lib/specialize.ml index a6009fcc6d..c1d8f366c6 100644 --- a/compiler/lib/specialize.ml +++ b/compiler/lib/specialize.ml @@ -40,7 +40,7 @@ let unknown_apply = function | Let (_, Apply { f = _; args = _; exact = false }) -> true | _ -> false -let specialize_apply opt_count function_arity ((acc, free_pc, extra), loc) i = +let specialize_apply opt_count function_arity update_def ((acc, free_pc, extra), loc) i = match i with | Let (x, Apply { f; args; exact = false }) -> ( let n' = List.length args in @@ -74,13 +74,13 @@ let specialize_apply opt_count function_arity ((acc, free_pc, extra), loc) i = ; branch = Return return' } in - ( Let (x, Closure (missing, (free_pc, missing), None)) :: acc - , free_pc + 1 - , (free_pc, block) :: extra ) + let expr = Closure (missing, (free_pc, missing), None) in + update_def x expr; + Let (x, expr) :: acc, free_pc + 1, (free_pc, block) :: extra | Some _ -> assert false) | _ -> i :: acc, free_pc, extra -let specialize_instrs ~function_arity opt_count p = +let specialize_instrs ~function_arity ~update_def opt_count p = let blocks, free_pc = Addr.Map.fold (fun pc block (blocks, free_pc) -> @@ -95,7 +95,7 @@ let specialize_instrs ~function_arity opt_count p = | Event loc -> let (body, free_pc, extra), _ = acc in (i :: body, free_pc, extra), Some loc - | _ -> specialize_apply opt_count function_arity acc i, None) + | _ -> specialize_apply opt_count function_arity update_def acc i, None) in let blocks = List.fold_left extra ~init:blocks ~f:(fun blocks (pc, b) -> @@ -108,13 +108,15 @@ let specialize_instrs ~function_arity opt_count p = in { p with blocks; free_pc } -let f ~function_arity p = +let f ~function_arity ~update_def p = Code.invariant p; let previous_p = p in let t = Timer.make () in let opt_count = ref 0 in let p = - if Config.Flag.optcall () then specialize_instrs ~function_arity opt_count p else p + if Config.Flag.optcall () + then specialize_instrs ~function_arity ~update_def opt_count p + else p in if times () then Format.eprintf " optcall: %a@." Timer.print t; if stats () then Format.eprintf "Stats - optcall: %d@." !opt_count; diff --git a/compiler/lib/specialize.mli b/compiler/lib/specialize.mli index 5a1a8f7a2a..59d71ea5c2 100644 --- a/compiler/lib/specialize.mli +++ b/compiler/lib/specialize.mli @@ -21,6 +21,10 @@ val function_arity : return_values:Code.Var.Set.t Code.Var.Map.t -> Flow.Info.t -> Code.Var.t -> int option -val f : function_arity:(Code.Var.t -> int option) -> Code.program -> Code.program +val f : + function_arity:(Code.Var.t -> int option) + -> update_def:(Code.Var.t -> Code.expr -> unit) + -> Code.program + -> Code.program val switches : Code.program -> Code.program From b4aff36d5b24ded7cb57440ad9e7dbe0ba660921 Mon Sep 17 00:00:00 2001 From: Hugo Heuzard Date: Wed, 21 May 2025 10:22:30 +0200 Subject: [PATCH 07/13] Compiler: Specialze.f use shapes to compute arity --- compiler/lib/driver.ml | 7 ++- compiler/lib/specialize.ml | 89 +++++++++++++++++++------------------ compiler/lib/specialize.mli | 5 +-- 3 files changed, 52 insertions(+), 49 deletions(-) diff --git a/compiler/lib/driver.ml b/compiler/lib/driver.ml index 2957d8cc97..1ae65f94a6 100644 --- a/compiler/lib/driver.ml +++ b/compiler/lib/driver.ml @@ -67,7 +67,7 @@ let specialize_1 (p, info) = if debug () then Format.eprintf "Specialize...@."; let return_values = Code.Var.Map.empty in Specialize.f - ~function_arity:(fun f -> Specialize.function_arity ~return_values info f) + ~shape:(fun f -> Flow.the_shape_of ~return_values ~pure:Pure_fun.empty info f) ~update_def:(fun x expr -> Flow.Info.update_def info x expr) p @@ -179,7 +179,10 @@ let effects_and_exact_calls | `Disabled | `Jspi -> let p = Specialize.f - ~function_arity:(fun f -> Global_flow.function_arity info f) + ~shape:(fun f -> + match Global_flow.function_arity info f with + | None -> Shape.Top + | Some arity -> Shape.Function { arity; pure = false; res = Top }) ~update_def:(fun x expr -> Global_flow.update_def info x expr) p in diff --git a/compiler/lib/specialize.ml b/compiler/lib/specialize.ml index c1d8f366c6..7837ff3962 100644 --- a/compiler/lib/specialize.ml +++ b/compiler/lib/specialize.ml @@ -26,11 +26,6 @@ let stats = Debug.find "stats" let debug_stats = Debug.find "stats-debug" -let function_arity ~return_values info x = - match Flow.the_shape_of ~return_values ~pure:Pure_fun.empty info x with - | Top | Block _ -> None - | Function { arity; _ } -> Some arity - let add_event loc instrs = match loc with | Some loc -> Event loc :: instrs @@ -40,83 +35,91 @@ let unknown_apply = function | Let (_, Apply { f = _; args = _; exact = false }) -> true | _ -> false -let specialize_apply opt_count function_arity update_def ((acc, free_pc, extra), loc) i = - match i with - | Let (x, Apply { f; args; exact = false }) -> ( - let n' = List.length args in - match function_arity f with - | None -> i :: acc, free_pc, extra - | Some n when n = n' -> - incr opt_count; - Let (x, Apply { f; args; exact = true }) :: acc, free_pc, extra - | Some n when n < n' -> +let specialize_apply opt_count shape update_def = + let rec loop x f args shape loc (acc, free_pc, extra) = + match (shape : Shape.t) with + | Top | Block _ -> Let (x, Apply { f; args; exact = false }) :: acc, free_pc, extra + | Function { arity; res; _ } -> + let nargs = List.length args in + if arity = nargs + then ( incr opt_count; - let v = Code.Var.fresh () in - let args, rest = List.take n args in - ( (* Reversed *) - Let (x, Apply { f = v; args = rest; exact = false }) - :: add_event loc (Let (v, Apply { f; args; exact = true }) :: acc) - , free_pc - , extra ) - | Some n when n > n' -> + let expr = Apply { f; args; exact = true } in + update_def x expr; + Let (x, expr) :: acc, free_pc, extra) + else if arity > nargs + then ( + (* under application *) incr opt_count; - let missing = Array.init (n - n') ~f:(fun _ -> Code.Var.fresh ()) in + let missing = Array.init (arity - nargs) ~f:(fun _ -> Code.Var.fresh ()) in let missing = Array.to_list missing in let block = - let params' = Array.init (n - n') ~f:(fun _ -> Code.Var.fresh ()) in - let params' = Array.to_list params' in + let params' = List.map missing ~f:Code.Var.fork in let return' = Code.Var.fresh () in + let args = args @ params' in + assert (List.length args = arity); { params = params' - ; body = - add_event - loc - [ Let (return', Apply { f; args = args @ params'; exact = true }) ] + ; body = add_event loc [ Let (return', Apply { f; args; exact = true }) ] ; branch = Return return' } in let expr = Closure (missing, (free_pc, missing), None) in update_def x expr; - Let (x, expr) :: acc, free_pc + 1, (free_pc, block) :: extra - | Some _ -> assert false) - | _ -> i :: acc, free_pc, extra + Let (x, expr) :: acc, free_pc + 1, (free_pc, block) :: extra) + else ( + assert (arity < nargs); + (* over application *) + incr opt_count; + let v = Code.Var.fresh () in + let args, rest = List.take arity args in + let exact_expr = Apply { f; args; exact = true } in + let body = + (* Reversed *) + add_event loc (Let (v, exact_expr) :: acc) + in + loop x v rest res loc (body, free_pc, extra)) + in + fun i (((body_rev, free_pc, extra) as acc), loc) -> + match i with + | Let (x, Apply { f; args; exact = false }) -> loop x f args (shape f) loc acc + | _ -> i :: body_rev, free_pc, extra -let specialize_instrs ~function_arity ~update_def opt_count p = +let specialize_instrs ~shape ~update_def opt_count p = let blocks, free_pc = + let specialize_instrs = specialize_apply opt_count shape update_def in Addr.Map.fold (fun pc block (blocks, free_pc) -> if List.exists ~f:unknown_apply block.body then - let (body, free_pc, extra), _ = + let (body_rev, free_pc, extra), _ = List.fold_left block.body ~init:(([], free_pc, []), None) ~f:(fun acc i -> match i with | Event loc -> - let (body, free_pc, extra), _ = acc in - (i :: body, free_pc, extra), Some loc - | _ -> specialize_apply opt_count function_arity update_def acc i, None) + let (body_rev, free_pc, extra), _ = acc in + (i :: body_rev, free_pc, extra), Some loc + | _ -> specialize_instrs i acc, None) in let blocks = List.fold_left extra ~init:blocks ~f:(fun blocks (pc, b) -> Addr.Map.add pc b blocks) in - Addr.Map.add pc { block with Code.body = List.rev body } blocks, free_pc + Addr.Map.add pc { block with Code.body = List.rev body_rev } blocks, free_pc else blocks, free_pc) p.blocks (p.blocks, p.free_pc) in { p with blocks; free_pc } -let f ~function_arity ~update_def p = +let f ~shape ~update_def p = Code.invariant p; let previous_p = p in let t = Timer.make () in let opt_count = ref 0 in let p = - if Config.Flag.optcall () - then specialize_instrs ~function_arity ~update_def opt_count p - else p + if Config.Flag.optcall () then specialize_instrs ~shape ~update_def opt_count p else p in if times () then Format.eprintf " optcall: %a@." Timer.print t; if stats () then Format.eprintf "Stats - optcall: %d@." !opt_count; diff --git a/compiler/lib/specialize.mli b/compiler/lib/specialize.mli index 59d71ea5c2..2ab4f3ecb5 100644 --- a/compiler/lib/specialize.mli +++ b/compiler/lib/specialize.mli @@ -18,11 +18,8 @@ * Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. *) -val function_arity : - return_values:Code.Var.Set.t Code.Var.Map.t -> Flow.Info.t -> Code.Var.t -> int option - val f : - function_arity:(Code.Var.t -> int option) + shape:(Code.Var.t -> Shape.t) -> update_def:(Code.Var.t -> Code.expr -> unit) -> Code.program -> Code.program From 87c9102df73f6666a980cb3bfbe610ad1bf82a55 Mon Sep 17 00:00:00 2001 From: Hugo Heuzard Date: Tue, 10 Jun 2025 14:55:18 +0200 Subject: [PATCH 08/13] Compiler: load shapes for cma.js and cmo.js --- compiler/lib/driver.ml | 12 +++--- compiler/lib/shape.ml | 87 +++++++++++++++++++++++++++++++++++++--- compiler/lib/shape.mli | 2 + compiler/tests-full/dune | 4 -- 4 files changed, 89 insertions(+), 16 deletions(-) diff --git a/compiler/lib/driver.ml b/compiler/lib/driver.ml index 1ae65f94a6..45001ca757 100644 --- a/compiler/lib/driver.ml +++ b/compiler/lib/driver.ml @@ -23,8 +23,6 @@ let debug = Debug.find "main" let times = Debug.find "times" -let debug_shapes = Debug.find "shapes" - type optimized_result = { program : Code.program ; variable_uses : Deadcode.variable_uses @@ -103,7 +101,7 @@ let ( +> ) f g x = g (f x) let map_fst5 f (x, y, z, t, u) = f x, y, z, t, u let collects_shapes ~shapes (p : Code.program) = - if debug_shapes () || shapes + if shapes then ( let t = Timer.make () in let shapes = ref StringMap.empty in @@ -729,17 +727,17 @@ let full ~standalone ~wrap_with_fun ~shapes ~profile ~link ~source_map ~formatte +> name_variables +> output formatter ~source_map () in - let shapes = optimized_code.shapes in + let shapes_v = optimized_code.shapes in StringMap.iter (fun name shape -> Shape.Store.set ~name shape; - if debug_shapes () + if shapes then Pretty_print.string formatter (Printf.sprintf "//# shape: %s:%s\n" name (Shape.to_string shape))) - shapes; - emit formatter optimized_code, shapes + shapes_v; + emit formatter optimized_code, shapes_v let full_no_source_map ~formatter ~shapes ~standalone ~wrap_with_fun ~profile ~link p = let (_ : Source_map.info * _) = diff --git a/compiler/lib/shape.ml b/compiler/lib/shape.ml index 764a1571e0..4aaea44710 100644 --- a/compiler/lib/shape.ml +++ b/compiler/lib/shape.ml @@ -64,6 +64,73 @@ let rec to_string (shape : t) = | Top -> "" | _ -> "->" ^ to_string res) +let of_string (s : string) = + let pos = ref 0 in + let current () = s.[!pos] in + let next () = incr pos in + let parse_char c = + let c' = current () in + if Char.equal c c' then next () else assert false + in + let parse_char_opt c = + let c' = current () in + if Char.equal c c' + then ( + next (); + true) + else false + in + let rec parse_int acc = + match current () with + | '0' .. '9' as c -> + let d = Char.code c - Char.code '0' in + let acc = (acc * 10) + d in + next (); + parse_int acc + | _ -> acc + in + let rec parse_shape () = + match current () with + | '[' -> + next (); + parse_block [] + | 'N' -> + next (); + Top + | 'F' -> + next (); + parse_fun () + | _ -> assert false + and parse_block acc = + match current () with + | ']' -> + next (); + Block (List.rev acc) + | _ -> ( + let x = parse_shape () in + match current () with + | ',' -> + next (); + parse_block (x :: acc) + | ']' -> + next (); + Block (List.rev (x :: acc)) + | _ -> assert false) + and parse_fun () = + let () = parse_char '(' in + let arity = parse_int 0 in + let () = parse_char ')' in + let pure = parse_char_opt '*' in + match current () with + | '-' -> + next (); + parse_char '>'; + let res = parse_shape () in + Function { arity; pure; res } + | _ -> Function { arity; pure; res = Top } + in + parse_shape () + module Store = struct let ext = ".jsoo-shape" @@ -82,11 +149,21 @@ module Store = struct let load' fn = let ic = open_in_bin fn in let m = really_input_string ic (String.length magic) in - if not (String.equal m magic) - then failwith (Printf.sprintf "Invalid magic number for shape file %s" fn); - let shapes : (string * shape) list = Marshal.from_channel ic in - close_in ic; - List.iter shapes ~f:(fun (name, shape) -> set ~name shape) + if String.equal m magic + then ( + let shapes : (string * shape) list = Marshal.from_channel ic in + close_in ic; + List.iter shapes ~f:(fun (name, shape) -> set ~name shape)) + else ( + close_in ic; + let l = file_lines_bin fn in + List.iter l ~f:(fun s -> + match String.drop_prefix ~prefix:"//#shape: " s with + | None -> () + | Some name_n_shape -> ( + match String.lsplit2 name_n_shape ~on:':' with + | None -> () + | Some (name, shape) -> set ~name (of_string shape)))) let load ~name ~paths = if String.Hashtbl.mem t name diff --git a/compiler/lib/shape.mli b/compiler/lib/shape.mli index 180840f9d6..32f290e98f 100644 --- a/compiler/lib/shape.mli +++ b/compiler/lib/shape.mli @@ -28,6 +28,8 @@ type t = val to_string : t -> string +val of_string : string -> t + val equal : t -> t -> bool val merge : t -> t -> t diff --git a/compiler/tests-full/dune b/compiler/tests-full/dune index 67c542571f..6a2d63700b 100644 --- a/compiler/tests-full/dune +++ b/compiler/tests-full/dune @@ -11,8 +11,6 @@ --debug var --debuginfo - --debug - shapes %{lib:stdlib:stdlib.cma} -o %{targets}))) @@ -50,8 +48,6 @@ %{bin:js_of_ocaml} --pretty --debuginfo - --debug - shapes %{dep:shapes.cma} -o %{targets}))) From 67fb89bc6a5110c15ea27c7b7fda6ef2427e924f Mon Sep 17 00:00:00 2001 From: Hugo Heuzard Date: Tue, 10 Jun 2025 14:57:31 +0200 Subject: [PATCH 09/13] Test: test shapes with 5.3 --- compiler/tests-full/dune | 12 +++++++++--- compiler/tests-full/shapes.cma.expected.js | 13 +++++++++---- 2 files changed, 18 insertions(+), 7 deletions(-) diff --git a/compiler/tests-full/dune b/compiler/tests-full/dune index 6a2d63700b..b07e4076cf 100644 --- a/compiler/tests-full/dune +++ b/compiler/tests-full/dune @@ -42,7 +42,9 @@ (rule (targets shapes.cma.js) (enabled_if - (= %{ocaml_version} "5.2.0")) + (and + (>= %{ocaml_version} "5.3") + (< %{ocaml_version} "5.4"))) (action (run %{bin:js_of_ocaml} @@ -55,7 +57,9 @@ (rule (targets shapes.cma.output.js) (enabled_if - (= %{ocaml_version} "5.2.0")) + (and + (>= %{ocaml_version} "5.3") + (< %{ocaml_version} "5.4"))) (action (with-stdout-to %{targets} @@ -64,7 +68,9 @@ (rule (alias runtest) (enabled_if - (= %{ocaml_version} "5.2.0")) + (and + (>= %{ocaml_version} "5.3") + (< %{ocaml_version} "5.4"))) (action (diff shapes.cma.expected.js shapes.cma.output.js))) diff --git a/compiler/tests-full/shapes.cma.expected.js b/compiler/tests-full/shapes.cma.expected.js index 8aabd47fe3..736bf99039 100644 --- a/compiler/tests-full/shapes.cma.expected.js +++ b/compiler/tests-full/shapes.cma.expected.js @@ -16,7 +16,7 @@ (globalThis){ "use strict"; var runtime = globalThis.jsoo_runtime; - function f(_a_, param){ + function f(a, param){ /*<>*/ return 0; /*<>*/ } var Shapes_M1 = /*<>*/ [0, f]; @@ -62,6 +62,11 @@ ? f(a0) : runtime.caml_call_gen(f, [a0]); } + function caml_call2(f, a0, a1){ + return (f.l >= 0 ? f.l : f.l = f.length) === 2 + ? f(a0, a1) + : runtime.caml_call_gen(f, [a0, a1]); + } var global_data = runtime.caml_get_global_data(), Shapes_M2 = global_data.Shapes__M2, @@ -72,14 +77,14 @@ < caml_call1(Stdlib_Random[5], 2) ? Shapes_M1[1] : function - (_a_, param){ + (a, param){ /*<>*/ return Shapes_M2[1].call (null, 0) /*<>*/ ; }; } var - x = /*<>*/ f(0)(0, 0), - Shapes_M3 = /*<>*/ [0, f, x]; + x = /*<>*/ caml_call2(f(0), 0, 0), + Shapes_M3 = /*<>*/ [0, f, x]; runtime.caml_register_global(3, Shapes_M3, "Shapes__M3"); return; /*<>*/ } From f1c6c2c1591e990da5091f5501ecf43c6135379d Mon Sep 17 00:00:00 2001 From: Hugo Heuzard Date: Tue, 10 Jun 2025 14:59:28 +0200 Subject: [PATCH 10/13] Compiler: remove --write-shape flag --- compiler/bin-js_of_ocaml/cmd_arg.ml | 13 +- compiler/bin-js_of_ocaml/cmd_arg.mli | 1 - compiler/bin-js_of_ocaml/compile.ml | 57 ++-- compiler/lib/driver.ml | 1 - compiler/lib/parse_bytecode.ml | 18 +- compiler/lib/shape.ml | 88 +----- compiler/lib/shape.mli | 8 +- compiler/tests-compiler/gh747.ml | 436 ++++++++++++++------------- compiler/tests-compiler/sourcemap.ml | 43 +-- 9 files changed, 281 insertions(+), 384 deletions(-) diff --git a/compiler/bin-js_of_ocaml/cmd_arg.ml b/compiler/bin-js_of_ocaml/cmd_arg.ml index 2b2d5b2ea6..ac0b2af78c 100644 --- a/compiler/bin-js_of_ocaml/cmd_arg.ml +++ b/compiler/bin-js_of_ocaml/cmd_arg.ml @@ -65,7 +65,6 @@ type t = ; wrap_with_fun : [ `Iife | `Named of string | `Anonymous ] ; target_env : Target_env.t ; shape_files : string list - ; write_shape : bool ; (* toplevel *) dynlink : bool ; linkall : bool @@ -120,10 +119,6 @@ let options = let doc = "load shape file [$(docv)]." in Arg.(value & opt_all string [] & info [ "load-shape" ] ~docv:"FILE" ~doc) in - let write_shape = - let doc = "Emit shape files" in - Arg.(value & flag & info [ "write-shape" ] ~doc) - in let input_file = let doc = "Compile the bytecode program [$(docv)]. " @@ -328,8 +323,7 @@ let options = js_files keep_unit_names effects - shape_files - write_shape = + shape_files = let inline_source_content = not sourcemap_don't_inline_content in let chop_extension s = try Filename.chop_extension s with Invalid_argument _ -> s in let runtime_files = js_files in @@ -401,7 +395,6 @@ let options = ; keep_unit_names ; effects ; shape_files - ; write_shape } in let t = @@ -435,8 +428,7 @@ let options = $ js_files $ keep_unit_names $ effects - $ shape_files - $ write_shape) + $ shape_files) in Term.ret t @@ -666,7 +658,6 @@ let options_runtime_only = ; keep_unit_names = false ; effects ; shape_files = [] - ; write_shape = false } in let t = diff --git a/compiler/bin-js_of_ocaml/cmd_arg.mli b/compiler/bin-js_of_ocaml/cmd_arg.mli index 8be8344fb1..79780ec8e8 100644 --- a/compiler/bin-js_of_ocaml/cmd_arg.mli +++ b/compiler/bin-js_of_ocaml/cmd_arg.mli @@ -38,7 +38,6 @@ type t = ] ; target_env : Target_env.t ; shape_files : string list - ; write_shape : bool ; (* toplevel *) dynlink : bool ; linkall : bool diff --git a/compiler/bin-js_of_ocaml/compile.ml b/compiler/bin-js_of_ocaml/compile.ml index 357fced377..6364f88776 100644 --- a/compiler/bin-js_of_ocaml/compile.ml +++ b/compiler/bin-js_of_ocaml/compile.ml @@ -54,15 +54,7 @@ let output_gen Driver.configure fmt; if standalone then header ~custom_header fmt; if Config.Flag.header () then jsoo_header fmt build_info; - let sm, shapes = f ~standalone ~shapes:write_shape ~source_map (k, fmt) in - (if write_shape - then - match output_file with - | `Stdout -> () - | `Name name -> - Shape.Store.save' - (Filename.remove_extension name ^ Shape.Store.ext) - (StringMap.bindings shapes)); + let sm = f ~standalone ~shapes:write_shape ~source_map (k, fmt) in match source_map, sm with | None, _ | _, None -> () | Some { output_file = output; source_map; keep_empty }, Some sm -> @@ -140,11 +132,6 @@ let sourcemap_of_infos ~base l = let sourcemap_of_info ~base info = sourcemap_of_infos ~base [ info ] -let map_fst f (x, y) = f x, y - -let merge_shape a b = - StringMap.union (fun _name s1 s2 -> if Shape.equal s1 s2 then Some s1 else None) a b - let run { Cmd_arg.common ; profile @@ -170,7 +157,6 @@ let run ; include_runtime ; effects ; shape_files - ; write_shape } = let source_map_base = Option.map ~f:(fun spec -> spec.Source_map.Encoding_spec.source_map) source_map @@ -273,7 +259,7 @@ let run output_file = if check_sourcemap then check_debug one; let init_pseudo_fs = fs_external && standalone in - let sm = + let sm, shapes = match output_file with | `Stdout, formatter -> let instr = @@ -326,6 +312,7 @@ let run Driver.f' ~standalone ~link:`Needed ?profile ~wrap_with_fun pfs_fmt code)); res in + StringMap.iter (fun name shape -> Shape.Store.set ~name shape) shapes; if times () then Format.eprintf "compilation: %a@." Timer.print t; sm in @@ -398,7 +385,7 @@ let run { code; cmis = StringSet.empty; debug = Parse_bytecode.Debug.default_summary } in output_gen - ~write_shape + ~write_shape:false ~standalone:true ~custom_header ~build_info:(Build_info.create `Runtime) @@ -415,7 +402,7 @@ let run ~shapes ~link:`All output_file - |> map_fst (sourcemap_of_info ~base:source_map_base)) + |> sourcemap_of_info ~base:source_map_base) | (`Stdin | `File _) as bytecode -> let kind, ic, close_ic, include_dirs = match bytecode with @@ -448,7 +435,7 @@ let run in if times () then Format.eprintf " parsing: %a@." Timer.print t1; output_gen - ~write_shape + ~write_shape:false ~standalone:true ~custom_header ~build_info:(Build_info.create `Exe) @@ -463,7 +450,7 @@ let run ~source_map ~link:(if linkall then `All else `Needed) output_file - |> map_fst (sourcemap_of_info ~base:source_map_base)) + |> sourcemap_of_info ~base:source_map_base) | `Cmo cmo -> let output_file = match output_file, keep_unit_names with @@ -488,7 +475,7 @@ let run in if times () then Format.eprintf " parsing: %a@." Timer.print t1; output_gen - ~write_shape + ~write_shape:true ~standalone:false ~custom_header ~build_info:(Build_info.create `Cmo) @@ -497,17 +484,16 @@ let run (fun ~standalone ~shapes ~source_map output -> match include_runtime with | true -> - let sm1, sh1 = + let sm1 = output_partial_runtime ~standalone ~shapes ~source_map output in - let sm2, sh2 = + let sm2 = output_partial cmo code ~standalone ~shapes ~source_map output in - ( sourcemap_of_infos ~base:source_map_base [ sm1; sm2 ] - , merge_shape sh1 sh2 ) + sourcemap_of_infos ~base:source_map_base [ sm1; sm2 ] | false -> output_partial cmo code ~standalone ~shapes ~source_map output - |> map_fst (sourcemap_of_info ~base:source_map_base)) + |> sourcemap_of_info ~base:source_map_base) | `Cma cma when keep_unit_names -> (if include_runtime then @@ -523,7 +509,7 @@ let run failwith "use [-o dirname/] or remove [--keep-unit-names]" in output_gen - ~write_shape + ~write_shape:false ~standalone:false ~custom_header ~build_info:(Build_info.create `Runtime) @@ -531,7 +517,7 @@ let run (`Name output_file) (fun ~standalone ~shapes ~source_map output -> output_partial_runtime ~standalone ~shapes ~source_map output - |> map_fst (sourcemap_of_info ~base:source_map_base))); + |> sourcemap_of_info ~base:source_map_base)); List.iter cma.lib_units ~f:(fun cmo -> let output_file = match output_file with @@ -560,7 +546,7 @@ let run t1 (Ocaml_compiler.Cmo_format.name cmo); output_gen - ~write_shape + ~write_shape:true ~standalone:false ~custom_header ~build_info:(Build_info.create `Cma) @@ -568,7 +554,7 @@ let run (`Name output_file) (fun ~standalone ~shapes ~source_map output -> output_partial ~standalone ~shapes ~source_map cmo code output - |> map_fst (sourcemap_of_info ~base:source_map_base))) + |> sourcemap_of_info ~base:source_map_base)) | `Cma cma -> let f ~standalone ~shapes ~source_map output = (* Always compute shapes because it can be used by other units of the cma *) @@ -599,20 +585,15 @@ let run (Ocaml_compiler.Cmo_format.name cmo); output_partial ~standalone ~shapes ~source_map cmo code output) in - let sm_and_shapes = + let sm = match runtime with | None -> units | Some x -> x :: units in - let shapes = - List.fold_left sm_and_shapes ~init:StringMap.empty ~f:(fun acc (_, s) -> - merge_shape s acc) - in - ( sourcemap_of_infos ~base:source_map_base (List.map sm_and_shapes ~f:fst) - , shapes ) + sourcemap_of_infos ~base:source_map_base sm in output_gen - ~write_shape + ~write_shape:true ~standalone:false ~custom_header ~build_info:(Build_info.create `Cma) diff --git a/compiler/lib/driver.ml b/compiler/lib/driver.ml index 45001ca757..7d514c74c0 100644 --- a/compiler/lib/driver.ml +++ b/compiler/lib/driver.ml @@ -730,7 +730,6 @@ let full ~standalone ~wrap_with_fun ~shapes ~profile ~link ~source_map ~formatte let shapes_v = optimized_code.shapes in StringMap.iter (fun name shape -> - Shape.Store.set ~name shape; if shapes then Pretty_print.string diff --git a/compiler/lib/parse_bytecode.ml b/compiler/lib/parse_bytecode.ml index 5a864d4979..6c2466ebf8 100644 --- a/compiler/lib/parse_bytecode.ml +++ b/compiler/lib/parse_bytecode.ml @@ -587,7 +587,6 @@ module State = struct ; globals : globals ; immutable : unit Code.Var.Hashtbl.t ; module_or_not : Ocaml_compiler.module_or_not Ident.Tbl.t - ; includes : string list } let fresh_var state = @@ -672,7 +671,7 @@ module State = struct let pop_handler state = { state with handlers = List.tl state.handlers } - let initial includes g immutable = + let initial g immutable = { accu = Unset ; stack = [] ; env = [||] @@ -681,7 +680,6 @@ module State = struct ; globals = g ; immutable ; module_or_not = Ident.Tbl.create 0 - ; includes } let rec print_stack f l = @@ -831,7 +829,7 @@ let get_global state instrs i = (match g.named_value.(i) with | None -> () | Some name -> ( - match Shape.Store.load ~name ~paths:state.includes with + match Shape.Store.load ~name with | None -> () | Some shape -> Shape.State.assign x shape)); x, state, instrs @@ -2538,9 +2536,9 @@ type one = ; debug : Debug.summary } -let parse_bytecode ~includes code globals debug_data = +let parse_bytecode code globals debug_data = let immutable = Code.Var.Hashtbl.create 0 in - let state = State.initial includes globals immutable in + let state = State.initial globals immutable in Code.Var.reset (); let blocks', joins = Blocks.analyse code in Shape.State.reset (); @@ -2725,7 +2723,7 @@ let from_exe Ocaml_compiler.Symtable.GlobalMap.iter symbols ~f:(fun id n -> globals.named_value.(n) <- Some (Ocaml_compiler.Symtable.Global.name id); globals.is_exported.(n) <- true); - let p = parse_bytecode ~includes code globals debug_data in + let p = parse_bytecode code globals debug_data in (* register predefined exception *) let body = List.fold_left predefined_exceptions ~init:[] ~f:(fun body (i, name) -> @@ -2855,7 +2853,7 @@ let from_bytes ~prims ~debug (code : bytecode) = t in let globals = make_globals 0 [||] prims in - let p = parse_bytecode ~includes:[] code globals debug_data in + let p = parse_bytecode code globals debug_data in let gdata = Var.fresh_n "global_data" in let need_gdata = ref false in let find_name i = @@ -2987,7 +2985,7 @@ module Reloc = struct globals end -let from_compilation_units ~includes ~include_cmis ~debug_data l = +let from_compilation_units ~includes:_ ~include_cmis ~debug_data l = let reloc = Reloc.create () in List.iter l ~f:(fun (compunit, code) -> Reloc.step1 reloc compunit code); List.iter l ~f:(fun (compunit, code) -> Reloc.step2 reloc compunit code); @@ -2996,7 +2994,7 @@ let from_compilation_units ~includes ~include_cmis ~debug_data l = let l = List.map l ~f:(fun (_, c) -> Bytes.to_string c) in String.concat ~sep:"" l in - let prog = parse_bytecode ~includes code globals debug_data in + let prog = parse_bytecode code globals debug_data in let gdata = Var.fresh_n "global_data" in let need_gdata = ref false in let body = diff --git a/compiler/lib/shape.ml b/compiler/lib/shape.ml index 4aaea44710..45d64e97d3 100644 --- a/compiler/lib/shape.ml +++ b/compiler/lib/shape.ml @@ -28,8 +28,6 @@ type t = ; res : t } -type shape = t - let rec equal a b = match a, b with | Top, Top -> true @@ -132,89 +130,23 @@ let of_string (s : string) = parse_shape () module Store = struct - let ext = ".jsoo-shape" - - let filename ~dir ~name = Filename.concat dir (name ^ ext) - let t = String.Hashtbl.create 17 - let loaded = String.Hashtbl.create 17 - let set ~name shape = String.Hashtbl.replace t name shape let get ~name = String.Hashtbl.find_opt t name - let magic = "JsooShape000" - let load' fn = - let ic = open_in_bin fn in - let m = really_input_string ic (String.length magic) in - if String.equal m magic - then ( - let shapes : (string * shape) list = Marshal.from_channel ic in - close_in ic; - List.iter shapes ~f:(fun (name, shape) -> set ~name shape)) - else ( - close_in ic; - let l = file_lines_bin fn in - List.iter l ~f:(fun s -> - match String.drop_prefix ~prefix:"//#shape: " s with - | None -> () - | Some name_n_shape -> ( - match String.lsplit2 name_n_shape ~on:':' with - | None -> () - | Some (name, shape) -> set ~name (of_string shape)))) - - let load ~name ~paths = - if String.Hashtbl.mem t name - then get ~name - else if not (Config.Flag.load_shapes_auto ()) - then None - else - match Fs.find_in_path paths (filename ~dir:"." ~name) with - | Some f -> - load' f; - get ~name - | None -> - let rec scan : _ -> shape option = function - | [] -> None - | dir :: xs -> ( - let l = - Sys.readdir dir - |> Array.to_list - |> List.sort ~cmp:String.compare - |> List.map ~f:(fun n -> Filename.concat dir n) - in - match - List.find_map l ~f:(fun s -> - if Filename.check_suffix s ext && not (String.Hashtbl.mem loaded s) - then ( - load' s; - String.Hashtbl.add loaded s (); - match get ~name with - | None -> None - | Some shape -> Some (s, shape)) - else None) - with - | None -> scan xs - | Some (fn, shape) -> - Format.eprintf "Shape: %s loaded from %s\n" name fn; - Some shape) - in - scan paths - - let save' fn (l : (string * shape) list) = - let oc = open_out_bin fn in - output_string oc magic; - Marshal.to_channel oc l []; - close_out oc - - let save ~name ~dir = - match get ~name with - | None -> failwith (Printf.sprintf "Don't know any shape for %s" name) - | Some shape -> - let fn = filename ~dir ~name in - save' fn [ name, shape ] + let l = file_lines_bin fn in + List.iter l ~f:(fun s -> + match String.drop_prefix ~prefix:"//#shape: " s with + | None -> () + | Some name_n_shape -> ( + match String.lsplit2 name_n_shape ~on:':' with + | None -> () + | Some (name, shape) -> set ~name (of_string shape))) + + let load ~name = if String.Hashtbl.mem t name then get ~name else None end module State = struct diff --git a/compiler/lib/shape.mli b/compiler/lib/shape.mli index 32f290e98f..926f70ada7 100644 --- a/compiler/lib/shape.mli +++ b/compiler/lib/shape.mli @@ -35,19 +35,13 @@ val equal : t -> t -> bool val merge : t -> t -> t module Store : sig - val ext : string - val set : name:string -> t -> unit val get : name:string -> t option val load' : string -> unit - val load : name:string -> paths:string list -> t option - - val save : name:string -> dir:string -> unit - - val save' : string -> (string * t) list -> unit + val load : name:string -> t option end module State : sig diff --git a/compiler/tests-compiler/gh747.ml b/compiler/tests-compiler/gh747.ml index cddb3e7c30..c94af5cb4e 100644 --- a/compiler/tests-compiler/gh747.ml +++ b/compiler/tests-compiler/gh747.ml @@ -56,55 +56,56 @@ print_endline(String.make 1 "Ɋ".[0] ^ String.make 1 "Ɋ".[1]);; 1: 2: //# unitInfo: Provides: Test 3: //# unitInfo: Requires: Stdlib, Stdlib__Random, Stdlib__String - 4: (function - 5: (globalThis){ - 6: "use strict"; - 7: var - 8: runtime = globalThis.jsoo_runtime, - 9: caml_string_of_jsbytes = runtime.caml_string_of_jsbytes; - 10: function caml_call1(f, a0){ - 11: return (f.l >= 0 ? f.l : f.l = f.length) === 1 - 12: ? f(a0) - 13: : runtime.caml_call_gen(f, [a0]); - 14: } - 15: function caml_call2(f, a0, a1){ - 16: return (f.l >= 0 ? f.l : f.l = f.length) === 2 - 17: ? f(a0, a1) - 18: : runtime.caml_call_gen(f, [a0, a1]); - 19: } - 20: var - 21: global_data = runtime.caml_get_global_data(), - 22: greeting = caml_string_of_jsbytes("hello world"), - 23: greeting$0 = caml_string_of_jsbytes("hello world with unicode: \xc9\x8a"), - 24: Stdlib = global_data.Stdlib, - 25: Stdlib_Random = global_data.Stdlib__Random, - 26: Stdlib_String = global_data.Stdlib__String; - 27: /*<>*/ caml_call1(Stdlib[46], greeting); - 28: /*<>*/ caml_call1(Stdlib[46], greeting$0); - 29: var - 30: _a_ = /*<>*/ caml_call1(Stdlib_Random[5], 30), - 31: unicodeLength = - 32: /*<>*/ /*<>*/ runtime.caml_ml_string_length - 33: ( /*<>*/ caml_call2(Stdlib_String[1], _a_, 105)), - 34: _b_ = /*<>*/ caml_call1(Stdlib[33], unicodeLength), - 35: _c_ = - 36: /*<>*/ caml_call2 - 37: (Stdlib[28], - 38: caml_string_of_jsbytes('String.length("\xc9\x8a") should be two:'), - 39: _b_); - 40: /*<>*/ caml_call1(Stdlib[46], _c_); - 41: var - 42: _d_ = /*<>*/ caml_call2(Stdlib_String[1], 1, 138), - 43: _e_ = /*<>*/ caml_call2(Stdlib_String[1], 1, 201), - 44: _f_ = /*<>*/ caml_call2(Stdlib[28], _e_, _d_); - 45: /*<>*/ caml_call1(Stdlib[46], _f_); - 46: var Test = /*<>*/ [0, greeting$0, unicodeLength]; - 47: runtime.caml_register_global(8, Test, "Test"); - 48: return; - 49: /*<>*/ } - 50: (globalThis)); - 51: - 52: //# sourceMappingURL=test.map + 4: //# shape: Test:[N,N] + 5: (function + 6: (globalThis){ + 7: "use strict"; + 8: var + 9: runtime = globalThis.jsoo_runtime, + 10: caml_string_of_jsbytes = runtime.caml_string_of_jsbytes; + 11: function caml_call1(f, a0){ + 12: return (f.l >= 0 ? f.l : f.l = f.length) === 1 + 13: ? f(a0) + 14: : runtime.caml_call_gen(f, [a0]); + 15: } + 16: function caml_call2(f, a0, a1){ + 17: return (f.l >= 0 ? f.l : f.l = f.length) === 2 + 18: ? f(a0, a1) + 19: : runtime.caml_call_gen(f, [a0, a1]); + 20: } + 21: var + 22: global_data = runtime.caml_get_global_data(), + 23: greeting = caml_string_of_jsbytes("hello world"), + 24: greeting$0 = caml_string_of_jsbytes("hello world with unicode: \xc9\x8a"), + 25: Stdlib = global_data.Stdlib, + 26: Stdlib_Random = global_data.Stdlib__Random, + 27: Stdlib_String = global_data.Stdlib__String; + 28: /*<>*/ caml_call1(Stdlib[46], greeting); + 29: /*<>*/ caml_call1(Stdlib[46], greeting$0); + 30: var + 31: _a_ = /*<>*/ caml_call1(Stdlib_Random[5], 30), + 32: unicodeLength = + 33: /*<>*/ /*<>*/ runtime.caml_ml_string_length + 34: ( /*<>*/ caml_call2(Stdlib_String[1], _a_, 105)), + 35: _b_ = /*<>*/ caml_call1(Stdlib[33], unicodeLength), + 36: _c_ = + 37: /*<>*/ caml_call2 + 38: (Stdlib[28], + 39: caml_string_of_jsbytes('String.length("\xc9\x8a") should be two:'), + 40: _b_); + 41: /*<>*/ caml_call1(Stdlib[46], _c_); + 42: var + 43: _d_ = /*<>*/ caml_call2(Stdlib_String[1], 1, 138), + 44: _e_ = /*<>*/ caml_call2(Stdlib_String[1], 1, 201), + 45: _f_ = /*<>*/ caml_call2(Stdlib[28], _e_, _d_); + 46: /*<>*/ caml_call1(Stdlib[46], _f_); + 47: var Test = /*<>*/ [0, greeting$0, unicodeLength]; + 48: runtime.caml_register_global(8, Test, "Test"); + 49: return; + 50: /*<>*/ } + 51: (globalThis)); + 52: + 53: //# sourceMappingURL=test.map |}] let%expect_test _ = @@ -221,175 +222,176 @@ end 1: 2: //# unitInfo: Provides: Test 3: //# unitInfo: Requires: Stdlib__Printf - 4: (function - 5: (globalThis){ - 6: "use strict"; - 7: var - 8: runtime = globalThis.jsoo_runtime, - 9: caml_string_of_jsbytes = runtime.caml_string_of_jsbytes; - 10: function caml_call2(f, a0, a1){ - 11: return (f.l >= 0 ? f.l : f.l = f.length) === 2 - 12: ? f(a0, a1) - 13: : runtime.caml_call_gen(f, [a0, a1]); - 14: } - 15: function caml_call3(f, a0, a1, a2){ - 16: return (f.l >= 0 ? f.l : f.l = f.length) === 3 - 17: ? f(a0, a1, a2) - 18: : runtime.caml_call_gen(f, [a0, a1, a2]); - 19: } - 20: function caml_call8(f, a0, a1, a2, a3, a4, a5, a6, a7){ - 21: return (f.l >= 0 ? f.l : f.l = f.length) === 8 - 22: ? f(a0, a1, a2, a3, a4, a5, a6, a7) - 23: : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4, a5, a6, a7]); - 24: } - 25: var - 26: global_data = runtime.caml_get_global_data(), - 27: cst = caml_string_of_jsbytes(""), - 28: partial = [4, 0, 0, 0, [12, 45, [4, 0, 0, 0, 0]]], - 29: Stdlib_Printf = global_data.Stdlib__Printf, - 30: executable_name = - 31: /*<>*/ runtime.caml_sys_executable_name(0), - 32: os_type = /*<>*/ runtime.caml_sys_get_config(0)[1], - 33: backend_type = - 34: /*<>*/ [0, caml_string_of_jsbytes("js_of_ocaml")], - 35: unix = runtime.caml_sys_const_ostype_unix(0), - 36: win32 = runtime.caml_sys_const_ostype_win32(0), - 37: cygwin = runtime.caml_sys_const_ostype_cygwin(0), - 38: max_array_length = runtime.caml_sys_const_max_wosize(0), - 39: max_floatarray_length = max_array_length / 2 | 0, - 40: max_string_length = (4 * max_array_length | 0) - 1 | 0, - 41: Unhandled = - 42: [248, - 43: caml_string_of_jsbytes("Test.Unhandled"), - 44: runtime.caml_fresh_oo_id(0)], - 45: cst_Raised_at = caml_string_of_jsbytes("Raised at"), - 46: cst_Re_raised_at = caml_string_of_jsbytes("Re-raised at"), - 47: cst_Raised_by_primitive_operat = - 48: caml_string_of_jsbytes("Raised by primitive operation at"), - 49: cst_Called_from = caml_string_of_jsbytes("Called from"), - 50: cst_inlined = caml_string_of_jsbytes(" (inlined)"), - 51: _a_ = - 52: [0, - 53: [2, - 54: 0, - 55: [12, - 56: 32, - 57: [2, - 58: 0, - 59: [11, - 60: caml_string_of_jsbytes(' in file "'), - 61: [2, - 62: 0, - 63: [12, - 64: 34, - 65: [2, - 66: 0, - 67: [11, - 68: caml_string_of_jsbytes(", line "), - 69: [4, - 70: 0, + 4: //# shape: Test:[N,N,[N],N,N,N,N,N,N,N,N,N,N,F(2),F(2),[F(4)]] + 5: (function + 6: (globalThis){ + 7: "use strict"; + 8: var + 9: runtime = globalThis.jsoo_runtime, + 10: caml_string_of_jsbytes = runtime.caml_string_of_jsbytes; + 11: function caml_call2(f, a0, a1){ + 12: return (f.l >= 0 ? f.l : f.l = f.length) === 2 + 13: ? f(a0, a1) + 14: : runtime.caml_call_gen(f, [a0, a1]); + 15: } + 16: function caml_call3(f, a0, a1, a2){ + 17: return (f.l >= 0 ? f.l : f.l = f.length) === 3 + 18: ? f(a0, a1, a2) + 19: : runtime.caml_call_gen(f, [a0, a1, a2]); + 20: } + 21: function caml_call8(f, a0, a1, a2, a3, a4, a5, a6, a7){ + 22: return (f.l >= 0 ? f.l : f.l = f.length) === 8 + 23: ? f(a0, a1, a2, a3, a4, a5, a6, a7) + 24: : runtime.caml_call_gen(f, [a0, a1, a2, a3, a4, a5, a6, a7]); + 25: } + 26: var + 27: global_data = runtime.caml_get_global_data(), + 28: cst = caml_string_of_jsbytes(""), + 29: partial = [4, 0, 0, 0, [12, 45, [4, 0, 0, 0, 0]]], + 30: Stdlib_Printf = global_data.Stdlib__Printf, + 31: executable_name = + 32: /*<>*/ runtime.caml_sys_executable_name(0), + 33: os_type = /*<>*/ runtime.caml_sys_get_config(0)[1], + 34: backend_type = + 35: /*<>*/ [0, caml_string_of_jsbytes("js_of_ocaml")], + 36: unix = runtime.caml_sys_const_ostype_unix(0), + 37: win32 = runtime.caml_sys_const_ostype_win32(0), + 38: cygwin = runtime.caml_sys_const_ostype_cygwin(0), + 39: max_array_length = runtime.caml_sys_const_max_wosize(0), + 40: max_floatarray_length = max_array_length / 2 | 0, + 41: max_string_length = (4 * max_array_length | 0) - 1 | 0, + 42: Unhandled = + 43: [248, + 44: caml_string_of_jsbytes("Test.Unhandled"), + 45: runtime.caml_fresh_oo_id(0)], + 46: cst_Raised_at = caml_string_of_jsbytes("Raised at"), + 47: cst_Re_raised_at = caml_string_of_jsbytes("Re-raised at"), + 48: cst_Raised_by_primitive_operat = + 49: caml_string_of_jsbytes("Raised by primitive operation at"), + 50: cst_Called_from = caml_string_of_jsbytes("Called from"), + 51: cst_inlined = caml_string_of_jsbytes(" (inlined)"), + 52: _a_ = + 53: [0, + 54: [2, + 55: 0, + 56: [12, + 57: 32, + 58: [2, + 59: 0, + 60: [11, + 61: caml_string_of_jsbytes(' in file "'), + 62: [2, + 63: 0, + 64: [12, + 65: 34, + 66: [2, + 67: 0, + 68: [11, + 69: caml_string_of_jsbytes(", line "), + 70: [4, 71: 0, 72: 0, - 73: [11, caml_string_of_jsbytes(", characters "), partial]]]]]]]]]], - 74: caml_string_of_jsbytes - 75: ('%s %s in file "%s"%s, line %d, characters %d-%d')], - 76: _b_ = - 77: [0, - 78: [2, 0, [11, caml_string_of_jsbytes(" unknown location"), 0]], - 79: caml_string_of_jsbytes("%s unknown location")], - 80: _c_ = [0, [2, 0, [12, 10, 0]], caml_string_of_jsbytes("%s\n")], - 81: _d_ = - 82: [0, - 83: [11, - 84: caml_string_of_jsbytes - 85: ("(Program not linked with -g, cannot print stack backtrace)\n"), - 86: 0], - 87: caml_string_of_jsbytes - 88: ("(Program not linked with -g, cannot print stack backtrace)\n")]; - 89: function format_backtrace_slot(pos, slot){ - 90: function info(is_raise){ - 91: /*<>*/ return is_raise - 92: ? 0 === pos ? cst_Raised_at : cst_Re_raised_at - 93: : 0 === pos ? cst_Raised_by_primitive_operat : cst_Called_from /*<>*/ ; - 94: } - 95: /*<>*/ if(0 === slot[0]){ - 96: var - 97: _g_ = /*<>*/ slot[5], - 98: _h_ = slot[4], - 99: _i_ = slot[3], - 100: _j_ = slot[6] ? cst_inlined : cst, - 101: _k_ = /*<>*/ slot[2], - 102: _l_ = slot[7], - 103: _m_ = info(slot[1]); - 104: /*<>*/ return [0, - 105: caml_call8 - 106: (Stdlib_Printf[4], _a_, _m_, _l_, _k_, _j_, _i_, _h_, _g_)] /*<>*/ ; - 107: } - 108: /*<>*/ if(slot[1]) /*<>*/ return 0; - 109: var _n_ = /*<>*/ info(0); - 110: /*<>*/ return [0, caml_call2(Stdlib_Printf[4], _b_, _n_)] /*<>*/ ; - 111: /*<>*/ } - 112: function print_exception_backtrace(outchan, backtrace){ - 113: /*<>*/ if(! backtrace) - 114: /*<>*/ return caml_call2(Stdlib_Printf[1], outchan, _d_) /*<>*/ ; - 115: var - 116: a = /*<>*/ backtrace[1], - 117: _e_ = /*<>*/ a.length - 2 | 0, - 118: _f_ = 0; - 119: if(_e_ >= 0){ - 120: var i = _f_; - 121: for(;;){ - 122: var - 123: match = - 124: /*<>*/ /*<>*/ format_backtrace_slot - 125: (i, /*<>*/ runtime.caml_check_bound(a, i)[i + 1]); - 126: /*<>*/ if(match){ - 127: var str = match[1]; - 128: /*<>*/ caml_call3(Stdlib_Printf[1], outchan, _c_, str); - 129: } - 130: var _g_ = /*<>*/ i + 1 | 0; - 131: if(_e_ === i) break; - 132: i = _g_; - 133: } - 134: } - 135: /*<>*/ return 0; - 136: /*<>*/ } - 137: function compare(left, right, e1, e2){ - 138: /*<>*/ if(0 === e1[0]){ - 139: var v1 = e1[1]; - 140: if(0 !== e2[0]) /*<>*/ return -1; - 141: var v2 = /*<>*/ e2[1]; - 142: /*<>*/ return caml_call2(left, v1, v2) /*<>*/ ; - 143: } - 144: var v1$0 = /*<>*/ e1[1]; - 145: if(0 === e2[0]) /*<>*/ return 1; - 146: var v2$0 = /*<>*/ e2[1]; - 147: /*<>*/ return caml_call2(right, v1$0, v2$0) /*<>*/ ; - 148: } - 149: var - 150: Either = /*<>*/ [0, compare], - 151: Test = - 152: [0, - 153: executable_name, - 154: os_type, - 155: backend_type, - 156: 0, - 157: 32, + 73: 0, + 74: [11, caml_string_of_jsbytes(", characters "), partial]]]]]]]]]], + 75: caml_string_of_jsbytes + 76: ('%s %s in file "%s"%s, line %d, characters %d-%d')], + 77: _b_ = + 78: [0, + 79: [2, 0, [11, caml_string_of_jsbytes(" unknown location"), 0]], + 80: caml_string_of_jsbytes("%s unknown location")], + 81: _c_ = [0, [2, 0, [12, 10, 0]], caml_string_of_jsbytes("%s\n")], + 82: _d_ = + 83: [0, + 84: [11, + 85: caml_string_of_jsbytes + 86: ("(Program not linked with -g, cannot print stack backtrace)\n"), + 87: 0], + 88: caml_string_of_jsbytes + 89: ("(Program not linked with -g, cannot print stack backtrace)\n")]; + 90: function format_backtrace_slot(pos, slot){ + 91: function info(is_raise){ + 92: /*<>*/ return is_raise + 93: ? 0 === pos ? cst_Raised_at : cst_Re_raised_at + 94: : 0 === pos ? cst_Raised_by_primitive_operat : cst_Called_from /*<>*/ ; + 95: } + 96: /*<>*/ if(0 === slot[0]){ + 97: var + 98: _g_ = /*<>*/ slot[5], + 99: _h_ = slot[4], + 100: _i_ = slot[3], + 101: _j_ = slot[6] ? cst_inlined : cst, + 102: _k_ = /*<>*/ slot[2], + 103: _l_ = slot[7], + 104: _m_ = info(slot[1]); + 105: /*<>*/ return [0, + 106: caml_call8 + 107: (Stdlib_Printf[4], _a_, _m_, _l_, _k_, _j_, _i_, _h_, _g_)] /*<>*/ ; + 108: } + 109: /*<>*/ if(slot[1]) /*<>*/ return 0; + 110: var _n_ = /*<>*/ info(0); + 111: /*<>*/ return [0, caml_call2(Stdlib_Printf[4], _b_, _n_)] /*<>*/ ; + 112: /*<>*/ } + 113: function print_exception_backtrace(outchan, backtrace){ + 114: /*<>*/ if(! backtrace) + 115: /*<>*/ return caml_call2(Stdlib_Printf[1], outchan, _d_) /*<>*/ ; + 116: var + 117: a = /*<>*/ backtrace[1], + 118: _e_ = /*<>*/ a.length - 2 | 0, + 119: _f_ = 0; + 120: if(_e_ >= 0){ + 121: var i = _f_; + 122: for(;;){ + 123: var + 124: match = + 125: /*<>*/ /*<>*/ format_backtrace_slot + 126: (i, /*<>*/ runtime.caml_check_bound(a, i)[i + 1]); + 127: /*<>*/ if(match){ + 128: var str = match[1]; + 129: /*<>*/ caml_call3(Stdlib_Printf[1], outchan, _c_, str); + 130: } + 131: var _g_ = /*<>*/ i + 1 | 0; + 132: if(_e_ === i) break; + 133: i = _g_; + 134: } + 135: } + 136: /*<>*/ return 0; + 137: /*<>*/ } + 138: function compare(left, right, e1, e2){ + 139: /*<>*/ if(0 === e1[0]){ + 140: var v1 = e1[1]; + 141: if(0 !== e2[0]) /*<>*/ return -1; + 142: var v2 = /*<>*/ e2[1]; + 143: /*<>*/ return caml_call2(left, v1, v2) /*<>*/ ; + 144: } + 145: var v1$0 = /*<>*/ e1[1]; + 146: if(0 === e2[0]) /*<>*/ return 1; + 147: var v2$0 = /*<>*/ e2[1]; + 148: /*<>*/ return caml_call2(right, v1$0, v2$0) /*<>*/ ; + 149: } + 150: var + 151: Either = /*<>*/ [0, compare], + 152: Test = + 153: [0, + 154: executable_name, + 155: os_type, + 156: backend_type, + 157: 0, 158: 32, - 159: unix, - 160: win32, - 161: cygwin, - 162: max_array_length, - 163: max_floatarray_length, - 164: max_string_length, - 165: Unhandled, - 166: format_backtrace_slot, - 167: print_exception_backtrace, - 168: Either]; - 169: runtime.caml_register_global(12, Test, "Test"); - 170: return; - 171: /*<>*/ } - 172: (globalThis)); - 173: - 174: //# sourceMappingURL=test.map + 159: 32, + 160: unix, + 161: win32, + 162: cygwin, + 163: max_array_length, + 164: max_floatarray_length, + 165: max_string_length, + 166: Unhandled, + 167: format_backtrace_slot, + 168: print_exception_backtrace, + 169: Either]; + 170: runtime.caml_register_global(12, Test, "Test"); + 171: return; + 172: /*<>*/ } + 173: (globalThis)); + 174: + 175: //# sourceMappingURL=test.map |}] diff --git a/compiler/tests-compiler/sourcemap.ml b/compiler/tests-compiler/sourcemap.ml index 661911190f..03c5ac62c0 100644 --- a/compiler/tests-compiler/sourcemap.ml +++ b/compiler/tests-compiler/sourcemap.ml @@ -72,27 +72,28 @@ let%expect_test _ = $ cat "test.js" 1: 2: //# unitInfo: Provides: Test - 3: (function(globalThis){ - 4: "use strict"; - 5: var runtime = globalThis.jsoo_runtime; - 6: function id(x){return x;} - 7: var Test = [0, id]; - 8: runtime.caml_register_global(0, Test, "Test"); - 9: return; - 10: } - 11: (globalThis)); - 12: - 13: //# sourceMappingURL=test.map - /builtin/blackbox.ml:1:0 -> 5:7 - /builtin/blackbox.ml:1:0 -> 5:17 - /builtin/blackbox.ml:1:0 -> 6:0 - /builtin/blackbox.ml:1:0 -> 6:12 - /builtin/blackbox.ml:1:0 -> 6:15 - /dune-root/test.ml:1:11 -> 6:18 - /dune-root/test.ml:1:12 -> 6:27 - /dune-root/test.ml:1:12 -> 7:0 - /dune-root/test.ml:1:12 -> 7:7 - /builtin/blackbox.ml:1:0 -> 7:14 + 3: //# shape: Test:[F(1)*] + 4: (function(globalThis){ + 5: "use strict"; + 6: var runtime = globalThis.jsoo_runtime; + 7: function id(x){return x;} + 8: var Test = [0, id]; + 9: runtime.caml_register_global(0, Test, "Test"); + 10: return; + 11: } + 12: (globalThis)); + 13: + 14: //# sourceMappingURL=test.map + /builtin/blackbox.ml:1:0 -> 6:7 + /builtin/blackbox.ml:1:0 -> 6:17 + /builtin/blackbox.ml:1:0 -> 7:0 + /builtin/blackbox.ml:1:0 -> 7:12 + /builtin/blackbox.ml:1:0 -> 7:15 + /dune-root/test.ml:1:11 -> 7:18 + /dune-root/test.ml:1:12 -> 7:27 + /dune-root/test.ml:1:12 -> 8:0 + /dune-root/test.ml:1:12 -> 8:7 + /builtin/blackbox.ml:1:0 -> 8:14 |}] let%expect_test _ = From acfe19674657526e21d46e67750990a27b6a357a Mon Sep 17 00:00:00 2001 From: Hugo Heuzard Date: Tue, 10 Jun 2025 15:55:36 +0200 Subject: [PATCH 11/13] Misc: Bump version to accomodate dune version check --- VERSION | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/VERSION b/VERSION index 5fe6072304..dfda3e0b4f 100644 --- a/VERSION +++ b/VERSION @@ -1 +1 @@ -6.0.1 +6.1.0 From 681827db4e4720063125cc9e8045e47835f1fa72 Mon Sep 17 00:00:00 2001 From: Hugo Heuzard Date: Tue, 10 Jun 2025 19:52:07 +0200 Subject: [PATCH 12/13] Compiler: wasmoo support for shapes --- compiler/bin-wasm_of_ocaml/cmd_arg.ml | 13 ++++- compiler/bin-wasm_of_ocaml/cmd_arg.mli | 1 + compiler/bin-wasm_of_ocaml/compile.ml | 77 +++++++++++++++++++++----- compiler/lib-wasm/link.ml | 1 + compiler/lib/driver.ml | 2 + compiler/lib/parse_bytecode.ml | 3 + 6 files changed, 80 insertions(+), 17 deletions(-) diff --git a/compiler/bin-wasm_of_ocaml/cmd_arg.ml b/compiler/bin-wasm_of_ocaml/cmd_arg.ml index c965736f7b..1dcce5b33d 100644 --- a/compiler/bin-wasm_of_ocaml/cmd_arg.ml +++ b/compiler/bin-wasm_of_ocaml/cmd_arg.ml @@ -63,6 +63,7 @@ type t = ; params : (string * string) list ; include_dirs : string list ; effects : Config.effects_backend + ; shape_files : string list } let options () = @@ -78,6 +79,10 @@ let options () = let doc = "Compile the bytecode program [$(docv)]. " in Arg.(required & pos ~rev:true 0 (some string) None & info [] ~docv:"PROGRAM" ~doc) in + let shape_files = + let doc = "load shape file [$(docv)]." in + Arg.(value & opt_all string [] & info [ "load-shape" ] ~docv:"FILE" ~doc) + in let profile = let doc = "Set optimization profile : [$(docv)]." in let profile = @@ -140,7 +145,8 @@ let options () = output_file input_file runtime_files - effects = + effects + shape_files = let chop_extension s = try Filename.chop_extension s with Invalid_argument _ -> s in let output_file = let ext = @@ -172,6 +178,7 @@ let options () = ; sourcemap_root ; sourcemap_don't_inline_content ; effects + ; shape_files } in let t = @@ -189,7 +196,8 @@ let options () = $ output_file $ input_file $ runtime_files - $ effects) + $ effects + $ shape_files) in Term.ret t @@ -270,6 +278,7 @@ let options_runtime_only () = ; sourcemap_root ; sourcemap_don't_inline_content ; effects + ; shape_files = [] } in let t = diff --git a/compiler/bin-wasm_of_ocaml/cmd_arg.mli b/compiler/bin-wasm_of_ocaml/cmd_arg.mli index cb73999673..5f869ed796 100644 --- a/compiler/bin-wasm_of_ocaml/cmd_arg.mli +++ b/compiler/bin-wasm_of_ocaml/cmd_arg.mli @@ -32,6 +32,7 @@ type t = ; params : (string * string) list ; include_dirs : string list ; effects : Config.effects_backend + ; shape_files : string list } val options : unit -> t Cmdliner.Term.t diff --git a/compiler/bin-wasm_of_ocaml/compile.ml b/compiler/bin-wasm_of_ocaml/compile.ml index 8b9ee787df..9a11c79802 100644 --- a/compiler/bin-wasm_of_ocaml/compile.ml +++ b/compiler/bin-wasm_of_ocaml/compile.ml @@ -245,7 +245,15 @@ let generate_prelude ~out_file = @@ fun ch -> let code, uinfo = Parse_bytecode.predefined_exceptions () in let profile = Profile.O1 in - let Driver.{ program; variable_uses; in_cps; deadcode_sentinal; _ }, global_flow_data = + let ( Driver. + { program + ; variable_uses + ; in_cps + ; deadcode_sentinal + ; shapes = _ + ; trampolined_calls = _ + } + , global_flow_data ) = Driver.optimize_for_wasm ~profile ~shapes:false code in let context = Generate.start () in @@ -328,6 +336,16 @@ let add_source_map sourcemap_don't_inline_content z opt_source_map = ~name:(Link.source_name i j file) ~contents:(Yojson.Basic.to_string (`String sm)))) +let merge_shape a b = + StringMap.union (fun _name s1 s2 -> if Shape.equal s1 s2 then Some s1 else None) a b + +let sexp_of_shapes s = + StringMap.bindings s + |> List.map ~f:(fun (name, shape) -> + Sexp.List [ Atom name; Atom (Shape.to_string shape) ]) + +let string_of_shapes s = Sexp.List (sexp_of_shapes s) |> Sexp.to_string + let run { Cmd_arg.common ; profile @@ -341,11 +359,24 @@ let run ; sourcemap_root ; sourcemap_don't_inline_content ; effects + ; shape_files } = Config.set_target `Wasm; Jsoo_cmdline.Arg.eval common; Config.set_effects_backend effects; Generate.init (); + List.iter shape_files ~f:(fun s -> + let z = Zip.open_in s in + if Zip.has_entry z ~name:"shapes.sexp" + then + let s = Zip.read_entry z ~name:"shapes.sexp" in + match Sexp.from_string s with + | List l -> + List.iter l ~f:(function + | Sexp.List [ Atom name; Atom shape ] -> + Shape.Store.set ~name (Shape.of_string shape) + | _ -> ()) + | _ -> ()); let output_file = fst output_file in if debug_mem () then Debug.start_profiling output_file; List.iter params ~f:(fun (s, v) -> Config.Param.set s v); @@ -398,10 +429,18 @@ let run check_debug one; let code = one.code in let standalone = Option.is_none unit_name in - let Driver.{ program; variable_uses; in_cps; deadcode_sentinal; _ }, global_flow_data - = - Driver.optimize_for_wasm ~profile ~shapes:false code + let ( Driver. + { program + ; variable_uses + ; in_cps + ; deadcode_sentinal + ; shapes + ; trampolined_calls = _ + } + , global_flow_data ) = + Driver.optimize_for_wasm ~profile ~shapes:true code in + StringMap.iter (fun name shape -> Shape.Store.set ~name shape) shapes; let context = Generate.start () in let toplevel_name, generated_js = Generate.f @@ -423,7 +462,7 @@ let run Generate.output ch ~context; close_out ch); if times () then Format.eprintf "compilation: %a@." Timer.print t; - generated_js + generated_js, shapes in (if runtime_only then ( @@ -479,7 +518,7 @@ let run then Some (Filename.temp_file unit_name ".wasm.map") else None) @@ fun opt_tmp_map_file -> - let unit_data = + let unit_data, shapes = Fs.with_intermediate_file (Filename.temp_file unit_name ".wasm") @@ fun input_file -> opt_with @@ -488,7 +527,7 @@ let run then Some (Filename.temp_file unit_name ".wasm.map") else None) @@ fun opt_input_sourcemap -> - let fragments = + let fragments, shapes = output code ~wat_file: @@ -504,9 +543,9 @@ let run ~input_file ~output_file:tmp_wasm_file (); - { Link.unit_name; unit_info; fragments } + { Link.unit_name; unit_info; fragments }, shapes in - cont unit_data unit_name tmp_wasm_file opt_tmp_map_file + cont unit_data unit_name tmp_wasm_file opt_tmp_map_file shapes in (match kind with | `Exe -> @@ -537,7 +576,7 @@ let run then Some (Filename.temp_file "code" ".wasm.map") else None in - let generated_js = + let generated_js, _shapes = output code ~unit_name:None @@ -601,8 +640,9 @@ let run @@ fun tmp_output_file -> let z = Zip.open_out tmp_output_file in let compile_cmo' z cmo = - compile_cmo cmo (fun unit_data _ tmp_wasm_file opt_tmp_map_file -> + compile_cmo cmo (fun unit_data _ tmp_wasm_file opt_tmp_map_file shapes -> Zip.add_file z ~name:"code.wasm" ~file:tmp_wasm_file; + Zip.add_entry z ~name:"shapes.sexp" ~contents:(string_of_shapes shapes); add_source_map sourcemap_don't_inline_content z (`File opt_tmp_map_file); unit_data) in @@ -618,8 +658,8 @@ let run List.fold_right ~f:(fun cmo cont l -> compile_cmo cmo - @@ fun unit_data unit_name tmp_wasm_file opt_tmp_map_file -> - cont ((unit_data, unit_name, tmp_wasm_file, opt_tmp_map_file) :: l)) + @@ fun unit_data unit_name tmp_wasm_file opt_tmp_map_file shapes -> + cont ((unit_data, unit_name, tmp_wasm_file, opt_tmp_map_file, shapes) :: l)) cma.lib_units ~init:(fun l -> Fs.with_intermediate_file (Filename.temp_file "wasm" ".wasm") @@ -628,7 +668,7 @@ let run let source_map = Wasm_link.f (List.map - ~f:(fun (_, _, file, opt_source_map) -> + ~f:(fun (_, _, file, opt_source_map, _) -> { Wasm_link.module_name = "OCaml" ; file ; code = None @@ -641,10 +681,17 @@ let run ~output_file:tmp_wasm_file in Zip.add_file z ~name:"code.wasm" ~file:tmp_wasm_file; + let shapes = + List.fold_left + ~init:StringMap.empty + ~f:(fun acc (_, _, _, _, shapes) -> merge_shape acc shapes) + l + in + Zip.add_entry z ~name:"shapes.sexp" ~contents:(string_of_shapes shapes); if enable_source_maps then add_source_map sourcemap_don't_inline_content z (`Source_map source_map); - List.map ~f:(fun (unit_data, _, _, _) -> unit_data) l) + List.map ~f:(fun (unit_data, _, _, _, _) -> unit_data) l) [] in Link.add_info z ~build_info:(Build_info.create `Cma) ~unit_data (); diff --git a/compiler/lib-wasm/link.ml b/compiler/lib-wasm/link.ml index f2c527323b..272cc19054 100644 --- a/compiler/lib-wasm/link.ml +++ b/compiler/lib-wasm/link.ml @@ -345,6 +345,7 @@ let info_from_sexp info = let build_info = info |> member "build_info" |> mandatory (single Build_info.from_sexp) in + let predefined_exceptions = info |> member "predefined_exceptions" diff --git a/compiler/lib/driver.ml b/compiler/lib/driver.ml index 7d514c74c0..b5bb3c1211 100644 --- a/compiler/lib/driver.ml +++ b/compiler/lib/driver.ml @@ -120,6 +120,8 @@ let collects_shapes ~shapes (p : Code.program) = | Utf (Utf8 s) -> s in shapes := StringMap.add name block !shapes + | Code.Let (_, Prim (Extern "caml_set_global", [ Pc (String name); Pv block ])) + -> shapes := StringMap.add name block !shapes | _ -> ())) p.blocks; let map = diff --git a/compiler/lib/parse_bytecode.ml b/compiler/lib/parse_bytecode.ml index 6c2466ebf8..56d870704e 100644 --- a/compiler/lib/parse_bytecode.ml +++ b/compiler/lib/parse_bytecode.ml @@ -844,6 +844,9 @@ let get_global state instrs i = let x, state = State.fresh_var state in if debug_parser () then Format.printf "%a = get_global(%s)@." Var.print x name; + (match Shape.Store.load ~name with + | None -> () + | Some shape -> Shape.State.assign x shape); ( x , state , Let (x, Prim (Extern "caml_get_global", [ Pc (String name) ])) :: instrs From 7034a9dec9b46b388bf72feb3abb53ca514529c4 Mon Sep 17 00:00:00 2001 From: Hugo Heuzard Date: Wed, 18 Jun 2025 21:04:17 +0200 Subject: [PATCH 13/13] small cleanup --- compiler/lib-wasm/link.ml | 1 - compiler/lib/shape.ml | 2 +- 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/compiler/lib-wasm/link.ml b/compiler/lib-wasm/link.ml index 272cc19054..f2c527323b 100644 --- a/compiler/lib-wasm/link.ml +++ b/compiler/lib-wasm/link.ml @@ -345,7 +345,6 @@ let info_from_sexp info = let build_info = info |> member "build_info" |> mandatory (single Build_info.from_sexp) in - let predefined_exceptions = info |> member "predefined_exceptions" diff --git a/compiler/lib/shape.ml b/compiler/lib/shape.ml index 45d64e97d3..9337f46819 100644 --- a/compiler/lib/shape.ml +++ b/compiler/lib/shape.ml @@ -45,7 +45,7 @@ let rec merge (u : t) (v : t) = , Function { arity = a2; pure = p2; res = r2 } ) -> if a1 = a2 then Function { arity = a1; pure = p1 && p2; res = merge r1 r2 } else Top | Block b1, Block b2 -> - if List.length b1 = List.length b2 then Block (List.map2 b1 b2 ~f:merge) else Top + if List.compare_lengths b1 b2 = 0 then Block (List.map2 b1 b2 ~f:merge) else Top | Top, _ | _, Top -> Top | Function _, Block _ | Block _, Function _ -> Top