diff --git a/asmcomp/asmgen.ml b/asmcomp/asmgen.ml index c3bd1cb55..99e7dbe0d 100644 --- a/asmcomp/asmgen.ml +++ b/asmcomp/asmgen.ml @@ -27,8 +27,7 @@ type error = Assembler_error of string exception Error of error -let liveness ppf phrase = - Liveness.fundecl ppf phrase; phrase +let liveness phrase = Liveness.fundecl phrase; phrase let dump_if ppf flag message phrase = if !flag then Printmach.phase message ppf phrase @@ -96,7 +95,7 @@ let rec regalloc ppf round fd = let (newfd, redo_regalloc) = Reload.fundecl fd in dump_if ppf dump_reload "After insertion of reloading code" newfd; if redo_regalloc then begin - Reg.reinit(); Liveness.fundecl ppf newfd; regalloc ppf (round + 1) newfd + Reg.reinit(); Liveness.fundecl newfd; regalloc ppf (round + 1) newfd end else newfd let (++) x f = f x @@ -111,15 +110,15 @@ let compile_fundecl (ppf : formatter) fd_cmm = ++ pass_dump_if ppf dump_combine "After allocation combining" ++ Profile.record ~accumulate:true "cse" CSE.fundecl ++ pass_dump_if ppf dump_cse "After CSE" - ++ Profile.record ~accumulate:true "liveness" (liveness ppf) + ++ Profile.record ~accumulate:true "liveness" liveness ++ Profile.record ~accumulate:true "deadcode" Deadcode.fundecl ++ pass_dump_if ppf dump_live "Liveness analysis" ++ Profile.record ~accumulate:true "spill" Spill.fundecl - ++ Profile.record ~accumulate:true "liveness" (liveness ppf) + ++ Profile.record ~accumulate:true "liveness" liveness ++ pass_dump_if ppf dump_spill "After spilling" ++ Profile.record ~accumulate:true "split" Split.fundecl ++ pass_dump_if ppf dump_split "After live range splitting" - ++ Profile.record ~accumulate:true "liveness" (liveness ppf) + ++ Profile.record ~accumulate:true "liveness" liveness ++ Profile.record ~accumulate:true "regalloc" (regalloc ppf 1) ++ Profile.record ~accumulate:true "available_regs" Available_regs.fundecl ++ Profile.record ~accumulate:true "linearize" Linearize.fundecl diff --git a/asmcomp/liveness.ml b/asmcomp/liveness.ml index 9791e8c5c..28c5868c3 100644 --- a/asmcomp/liveness.ml +++ b/asmcomp/liveness.ml @@ -160,7 +160,7 @@ let reset () = live_at_raise := Reg.Set.empty; live_at_exit := [] -let fundecl ppf f = +let fundecl f = let initially_live = live f.fun_body Reg.Set.empty in (* Sanity check: only function parameters (and the Spacetime node hole register, if profiling) can be live at entrypoint *) @@ -170,6 +170,6 @@ let fundecl ppf f = else Reg.Set.remove Proc.loc_spacetime_node_hole wrong_live in if not (Reg.Set.is_empty wrong_live) then begin - Format.fprintf ppf "%a@." Printmach.regset wrong_live; - Misc.fatal_error "Liveness.fundecl" + Misc.fatal_errorf "@[Liveness.fundecl:@\n%a@]" + Printmach.regset wrong_live end diff --git a/asmcomp/liveness.mli b/asmcomp/liveness.mli index 7a8fae627..37f5c170b 100644 --- a/asmcomp/liveness.mli +++ b/asmcomp/liveness.mli @@ -16,7 +16,5 @@ (* Liveness analysis. Annotate mach code with the set of regs live at each point. *) -open Format - val reset : unit -> unit -val fundecl: formatter -> Mach.fundecl -> unit +val fundecl: Mach.fundecl -> unit