diff options
-rw-r--r-- | asmcomp/selectgen.ml | 24 | ||||
-rw-r--r-- | asmcomp/selectgen.mli | 43 |
2 files changed, 20 insertions, 47 deletions
diff --git a/asmcomp/selectgen.ml b/asmcomp/selectgen.ml index eee116932..7d0f9c805 100644 --- a/asmcomp/selectgen.ml +++ b/asmcomp/selectgen.ml @@ -243,7 +243,7 @@ method select_operation op args = | (Ccheckbound, _) -> self#select_arith Icheckbound args | _ -> fatal_error "Selection.select_oper" -method select_arith_comm op = function +private method select_arith_comm op = function [arg; Cconst_int n] when self#is_immediate n -> (Iintop_imm(op, n), [arg]) | [arg; Cconst_pointer n] when self#is_immediate n -> @@ -255,7 +255,7 @@ method select_arith_comm op = function | args -> (Iintop op, args) -method select_arith op = function +private method select_arith op = function [arg; Cconst_int n] when self#is_immediate n -> (Iintop_imm(op, n), [arg]) | [arg; Cconst_pointer n] when self#is_immediate n -> @@ -263,13 +263,13 @@ method select_arith op = function | args -> (Iintop op, args) -method select_shift op = function +private method select_shift op = function [arg; Cconst_int n] when n >= 0 & n < Arch.size_int * 8 -> (Iintop_imm(op, n), [arg]) | args -> (Iintop op, args) -method select_arith_comp cmp = function +private method select_arith_comp cmp = function [arg; Cconst_int n] when self#is_immediate n -> (Iintop_imm(Icomp cmp, n), [arg]) | [arg; Cconst_pointer n] when self#is_immediate n -> @@ -496,12 +496,12 @@ method emit_expr env exp = [||] [||]; r -method emit_sequence env exp = +private method emit_sequence env exp = let s = {< instr_seq = dummy_instr >} in let r = s#emit_expr env exp in (r, s) -method emit_let env v e1 = +private method emit_let env v e1 = let r1 = self#emit_expr env e1 in if all_regs_anonymous r1 then begin name_regs v r1; @@ -514,7 +514,7 @@ method emit_let env v e1 = Tbl.add v rv env end -method emit_parts env exp = +private method emit_parts env exp = if is_simple_expr exp then (exp, env) else begin @@ -536,7 +536,7 @@ method emit_parts env exp = end end -method emit_parts_list env exp_list = +private method emit_parts_list env exp_list = match exp_list with [] -> ([], env) | exp :: rem -> @@ -546,7 +546,7 @@ method emit_parts_list env exp_list = let (new_exp, fin_env) = self#emit_parts new_env exp in (new_exp :: new_rem, fin_env) -method emit_tuple env exp_list = +private method emit_tuple env exp_list = let rec emit_list = function [] -> [] | exp :: rem -> @@ -562,7 +562,7 @@ method emit_extcall_args env args = self#insert_move_args r1 loc_arg stack_ofs; arg_stack -method emit_stores env data regs_addr addr = +private method emit_stores env data regs_addr addr = let a = ref addr in List.iter (fun e -> @@ -574,7 +574,7 @@ method emit_stores env data regs_addr addr = (* Same, but in tail position *) -method emit_return env exp = +private method emit_return env exp = let r = self#emit_expr env exp in let loc = Proc.loc_results r in self#insert_moves r loc; @@ -663,7 +663,7 @@ method emit_tail env exp = | _ -> self#emit_return env exp -method emit_tail_sequence env exp = +private method emit_tail_sequence env exp = let s = {< instr_seq = dummy_instr >} in s#emit_tail env exp; s#extract diff --git a/asmcomp/selectgen.mli b/asmcomp/selectgen.mli index f9fa2bb5d..2e8a8610b 100644 --- a/asmcomp/selectgen.mli +++ b/asmcomp/selectgen.mli @@ -44,47 +44,20 @@ class virtual selector_generic (unit) : 'a = environment -> Cmm.expression list -> Reg.t array * int (* Can be overriden to deal with stack-based calling conventions *) - (* The following methods should not be overriden *) - method emit_expr : - environment -> Cmm.expression -> Reg.t array + (* The following method is the entry point and should not be overriden *) method emit_fundecl : Cmm.fundecl -> Mach.fundecl - method emit_let : - environment -> - Ident.t -> Cmm.expression -> environment - method emit_parts : - environment -> - Cmm.expression -> Cmm.expression * environment - method emit_parts_list : - environment -> - Cmm.expression list -> Cmm.expression list * environment - method emit_return : environment -> Cmm.expression -> unit - method emit_sequence : - environment -> Cmm.expression -> Reg.t array * 'a - method emit_stores : - environment -> - Cmm.expression list -> Reg.t array -> Arch.addressing_mode -> unit - method emit_tail : environment -> Cmm.expression -> unit - method emit_tail_sequence : - environment -> Cmm.expression -> Mach.instruction - method emit_tuple : - environment -> Cmm.expression list -> Reg.t array + + (* The following methods should not be overriden. They cannot be + declared "private" in the current implementation because they + are not always applied to "self", but ideally they should be private. *) method extract : Mach.instruction method insert : Mach.instruction_desc -> Reg.t array -> Reg.t array -> unit method insert_move : Reg.t -> Reg.t -> unit method insert_move_args : Reg.t array -> Reg.t array -> int -> unit method insert_move_results : Reg.t array -> Reg.t array -> int -> unit method insert_moves : Reg.t array -> Reg.t array -> unit - method select_arith : - Mach.integer_operation -> - Cmm.expression list -> Mach.operation * Cmm.expression list - method select_arith_comm : - Mach.integer_operation -> - Cmm.expression list -> Mach.operation * Cmm.expression list - method select_arith_comp : - Mach.integer_comparison -> - Cmm.expression list -> Mach.operation * Cmm.expression list - method select_shift : - Mach.integer_operation -> - Cmm.expression list -> Mach.operation * Cmm.expression list + method emit_expr : + (Ident.t, Reg.t array) Tbl.t -> Cmm.expression -> Reg.t array + method emit_tail : (Ident.t, Reg.t array) Tbl.t -> Cmm.expression -> unit end |