File tree Expand file tree Collapse file tree 11 files changed +73
-66
lines changed Expand file tree Collapse file tree 11 files changed +73
-66
lines changed Original file line number Diff line number Diff line change @@ -304,10 +304,11 @@ let run
304304 if times () then Format. eprintf " Start parsing...@." ;
305305 let need_debug = enable_source_maps || Config.Flag. debuginfo () in
306306 let check_debug (one : Parse_bytecode.one ) =
307- if (not runtime_only)
308- && enable_source_maps
309- && Parse_bytecode.Debug. is_empty one.debug
310- && not (Code. is_empty one.code)
307+ if
308+ (not runtime_only)
309+ && enable_source_maps
310+ && Parse_bytecode.Debug. is_empty one.debug
311+ && not (Code. is_empty one.code)
311312 then
312313 warn
313314 " Warning: '--source-map' is enabled but the bytecode program was compiled with \
Original file line number Diff line number Diff line change @@ -28,8 +28,8 @@ let () =
2828 String. length x > 0
2929 && (not (Char. equal x.[0 ] '-' ))
3030 && String. for_all x ~f: (function
31- | 'a' .. 'z' | 'A' .. 'Z' | '-' -> true
32- | _ -> false )
31+ | 'a' .. 'z' | 'A' .. 'Z' | '-' -> true
32+ | _ -> false )
3333 in
3434 match Array. to_list argv with
3535 | exe :: maybe_command :: rest ->
Original file line number Diff line number Diff line change @@ -63,15 +63,15 @@ let link ~runtime_files ~input_files ~opt_output_sourcemap ~output_file =
6363let generate_dependencies ~dependencies primitives =
6464 Yojson.Basic. to_string
6565 (`List
66- (StringSet. fold
67- (fun nm s ->
68- `Assoc
69- [ " name" , `String (" js:" ^ nm)
70- ; " import" , `List [ `String " js" ; `String nm ]
71- ]
72- :: s)
73- primitives
74- (Yojson.Basic.Util. to_list (Yojson.Basic. from_string dependencies))))
66+ (StringSet. fold
67+ (fun nm s ->
68+ `Assoc
69+ [ " name" , `String (" js:" ^ nm)
70+ ; " import" , `List [ `String " js" ; `String nm ]
71+ ]
72+ :: s)
73+ primitives
74+ (Yojson.Basic.Util. to_list (Yojson.Basic. from_string dependencies))))
7575
7676let filter_unused_primitives primitives usage_file =
7777 let ch = open_in usage_file in
Original file line number Diff line number Diff line change @@ -909,18 +909,18 @@ module Constant = struct
909909 let str_js_utf8 s =
910910 let b = Buffer. create (String. length s) in
911911 String. iter s ~f: (function
912- | '\\' -> Buffer. add_string b " \\\\ "
913- | c -> Buffer. add_char b c);
912+ | '\\' -> Buffer. add_string b " \\\\ "
913+ | c -> Buffer. add_char b c);
914914 Buffer. contents b
915915
916916 let str_js_byte s =
917917 let b = Buffer. create (String. length s) in
918918 String. iter s ~f: (function
919- | '\\' -> Buffer. add_string b " \\\\ "
920- | '\128' .. '\255' as c ->
921- Buffer. add_string b " \\ x" ;
922- Buffer. add_char_hex b c
923- | c -> Buffer. add_char b c);
919+ | '\\' -> Buffer. add_string b " \\\\ "
920+ | '\128' .. '\255' as c ->
921+ Buffer. add_string b " \\ x" ;
922+ Buffer. add_char_hex b c
923+ | c -> Buffer. add_char b c);
924924 Buffer. contents b
925925
926926 type t =
@@ -952,12 +952,13 @@ module Constant = struct
952952 l
953953 in
954954 let c = W. ArrayNewFixed (ty, RefI31 (Const (I32 (Int32. of_int tag))) :: l') in
955- if List. exists
956- ~f: (fun (const , _ ) ->
957- match const with
958- | Const | Const_named _ -> false
959- | Mutated -> true )
960- l
955+ if
956+ List. exists
957+ ~f: (fun (const , _ ) ->
958+ match const with
959+ | Const | Const_named _ -> false
960+ | Mutated -> true )
961+ l
961962 then
962963 let * c = store_in_global c in
963964 let * () =
Original file line number Diff line number Diff line change @@ -890,12 +890,13 @@ module Generate (Target : Target_sig.S) = struct
890890 in
891891 (* Do not insert a block if the inner code contains a
892892 structured control flow instruction ([if] or [try] *)
893- if (not (List. is_empty rem))
894- ||
895- let block = Addr.Map. find pc ctx.blocks in
896- match block.branch with
897- | Cond _ | Pushtrap _ -> false (* ZZZ also some Switch*)
898- | _ -> true
893+ if
894+ (not (List. is_empty rem))
895+ ||
896+ let block = Addr.Map. find pc ctx.blocks in
897+ match block.branch with
898+ | Cond _ | Pushtrap _ -> false (* ZZZ also some Switch*)
899+ | _ -> true
899900 then
900901 block { params = [] ; result = [] } (code ~context: (`Block pc' :: context))
901902 else code ~context
@@ -967,8 +968,8 @@ module Generate (Target : Target_sig.S) = struct
967968 match fall_through with
968969 | `Block dst' when dst = dst' -> return ()
969970 | _ ->
970- if (src > = 0 && Structure. is_backward g src dst)
971- || Structure. is_merge_node g dst
971+ if
972+ (src > = 0 && Structure. is_backward g src dst) || Structure. is_merge_node g dst
972973 then instr (Br (label_index context dst, None ))
973974 else translate_tree result_typ fall_through dst context
974975 in
Original file line number Diff line number Diff line change @@ -739,14 +739,15 @@ let link ~output_file ~linkall ~enable_source_maps ~files =
739739 | `Cmo -> true
740740 | `Cma | `Exe | `Runtime | `Unknown -> false
741741 in
742- if (not (Config.Flag. auto_link () ))
743- || cmo_file
744- || linkall
745- || List. exists ~f: (fun { unit_info; _ } -> unit_info.force_link) units
746- || List. exists
747- ~f: (fun { unit_info; _ } ->
748- not (StringSet. is_empty (StringSet. inter requires unit_info.provides)))
749- units
742+ if
743+ (not (Config.Flag. auto_link () ))
744+ || cmo_file
745+ || linkall
746+ || List. exists ~f: (fun { unit_info; _ } -> unit_info.force_link) units
747+ || List. exists
748+ ~f: (fun { unit_info; _ } ->
749+ not (StringSet. is_empty (StringSet. inter requires unit_info.provides)))
750+ units
750751 then
751752 ( List. fold_right units ~init: requires ~f: (fun { unit_info; _ } requires ->
752753 StringSet. diff
@@ -769,11 +770,12 @@ let link ~output_file ~linkall ~enable_source_maps ~files =
769770 units
770771 ~init: acc
771772 ~f: (fun { unit_name; unit_info; _ } (requires , to_link ) ->
772- if (not (Config.Flag. auto_link () ))
773- || cmo_file
774- || linkall
775- || unit_info.force_link
776- || not (StringSet. is_empty (StringSet. inter requires unit_info.provides))
773+ if
774+ (not (Config.Flag. auto_link () ))
775+ || cmo_file
776+ || linkall
777+ || unit_info.force_link
778+ || not (StringSet. is_empty (StringSet. inter requires unit_info.provides))
777779 then
778780 ( StringSet. diff
779781 (StringSet. union unit_info.requires requires)
Original file line number Diff line number Diff line change @@ -365,8 +365,9 @@ module Read = struct
365365 let header = " \000 asm\001\000\000\000 "
366366
367367 let check_header file contents =
368- if String. length contents < 8
369- || not (String. equal header (String. sub contents ~pos: 0 ~len: 8 ))
368+ if
369+ String. length contents < 8
370+ || not (String. equal header (String. sub contents ~pos: 0 ~len: 8 ))
370371 then failwith (file ^ " is not a Wasm binary file (bad magic)" )
371372
372373 type ch =
Original file line number Diff line number Diff line change @@ -914,7 +914,7 @@ end = struct
914914 set
915915 |> expr_function_references e
916916 |> (fun init ->
917- List. fold_left ~f: (fun set i -> instr_function_references i set) ~init l1)
917+ List. fold_left ~f: (fun set i -> instr_function_references i set) ~init l1)
918918 |> fun init ->
919919 List. fold_left ~f: (fun set i -> instr_function_references i set) ~init l2
920920 | Br (_ , None ) | Return None | Nop | Rethrow _ -> set
Original file line number Diff line number Diff line change @@ -119,22 +119,23 @@ let rec format_sexp f s =
119119 | List l ->
120120 let has_comment =
121121 List. exists l ~f: (function
122- | Comment _ -> true
123- | _ -> false )
122+ | Comment _ -> true
123+ | _ -> false )
124124 in
125125 if has_comment
126126 then (* Ensure comments are on their own line *)
127127 Format. fprintf f " @[<v 2>("
128128 else Format. fprintf f " @[<2>(" ;
129129 Format. pp_print_list ~pp_sep: (fun f () -> Format. fprintf f " @ " ) format_sexp f l;
130- if has_comment
131- && List. fold_left
132- ~f: (fun _ i ->
133- match i with
134- | Comment _ -> true
135- | _ -> false )
136- ~init: false
137- l
130+ if
131+ has_comment
132+ && List. fold_left
133+ ~f: (fun _ i ->
134+ match i with
135+ | Comment _ -> true
136+ | _ -> false )
137+ ~init: false
138+ l
138139 then
139140 (* Make sure there is a newline when a comment is at the very end. *)
140141 Format. fprintf f " @ " ;
Original file line number Diff line number Diff line change @@ -237,8 +237,8 @@ let expr_escape st _x e =
237237 Array. iter a ~f: (fun x -> block_escape st x)
238238 | Expr
239239 (Prim
240- ( Extern (" caml_make_array" | " caml_array_of_uniform_array" )
241- , [ Pv y ] )) -> (
240+ ( Extern (" caml_make_array" | " caml_array_of_uniform_array" )
241+ , [ Pv y ] )) -> (
242242 match st.defs.(Var. idx y) with
243243 | Expr (Block (_ , a , _ , _ )) ->
244244 Array. iter a ~f: (fun x -> block_escape st x)
You can’t perform that action at this time.
0 commit comments