mirror of
https://github.com/Mercury-Language/mercury.git
synced 2025-12-16 22:35:41 +00:00
Estimated hours taken: 220
Aditi update syntax, type and mode checking.
Change the hlds_goal for constructions in preparation for
structure reuse to avoid making multiple conflicting changes.
compiler/hlds_goal.m:
Merge `higher_order_call' and `class_method_call' into a single
`generic_call' goal type. This also has alternatives for the
various Aditi builtins for which type declarations can't
be written.
Remove the argument types field from higher-order/class method calls.
It wasn't used often, and wasn't updated by optimizations
such as inlining. The types can be obtained from the vartypes
field of the proc_info.
Add a `lambda_eval_method' field to lambda_goals.
Add a field to constructions to identify which RL code fragment should
be used for an top-down Aditi closure.
Add fields to constructions to hold structure reuse information.
This is currently ignored -- the changes to implement structure
reuse will be committed to the alias branch.
This is included here to avoid lots of CVS conflicts caused by
changing the definition of `hlds_goal' twice.
Add a field to `some' goals to specify whether the quantification
can be removed. This is used to make it easier to ensure that
indexes are used for updates.
Add a field to lambda_goals to describe whether the modes were
guessed by the compiler and may need fixing up after typechecking
works out the argument types.
Add predicate `hlds_goal__generic_call_id' to work out a call_id
for a generic call for use in error messages.
compiler/purity.m:
compiler/post_typecheck.m:
Fill in the modes of Aditi builtin calls and closure constructions.
This needs to know which are the `aditi__state' arguments, so
it must be done after typechecking.
compiler/prog_data.m:
Added `:- type sym_name_and_arity ---> sym_name/arity'.
Add a type `lambda_eval_method', which describes how a closure
is to be executed. The alternatives are normal Mercury execution,
bottom-up execution by Aditi and top-down execution by Aditi.
compiler/prog_out.m:
Add predicate `prog_out__write_sym_name_and_arity', which
replaces duplicated inline code in a few places.
compiler/hlds_data.m:
Add a `lambda_eval_method' field to `pred_const' cons_ids and
`pred_closure_tag' cons_tags.
compiler/hlds_pred.m:
Remove type `pred_call_id', replace it with type `simple_call_id',
which combines a `pred_or_func' and a `sym_name_and_arity'.
Add a type `call_id' which describes all the different types of call,
including normal calls, higher-order and class-method calls
and Aditi builtins.
Add `aditi_top_down' to the type `marker'.
Remove `aditi_interface' from type `marker'. Interfacing to
Aditi predicates is now handled by `generic_call' hlds_goals.
Add a type `rl_exprn_id' which identifies a predicate to
be executed top-down by Aditi.
Add a `maybe(rl_exprn_id)' field to type `proc_info'.
Add predicate `adjust_func_arity' to convert between the arity
of a function to its arity as a predicate.
Add predicates `get_state_args' and `get_state_args_det' to
extract the DCG state arguments from an argument list.
Add predicate `pred_info_get_call_id' to get a `simple_call_id'
for a predicate for use in error messages.
compiler/hlds_out.m:
Write the new representation for call_ids.
Add a predicate `hlds_out__write_call_arg_id' which
replaces similar code in mode_errors.m and typecheck.m.
compiler/prog_io_goal.m:
Add support for `aditi_bottom_up' and `aditi_top_down' annotations
on pred expressions.
compiler/prog_io_util.m:
compiler/prog_io_pragma.m:
Add predicates
- `prog_io_util:parse_name_and_arity' to parse `SymName/Arity'
(moved from prog_io_pragma.m).
- `prog_io_util:parse_pred_or_func_name_and_arity to parse
`pred SymName/Arity' or `func SymName/Arity'.
- `prog_io_util:parse_pred_or_func_and_args' to parse terms resembling
a clause head (moved from prog_io_pragma.m).
compiler/type_util.m:
Add support for `aditi_bottom_up' and `aditi_top_down' annotations
on higher-order types.
Add predicates `construct_higher_order_type',
`construct_higher_order_pred_type' and
`construct_higher_order_func_type' to avoid some code duplication.
compiler/mode_util.m:
Add predicate `unused_mode/1', which returns `builtin:unused'.
Add functions `aditi_di_mode/0', `aditi_ui_mode/0' and
`aditi_uo_mode/0' which return `in', `in', and `out', but will
be changed to return `di', `ui' and `uo' when alias tracking
is implemented.
compiler/goal_util.m:
Add predicate `goal_util__generic_call_vars' which returns
any arguments to a generic_call which are not in the argument list,
for example the closure passed to a higher-order call or
the typeclass_info for a class method call.
compiler/llds.m:
compiler/exprn_aux.m:
compiler/dupelim.m:
compiler/llds_out.m:
compiler/opt_debug.m:
Add builtin labels for the Aditi update operations.
compiler/hlds_module.m:
Add predicate predicate_table_search_pf_sym, used for finding
possible matches for a call with the wrong number of arguments.
compiler/intermod.m:
Don't write predicates which build `aditi_top_down' goals,
because there is currently no way to tell importing modules
which RL code fragment to use.
compiler/simplify.m:
Obey the `cannot_remove' field of explicit quantification goals.
compiler/make_hlds.m:
Parse Aditi updates.
Don't typecheck clauses for which syntax errors in Aditi updates
are found - this avoids spurious "undefined predicate `aditi_insert/3'"
errors.
Factor out some common code to handle terms of the form `Head :- Body'.
Factor out common code in the handling of pred and func expressions.
compiler/typecheck.m:
Typecheck Aditi builtins.
Allow the argument types of matching predicates to be adjusted
when typechecking the higher-order arguments of Aditi builtins.
Change `typecheck__resolve_pred_overloading' to take a list of
argument types rather than a `map(var, type)' and a list of
arguments to allow a transformation to be performed on the
argument types before passing them.
compiler/error_util.m:
Move the part of `report_error_num_args' which writes
"wrong number of arguments (<x>; expected <y>)" from
typecheck.m for use by make_hlds.m when reporting errors
for Aditi builtins.
compiler/modes.m:
compiler/unique_modes.m:
compiler/modecheck_call.m:
Modecheck Aditi builtins.
compiler/lambda.m:
Handle the markers for predicates introduced for
`aditi_top_down' and `aditi_bottom_up' lambda expressions.
compiler/polymorphism.m:
Add extra type_infos to `aditi_insert' calls
describing the tuple to insert.
compiler/call_gen.m:
Generate code for Aditi builtins.
compiler/unify_gen.m:
compiler/bytecode_gen.m:
Abort on `aditi_top_down' and `aditi_bottom_up' lambda
expressions - code generation for them is not yet implemented.
compiler/magic.m:
Use the `aditi_call' generic_call rather than create
a new procedure for each Aditi predicate called from C.
compiler/rl_out.pp:
compiler/rl_gen.m:
compiler/rl.m:
Move some utility code used by magic.m and call_gen.m into rl.m.
Remove an XXX comment about reference counting being not yet
implemented - Evan has fixed that.
library/ops.m:
compiler/mercury_to_mercury.m:
doc/transition_guide.texi:
Add unary prefix operators `aditi_bottom_up' and `aditi_top_down',
used as qualifiers on lambda expressions.
Add infix operator `==>' to separate the tuples in an
`aditi_modify' call.
compiler/follow_vars.m:
Thread a `map(prog_var, type)' through, needed because
type information is no longer held in higher-order call goals.
compiler/table_gen.m:
Use the `make_*_construction' predicates in hlds_goal.m
to construct constants.
compiler/*.m:
Trivial changes to add extra fields to hlds_goal structures.
doc/reference_manual.texi:
Document Aditi updates.
Use @samp{pragma base_relation} instead of
@samp{:- pragma base_relation} throughout the Aditi documentation
to be consistent with other parts of the reference manual.
tests/valid/Mmakefile:
tests/valid/aditi_update.m:
tests/valid/aditi.m:
Test case.
tests/valid/Mmakefile:
Remove some hard-coded --intermodule-optimization rules which are
no longer needed because `mmake depend' is now run in this directory.
tests/invalid/*.err_exp:
Fix expected output for changes in reporting of call_ids
in typecheck.m.
tests/invalid/Mmakefile
tests/invalid/aditi_update_errors.{m,err_exp}:
tests/invalid/aditi_update_mode_errors.{m,err_exp}:
Test error messages for Aditi updates.
tests/valid/aditi.m:
tests/invalid/aditi.m:
Cut down version of extras/aditi/aditi.m to provide basic declarations
for Aditi compilation such as `aditi__state' and the modes
`aditi_di', `aditi_uo' and `aditi_ui'. Installing extras/aditi/aditi.m
somewhere would remove the need for these.
355 lines
13 KiB
Mathematica
355 lines
13 KiB
Mathematica
%-----------------------------------------------------------------------------%
|
|
% Copyright (C) 1994-1999 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: switch_gen.m
|
|
% Authors: conway, fjh, zs
|
|
%
|
|
% This module handles the generation of code for switches, which are
|
|
% disjunctions that do not require backtracking. Switches are detected
|
|
% in switch_detection.m. This is the module that determines what
|
|
% sort of indexing to use for each switch and then actually generates the
|
|
% code.
|
|
%
|
|
% Currently the following forms of indexing are used:
|
|
%
|
|
% For switches on atomic data types (int, char, enums),
|
|
% if the cases are not sparse, we use the value of the switch variable
|
|
% to index into a jump table.
|
|
%
|
|
% If all the alternative goals for a switch on an atomic data type
|
|
% contain only construction unifications of constants, then we generate
|
|
% a dense lookup table (an array) for each output variable of the switch,
|
|
% rather than a dense jump table, so that executing the switch becomes
|
|
% a matter of doing an array index for each output variable - avoiding
|
|
% the branch overhead of the jump-table.
|
|
%
|
|
% For switches on discriminated union types, we generate code that does
|
|
% indexing first on the primary tag, and then on the secondary tag (if
|
|
% the primary tag is shared between several function symbols). The
|
|
% indexing code for switches on both primary and secondary tags can be
|
|
% in the form of a try-me-else chain, a try chain, a dense jump table
|
|
% or a binary search.
|
|
%
|
|
% For switches on strings, we lookup the address to jump to in a
|
|
% hash table, using open addressing to resolve hash collisions.
|
|
%
|
|
% For all other cases (or if the --smart-indexing option was
|
|
% disabled), we just generate a chain of if-then-elses.
|
|
%
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- module switch_gen.
|
|
|
|
:- interface.
|
|
|
|
:- import_module prog_data, hlds_goal, hlds_data, code_info, llds.
|
|
:- import_module list.
|
|
|
|
:- pred switch_gen__generate_switch(code_model, prog_var, can_fail, list(case),
|
|
store_map, hlds_goal_info, code_tree, code_info, code_info).
|
|
:- mode switch_gen__generate_switch(in, in, in, in, in, in, out, in, out)
|
|
is det.
|
|
|
|
% The following types are exported to the modules that implement
|
|
% specialized kinds of switches.
|
|
|
|
:- type extended_case ---> case(int, cons_tag, cons_id, hlds_goal).
|
|
:- type cases_list == list(extended_case).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- implementation.
|
|
|
|
:- import_module dense_switch, string_switch, tag_switch, lookup_switch.
|
|
:- import_module code_gen, unify_gen, code_aux, type_util, code_util.
|
|
:- import_module trace, globals, options.
|
|
:- import_module bool, int, string, map, tree, std_util, require.
|
|
|
|
:- type switch_category
|
|
---> atomic_switch
|
|
; string_switch
|
|
; tag_switch
|
|
; other_switch.
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
% Choose which method to use to generate the switch.
|
|
% CanFail says whether the switch covers all cases.
|
|
|
|
switch_gen__generate_switch(CodeModel, CaseVar, CanFail, Cases, StoreMap,
|
|
GoalInfo, Code) -->
|
|
switch_gen__determine_category(CaseVar, SwitchCategory),
|
|
code_info__get_next_label(EndLabel),
|
|
switch_gen__lookup_tags(Cases, CaseVar, TaggedCases0),
|
|
{ list__sort_and_remove_dups(TaggedCases0, TaggedCases) },
|
|
code_info__get_globals(Globals),
|
|
{ globals__lookup_bool_option(Globals, smart_indexing,
|
|
Indexing) },
|
|
(
|
|
{ Indexing = yes },
|
|
{ SwitchCategory = atomic_switch },
|
|
code_info__get_maybe_trace_info(MaybeTraceInfo),
|
|
{ MaybeTraceInfo = no },
|
|
{ list__length(TaggedCases, NumCases) },
|
|
{ globals__lookup_int_option(Globals, lookup_switch_size,
|
|
LookupSize) },
|
|
{ NumCases >= LookupSize },
|
|
{ globals__lookup_int_option(Globals, lookup_switch_req_density,
|
|
ReqDensity) },
|
|
lookup_switch__is_lookup_switch(CaseVar, TaggedCases, GoalInfo,
|
|
CanFail, ReqDensity, CodeModel, FirstVal, LastVal,
|
|
NeedRangeCheck, NeedBitVecCheck,
|
|
OutVars, CaseVals, MLiveness)
|
|
->
|
|
lookup_switch__generate(CaseVar, OutVars, CaseVals,
|
|
FirstVal, LastVal, NeedRangeCheck, NeedBitVecCheck,
|
|
MLiveness, StoreMap, no, MaybeEnd, Code)
|
|
;
|
|
{ Indexing = yes },
|
|
{ SwitchCategory = atomic_switch },
|
|
{ list__length(TaggedCases, NumCases) },
|
|
{ globals__lookup_int_option(Globals, dense_switch_size,
|
|
DenseSize) },
|
|
{ NumCases >= DenseSize },
|
|
{ globals__lookup_int_option(Globals, dense_switch_req_density,
|
|
ReqDensity) },
|
|
dense_switch__is_dense_switch(CaseVar, TaggedCases, CanFail,
|
|
ReqDensity, FirstVal, LastVal, CanFail1)
|
|
->
|
|
dense_switch__generate(TaggedCases,
|
|
FirstVal, LastVal, CaseVar, CodeModel, CanFail1,
|
|
StoreMap, EndLabel, no, MaybeEnd, Code)
|
|
;
|
|
{ Indexing = yes },
|
|
{ SwitchCategory = string_switch },
|
|
{ list__length(TaggedCases, NumCases) },
|
|
{ globals__lookup_int_option(Globals, string_switch_size,
|
|
StringSize) },
|
|
{ NumCases >= StringSize }
|
|
->
|
|
string_switch__generate(TaggedCases, CaseVar, CodeModel,
|
|
CanFail, StoreMap, EndLabel, no, MaybeEnd, Code)
|
|
;
|
|
{ Indexing = yes },
|
|
{ SwitchCategory = tag_switch },
|
|
{ list__length(TaggedCases, NumCases) },
|
|
{ globals__lookup_int_option(Globals, tag_switch_size,
|
|
TagSize) },
|
|
{ NumCases >= TagSize }
|
|
->
|
|
tag_switch__generate(TaggedCases, CaseVar, CodeModel, CanFail,
|
|
StoreMap, EndLabel, no, MaybeEnd, Code)
|
|
;
|
|
% To generate a switch, first we flush the
|
|
% variable on whose tag we are going to switch, then we
|
|
% generate the cases for the switch.
|
|
|
|
switch_gen__generate_all_cases(TaggedCases, CaseVar,
|
|
CodeModel, CanFail, StoreMap, EndLabel, no, MaybeEnd,
|
|
Code)
|
|
),
|
|
code_info__after_all_branches(StoreMap, MaybeEnd).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
% We categorize switches according to whether the value
|
|
% being switched on is an atomic type, a string, or
|
|
% something more complicated.
|
|
|
|
:- pred switch_gen__determine_category(prog_var, switch_category,
|
|
code_info, code_info).
|
|
:- mode switch_gen__determine_category(in, out, in, out) is det.
|
|
|
|
switch_gen__determine_category(CaseVar, SwitchCategory) -->
|
|
code_info__variable_type(CaseVar, Type),
|
|
code_info__get_module_info(ModuleInfo),
|
|
{ classify_type(Type, ModuleInfo, TypeCategory) },
|
|
{ switch_gen__type_cat_to_switch_cat(TypeCategory, SwitchCategory) }.
|
|
|
|
:- pred switch_gen__type_cat_to_switch_cat(builtin_type, switch_category).
|
|
:- mode switch_gen__type_cat_to_switch_cat(in, out) is det.
|
|
|
|
switch_gen__type_cat_to_switch_cat(enum_type, atomic_switch).
|
|
switch_gen__type_cat_to_switch_cat(int_type, atomic_switch).
|
|
switch_gen__type_cat_to_switch_cat(char_type, atomic_switch).
|
|
switch_gen__type_cat_to_switch_cat(float_type, other_switch).
|
|
switch_gen__type_cat_to_switch_cat(str_type, string_switch).
|
|
switch_gen__type_cat_to_switch_cat(pred_type, other_switch).
|
|
switch_gen__type_cat_to_switch_cat(user_type, tag_switch).
|
|
switch_gen__type_cat_to_switch_cat(polymorphic_type, other_switch).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- pred switch_gen__lookup_tags(list(case), prog_var, cases_list,
|
|
code_info, code_info).
|
|
:- mode switch_gen__lookup_tags(in, in, out, in, out) is det.
|
|
|
|
switch_gen__lookup_tags([], _, []) --> [].
|
|
switch_gen__lookup_tags([Case | Cases], Var, [TaggedCase | TaggedCases]) -->
|
|
{ Case = case(ConsId, Goal) },
|
|
code_info__cons_id_to_tag(Var, ConsId, Tag),
|
|
{ switch_gen__priority(Tag, Priority) },
|
|
{ TaggedCase = case(Priority, Tag, ConsId, Goal) },
|
|
switch_gen__lookup_tags(Cases, Var, TaggedCases).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- pred switch_gen__priority(cons_tag, int).
|
|
:- mode switch_gen__priority(in, out) is det.
|
|
|
|
% prioritize tag tests - the most efficient ones first.
|
|
|
|
switch_gen__priority(no_tag, 0). % should never occur
|
|
switch_gen__priority(int_constant(_), 1).
|
|
switch_gen__priority(shared_local_tag(_, _), 1).
|
|
switch_gen__priority(unshared_tag(_), 2).
|
|
switch_gen__priority(float_constant(_), 3).
|
|
switch_gen__priority(shared_remote_tag(_, _), 4).
|
|
switch_gen__priority(string_constant(_), 5).
|
|
switch_gen__priority(pred_closure_tag(_, _, _), 6). % should never occur
|
|
switch_gen__priority(code_addr_constant(_, _), 6). % should never occur
|
|
switch_gen__priority(type_ctor_info_constant(_, _, _), 6).% should never occur
|
|
switch_gen__priority(base_typeclass_info_constant(_, _, _), 6).% shouldn't occur
|
|
switch_gen__priority(tabling_pointer_constant(_, _), 6). % shouldn't occur
|
|
|
|
%---------------------------------------------------------------------------%
|
|
%---------------------------------------------------------------------------%
|
|
|
|
% Generate a switch as a chain of if-then-elses.
|
|
%
|
|
% To generate a case for a switch we generate
|
|
% code to do a tag-test and fall through to the next case in
|
|
% the event of failure.
|
|
%
|
|
% Each case except the last consists of
|
|
%
|
|
% a tag test, jumping to the next case if it fails
|
|
% the goal for that case
|
|
% code to move variables to where the store map says they
|
|
% ought to be
|
|
% a branch to the end of the switch.
|
|
%
|
|
% For the last case, if the switch covers all cases that can occur,
|
|
% we don't need to generate the tag test, and we never need to
|
|
% generate the branch to the end of the switch.
|
|
%
|
|
% After the last case, we put the end-of-switch label which other
|
|
% cases branch to after their case goals.
|
|
%
|
|
% In the important special case of a det switch with two cases,
|
|
% we try to find out which case will be executed more frequently,
|
|
% and put that one first. This minimizes the number of pipeline
|
|
% breaks caused by taken branches.
|
|
|
|
:- pred switch_gen__generate_all_cases(list(extended_case), prog_var,
|
|
code_model, can_fail, store_map, label, branch_end, branch_end,
|
|
code_tree, code_info, code_info).
|
|
:- mode switch_gen__generate_all_cases(in, in, in, in, in, in, in, out, out,
|
|
in, out) is det.
|
|
|
|
switch_gen__generate_all_cases(Cases0, Var, CodeModel, CanFail, StoreMap,
|
|
EndLabel, MaybeEnd0, MaybeEnd, Code) -->
|
|
code_info__produce_variable(Var, VarCode, _Rval),
|
|
(
|
|
{ CodeModel = model_det },
|
|
{ CanFail = cannot_fail },
|
|
{ Cases0 = [Case1, Case2] },
|
|
{ Case1 = case(_, _, _, Goal1) },
|
|
{ Case2 = case(_, _, _, Goal2) }
|
|
->
|
|
code_info__get_pred_id(PredId),
|
|
code_info__get_proc_id(ProcId),
|
|
{ code_util__count_recursive_calls(Goal1, PredId, ProcId,
|
|
Min1, Max1) },
|
|
{ code_util__count_recursive_calls(Goal2, PredId, ProcId,
|
|
Min2, Max2) },
|
|
{
|
|
Max1 = 0, % Goal1 is a base case
|
|
Min2 = 1 % Goal2 is probably singly recursive
|
|
->
|
|
Cases = [Case2, Case1]
|
|
;
|
|
Max2 = 0, % Goal2 is a base case
|
|
Min1 > 1 % Goal1 is at least doubly recursive
|
|
->
|
|
Cases = [Case2, Case1]
|
|
;
|
|
Cases = Cases0
|
|
}
|
|
;
|
|
{ Cases = Cases0 }
|
|
),
|
|
switch_gen__generate_cases(Cases, Var, CodeModel, CanFail,
|
|
StoreMap, EndLabel, MaybeEnd0, MaybeEnd, CasesCode),
|
|
{ Code = tree(VarCode, CasesCode) }.
|
|
|
|
:- pred switch_gen__generate_cases(list(extended_case), prog_var, code_model,
|
|
can_fail, store_map, label, branch_end, branch_end, code_tree,
|
|
code_info, code_info).
|
|
:- mode switch_gen__generate_cases(in, in, in, in, in, in, in, out, out,
|
|
in, out) is det.
|
|
|
|
% At the end of a locally semidet switch, we fail because we
|
|
% came across a tag which was not covered by one of the cases.
|
|
% It is followed by the end of switch label to which the cases
|
|
% branch.
|
|
switch_gen__generate_cases([], _Var, _CodeModel, CanFail, _StoreMap,
|
|
EndLabel, MaybeEnd, MaybeEnd, Code) -->
|
|
( { CanFail = can_fail } ->
|
|
code_info__generate_failure(FailCode)
|
|
;
|
|
{ FailCode = empty }
|
|
),
|
|
{ EndCode = node([
|
|
label(EndLabel) -
|
|
"end of switch"
|
|
]) },
|
|
{ Code = tree(FailCode, EndCode) }.
|
|
|
|
switch_gen__generate_cases([case(_, _, Cons, Goal) | Cases], Var, CodeModel,
|
|
CanFail, StoreMap, EndLabel, MaybeEnd0, MaybeEnd, CasesCode) -->
|
|
code_info__remember_position(BranchStart),
|
|
(
|
|
{ Cases = [_|_] ; CanFail = can_fail }
|
|
->
|
|
unify_gen__generate_tag_test(Var, Cons, branch_on_failure,
|
|
NextLabel, TestCode),
|
|
trace__maybe_generate_internal_event_code(Goal, TraceCode),
|
|
code_gen__generate_goal(CodeModel, Goal, GoalCode),
|
|
code_info__generate_branch_end(StoreMap, MaybeEnd0, MaybeEnd1,
|
|
SaveCode),
|
|
{ ElseCode = node([
|
|
goto(label(EndLabel)) -
|
|
"skip to the end of the switch",
|
|
label(NextLabel) -
|
|
"next case"
|
|
]) },
|
|
{ ThisCaseCode =
|
|
tree(TestCode,
|
|
tree(TraceCode,
|
|
tree(GoalCode,
|
|
tree(SaveCode,
|
|
ElseCode))))
|
|
}
|
|
;
|
|
trace__maybe_generate_internal_event_code(Goal, TraceCode),
|
|
code_gen__generate_goal(CodeModel, Goal, GoalCode),
|
|
code_info__generate_branch_end(StoreMap, MaybeEnd0, MaybeEnd1,
|
|
SaveCode),
|
|
{ ThisCaseCode =
|
|
tree(TraceCode,
|
|
tree(GoalCode,
|
|
SaveCode))
|
|
}
|
|
),
|
|
code_info__reset_to_position(BranchStart),
|
|
% generate the rest of the cases.
|
|
switch_gen__generate_cases(Cases, Var, CodeModel, CanFail, StoreMap,
|
|
EndLabel, MaybeEnd1, MaybeEnd, OtherCasesCode),
|
|
{ CasesCode = tree(ThisCaseCode, OtherCasesCode) }.
|
|
|
|
%------------------------------------------------------------------------------%
|