Skip to content

Commit

Permalink
remove stub parameter instead of asserting
Browse files Browse the repository at this point in the history
  • Loading branch information
sadiqj committed Nov 3, 2021
1 parent 705c6d9 commit cf40f68
Show file tree
Hide file tree
Showing 3 changed files with 2 additions and 6 deletions.
6 changes: 2 additions & 4 deletions middle_end/flambda/flambda_utils.ml
Original file line number Diff line number Diff line change
Expand Up @@ -328,7 +328,7 @@ let toplevel_substitution_named sb named =
| _ -> assert false

let make_closure_declaration
~is_classic_mode ~id ~body ~params ~stub : Flambda.t =
~is_classic_mode ~id ~body ~params : Flambda.t =
let free_variables = Flambda.free_variables body in
let param_set = Parameter.Set.vars params in
if not (Variable.Set.subset param_set free_variables) then begin
Expand All @@ -347,14 +347,12 @@ let make_closure_declaration
let subst_param param = Parameter.map_var subst param in
let function_declaration =
Flambda.create_function_declaration ~params:(List.map subst_param params)
~body ~stub ~dbg:Debuginfo.none ~inline:Default_inline
~body ~stub:true ~dbg:Debuginfo.none ~inline:Default_inline
~specialise:Default_specialise ~is_a_functor:false
~closure_origin:(Closure_origin.create (Closure_id.wrap id))
~poll:Default_poll
in
begin
(* this is required because we hardcode poll behaviour above *)
assert( stub );
assert (Variable.Set.equal (Variable.Set.map subst free_variables)
function_declaration.free_variables);
end;
Expand Down
1 change: 0 additions & 1 deletion middle_end/flambda/flambda_utils.mli
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,6 @@ val make_closure_declaration
-> id:Variable.t
-> body:Flambda.t
-> params:Parameter.t list
-> stub:bool
-> Flambda.t

val toplevel_substitution
Expand Down
1 change: 0 additions & 1 deletion middle_end/flambda/inline_and_simplify.ml
Original file line number Diff line number Diff line change
Expand Up @@ -835,7 +835,6 @@ and simplify_partial_application env r ~lhs_of_application
~is_classic_mode:false
~body
~params:remaining_args
~stub:true
in
let with_known_args =
Flambda_utils.bind
Expand Down

0 comments on commit cf40f68

Please sign in to comment.