for review: new method of handling failures, part 2 of 6
Zoltan Somogyi
zs at cs.mu.OZ.AU
Thu Jul 2 16:20:11 AEST 1998
<continuing the new code_info.m>
% Submodule to deal with code_exprn.
:- interface.
:- pred code_info__variable_locations(map(var, set(rval)),
code_info, code_info).
:- mode code_info__variable_locations(out, in, out) is det.
:- pred code_info__set_var_location(var, lval, code_info, code_info).
:- mode code_info__set_var_location(in, in, in, out) is det.
:- pred code_info__cache_expression(var, rval, code_info, code_info).
:- mode code_info__cache_expression(in, in, in, out) is det.
:- pred code_info__place_var(var, lval, code_tree, code_info, code_info).
:- mode code_info__place_var(in, in, out, in, out) is det.
:- pred code_info__produce_variable(var, code_tree, rval, code_info, code_info).
:- mode code_info__produce_variable(in, out, out, in, out) is det.
:- pred code_info__produce_variable_in_reg(var, code_tree, rval,
code_info, code_info).
:- mode code_info__produce_variable_in_reg(in, out, out, in, out) is det.
:- pred code_info__produce_variable_in_reg_or_stack(var, code_tree, rval,
code_info, code_info).
:- mode code_info__produce_variable_in_reg_or_stack(in, out, out, in, out)
is det.
:- pred code_info__materialize_vars_in_rval(rval, rval, code_tree, code_info,
code_info).
:- mode code_info__materialize_vars_in_rval(in, out, out, in, out) is det.
:- pred code_info__lock_reg(lval, code_info, code_info).
:- mode code_info__lock_reg(in, in, out) is det.
:- pred code_info__unlock_reg(lval, code_info, code_info).
:- mode code_info__unlock_reg(in, in, out) is det.
:- pred code_info__acquire_reg_for_var(var, lval, code_info, code_info).
:- mode code_info__acquire_reg_for_var(in, out, in, out) is det.
:- pred code_info__acquire_reg(reg_type, lval, code_info, code_info).
:- mode code_info__acquire_reg(in, out, in, out) is det.
:- pred code_info__release_reg(lval, code_info, code_info).
:- mode code_info__release_reg(in, in, out) is det.
:- pred code_info__clear_r1(code_tree, code_info, code_info).
:- mode code_info__clear_r1(out, in, out) is det.
:- type call_direction ---> caller ; callee.
% Generate code to either setup the input arguments for a call
% (i.e. in the caller), or to setup the output arguments in the
% predicate epilog (i.e. in the callee).
:- pred code_info__setup_call(assoc_list(var, arg_info),
call_direction, code_tree, code_info, code_info).
:- mode code_info__setup_call(in, in, out, in, out) is det.
:- pred code_info__clear_all_registers(code_info, code_info).
:- mode code_info__clear_all_registers(in, out) is det.
:- pred code_info__save_variable_on_stack(var, code_tree,
code_info, code_info).
:- mode code_info__save_variable_on_stack(in, out, in, out) is det.
:- pred code_info__save_variables_on_stack(list(var), code_tree,
code_info, code_info).
:- mode code_info__save_variables_on_stack(in, out, in, out) is det.
:- pred code_info__max_reg_in_use(int, code_info, code_info).
:- mode code_info__max_reg_in_use(out, in, out) is det.
%---------------------------------------------------------------------------%
:- implementation.
:- pred code_info__place_vars(assoc_list(var, set(rval)), code_tree,
code_info, code_info).
:- mode code_info__place_vars(in, out, in, out) is det.
code_info__variable_locations(Locations) -->
code_info__get_exprn_info(Exprn),
{ code_exprn__get_varlocs(Exprn, Locations) }.
code_info__set_var_location(Var, Lval) -->
code_info__get_exprn_info(Exprn0),
{ code_exprn__set_var_location(Var, Lval, Exprn0, Exprn) },
code_info__set_exprn_info(Exprn).
code_info__cache_expression(Var, Rval) -->
code_info__get_exprn_info(Exprn0),
{ code_exprn__cache_exprn(Var, Rval, Exprn0, Exprn) },
code_info__set_exprn_info(Exprn).
code_info__place_var(Var, Lval, Code) -->
code_info__get_exprn_info(Exprn0),
{ code_exprn__place_var(Var, Lval, Code, Exprn0, Exprn) },
code_info__set_exprn_info(Exprn).
code_info__place_vars([], empty) --> [].
code_info__place_vars([V - Rs | RestList], Code) -->
(
{ set__to_sorted_list(Rs, RList) },
{ code_info__lval_in_rval_list(L, RList) }
->
code_info__place_var(V, L, ThisCode)
;
{ ThisCode = empty }
),
code_info__place_vars(RestList, RestCode),
{ Code = tree(ThisCode, RestCode) }.
:- pred code_info__lval_in_rval_list(lval, list(rval)).
:- mode code_info__lval_in_rval_list(out, in) is semidet.
code_info__lval_in_rval_list(Lval, [Rval | Rvals]) :-
( Rval = lval(Lval0) ->
Lval = Lval0
;
code_info__lval_in_rval_list(Lval, Rvals)
).
code_info__produce_variable(Var, Code, Rval) -->
code_info__get_exprn_info(Exprn0),
{ code_exprn__produce_var(Var, Rval, Code, Exprn0, Exprn) },
code_info__set_exprn_info(Exprn).
code_info__produce_variable_in_reg(Var, Code, Rval) -->
code_info__get_exprn_info(Exprn0),
{ code_exprn__produce_var_in_reg(Var, Rval, Code, Exprn0, Exprn) },
code_info__set_exprn_info(Exprn).
code_info__produce_variable_in_reg_or_stack(Var, Code, Rval) -->
code_info__get_exprn_info(Exprn0),
{ code_exprn__produce_var_in_reg_or_stack(Var, Rval, Code,
Exprn0, Exprn) },
code_info__set_exprn_info(Exprn).
code_info__materialize_vars_in_rval(Rval0, Rval, Code) -->
code_info__get_exprn_info(Exprn0),
{ code_exprn__materialize_vars_in_rval(Rval0, Rval, Code,
Exprn0, Exprn) },
code_info__set_exprn_info(Exprn).
code_info__lock_reg(Reg) -->
code_info__get_exprn_info(Exprn0),
{ code_exprn__lock_reg(Reg, Exprn0, Exprn) },
code_info__set_exprn_info(Exprn).
code_info__unlock_reg(Reg) -->
code_info__get_exprn_info(Exprn0),
{ code_exprn__unlock_reg(Reg, Exprn0, Exprn) },
code_info__set_exprn_info(Exprn).
code_info__acquire_reg_for_var(Var, Lval) -->
code_info__get_exprn_info(Exprn0),
code_info__get_follow_vars(Follow),
(
{ map__search(Follow, Var, PrefLval) },
{ PrefLval = reg(PrefRegType, PrefRegNum) }
->
{ code_exprn__acquire_reg_prefer_given(PrefRegType, PrefRegNum,
Lval, Exprn0, Exprn) }
;
{ code_exprn__acquire_reg(r, Lval, Exprn0, Exprn) }
),
code_info__set_exprn_info(Exprn).
code_info__acquire_reg(Type, Lval) -->
code_info__get_exprn_info(Exprn0),
{ code_exprn__acquire_reg(Type, Lval, Exprn0, Exprn) },
code_info__set_exprn_info(Exprn).
code_info__release_reg(Lval) -->
code_info__get_exprn_info(Exprn0),
{ code_exprn__release_reg(Lval, Exprn0, Exprn) },
code_info__set_exprn_info(Exprn).
code_info__clear_r1(Code) -->
code_info__get_exprn_info(Exprn0),
{ code_exprn__clear_r1(Code, Exprn0, Exprn) },
code_info__set_exprn_info(Exprn).
%---------------------------------------------------------------------------%
code_info__setup_call([], _Direction, empty) --> [].
code_info__setup_call([V - arg_info(Loc, Mode) | Rest], Direction, Code) -->
(
{
Mode = top_in,
Direction = caller
;
Mode = top_out,
Direction = callee
}
->
{ code_util__arg_loc_to_register(Loc, Reg) },
code_info__get_exprn_info(Exprn0),
{ code_exprn__place_var(V, Reg, Code0, Exprn0, Exprn1) },
% We need to test that either the variable
% is live OR it occurs in the remaining arguments
% because of a bug in polymorphism.m which
% causes some compiler generated code to violate
% superhomogeneous form
(
code_info__variable_is_forward_live(V)
->
{ IsLive = yes }
;
{ IsLive = no }
),
{
list__member(Vtmp - _, Rest),
V = Vtmp
->
Occurs = yes
;
Occurs = no
},
(
% We can't simply use a disj here
% because of bugs in modes/det_analysis
{ bool__or(Occurs, IsLive, yes) }
->
{ code_exprn__lock_reg(Reg, Exprn1, Exprn2) },
code_info__set_exprn_info(Exprn2),
code_info__setup_call(Rest, Direction, Code1),
code_info__get_exprn_info(Exprn3),
{ code_exprn__unlock_reg(Reg, Exprn3, Exprn) },
code_info__set_exprn_info(Exprn),
{ Code = tree(Code0, Code1) }
;
{ code_exprn__lock_reg(Reg, Exprn1, Exprn2) },
code_info__set_exprn_info(Exprn2),
{ set__singleton_set(Vset, V) },
code_info__make_vars_forward_dead(Vset),
code_info__setup_call(Rest, Direction, Code1),
code_info__get_exprn_info(Exprn4),
{ code_exprn__unlock_reg(Reg, Exprn4, Exprn) },
code_info__set_exprn_info(Exprn),
{ Code = tree(Code0, Code1) }
)
;
code_info__setup_call(Rest, Direction, Code)
).
% XXX We could use the sanity checking mechanism...
code_info__clear_all_registers -->
code_info__get_exprn_info(Exprn0),
{ code_exprn__clobber_regs([], Exprn0, Exprn) },
code_info__set_exprn_info(Exprn).
code_info__save_variable_on_stack(Var, Code) -->
code_info__get_variable_slot(Var, Slot),
code_info__get_exprn_info(Exprn0),
{ code_exprn__place_var(Var, Slot, Code, Exprn0, Exprn) },
code_info__set_exprn_info(Exprn).
code_info__save_variables_on_stack([], empty) --> [].
code_info__save_variables_on_stack([Var | Vars], Code) -->
code_info__save_variable_on_stack(Var, FirstCode),
code_info__save_variables_on_stack(Vars, RestCode),
{ Code = tree(FirstCode, RestCode) }.
code_info__max_reg_in_use(Max) -->
code_info__get_exprn_info(Exprn),
{ code_exprn__max_reg_in_use(Exprn, Max) }.
%---------------------------------------------------------------------------%
%---------------------------------------------------------------------------%
% Submodule for dealing with information for garbage collection
% and value numbering.
:- interface.
:- pred code_info__generate_stack_livevals(set(var), set(lval),
code_info, code_info).
:- mode code_info__generate_stack_livevals(in, out, in, out) is det.
:- pred code_info__generate_stack_livelvals(set(var), instmap,
list(liveinfo), code_info, code_info).
:- mode code_info__generate_stack_livelvals(in, in, out, in, out) is det.
%---------------------------------------------------------------------------%
:- implementation.
code_info__generate_stack_livevals(Args, LiveVals) -->
code_info__get_known_variables(LiveVars),
{ set__list_to_set(LiveVars, Vars0) },
{ set__difference(Vars0, Args, Vars) },
{ set__to_sorted_list(Vars, VarList) },
{ set__init(LiveVals0) },
code_info__generate_var_livevals(VarList, LiveVals0, LiveVals1),
code_info__get_temps_in_use(TempsSet),
{ map__to_assoc_list(TempsSet, Temps) },
{ code_info__generate_temp_livevals(Temps, LiveVals1, LiveVals) }.
:- pred code_info__generate_var_livevals(list(var), set(lval), set(lval),
code_info, code_info).
:- mode code_info__generate_var_livevals(in, in, out, in, out) is det.
code_info__generate_var_livevals([], Vals, Vals) --> [].
code_info__generate_var_livevals([V | Vs], Vals0, Vals) -->
code_info__get_variable_slot(V, Slot),
{ set__insert(Vals0, Slot, Vals1) },
code_info__generate_var_livevals(Vs, Vals1, Vals).
:- pred code_info__generate_temp_livevals(assoc_list(lval, slot_contents),
set(lval), set(lval)).
:- mode code_info__generate_temp_livevals(in, in, out) is det.
code_info__generate_temp_livevals([], Vals, Vals).
code_info__generate_temp_livevals([Slot - _ | Slots], Vals0, Vals) :-
set__insert(Vals0, Slot, Vals1),
code_info__generate_temp_livevals(Slots, Vals1, Vals).
%---------------------------------------------------------------------------%
code_info__generate_stack_livelvals(Args, AfterCallInstMap, LiveVals) -->
code_info__get_known_variables(LiveVars),
{ set__list_to_set(LiveVars, Vars0) },
{ set__difference(Vars0, Args, Vars) },
{ set__to_sorted_list(Vars, VarList) },
{ set__init(LiveVals0) },
code_info__generate_var_livelvals(VarList, LiveVals0, LiveVals1),
{ set__to_sorted_list(LiveVals1, LiveVals2) },
code_info__get_globals(Globals),
{ globals__get_gc_method(Globals, GC_Method) },
{ globals__get_trace_level(Globals, TraceLevel) },
{
( GC_Method = accurate
; trace_level_trace_returns(TraceLevel, yes)
)
->
NeedVarInfo = yes
;
NeedVarInfo = no
},
code_info__livevals_to_livelvals(LiveVals2, NeedVarInfo,
AfterCallInstMap, LiveVals3),
code_info__get_temps_in_use(TempsSet),
{ map__to_assoc_list(TempsSet, Temps) },
{ code_info__generate_temp_livelvals(Temps, LiveVals3, LiveVals) }.
:- pred code_info__generate_var_livelvals(list(var),
set(pair(lval, var)), set(pair(lval, var)), code_info, code_info).
:- mode code_info__generate_var_livelvals(in, in, out, in, out) is det.
code_info__generate_var_livelvals([], Vals, Vals) --> [].
code_info__generate_var_livelvals([V | Vs], Vals0, Vals) -->
code_info__get_variable_slot(V, Slot),
{ set__insert(Vals0, Slot - V, Vals1) },
code_info__generate_var_livelvals(Vs, Vals1, Vals).
:- pred code_info__generate_temp_livelvals(assoc_list(lval, slot_contents),
list(liveinfo), list(liveinfo)).
:- mode code_info__generate_temp_livelvals(in, in, out) is det.
code_info__generate_temp_livelvals([], LiveInfo, LiveInfo).
code_info__generate_temp_livelvals([Slot - StoredLval | Slots], LiveInfo0,
[live_lvalue(Slot, LiveValueType, "", []) | LiveInfo1]) :-
code_info__get_live_value_type(StoredLval, LiveValueType),
code_info__generate_temp_livelvals(Slots, LiveInfo0, LiveInfo1).
:- pred code_info__livevals_to_livelvals(assoc_list(lval, var), bool,
instmap, list(liveinfo), code_info, code_info).
:- mode code_info__livevals_to_livelvals(in, in, in, out, in, out) is det.
code_info__livevals_to_livelvals([], _, _, []) --> [].
code_info__livevals_to_livelvals([Lval - Var | Ls], NeedVarInfo,
AfterCallInstMap, [LiveLval | Lives]) -->
code_info__get_varset(VarSet),
{ varset__lookup_name(VarSet, Var, Name) },
(
{ NeedVarInfo = yes }
->
{ instmap__lookup_var(AfterCallInstMap, Var, Inst) },
code_info__variable_type(Var, Type),
{ type_util__vars(Type, TypeVars) },
code_info__find_type_infos(TypeVars, TypeParams),
{ LiveLval = live_lvalue(Lval, var(Type, Inst), Name,
TypeParams) }
;
{ LiveLval = live_lvalue(Lval, unwanted, Name, []) }
),
code_info__livevals_to_livelvals(Ls, NeedVarInfo, AfterCallInstMap,
Lives).
:- pred code_info__get_live_value_type(slot_contents, live_value_type).
:- mode code_info__get_live_value_type(in, out) is det.
code_info__get_live_value_type(lval(succip), succip).
code_info__get_live_value_type(lval(hp), hp).
code_info__get_live_value_type(lval(maxfr), maxfr).
code_info__get_live_value_type(lval(curfr), curfr).
code_info__get_live_value_type(lval(succfr(_)), unwanted).
code_info__get_live_value_type(lval(prevfr(_)), unwanted).
code_info__get_live_value_type(lval(redofr(_)), unwanted).
code_info__get_live_value_type(lval(redoip(_)), unwanted).
code_info__get_live_value_type(lval(succip(_)), unwanted).
code_info__get_live_value_type(lval(sp), unwanted).
code_info__get_live_value_type(lval(lvar(_)), unwanted).
code_info__get_live_value_type(lval(field(_, _, _)), unwanted).
code_info__get_live_value_type(lval(temp(_, _)), unwanted).
code_info__get_live_value_type(lval(reg(_, _)), unwanted).
code_info__get_live_value_type(lval(stackvar(_)), unwanted).
code_info__get_live_value_type(lval(framevar(_)), unwanted).
code_info__get_live_value_type(lval(mem_ref(_)), unwanted). % XXX
code_info__get_live_value_type(ticket, unwanted). % XXX we may need to
% modify this, if the GC is going
% to garbage-collect the trail.
code_info__get_live_value_type(ticket_counter, unwanted).
code_info__get_live_value_type(sync_term, unwanted).
code_info__get_live_value_type(trace_data, unwanted).
%---------------------------------------------------------------------------%
%---------------------------------------------------------------------------%
% Submodule for managing stack slots.
% The det stack frame is organized as follows.
%
% ... unused ...
% sp ---> <first unused slot>
% <space for local var 1>
% ... local vars ...
% <space for local var n>
% <space for temporary reg save 1>
% ... temporary reg saves ...
% <space for temporary reg save n>
% <space for succip>
%
% The stack pointer points to the first free location at the
% top of the stack.
%
% `code_info__num_stackslots' counts the number of slots reserved
% for saving local variables. XXX
%
% `code_info__max_push_count' counts the number of slots reserved
% for saving and restoring registers (hp, redoip, etc.)
%
% `code_info__succip_used' determines whether we need a slot to
% hold the succip.
%
% The variable part of the nondet stack is organized in the same way
% as the det stack (but the nondet stack also contains several other
% fixed fields.)
:- interface.
:- type slot_contents
---> ticket % a ticket (trail pointer)
; ticket_counter % a copy of the ticket counter
; trace_data
; sync_term % a syncronization term used
% at the end of par_conjs.
% see par_conj_gen.m for details.
; lval(lval).
% Returns the total stackslot count, but not including space for
% succip.
:- pred code_info__get_total_stackslot_count(int, code_info, code_info).
:- mode code_info__get_total_stackslot_count(out, in, out) is det.
:- pred code_info__get_trace_slot(lval, code_info, code_info).
:- mode code_info__get_trace_slot(out, in, out) is det.
:- pred code_info__acquire_temp_slot(slot_contents, lval,
code_info, code_info).
:- mode code_info__acquire_temp_slot(in, out, in, out) is det.
:- pred code_info__release_temp_slot(lval, code_info, code_info).
:- mode code_info__release_temp_slot(in, in, out) is det.
:- pred code_info__get_variable_slot(var, lval, code_info, code_info).
:- mode code_info__get_variable_slot(in, out, in, out) is det.
%---------------------------------------------------------------------------%
%---------------------------------------------------------------------------%
:- implementation.
:- pred code_info__stack_variable(int, lval, code_info, code_info).
:- mode code_info__stack_variable(in, out, in, out) is det.
:- pred code_info__stack_variable_reference(int, rval, code_info, code_info).
:- mode code_info__stack_variable_reference(in, out, in, out) is det.
:- pred code_info__max_var_slot(stack_slots, int).
:- mode code_info__max_var_slot(in, out) is det.
code_info__get_trace_slot(StackVar) -->
code_info__acquire_temp_slot(trace_data, StackVar).
code_info__acquire_temp_slot(Item, StackVar) -->
code_info__get_avail_temp_slots(AvailSlots0),
( { set__remove_least(AvailSlots0, StackVarPrime, AvailSlots) } ->
{ StackVar = StackVarPrime },
code_info__set_avail_temp_slots(AvailSlots)
;
code_info__get_var_slot_count(VarSlots),
code_info__get_max_temp_slot_count(TempSlots0),
{ TempSlots is TempSlots0 + 1 },
{ Slot is VarSlots + TempSlots },
code_info__stack_variable(Slot, StackVar),
code_info__set_max_temp_slot_count(TempSlots)
),
code_info__get_temps_in_use(TempsInUse0),
{ map__det_insert(TempsInUse0, StackVar, Item, TempsInUse) },
code_info__set_temps_in_use(TempsInUse).
code_info__release_temp_slot(StackVar) -->
code_info__get_avail_temp_slots(AvailSlots0),
{ set__insert(AvailSlots0, StackVar, AvailSlots) },
code_info__set_avail_temp_slots(AvailSlots),
code_info__get_temps_in_use(TempsInUse0),
{ map__delete(TempsInUse0, StackVar, TempsInUse) },
code_info__set_temps_in_use(TempsInUse).
%---------------------------------------------------------------------------%
code_info__get_variable_slot(Var, Slot) -->
code_info__get_stack_slots(StackSlots),
( { map__search(StackSlots, Var, SlotPrime) } ->
{ Slot = SlotPrime }
;
code_info__variable_to_string(Var, Name),
{ term__var_to_int(Var, Num) },
{ string__int_to_string(Num, NumStr) },
{ string__append_list([
"code_info__get_variable_slot: variable `",
Name, "' (", NumStr, ") not found"], Str) },
{ error(Str) }
).
code_info__max_var_slot(StackSlots, SlotCount) :-
map__values(StackSlots, StackSlotList),
code_info__max_var_slot_2(StackSlotList, 0, SlotCount).
:- pred code_info__max_var_slot_2(list(lval), int, int).
:- mode code_info__max_var_slot_2(in, in, out) is det.
code_info__max_var_slot_2([], Max, Max).
code_info__max_var_slot_2([L | Ls], Max0, Max) :-
( L = stackvar(N) ->
int__max(N, Max0, Max1)
; L = framevar(N) ->
int__max(N, Max0, Max1)
;
Max1 = Max0
),
code_info__max_var_slot_2(Ls, Max1, Max).
code_info__get_total_stackslot_count(NumSlots) -->
code_info__get_var_slot_count(SlotsForVars),
code_info__get_max_temp_slot_count(SlotsForTemps),
{ NumSlots is SlotsForVars + SlotsForTemps }.
code_info__stack_variable(Num, Lval) -->
code_info__get_proc_model(CodeModel),
( { CodeModel = model_non } ->
{ Num1 is Num - 1 }, % framevars start at zero
{ Lval = framevar(Num1) }
;
{ Lval = stackvar(Num) } % stackvars start at one
).
code_info__stack_variable_reference(Num, mem_addr(Ref)) -->
code_info__get_proc_model(CodeModel),
( { CodeModel = model_non } ->
{ Num1 is Num - 1 }, % framevars start at zero
{ Ref = framevar_ref(Num1) }
;
{ Ref = stackvar_ref(Num) } % stackvars start at one
).
%---------------------------------------------------------------------------%
%---------------------------------------------------------------------------%
::::::::::::::
code_gen.m
::::::::::::::
%---------------------------------------------------------------------------%
% Copyright (C) 1994-1998 The University of Melbourne.
% This file may only be copied under the terms of the GNU General
% Public License - see the file COPYING in the Mercury distribution.
%---------------------------------------------------------------------------%
%
% Code generation - convert from HLDS to LLDS.
%
% Main authors: conway, zs.
%
% The two main tasks of this module are
%
% 1 to look after the aspects of generating code for a procedure
% that do not involve generating code for a specific goal, and
%
% 2 to provide a generic predicate that can be called from anywhere in
% the code generator to generate code for a goal.
%
% Code_gen forwards most of the actual construction of code for particular
% goals to other modules. The generation of code for unifications is done
% by unify_gen, for calls, higher-order calls and method calls by call_gen,
% for commits by commit_gen, for if-then-elses and negations by ite_gen,
% for switches by switch_gen and its subsidiary modules, for disjunctions
% by disj_gen, and for pragma_c_codes by pragma_c_gen. The only kind of goal
% handled directly by code_gen is the conjunction.
%
%---------------------------------------------------------------------------%
:- module code_gen.
:- interface.
:- import_module hlds_module, hlds_pred, hlds_goal, llds, code_info.
:- import_module continuation_info, globals.
:- import_module list, io.
% Translate a HLDS module to LLDS.
:- pred generate_code(module_info::in, module_info::out,
list(c_procedure)::out, io__state::di, io__state::uo) is det.
% Translate a HLDS procedure to LLDS, threading through
% the data structure that records information about layout
% structures and the counter for ensuring the uniqueness
% of cell numbers.
:- pred generate_proc_code(proc_info::in, proc_id::in, pred_id::in,
module_info::in, globals::in,
continuation_info::in, continuation_info::out, int::in, int::out,
c_procedure::out) is det.
% Translate a HLDS goal to LLDS.
:- pred code_gen__generate_goal(code_model::in, hlds_goal::in, code_tree::out,
code_info::in, code_info::out) is det.
%---------------------------------------------------------------------------%
%---------------------------------------------------------------------------%
:- implementation.
:- import_module call_gen, unify_gen, ite_gen, switch_gen, disj_gen.
:- import_module par_conj_gen, pragma_c_gen, commit_gen.
:- import_module trace, options, hlds_out.
:- import_module code_aux, middle_rec, passes_aux, llds_out.
:- import_module code_util, type_util, mode_util.
:- import_module prog_data, prog_out, instmap.
:- import_module bool, char, int, string.
:- import_module map, assoc_list, set, term, tree, std_util, require, varset.
%---------------------------------------------------------------------------%
generate_code(ModuleInfo0, ModuleInfo, Procedures) -->
% get a list of all the predicate ids
% for which we are going to generate code.
{ module_info_predids(ModuleInfo0, PredIds) },
% now generate the code for each predicate
generate_pred_list_code(ModuleInfo0, ModuleInfo, PredIds, Procedures).
% Translate a list of HLDS predicates to LLDS.
:- pred generate_pred_list_code(module_info::in, module_info::out,
list(pred_id)::in, list(c_procedure)::out,
io__state::di, io__state::uo) is det.
generate_pred_list_code(ModuleInfo, ModuleInfo, [], []) --> [].
generate_pred_list_code(ModuleInfo0, ModuleInfo, [PredId | PredIds],
Predicates) -->
{ module_info_preds(ModuleInfo0, PredInfos) },
% get the pred_info structure for this predicate
{ map__lookup(PredInfos, PredId, PredInfo) },
% extract a list of all the procedure ids for this
% predicate and generate code for them
{ pred_info_non_imported_procids(PredInfo, ProcIds) },
( { ProcIds = [] } ->
{ Predicates0 = [] },
{ ModuleInfo1 = ModuleInfo0 }
;
generate_pred_code(ModuleInfo0, ModuleInfo1, PredId,
PredInfo, ProcIds, Predicates0)
),
{ list__append(Predicates0, Predicates1, Predicates) },
% and generate the code for the rest of the predicates
generate_pred_list_code(ModuleInfo1, ModuleInfo, PredIds, Predicates1).
% Translate a HLDS predicate to LLDS.
:- pred generate_pred_code(module_info::in, module_info::out,
pred_id::in, pred_info::in, list(proc_id)::in, list(c_procedure)::out,
io__state::di, io__state::uo) is det.
generate_pred_code(ModuleInfo0, ModuleInfo, PredId, PredInfo, ProcIds, Code) -->
globals__io_lookup_bool_option(very_verbose, VeryVerbose),
( { VeryVerbose = yes } ->
io__write_string("% Generating code for "),
hlds_out__write_pred_id(ModuleInfo0, PredId),
io__write_string("\n"),
globals__io_lookup_bool_option(statistics, Statistics),
maybe_report_stats(Statistics)
;
[]
),
{ module_info_get_continuation_info(ModuleInfo0, ContInfo0) },
{ module_info_get_cell_count(ModuleInfo0, CellCount0) },
globals__io_get_globals(Globals),
{ generate_proc_list_code(ProcIds, PredId, PredInfo, ModuleInfo0,
Globals, ContInfo0, ContInfo, CellCount0, CellCount,
[], Code) },
{ module_info_set_cell_count(ModuleInfo0, CellCount, ModuleInfo1) },
{ module_info_set_continuation_info(ModuleInfo1, ContInfo,
ModuleInfo) }.
% Translate all the procedures of a HLDS predicate to LLDS.
:- pred generate_proc_list_code(list(proc_id)::in, pred_id::in, pred_info::in,
module_info::in, globals::in,
continuation_info::in, continuation_info::out, int::in, int::out,
list(c_procedure)::in, list(c_procedure)::out) is det.
generate_proc_list_code([], _PredId, _PredInfo, _ModuleInfo, _Globals,
ContInfo, ContInfo, CellCount, CellCount, Procs, Procs).
generate_proc_list_code([ProcId | ProcIds], PredId, PredInfo, ModuleInfo0,
Globals, ContInfo0, ContInfo, CellCount0, CellCount,
Procs0, Procs) :-
pred_info_procedures(PredInfo, ProcInfos),
map__lookup(ProcInfos, ProcId, ProcInfo),
generate_proc_code(ProcInfo, ProcId, PredId, ModuleInfo0, Globals,
ContInfo0, ContInfo1, CellCount0, CellCount1, Proc),
generate_proc_list_code(ProcIds, PredId, PredInfo, ModuleInfo0,
Globals, ContInfo1, ContInfo, CellCount1, CellCount,
[Proc | Procs0], Procs).
%---------------------------------------------------------------------------%
% Values of this type hold information about stack frames that is
% generated when generating prologs and is used in generating epilogs
% and when massaging the code generated for the procedure.
:- type frame_info ---> frame(
int, % Number of slots in frame.
maybe(int), % Slot number of succip
% if succip is present
% in a general slot.
bool % Is this the frame of a
% model_non proc defined
% via pragma C code?
).
%---------------------------------------------------------------------------%
generate_proc_code(ProcInfo, ProcId, PredId, ModuleInfo, Globals,
ContInfo0, ContInfo, CellCount0, CellCount, Proc) :-
proc_info_interface_determinism(ProcInfo, Detism),
proc_info_interface_code_model(ProcInfo, CodeModel),
proc_info_goal(ProcInfo, Goal),
proc_info_varset(ProcInfo, VarSet),
proc_info_liveness_info(ProcInfo, Liveness),
proc_info_stack_slots(ProcInfo, StackSlots),
proc_info_get_initial_instmap(ProcInfo, ModuleInfo, InitialInst),
Goal = _ - GoalInfo,
goal_info_get_follow_vars(GoalInfo, MaybeFollowVars),
(
MaybeFollowVars = yes(FollowVars)
;
MaybeFollowVars = no,
map__init(FollowVars)
),
globals__lookup_bool_option(Globals, basic_stack_layout,
BasicStackLayout),
( BasicStackLayout = yes ->
SaveSuccip = yes
;
SaveSuccip = no
),
% Initialise the code_info structure. Generate_category_code
% below will use the returned OutsideResumePoint as the
% entry to the code that handles the failure of the procedure,
% if such code is needed. It is never needed for model_det
% procedures, always needed for model_semi procedures, and
% needed for model_non procedures only if we are doing
% execution tracing.
code_info__init(VarSet, Liveness, StackSlots, SaveSuccip, Globals,
PredId, ProcId, ProcInfo, InitialInst, FollowVars,
ModuleInfo, CellCount0, OutsideResumePoint, CodeInfo0),
% Generate code for the procedure.
generate_category_code(CodeModel, Goal, OutsideResumePoint,
CodeTree, MaybeTraceCallLabel, FrameInfo, CodeInfo0, CodeInfo),
code_info__get_cell_count(CellCount, CodeInfo, _),
% Turn the code tree into a list.
tree__flatten(CodeTree, FragmentList),
% Now the code is a list of code fragments (== list(instr)),
% so we need to do a level of unwinding to get a flat list.
list__condense(FragmentList, Instructions0),
FrameInfo = frame(TotalSlots, MaybeSuccipSlot, _),
(
MaybeSuccipSlot = yes(SuccipSlot)
->
% The set of recorded live values at calls (for value
% numbering) and returns (for accurate gc and execution
% tracing) do not yet record the stack slot holding the
% succip, so add it to those sets.
code_gen__add_saved_succip(Instructions0,
SuccipSlot, Instructions)
;
Instructions = Instructions0
),
( BasicStackLayout = yes ->
% Create the procedure layout structure.
code_util__make_proc_label(ModuleInfo, PredId, ProcId,
ProcLabel),
code_info__get_layout_info(LayoutInfo, CodeInfo, _),
continuation_info__add_proc_info(proc(PredId, ProcId),
ProcLabel, TotalSlots, Detism, MaybeSuccipSlot,
MaybeTraceCallLabel, LayoutInfo, ContInfo0, ContInfo)
;
ContInfo = ContInfo0
),
predicate_name(ModuleInfo, PredId, Name),
predicate_arity(ModuleInfo, PredId, Arity),
% Construct a c_procedure structure with all the information.
Proc = c_procedure(Name, Arity, proc(PredId, ProcId), Instructions).
%---------------------------------------------------------------------------%
%---------------------------------------------------------------------------%
% Generate_category_code generates code for an entire procedure.
% Its algorithm has three or four main stages:
%
% - generate code for the body goal
% - generate code for the procedure entry
% - generate code for the procedure exit
% - generate code for the procedure fail (if needed)
%
% The first three tasks are forwarded to other procedures.
% The fourth task, if needed, is done by generate_category_code.
%
% The only caller of generate_category_code, generate_proc_code,
% has set up the code generator state to reflect what the machine
% state will be on entry to the procedure. Ensuring that the
% machine state at exit will conform to the expectation
% of the caller is the job of code_gen__generate_exit.
%
% The reason why we generate the entry code after the body is that
% information such as the total number of stack slots needed,
% which is needed in the procedure entry prologue, cannot be
% conveniently obtained before generating the body, since the
% code generator may allocate temporary variables to hold values
% such as saved heap and trail pointers.
%
% Code_gen__generate_entry cannot depend on the code generator
% state, since when it is invoked this state is not appropriate
% for the procedure entry. Nor can it change the code generator state,
% since that would confuse code_gen__generate_exit.
%
% Generating CALL trace events is done by generate_category_code,
% since only on entry to generate_category_code is the code generator
% state set up right. Generating EXIT trace events is done by
% code_gen__generate_exit. Generating FAIL trace events is done
% by generate_category_code, since this requires modifying how
% we generate code for the body of the procedure (failures must
% now branch to a different place). Since FAIL trace events are
% part of the failure continuation, generate_category_code takes
% care of the failure continuation as well. (Model_det procedures
% of course have no failure continuation. Model_non procedures have
% a failure continuation, but in the absence of tracing this
% continuation needs no code. Only model_semi procedures need code
% for the failure continuation at all times.)
:- pred generate_category_code(code_model::in, hlds_goal::in,
resume_point_info::in, code_tree::out, maybe(label)::out,
frame_info::out, code_info::in, code_info::out) is det.
generate_category_code(model_det, Goal, ResumePoint, Code,
MaybeTraceCallLabel, FrameInfo) -->
% generate the code for the body of the clause
(
code_info__get_globals(Globals),
{ globals__lookup_bool_option(Globals, middle_rec, yes) },
middle_rec__match_and_generate(Goal, MiddleRecCode)
->
{ Code = MiddleRecCode },
{ MaybeTraceCallLabel = no },
{ FrameInfo = frame(0, no, no) }
;
code_info__get_maybe_trace_info(MaybeTraceInfo),
( { MaybeTraceInfo = yes(TraceInfo) } ->
trace__generate_external_event_code(call, TraceInfo,
TraceCallLabel, _TypeInfos, TraceCallCode),
{ MaybeTraceCallLabel = yes(TraceCallLabel) }
;
{ TraceCallCode = empty },
{ MaybeTraceCallLabel = no }
),
code_gen__generate_goal(model_det, Goal, BodyCode),
code_gen__generate_entry(model_det, Goal, ResumePoint,
FrameInfo, EntryCode),
code_gen__generate_exit(model_det, FrameInfo, _, ExitCode),
{ Code =
tree(EntryCode,
tree(TraceCallCode,
tree(BodyCode,
ExitCode)))
}
).
generate_category_code(model_semi, Goal, ResumePoint, Code,
MaybeTraceCallLabel, FrameInfo) -->
{ set__singleton_set(FailureLiveRegs, reg(r, 1)) },
{ FailCode = node([
assign(reg(r, 1), const(false)) - "Fail",
livevals(FailureLiveRegs) - "",
goto(succip) - "Return from procedure call"
]) },
code_info__get_maybe_trace_info(MaybeTraceInfo),
( { MaybeTraceInfo = yes(TraceInfo) } ->
trace__generate_external_event_code(call, TraceInfo,
TraceCallLabel, _TypeInfos, TraceCallCode),
{ MaybeTraceCallLabel = yes(TraceCallLabel) },
code_gen__generate_goal(model_semi, Goal, BodyCode),
code_gen__generate_entry(model_semi, Goal, ResumePoint,
FrameInfo, EntryCode),
code_gen__generate_exit(model_semi, FrameInfo,
RestoreDeallocCode, ExitCode),
code_info__generate_resume_point(ResumePoint, ResumeCode),
{ code_info__resume_point_vars(ResumePoint, ResumeVarList) },
{ set__list_to_set(ResumeVarList, ResumeVars) },
code_info__set_forward_live_vars(ResumeVars),
trace__generate_external_event_code(fail, TraceInfo, _, _,
TraceFailCode),
{ Code =
tree(EntryCode,
tree(TraceCallCode,
tree(BodyCode,
tree(ExitCode,
tree(ResumeCode,
tree(TraceFailCode,
tree(RestoreDeallocCode,
FailCode)))))))
}
;
{ MaybeTraceCallLabel = no },
code_gen__generate_goal(model_semi, Goal, BodyCode),
code_gen__generate_entry(model_semi, Goal, ResumePoint,
FrameInfo, EntryCode),
code_gen__generate_exit(model_semi, FrameInfo,
RestoreDeallocCode, ExitCode),
code_info__generate_resume_point(ResumePoint, ResumeCode),
{ Code =
tree(EntryCode,
tree(BodyCode,
tree(ExitCode,
tree(ResumeCode,
tree(RestoreDeallocCode,
FailCode)))))
}
).
generate_category_code(model_non, Goal, ResumePoint, Code,
MaybeTraceCallLabel, FrameInfo) -->
code_info__get_maybe_trace_info(MaybeTraceInfo),
( { MaybeTraceInfo = yes(TraceInfo) } ->
trace__generate_external_event_code(call, TraceInfo,
TraceCallLabel, _TypeInfos, TraceCallCode),
{ MaybeTraceCallLabel = yes(TraceCallLabel) },
code_gen__generate_goal(model_non, Goal, BodyCode),
code_gen__generate_entry(model_non, Goal, ResumePoint,
FrameInfo, EntryCode),
code_gen__generate_exit(model_non, FrameInfo, _, ExitCode),
code_info__generate_resume_point(ResumePoint, ResumeCode),
{ code_info__resume_point_vars(ResumePoint, ResumeVarList) },
{ set__list_to_set(ResumeVarList, ResumeVars) },
code_info__set_forward_live_vars(ResumeVars),
trace__generate_external_event_code(fail, TraceInfo, _, _,
TraceFailCode),
{ FailCode = node([
goto(do_fail) - "fail after fail trace port"
]) },
{ Code =
tree(EntryCode,
tree(TraceCallCode,
tree(BodyCode,
tree(ExitCode,
tree(ResumeCode,
tree(TraceFailCode,
FailCode))))))
}
;
{ MaybeTraceCallLabel = no },
code_gen__generate_goal(model_non, Goal, BodyCode),
code_gen__generate_entry(model_non, Goal, ResumePoint,
FrameInfo, EntryCode),
code_gen__generate_exit(model_non, FrameInfo, _, ExitCode),
{ Code =
tree(EntryCode,
tree(BodyCode,
ExitCode))
}
).
%---------------------------------------------------------------------------%
% Generate the prologue for a procedure.
%
% The prologue will contain
%
% a comment to mark prologue start
% a comment explaining the stack layout
% the procedure entry label
% code to allocate a stack frame
% code to fill in some special slots in the stack frame
% a comment to mark prologue end
%
% At the moment the only special slots are the succip slot, and
% the slots holding the call number and call depth for tracing.
%
% Not all frames will have all these components. For example, the code
% to allocate a stack frame will be missing if the procedure doesn't
% need a stack frame, and if the procedure is nondet, then the code
% to fill in the succip slot is subsumed by the mkframe.
:- pred code_gen__generate_entry(code_model::in, hlds_goal::in,
resume_point_info::in, frame_info::out, code_tree::out,
code_info::in, code_info::out) is det.
code_gen__generate_entry(CodeModel, Goal, OutsideResumePoint,
FrameInfo, EntryCode) -->
code_info__get_stack_slots(StackSlots),
code_info__get_varset(VarSet),
{ code_aux__explain_stack_slots(StackSlots, VarSet, SlotsComment) },
{ StartComment = node([
comment("Start of procedure prologue") - "",
comment(SlotsComment) - ""
]) },
code_info__get_total_stackslot_count(MainSlots),
code_info__get_pred_id(PredId),
code_info__get_proc_id(ProcId),
code_info__get_module_info(ModuleInfo),
{ code_util__make_local_entry_label(ModuleInfo, PredId, ProcId, no,
Entry) },
{ LabelCode = node([
label(Entry) - "Procedure entry point"
]) },
code_info__get_succip_used(Used),
(
% Do we need to save the succip across calls?
{ Used = yes },
% Do we need to use a general slot for storing succip?
{ CodeModel \= model_non }
->
{ SuccipSlot is MainSlots + 1 },
{ SaveSuccipCode = node([
assign(stackvar(SuccipSlot), lval(succip)) -
"Save the success ip"
]) },
{ TotalSlots = SuccipSlot },
{ MaybeSuccipSlot = yes(SuccipSlot) }
;
{ SaveSuccipCode = empty },
{ TotalSlots = MainSlots },
{ MaybeSuccipSlot = no }
),
code_info__get_maybe_trace_info(MaybeTraceInfo),
( { MaybeTraceInfo = yes(TraceInfo) } ->
{ trace__generate_slot_fill_code(TraceInfo, TraceFillCode) }
;
{ TraceFillCode = empty }
),
{ predicate_module(ModuleInfo, PredId, ModuleName) },
{ predicate_name(ModuleInfo, PredId, PredName) },
{ predicate_arity(ModuleInfo, PredId, Arity) },
{ prog_out__sym_name_to_string(ModuleName, ModuleNameString) },
{ string__int_to_string(Arity, ArityStr) },
{ string__append_list([ModuleNameString, ":", PredName, "/", ArityStr],
PushMsg) },
(
{ CodeModel = model_non }
->
{ code_info__resume_point_stack_addr(OutsideResumePoint,
OutsideResumeAddress) },
(
{ Goal = pragma_c_code(_,_,_,_,_,_, PragmaCode) - _},
{ PragmaCode = nondet(Fields, FieldsContext,
_,_,_,_,_,_,_) }
->
{ pragma_c_gen__struct_name(ModuleName, PredName,
Arity, ProcId, StructName) },
{ Struct = pragma_c_struct(StructName,
Fields, FieldsContext) },
{ string__format("#define\tMR_ORDINARY_SLOTS\t%d\n",
[i(TotalSlots)], DefineStr) },
{ DefineComponents = [pragma_c_raw_code(DefineStr)] },
{ NondetFrameInfo = ordinary_frame(PushMsg, TotalSlots,
yes(Struct)) },
{ AllocCode = node([
mkframe(NondetFrameInfo, OutsideResumeAddress)
- "Allocate stack frame",
pragma_c([], DefineComponents,
will_not_call_mercury, no, no)
- ""
]) },
{ NondetPragma = yes }
;
{ NondetFrameInfo = ordinary_frame(PushMsg, TotalSlots,
no) },
{ AllocCode = node([
mkframe(NondetFrameInfo, OutsideResumeAddress)
- "Allocate stack frame"
]) },
{ NondetPragma = no }
)
;
{ TotalSlots > 0 }
->
{ AllocCode = node([
incr_sp(TotalSlots, PushMsg) -
"Allocate stack frame"
]) },
{ NondetPragma = no }
;
{ AllocCode = empty },
{ NondetPragma = no }
),
{ FrameInfo = frame(TotalSlots, MaybeSuccipSlot, NondetPragma) },
{ EndComment = node([
comment("End of procedure prologue") - ""
]) },
{ EntryCode =
tree(StartComment,
tree(LabelCode,
tree(AllocCode,
tree(SaveSuccipCode,
tree(TraceFillCode,
EndComment)))))
}.
%---------------------------------------------------------------------------%
% Generate the success epilogue for a procedure.
%
% The success epilogue will contain
%
% a comment to mark epilogue start
% code to place the output arguments where their caller expects
% code to restore registers from some special slots
% code to deallocate the stack frame
% code to set r1 to TRUE (for semidet procedures only)
% a jump back to the caller, including livevals information
% a comment to mark epilogue end
%
% The parts of this that restore registers and deallocate the stack
% frame are also part of the failure epilog, which is handled by
% our caller; this is why we return RestoreDeallocCode.
%
% At the moment the only special slots are the succip slot, and
% the slots holding the call number and call depth for tracing.
%
% Not all frames will have all these components. For example, for
% nondet procedures we don't deallocate the stack frame before
% success.
%
% Epilogues for procedures defined by nondet pragma C codes do not
% follow the rules above. For such procedures, the normal functions
% of the epilogue are handled when traversing the pragma C code goal;
% we need only #undef a macro defined by the procedure prologue.
:- pred code_gen__generate_exit(code_model::in, frame_info::in,
code_tree::out, code_tree::out, code_info::in, code_info::out) is det.
code_gen__generate_exit(CodeModel, FrameInfo, RestoreDeallocCode, ExitCode) -->
{ StartComment = node([
comment("Start of procedure epilogue") - ""
]) },
{ EndComment = node([
comment("End of procedure epilogue") - ""
]) },
{ FrameInfo = frame(TotalSlots, MaybeSuccipSlot, NondetPragma) },
( { NondetPragma = yes } ->
{ UndefStr = "#undef\tMR_ORDINARY_SLOTS\n" },
{ UndefComponents = [pragma_c_raw_code(UndefStr)] },
{ UndefCode = node([
pragma_c([], UndefComponents,
will_not_call_mercury, no, no)
- ""
]) },
{ RestoreDeallocCode = empty }, % always empty for nondet code
{ ExitCode =
tree(StartComment,
tree(UndefCode,
EndComment))
}
;
code_info__get_instmap(Instmap),
code_info__get_arginfo(ArgModes),
code_info__get_headvars(HeadVars),
{ assoc_list__from_corresponding_lists(HeadVars, ArgModes,
Args)},
(
{ instmap__is_unreachable(Instmap) }
->
{ FlushCode = empty }
;
code_info__setup_call(Args, callee, FlushCode)
),
(
{ MaybeSuccipSlot = yes(SuccipSlot) }
->
{ RestoreSuccipCode = node([
assign(succip, lval(stackvar(SuccipSlot))) -
"restore the success ip"
]) }
;
{ RestoreSuccipCode = empty }
),
(
{ TotalSlots = 0 ; CodeModel = model_non }
->
{ DeallocCode = empty }
;
{ DeallocCode = node([
decr_sp(TotalSlots) - "Deallocate stack frame"
]) }
),
{ RestoreDeallocCode = tree(RestoreSuccipCode, DeallocCode ) },
code_info__get_maybe_trace_info(MaybeTraceInfo),
( { MaybeTraceInfo = yes(TraceInfo) } ->
trace__generate_external_event_code(exit, TraceInfo,
_, TypeInfoDatas, TraceExitCode),
{ assoc_list__values(TypeInfoDatas, TypeInfoLvals) }
;
{ TraceExitCode = empty },
{ TypeInfoLvals = [] }
),
% Find out which locations should be mentioned
% in the success path livevals(...) annotation,
% so that value numbering doesn't optimize them away.
{ code_gen__select_args_with_mode(Args, top_out, _OutVars,
OutLvals) },
{ list__append(TypeInfoLvals, OutLvals, LiveArgLvals) },
{ set__list_to_set(LiveArgLvals, LiveArgs) },
(
{ CodeModel = model_det },
{ SuccessCode = node([
livevals(LiveArgs) - "",
goto(succip) - "Return from procedure call"
]) },
{ AllSuccessCode =
tree(TraceExitCode,
tree(RestoreDeallocCode,
SuccessCode))
}
;
{ CodeModel = model_semi },
{ set__insert(LiveArgs, reg(r, 1), SuccessLiveRegs) },
{ SuccessCode = node([
assign(reg(r, 1), const(true)) - "Succeed",
livevals(SuccessLiveRegs) - "",
goto(succip) - "Return from procedure call"
]) },
{ AllSuccessCode =
tree(TraceExitCode,
tree(RestoreDeallocCode,
SuccessCode))
}
;
{ CodeModel = model_non },
{ SuccessCode = node([
livevals(LiveArgs) - "",
goto(do_succeed(no))
- "Return from procedure call"
]) },
{ AllSuccessCode =
tree(TraceExitCode,
SuccessCode)
}
),
{ ExitCode =
tree(StartComment,
tree(FlushCode,
tree(AllSuccessCode,
EndComment)))
}
).
%---------------------------------------------------------------------------%
% Generate a goal. This predicate arranges for the necessary updates of
% the generic data structures before and after the actual code generation,
% which is delegated to context-specific predicates.
code_gen__generate_goal(ContextModel, Goal - GoalInfo, Code) -->
% Make any changes to liveness before Goal
{ goal_is_atomic(Goal) ->
IsAtomic = yes
;
IsAtomic = no
},
code_info__pre_goal_update(GoalInfo, IsAtomic),
code_info__get_instmap(Instmap),
(
{ instmap__is_reachable(Instmap) }
->
{ goal_info_get_code_model(GoalInfo, CodeModel) },
% sanity check: code of some code models
% should occur only in limited contexts
{
CodeModel = model_det
;
CodeModel = model_semi,
( ContextModel \= model_det ->
true
;
error("semidet model in det context")
)
;
CodeModel = model_non,
( ContextModel = model_non ->
true
;
error("nondet model in det/semidet context")
)
},
code_gen__generate_goal_2(Goal, GoalInfo, CodeModel, Code),
% Make live any variables which subsequent goals
% will expect to be live, but were not generated
code_info__set_instmap(Instmap),
code_info__post_goal_update(GoalInfo)
;
{ Code = empty }
),
!.
%---------------------------------------------------------------------------%
:- pred code_gen__generate_goal_2(hlds_goal_expr::in, hlds_goal_info::in,
code_model::in, code_tree::out, code_info::in, code_info::out) is det.
code_gen__generate_goal_2(unify(_, _, _, Uni, _), _, CodeModel, Code) -->
unify_gen__generate_unification(CodeModel, Uni, Code).
code_gen__generate_goal_2(conj(Goals), _GoalInfo, CodeModel, Code) -->
code_gen__generate_goals(Goals, CodeModel, Code).
code_gen__generate_goal_2(par_conj(Goals, _SM), GoalInfo, CodeModel, Code) -->
par_conj_gen__generate_par_conj(Goals, GoalInfo, CodeModel, Code).
code_gen__generate_goal_2(disj(Goals, StoreMap), _, CodeModel, Code) -->
disj_gen__generate_disj(CodeModel, Goals, StoreMap, Code).
code_gen__generate_goal_2(not(Goal), _GoalInfo, CodeModel, Code) -->
ite_gen__generate_negation(CodeModel, Goal, Code).
code_gen__generate_goal_2(if_then_else(_Vars, Cond, Then, Else, StoreMap),
_GoalInfo, CodeModel, Code) -->
ite_gen__generate_ite(CodeModel, Cond, Then, Else, StoreMap, Code).
code_gen__generate_goal_2(switch(Var, CanFail, CaseList, StoreMap),
GoalInfo, CodeModel, Code) -->
switch_gen__generate_switch(CodeModel, Var, CanFail, CaseList,
StoreMap, GoalInfo, Code).
code_gen__generate_goal_2(some(_Vars, Goal), _GoalInfo, CodeModel, Code) -->
commit_gen__generate_commit(CodeModel, Goal, Code).
code_gen__generate_goal_2(higher_order_call(PredVar, Args, Types,
Modes, Det, _PredOrFunc), GoalInfo, CodeModel, Code) -->
call_gen__generate_higher_order_call(CodeModel, PredVar, Args,
Types, Modes, Det, GoalInfo, Code).
code_gen__generate_goal_2(class_method_call(TCVar, Num, Args, Types,
Modes, Det), GoalInfo, CodeModel, Code) -->
call_gen__generate_class_method_call(CodeModel, TCVar, Num, Args,
Types, Modes, Det, GoalInfo, Code).
code_gen__generate_goal_2(call(PredId, ProcId, Args, BuiltinState, _, _),
GoalInfo, CodeModel, Code) -->
(
{ BuiltinState = not_builtin }
->
call_gen__generate_call(CodeModel, PredId, ProcId, Args,
GoalInfo, Code)
;
call_gen__generate_builtin(CodeModel, PredId, ProcId, Args,
Code)
).
code_gen__generate_goal_2(pragma_c_code(MayCallMercury, PredId, ProcId,
Args, ArgNames, OrigArgTypes, PragmaImpl),
GoalInfo, CodeModel, Code) -->
pragma_c_gen__generate_pragma_c_code(CodeModel, MayCallMercury,
PredId, ProcId, Args, ArgNames, OrigArgTypes, GoalInfo,
PragmaImpl, Code).
%---------------------------------------------------------------------------%
% Generate a conjoined series of goals.
% Note of course, that with a conjunction, state information
% flows directly from one conjunct to the next.
:- pred code_gen__generate_goals(hlds_goals::in, code_model::in,
code_tree::out, code_info::in, code_info::out) is det.
code_gen__generate_goals([], _, empty) --> [].
code_gen__generate_goals([Goal | Goals], CodeModel, Instr) -->
code_gen__generate_goal(CodeModel, Goal, Instr1),
code_info__get_instmap(Instmap),
(
{ instmap__is_unreachable(Instmap) }
->
{ Instr = Instr1 }
;
code_gen__generate_goals(Goals, CodeModel, Instr2),
{ Instr = tree(Instr1, Instr2) }
).
%---------------------------------------------------------------------------%
:- pred code_gen__select_args_with_mode(assoc_list(var, arg_info)::in,
arg_mode::in, list(var)::out, list(lval)::out) is det.
code_gen__select_args_with_mode([], _, [], []).
code_gen__select_args_with_mode([Var - ArgInfo | Args], DesiredMode, Vs, Ls) :-
code_gen__select_args_with_mode(Args, DesiredMode, Vs0, Ls0),
ArgInfo = arg_info(Loc, Mode),
(
Mode = DesiredMode
->
code_util__arg_loc_to_register(Loc, Reg),
Vs = [Var | Vs0],
Ls = [Reg | Ls0]
;
Vs = Vs0,
Ls = Ls0
).
%---------------------------------------------------------------------------%
% Add the succip to the livevals before and after calls.
% Traverses the list of instructions looking for livevals and calls,
% adding succip in the stackvar number given as an argument.
:- pred code_gen__add_saved_succip(list(instruction)::in, int::in,
list(instruction)::out) is det.
code_gen__add_saved_succip([], _StackLoc, []).
code_gen__add_saved_succip([Instrn0 - Comment | Instrns0 ], StackLoc,
[Instrn - Comment | Instrns]) :-
(
Instrn0 = livevals(LiveVals0),
Instrns0 \= [goto(succip) - _ | _]
% XXX We should also test for tailcalls
% once we start generating them directly.
->
set__insert(LiveVals0, stackvar(StackLoc), LiveVals1),
Instrn = livevals(LiveVals1)
;
Instrn0 = call(Target, ReturnLabel, LiveVals0, CM)
->
Instrn = call(Target, ReturnLabel,
[live_lvalue(stackvar(StackLoc), succip, "", []) |
LiveVals0], CM)
;
Instrn = Instrn0
),
code_gen__add_saved_succip(Instrns0, StackLoc, Instrns).
%---------------------------------------------------------------------------%
::::::::::::::
disj_gen.m
::::::::::::::
%-----------------------------------------------------------------------------%
% Copyright (C) 1994-1998 The University of Melbourne.
% This file may only be copied under the terms of the GNU General
% Public License - see the file COPYING in the Mercury distribution.
%---------------------------------------------------------------------------%
%
% File: disj_gen.m:
%
% Main authors: conway, zs.
%
% The predicates of this module generate code for disjunctions.
%
%---------------------------------------------------------------------------%
%---------------------------------------------------------------------------%
:- module disj_gen.
:- interface.
:- import_module hlds_goal, llds, code_info.
:- import_module list.
:- pred disj_gen__generate_disj(code_model::in, list(hlds_goal)::in,
store_map::in, code_tree::out, code_info::in, code_info::out) is det.
%---------------------------------------------------------------------------%
:- implementation.
:- import_module hlds_data, code_gen, code_util, trace, options, globals.
:- import_module bool, set, tree, map, std_util, term, require.
disj_gen__generate_disj(CodeModel, Goals, StoreMap, Code) -->
(
{ Goals = [] },
( { CodeModel = model_semi } ->
code_info__generate_failure(Code)
;
{ error("empty disjunction") }
)
;
{ Goals = [Goal | _] },
{ Goal = _ - GoalInfo },
{ goal_info_get_resume_point(GoalInfo, Resume) },
{ Resume = resume_point(ResumeVarsPrime, _) ->
ResumeVars = ResumeVarsPrime
;
set__init(ResumeVars)
},
disj_gen__generate_real_disj(CodeModel, ResumeVars,
Goals, StoreMap, Code)
).
%---------------------------------------------------------------------------%
:- pred disj_gen__generate_real_disj(code_model::in, set(var)::in,
list(hlds_goal)::in, store_map::in, code_tree::out,
code_info::in, code_info::out) is det.
disj_gen__generate_real_disj(CodeModel, ResumeVars, Goals, StoreMap, Code) -->
% Make sure that the variables whose values will be needed
% on backtracking to any disjunct are materialized into
% registers or stack slots. Their locations are recorded
% in ResumeMap.
code_info__produce_vars(ResumeVars, ResumeMap, FlushCode),
% If we are using a trail, save the current trail state
% before the first disjunct.
% XXX We should use a scheme such as the one we use for heap
% recovery for semi and det disjunctions, and delay saving
% the ticket until necessary.
code_info__get_globals(Globals),
{ globals__lookup_bool_option(Globals, use_trail, UseTrail) },
code_info__maybe_save_ticket(UseTrail, SaveTicketCode,
MaybeTicketSlot),
% If we are using a grade in which we can recover memory
% by saving and restoring the heap pointer, set up for
% doing so if necessary.
( { CodeModel = model_non } ->
% With nondet disjunctions, we must recover memory
% across all disjuncts, even disjuncts that cannot
% themselves allocate memory, since we can backtrack
% to disjunct N after control leaves disjunct N-1.
{ globals__lookup_bool_option(Globals,
reclaim_heap_on_nondet_failure, ReclaimHeap) },
code_info__maybe_save_hp(ReclaimHeap, SaveHpCode,
MaybeHpSlot)
;
% With other disjunctions, we can backtrack to
% disjunct N only from disjunct N-1, so if disjunct
% N-1 does not allocate memory, we need not recover
% memory across it. Since it is possible (and common)
% for no disjunct to allocate memory, we delay saving
% the heap pointer and allocating a stack slot for
% the saved hp as long as possible.
{ globals__lookup_bool_option(Globals,
reclaim_heap_on_semidet_failure, ReclaimHeap) },
{ SaveHpCode = empty },
{ MaybeHpSlot = no }
),
% Save the values of any stack slots we may hijack,
% and if necessary, set the redofr slot of the top frame
% to point to this frame.
code_info__prepare_for_disj_hijack(CodeModel,
HijackInfo, PrepareHijackCode),
code_info__get_next_label(EndLabel),
code_info__remember_position(BranchStart),
disj_gen__generate_disjuncts(Goals, CodeModel, ResumeMap, no,
HijackInfo, StoreMap, EndLabel,
ReclaimHeap, MaybeHpSlot, MaybeTicketSlot,
BranchStart, no, MaybeEnd, GoalsCode),
code_info__after_all_branches(StoreMap, MaybeEnd),
( { CodeModel = model_non } ->
code_info__set_resume_point_to_unknown
;
[]
),
% XXX release any temp slots holding heap or trail pointers
{ Code =
tree(FlushCode,
tree(SaveTicketCode,
tree(SaveHpCode,
tree(PrepareHijackCode,
GoalsCode))))
}.
%---------------------------------------------------------------------------%
:- pred disj_gen__generate_disjuncts(list(hlds_goal)::in,
code_model::in, resume_map::in, maybe(resume_point_info)::in,
disj_hijack_info::in, store_map::in, label::in,
bool::in, maybe(lval)::in, maybe(lval)::in, position_info::in,
maybe(branch_end_info)::in, maybe(branch_end_info)::out,
code_tree::out, code_info::in, code_info::out) is det.
disj_gen__generate_disjuncts([], _, _, _, _, _, _, _, _, _, _, _, _, _) -->
{ error("empty disjunction!") }.
disj_gen__generate_disjuncts([Goal0 | Goals], CodeModel, FullResumeMap,
MaybeEntryResumePoint, HijackInfo, StoreMap, EndLabel,
ReclaimHeap, MaybeHpSlot0, MaybeTicketSlot,
BranchStart, MaybeEnd0, MaybeEnd, Code) -->
code_info__reset_to_position(BranchStart),
% If this is not the first disjunct, generate the
% resume point by which arrive at this disjunct.
( { MaybeEntryResumePoint = yes(EntryResumePoint) } ->
code_info__generate_resume_point(EntryResumePoint,
EntryResumePointCode)
;
{ EntryResumePointCode = empty }
),
{ Goal0 = GoalExpr0 - GoalInfo0 },
{ goal_info_get_resume_point(GoalInfo0, Resume) },
(
{ Resume = resume_point(ResumeVars, ResumeLocs) }
->
% Emit code for a non-last disjunct, including setting things
% up for the execution of the next disjunct.
( { MaybeEntryResumePoint = yes(_) } ->
% Reset the heap pointer to recover memory
% allocated by the previous disjunct(s),
% if necessary.
code_info__maybe_restore_hp(MaybeHpSlot0,
RestoreHpCode),
% Reset the solver state if necessary.
code_info__maybe_reset_ticket(MaybeTicketSlot, undo,
RestoreTicketCode)
;
{ RestoreHpCode = empty },
{ RestoreTicketCode = empty }
),
% The pre_goal_update sanity check insist on
% no_resume_point, to make sure that all resume
% points have been handled by surrounding code.
{ goal_info_set_resume_point(GoalInfo0, no_resume_point,
GoalInfo) },
{ Goal = GoalExpr0 - GoalInfo },
% Save hp if it needs to be saved and hasn't been
% saved previously.
(
{ ReclaimHeap = yes },
{ code_util__goal_may_allocate_heap(Goal) },
{ MaybeHpSlot0 = no }
->
code_info__save_hp(SaveHpCode, HpSlot),
{ MaybeHpSlot = yes(HpSlot) }
;
{ SaveHpCode = empty },
{ MaybeHpSlot = MaybeHpSlot0 }
),
code_info__make_resume_point(ResumeVars, ResumeLocs,
FullResumeMap, NextResumePoint),
code_info__effect_resume_point(NextResumePoint, CodeModel,
ModContCode),
trace__maybe_generate_internal_event_code(Goal, TraceCode),
{ goal_info_get_code_model(GoalInfo, GoalCodeModel) },
code_gen__generate_goal(GoalCodeModel, Goal, GoalCode),
( { CodeModel = model_non } ->
% We can backtrack to the next disjunct from outside,
% so we make sure every variable in the resume set
% is in its stack slot.
code_info__flush_resume_vars_to_stack(ResumeVarsCode)
;
{ ResumeVarsCode = empty }
),
% Put every variable whose value is needed after
% the disjunction to the place indicated by StoreMap,
% and accumulate information about the code_info state
% at the ends of the branches so far.
code_info__generate_branch_end(StoreMap, MaybeEnd0, MaybeEnd1,
SaveCode),
{ BranchCode = node([
goto(label(EndLabel)) -
"skip to end of nondet disj"
]) },
disj_gen__generate_disjuncts(Goals, CodeModel, FullResumeMap,
yes(NextResumePoint), HijackInfo, StoreMap, EndLabel,
ReclaimHeap, MaybeHpSlot, MaybeTicketSlot,
BranchStart, MaybeEnd1, MaybeEnd, RestCode),
{ Code =
tree(EntryResumePointCode,
tree(RestoreHpCode,
tree(RestoreTicketCode,
tree(SaveHpCode,
tree(ModContCode,
tree(TraceCode,
tree(GoalCode,
tree(ResumeVarsCode,
tree(SaveCode,
tree(BranchCode,
RestCode))))))))))
}
;
% Emit code for the last disjunct
% Restore the heap pointer and solver state
% if necessary.
( { CodeModel = model_non } ->
% Note that we can't release the temps used for the
% heap pointer and ticket, because those values may be
% required again after backtracking after control
% leaves the disjunction. If we were to reuse either
% of their stack slots for something else when
% generating the code that follows this goal,
% then the values that earlier disjuncts need on
% backtracking would get clobbered.
% Thus we must not use the `_discard' versions
% of the two predicates below.
code_info__maybe_restore_hp(MaybeHpSlot0,
RestoreHpCode),
code_info__maybe_reset_and_pop_ticket(
MaybeTicketSlot, undo, RestoreTicketCode)
;
code_info__maybe_restore_and_discard_hp(MaybeHpSlot0,
RestoreHpCode),
code_info__maybe_reset_and_discard_ticket(
MaybeTicketSlot, undo, RestoreTicketCode)
),
code_info__undo_disj_hijack(HijackInfo, UndoCode),
trace__maybe_generate_internal_event_code(Goal0, TraceCode),
code_gen__generate_goal(CodeModel, Goal0, GoalCode),
code_info__generate_branch_end(StoreMap, MaybeEnd0, MaybeEnd,
SaveCode),
{ EndCode = node([
label(EndLabel) - "End of nondet disj"
]) },
{ Code =
tree(EntryResumePointCode,
tree(TraceCode,
tree(RestoreHpCode,
tree(RestoreTicketCode,
tree(UndoCode,
tree(GoalCode,
tree(SaveCode,
EndCode)))))))
}
).
%---------------------------------------------------------------------------%
::::::::::::::
ite_gen.m
::::::::::::::
%---------------------------------------------------------------------------%
% Copyright (C) 1994-1998 The University of Melbourne.
% This file may only be copied under the terms of the GNU General
% Public License - see the file COPYING in the Mercury distribution.
%---------------------------------------------------------------------------%
%
% File: ite_gen.m
%
% Main authors: conway, fjh, zs.
%
% The predicates of this module generate code for if-then-elses, and for
% negations (which are cut-down versions of if-then-elses, since not(G)
% is equivalent to (G -> fail ; true).
%
%---------------------------------------------------------------------------%
:- module ite_gen.
:- interface.
:- import_module hlds_goal, llds, code_info.
:- pred ite_gen__generate_ite(code_model::in, hlds_goal::in, hlds_goal::in,
hlds_goal::in, store_map::in, code_tree::out,
code_info::in, code_info::out) is det.
:- pred ite_gen__generate_negation(code_model::in, hlds_goal::in,
code_tree::out, code_info::in, code_info::out) is det.
%---------------------------------------------------------------------------%
:- implementation.
:- import_module code_gen, code_util, trace, options, globals.
:- import_module bool, set, tree, list, map, std_util, term, require.
ite_gen__generate_ite(CodeModel, CondGoal0, ThenGoal, ElseGoal, StoreMap, Code)
-->
{ CondGoal0 = CondExpr - CondInfo0 },
{ goal_info_get_code_model(CondInfo0, CondCodeModel) },
{
CodeModel = model_non,
CondCodeModel \= model_non
->
EffCodeModel = model_semi
;
EffCodeModel = CodeModel
},
{ goal_info_get_resume_point(CondInfo0, Resume) },
{
Resume = resume_point(ResumeVarsPrime, ResumeLocsPrime)
->
ResumeVars = ResumeVarsPrime,
ResumeLocs = ResumeLocsPrime,
% The pre_goal_update sanity check insists on
% no_resume_point, to make sure that all resume
% points have been handled by surrounding code.
goal_info_set_resume_point(CondInfo0, no_resume_point,
CondInfo),
CondGoal = CondExpr - CondInfo
;
error("condition of an if-then-else has no resume point")
},
% Make sure that the variables whose values will be needed
% on backtracking to the else part are materialized into
% registers or stack slots. Their locations are recorded
% in ResumeMap.
code_info__produce_vars(ResumeVars, ResumeMap, FlushCode),
% Maybe save the heap state current before the condition.
% This is after code_info__produce_vars since code that
% flushes the cache may allocate memory we must not "recover".
code_info__get_globals(Globals),
{
globals__lookup_bool_option(Globals,
reclaim_heap_on_semidet_failure, yes),
code_util__goal_may_allocate_heap(CondGoal)
->
ReclaimHeap = yes
;
ReclaimHeap = no
},
code_info__maybe_save_hp(ReclaimHeap, SaveHpCode, MaybeHpSlot),
% Maybe save the current trail state before the condition
{ globals__lookup_bool_option(Globals, use_trail, UseTrail) },
code_info__maybe_save_ticket(UseTrail, SaveTicketCode,
MaybeTicketSlot),
code_info__remember_position(BranchStart),
code_info__prepare_for_ite_hijack(EffCodeModel, HijackInfo,
PrepareHijackCode),
code_info__make_resume_point(ResumeVars, ResumeLocs, ResumeMap,
ResumePoint),
code_info__effect_resume_point(ResumePoint, EffCodeModel,
EffectResumeCode),
{ goal_may_hijack_top_redoip(CondGoal, CondMayHijack) },
code_info__maybe_push_temp_frame(EffCodeModel, CondMayHijack,
HijackInfo, CurFrameLval, TempFrameCode),
% Generate the condition
code_gen__generate_goal(CondCodeModel, CondGoal, CondCode),
code_info__ite_enter_then(HijackInfo, CurFrameLval,
ThenNeckCode, ElseNeckCode),
% Kill again any variables that have become zombies
code_info__pickup_zombies(Zombies),
code_info__make_vars_forward_dead(Zombies),
% Discard hp and trail ticket if the condition succeeded
% XXX is this the right thing to do?
code_info__maybe_reset_and_discard_ticket(MaybeTicketSlot, commit,
DiscardTicketCode),
code_info__maybe_discard_hp(MaybeHpSlot),
% XXX release any temp slots holding heap or trail pointers
% XXX If instmap indicates we cannot reach then part,
% do not attempt to generate it (may cause aborts)
% Generate the then branch
trace__maybe_generate_internal_event_code(ThenGoal, ThenTraceCode),
code_gen__generate_goal(CodeModel, ThenGoal, ThenCode),
code_info__generate_branch_end(StoreMap, no, MaybeEnd0, ThenSaveCode),
% Generate the entry to the else branch
code_info__reset_to_position(BranchStart),
code_info__generate_resume_point(ResumePoint, ResumeCode),
( { CondCodeModel = model_non } ->
% We cannot release the stack slots used for
% the trail ticket and heap pointer if the
% condition can be backtracked into.
code_info__maybe_restore_hp(MaybeHpSlot, RestoreHpCode),
code_info__maybe_reset_and_pop_ticket(MaybeTicketSlot,
undo, RestoreTicketCode)
;
code_info__maybe_restore_and_discard_hp(MaybeHpSlot,
RestoreHpCode),
code_info__maybe_reset_and_discard_ticket(MaybeTicketSlot,
undo, RestoreTicketCode)
),
% Generate the else branch
trace__maybe_generate_internal_event_code(ElseGoal, ElseTraceCode),
code_gen__generate_goal(CodeModel, ElseGoal, ElseCode),
code_info__generate_branch_end(StoreMap, MaybeEnd0, MaybeEnd,
ElseSaveCode),
code_info__get_next_label(EndLabel),
{ JumpToEndCode = node([
goto(label(EndLabel))
- "Jump to the end of if-then-else"
]) },
{ EndLabelCode = node([
label(EndLabel)
- "end of if-then-else"
]) },
{ Code =
tree(FlushCode,
tree(SaveHpCode,
tree(SaveTicketCode,
tree(PrepareHijackCode,
tree(EffectResumeCode,
tree(TempFrameCode,
tree(CondCode,
tree(ThenNeckCode,
tree(DiscardTicketCode,
tree(ThenTraceCode,
tree(ThenCode,
tree(ThenSaveCode,
tree(JumpToEndCode,
tree(ResumeCode,
tree(ElseNeckCode,
tree(RestoreHpCode,
tree(RestoreTicketCode,
tree(ElseTraceCode,
tree(ElseCode,
tree(ElseSaveCode,
EndLabelCode))))))))))))))))))))
},
code_info__after_all_branches(StoreMap, MaybeEnd).
%---------------------------------------------------------------------------%
ite_gen__generate_negation(CodeModel, Goal0, Code) -->
{ CodeModel = model_non ->
error("nondet negation")
;
true
},
{ Goal0 = GoalExpr - GoalInfo0 },
{ goal_info_get_resume_point(GoalInfo0, Resume) },
{
Resume = resume_point(ResumeVarsPrime, ResumeLocsPrime)
->
ResumeVars = ResumeVarsPrime,
ResumeLocs = ResumeLocsPrime,
goal_info_set_resume_point(GoalInfo0, no_resume_point,
GoalInfo),
Goal = GoalExpr - GoalInfo
;
error("negated goal has no resume point")
},
% For a negated simple test, we can generate better code
% than the general mechanism, because we don't have to
% flush the cache.
(
{ CodeModel = model_semi },
{ GoalExpr = unify(_, _, _, simple_test(L, R), _) },
code_info__failure_is_direct_branch(CodeAddr),
code_info__get_globals(Globals),
{ globals__lookup_bool_option(Globals, simple_neg, yes) }
->
% Because we are generating the negated goal ourselves,
% we need to apply the pre- and post-goal updates
% that would normally be applied by
% code_gen__generate_goal.
code_info__enter_simple_neg(ResumeVars, GoalInfo, SimpleNeg),
code_info__produce_variable(L, CodeL, ValL),
code_info__produce_variable(R, CodeR, ValR),
code_info__variable_type(L, Type),
{ Type = term__functor(term__atom("string"), [], _) ->
Op = str_eq
; Type = term__functor(term__atom("float"), [], _) ->
Op = float_eq
;
Op = eq
},
{ TestCode = node([
if_val(binop(Op, ValL, ValR), CodeAddr) -
"test inequality"
]) },
code_info__leave_simple_neg(GoalInfo, SimpleNeg),
{ Code = tree(tree(CodeL, CodeR), TestCode) }
;
generate_negation_general(CodeModel, Goal,
ResumeVars, ResumeLocs, Code)
).
% The code of generate_negation_general is a cut-down version
% of the code for if-then-elses.
:- pred generate_negation_general(code_model::in, hlds_goal::in,
set(var)::in, resume_locs::in, code_tree::out,
code_info::in, code_info::out) is det.
generate_negation_general(CodeModel, Goal, ResumeVars, ResumeLocs, Code) -->
code_info__produce_vars(ResumeVars, ResumeMap, FlushCode),
% Maybe save the heap state current before the condition;
% this ought to be after we make the failure continuation
% because that causes the cache to get flushed
code_info__get_globals(Globals),
{
globals__lookup_bool_option(Globals,
reclaim_heap_on_semidet_failure, yes),
code_util__goal_may_allocate_heap(Goal)
->
ReclaimHeap = yes
;
ReclaimHeap = no
},
code_info__maybe_save_hp(ReclaimHeap, SaveHpCode, MaybeHpSlot),
{ globals__lookup_bool_option(Globals, use_trail, UseTrail) },
code_info__maybe_save_ticket(UseTrail, SaveTicketCode,
MaybeTicketSlot),
code_info__prepare_for_ite_hijack(CodeModel, HijackInfo,
PrepareHijackCode),
code_info__make_resume_point(ResumeVars, ResumeLocs, ResumeMap,
ResumePoint),
code_info__effect_resume_point(ResumePoint, CodeModel,
EffectResumeCode),
{ goal_may_hijack_top_redoip(Goal, MayHijack) },
code_info__maybe_push_temp_frame(CodeModel, MayHijack,
HijackInfo, CurFrameLval, TempFrameCode),
% Generate the negated goal.
code_gen__generate_goal(CodeModel, Goal, GoalCode),
code_info__ite_enter_then(HijackInfo, CurFrameLval,
ThenNeckCode, ElseNeckCode),
% Kill again any variables that have become zombies
code_info__pickup_zombies(Zombies),
code_info__make_vars_forward_dead(Zombies),
code_info__get_forward_live_vars(LiveVars),
( { CodeModel = model_det } ->
% the then branch will never be reached
{ DiscardTicketCode = empty },
{ FailCode = empty }
;
code_info__remember_position(AfterNegatedGoal),
% The call to reset_ticket(..., commit) here is necessary
% in order to properly detect floundering.
code_info__maybe_reset_and_discard_ticket(MaybeTicketSlot,
commit, DiscardTicketCode),
code_info__generate_failure(FailCode),
% We want liveness after not(G) to be the same as
% after G. Information about what variables are where
% will be set by code_info__generate_resume_point.
code_info__reset_to_position(AfterNegatedGoal)
),
% Generate the entry to the else branch
code_info__generate_resume_point(ResumePoint, ResumeCode),
code_info__set_forward_live_vars(LiveVars),
code_info__maybe_reset_and_discard_ticket(MaybeTicketSlot, undo,
RestoreTicketCode),
code_info__maybe_restore_and_discard_hp(MaybeHpSlot, RestoreHpCode),
{ Code =
tree(FlushCode,
tree(PrepareHijackCode,
tree(EffectResumeCode,
tree(TempFrameCode,
tree(SaveHpCode,
tree(SaveTicketCode,
tree(GoalCode,
tree(ThenNeckCode,
tree(DiscardTicketCode,
tree(FailCode,
tree(ResumeCode,
tree(ElseNeckCode,
tree(RestoreTicketCode,
RestoreHpCode)))))))))))))
}.
%---------------------------------------------------------------------------%
:- pred goal_may_hijack_top_redoip(hlds_goal::in, bool::out) is det.
goal_may_hijack_top_redoip(GoalExpr - GoalInfo, MayHijack) :-
(
GoalExpr = conj(Conj),
goals_may_hijack_top_redoip(Conj, MayHijack)
;
GoalExpr = par_conj(Conj, _),
goals_may_hijack_top_redoip(Conj, MayHijack)
;
GoalExpr = call(_, _, _, _, _, _),
MayHijack = yes
;
GoalExpr = higher_order_call(_, _, _, _, _, _),
MayHijack = yes
;
GoalExpr = class_method_call(_, _, _, _, _, _),
MayHijack = yes
;
GoalExpr = switch(_, _, Cases, _),
cases_may_hijack_top_redoip(Cases, MayHijack)
;
GoalExpr = unify(_, _, _, _, _),
MayHijack = no
;
GoalExpr = disj(Disj, _),
(
goal_info_get_code_model(GoalInfo, CodeModel),
CodeModel = model_non
->
MayHijack = yes
;
goals_may_hijack_top_redoip(Disj, MayHijack)
)
;
GoalExpr = not(_SubGoal),
MayHijack = yes
;
GoalExpr = some(_, _SubGoal),
MayHijack = yes
;
GoalExpr = if_then_else(_, _, _, _, _),
MayHijack = yes
;
GoalExpr = pragma_c_code(_, _, _, _, _, _, _),
MayHijack = yes
).
:- pred goals_may_hijack_top_redoip(list(hlds_goal)::in, bool::out) is det.
goals_may_hijack_top_redoip([], no).
goals_may_hijack_top_redoip([Goal | Goals], MayHijack) :-
goal_may_hijack_top_redoip(Goal, MayHijack0),
( MayHijack0 = yes ->
MayHijack = yes
;
goals_may_hijack_top_redoip(Goals, MayHijack)
).
:- pred cases_may_hijack_top_redoip(list(case)::in, bool::out) is det.
cases_may_hijack_top_redoip([], no).
cases_may_hijack_top_redoip([case(_, Goal) | Goals], MayHijack) :-
goal_may_hijack_top_redoip(Goal, MayHijack0),
( MayHijack0 = yes ->
MayHijack = yes
;
cases_may_hijack_top_redoip(Goals, MayHijack)
).
%---------------------------------------------------------------------------%
More information about the developers
mailing list