Skip to content

Commit

Permalink
reduce max_sensible_number_of_arguments
Browse files Browse the repository at this point in the history
  • Loading branch information
mshinwell committed Nov 9, 2015
1 parent d9b4402 commit 1c767bb
Show file tree
Hide file tree
Showing 4 changed files with 10 additions and 3 deletions.
2 changes: 1 addition & 1 deletion driver/optmain.ml
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ module Backend = struct

(* CR mshinwell: this needs tying through to [Proc], although it may
necessitate the introduction of a new field in that module. *)
let max_sensible_number_of_arguments = 15
let max_sensible_number_of_arguments = 9
end
let backend = (module Backend : Backend_intf.S)

Expand Down
6 changes: 4 additions & 2 deletions middle_end/backend_intf.mli
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,9 @@ module type S = sig
(** [true] iff the target architecture is big endian. *)
val big_endian : bool

(** Optimization passes should try not to add arguments to functions
that cause the total number of arguments to exceed this value. *)
(** The maximum number of arguments that is is reasonable for a function
to have. This should be fewer than the threshold that causes non-self
tail call optimization to be inhibited (in particular, if it would
entail passing arguments on the stack; see [Selectgen]). *)
val max_sensible_number_of_arguments : int
end
2 changes: 2 additions & 0 deletions middle_end/flambda.mli
Original file line number Diff line number Diff line change
Expand Up @@ -409,6 +409,8 @@ val fold_lets_option
-> init:'a
-> for_defining_expr:('a -> Variable.t -> named -> 'a * Variable.t * named)
-> for_last_body:('a -> t -> t * 'b)
(* CR-someday mshinwell: consider making [filter_defining_expr]
optional *)
-> filter_defining_expr:('b -> Variable.t -> named -> Variable.Set.t ->
'b * Variable.t * named option)
-> t * 'b
Expand Down
3 changes: 3 additions & 0 deletions middle_end/unbox_closures.ml
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,9 @@ let create_wrapper
~dbg:Debuginfo.none
~inline:Default_inline

(* It is important to limit the number of arguments added by this pass:
if arguments end up being passed on the stack, tail call optimization
will be disabled (see asmcomp/selectgen.ml). *)
let too_many_arguments ~backend
~(function_decl : Flambda.function_declaration) ~bound_by_closure =
let num_existing_arguments = List.length function_decl.params in
Expand Down

0 comments on commit 1c767bb

Please sign in to comment.