mirror of
https://github.com/Mercury-Language/mercury.git
synced 2025-12-11 11:53:51 +00:00
Estimated hours taken: 100
Branches: main
Make definitions of abstract types available when generating
code for importing modules. This is necessary for the .NET
back-end, and for `:- pragma export' on the C back-end.
compiler/prog_data.m:
compiler/modules.m:
compiler/make.dependencies.m:
compiler/recompilation.version.m:
Handle implementation sections in interface files.
There is a new pseudo-declaration `abstract_imported'
which is applied to items from the implementation
section of an interface file. `abstract_imported'
items may not be used in the error checking passes
for the curent module.
compiler/equiv_type_hlds.m:
compiler/notes/compiler_design.html:
New file.
Go over the HLDS expanding all types fully after
semantic checking has been run.
compiler/mercury_compile.m:
Add the new pass.
Don't write the `.opt' file if there are any errors.
compiler/instmap.m:
Add a predicate instmap_delta_map_foldl to apply
a procedure to all insts in an instmap.
compiler/equiv_type.m:
Export predicates for use by equiv_type_hlds.m
Reorder arguments so state variables and higher-order
programming can be used.
compiler/prog_data.m:
compiler/prog_io_pragma.m:
compiler/make_hlds.m:
compiler/mercury_to_mercury.m:
Handle `:- pragma foreign_type' as a form of type
declaration rather than a pragma.
compiler/hlds_data.m:
compiler/*.m:
Add a field to the type_info_cell_constructor cons_id
to identify the type_ctor, which is needed by
equiv_type_hlds.m.
compiler/module_qual.m:
Donn't allow items from the implementation section of
interface files to match items in the current module.
compiler/*.m:
tests/*/*.m:
Add missing imports which only became apparent with
the bug fixes above.
Remove unnecessary imports which only became apparent with
the bug fixes above.
tests/hard_coded/Mmakefile:
tests/hard_coded/export_test2.{m,exp}:
Test case.
tests/invalid/Mmakefile:
tests/invalid/missing_interface_import2.{m,err_exp}:
Test case.
288 lines
11 KiB
Mathematica
288 lines
11 KiB
Mathematica
%---------------------------------------------------------------------------%
|
|
% Copyright (C) 2000-2003 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.
|
|
%---------------------------------------------------------------------------%
|
|
%
|
|
% This module generates a representation of HLDS goals for the declarative
|
|
% debugger. Since this representation is to be included in debuggable
|
|
% executables, it should be as compact as possible, and therefore contains
|
|
% only the information required by the declarative debugger. The structure
|
|
% of this representation is defined by browser/program_representation.m.
|
|
%
|
|
% Author: zs.
|
|
%
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- module ll_backend__prog_rep.
|
|
|
|
:- interface.
|
|
|
|
:- import_module hlds__hlds_goal.
|
|
:- import_module hlds__hlds_module.
|
|
:- import_module hlds__hlds_pred.
|
|
:- import_module hlds__instmap.
|
|
:- import_module parse_tree__prog_data.
|
|
|
|
:- import_module mdbcomp.
|
|
:- import_module mdbcomp__program_representation.
|
|
|
|
:- import_module list.
|
|
|
|
:- pred prog_rep__represent_proc(list(prog_var)::in, hlds_goal::in,
|
|
instmap::in, vartypes::in, module_info::in, proc_rep::out) is det.
|
|
|
|
:- implementation.
|
|
|
|
:- import_module hlds__hlds_data.
|
|
:- import_module parse_tree__prog_out.
|
|
:- import_module parse_tree__prog_util.
|
|
|
|
:- import_module string, set, std_util, require, term.
|
|
|
|
:- type prog_rep__info
|
|
---> info(
|
|
vartypes :: vartypes,
|
|
module_info :: module_info
|
|
).
|
|
|
|
prog_rep__represent_proc(HeadVars, Goal, InstMap0, VarTypes, ModuleInfo,
|
|
proc_rep(HeadVarsRep, GoalRep)) :-
|
|
list__map(term__var_to_int, HeadVars, HeadVarsRep),
|
|
prog_rep__represent_goal(Goal, InstMap0, info(VarTypes, ModuleInfo),
|
|
GoalRep).
|
|
|
|
:- pred prog_rep__represent_goal(hlds_goal::in, instmap::in,
|
|
prog_rep__info::in, goal_rep::out) is det.
|
|
|
|
prog_rep__represent_goal(GoalExpr - GoalInfo, InstMap0, Info, Rep) :-
|
|
prog_rep__represent_goal_expr(GoalExpr, GoalInfo, InstMap0, Info, Rep).
|
|
|
|
:- pred prog_rep__represent_atomic_goal(hlds_goal_info::in,
|
|
instmap::in, prog_rep__info::in, detism_rep::out,
|
|
string::out, int::out, list(var_rep)::out) is det.
|
|
|
|
prog_rep__represent_atomic_goal(GoalInfo, InstMap0, Info,
|
|
DetismRep, FilenameRep, LinenoRep, ChangedVarsRep) :-
|
|
goal_info_get_determinism(GoalInfo, Detism),
|
|
prog_rep__represent_detism(Detism, DetismRep),
|
|
goal_info_get_context(GoalInfo, Context),
|
|
term__context_file(Context, FilenameRep),
|
|
term__context_line(Context, LinenoRep),
|
|
goal_info_get_instmap_delta(GoalInfo, InstMapDelta),
|
|
instmap__apply_instmap_delta(InstMap0, InstMapDelta, InstMap),
|
|
instmap_changed_vars(InstMap0, InstMap, Info ^ vartypes,
|
|
Info ^ module_info, ChangedVars),
|
|
set__to_sorted_list(ChangedVars, ChangedVarsList),
|
|
list__map(term__var_to_int, ChangedVarsList, ChangedVarsRep).
|
|
|
|
:- pred prog_rep__represent_detism(determinism::in,
|
|
detism_rep::out) is det.
|
|
|
|
prog_rep__represent_detism(det, det_rep).
|
|
prog_rep__represent_detism(semidet, semidet_rep).
|
|
prog_rep__represent_detism(nondet, nondet_rep).
|
|
prog_rep__represent_detism(multidet, multidet_rep).
|
|
prog_rep__represent_detism(cc_nondet, cc_nondet_rep).
|
|
prog_rep__represent_detism(cc_multidet, cc_multidet_rep).
|
|
prog_rep__represent_detism(erroneous, erroneous_rep).
|
|
prog_rep__represent_detism(failure, failure_rep).
|
|
|
|
:- pred prog_rep__represent_cons_id(cons_id::in,
|
|
cons_id_rep::out) is det.
|
|
|
|
prog_rep__represent_cons_id(cons(SymName, _), Rep) :-
|
|
prog_rep__represent_sym_name(SymName, Rep).
|
|
prog_rep__represent_cons_id(int_const(Int), Rep) :-
|
|
string__int_to_string(Int, Rep).
|
|
prog_rep__represent_cons_id(float_const(Float), Rep) :-
|
|
string__float_to_string(Float, Rep).
|
|
prog_rep__represent_cons_id(string_const(String), Rep) :-
|
|
string__append_list(["""", String, """"], Rep).
|
|
prog_rep__represent_cons_id(pred_const(_, _, _), Rep) :-
|
|
Rep = "$pred_const".
|
|
prog_rep__represent_cons_id(type_ctor_info_const(_, _, _), Rep) :-
|
|
Rep = "$type_ctor_info_const".
|
|
prog_rep__represent_cons_id(base_typeclass_info_const(_, _, _, _), Rep) :-
|
|
Rep = "$base_typeclass_info_const".
|
|
prog_rep__represent_cons_id(type_info_cell_constructor(_), Rep) :-
|
|
Rep = "$type_info_cell_constructor".
|
|
prog_rep__represent_cons_id(typeclass_info_cell_constructor, Rep) :-
|
|
Rep = "$typeclass_info_cell_constructor".
|
|
prog_rep__represent_cons_id(tabling_pointer_const(_, _), Rep) :-
|
|
Rep = "$tabling_pointer_const".
|
|
prog_rep__represent_cons_id(deep_profiling_proc_static(_), Rep) :-
|
|
Rep = "$deep_profiling_procedure_data".
|
|
prog_rep__represent_cons_id(table_io_decl(_), Rep) :-
|
|
Rep = "$table_io_decl".
|
|
|
|
:- pred prog_rep__represent_sym_name(sym_name::in, string::out) is det.
|
|
|
|
prog_rep__represent_sym_name(unqualified(String), String).
|
|
prog_rep__represent_sym_name(qualified(_, String), String).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- pred prog_rep__represent_goal_expr(hlds_goal_expr::in, hlds_goal_info::in,
|
|
instmap::in, prog_rep__info::in, goal_rep::out) is det.
|
|
|
|
prog_rep__represent_goal_expr(unify(_, _, _, Uni, _), GoalInfo, InstMap0,
|
|
Info, Rep) :-
|
|
(
|
|
Uni = assign(Target, Source),
|
|
term__var_to_int(Target, TargetRep),
|
|
term__var_to_int(Source, SourceRep),
|
|
AtomicGoalRep = unify_assign_rep(TargetRep, SourceRep)
|
|
;
|
|
Uni = construct(Var, ConsId, Args, _, _, _, _),
|
|
term__var_to_int(Var, VarRep),
|
|
prog_rep__represent_cons_id(ConsId, ConsIdRep),
|
|
list__map(term__var_to_int, Args, ArgsRep),
|
|
AtomicGoalRep = unify_construct_rep(VarRep, ConsIdRep, ArgsRep)
|
|
;
|
|
Uni = deconstruct(Var, ConsId, Args, _, _, _),
|
|
term__var_to_int(Var, VarRep),
|
|
prog_rep__represent_cons_id(ConsId, ConsIdRep),
|
|
list__map(term__var_to_int, Args, ArgsRep),
|
|
AtomicGoalRep = unify_deconstruct_rep(VarRep, ConsIdRep,
|
|
ArgsRep)
|
|
;
|
|
Uni = simple_test(Var1, Var2),
|
|
term__var_to_int(Var1, Var1Rep),
|
|
term__var_to_int(Var2, Var2Rep),
|
|
AtomicGoalRep = unify_simple_test_rep(Var1Rep, Var2Rep)
|
|
;
|
|
Uni = complicated_unify(_, _, _),
|
|
error("prog_rep__represent_goal_expr: complicated_unify")
|
|
),
|
|
prog_rep__represent_atomic_goal(GoalInfo, InstMap0, Info,
|
|
DetismRep, FilenameRep, LinenoRep, ChangedVarsRep),
|
|
Rep = atomic_goal_rep(DetismRep, FilenameRep, LinenoRep, ChangedVarsRep,
|
|
AtomicGoalRep).
|
|
prog_rep__represent_goal_expr(conj(Goals), _, InstMap0, Info, Rep) :-
|
|
prog_rep__represent_conj(Goals, InstMap0, Info, Reps),
|
|
Rep = conj_rep(Reps).
|
|
prog_rep__represent_goal_expr(par_conj(_), _, _, _, _) :-
|
|
error("Sorry, not yet implemented:\n\
|
|
parallel conjunctions and declarative debugging").
|
|
prog_rep__represent_goal_expr(disj(Goals), _, InstMap0, Info, Rep) :-
|
|
prog_rep__represent_disj(Goals, InstMap0, Info, DisjReps),
|
|
Rep = disj_rep(DisjReps).
|
|
prog_rep__represent_goal_expr(not(Goal), _GoalInfo, InstMap0, Info, Rep)
|
|
:-
|
|
prog_rep__represent_goal(Goal, InstMap0, Info, InnerRep),
|
|
Rep = negation_rep(InnerRep).
|
|
prog_rep__represent_goal_expr(if_then_else(_, Cond, Then, Else),
|
|
_, InstMap0, Info, Rep) :-
|
|
prog_rep__represent_goal(Cond, InstMap0, Info, CondRep),
|
|
Cond = _ - CondGoalInfo,
|
|
goal_info_get_instmap_delta(CondGoalInfo, InstMapDelta),
|
|
instmap__apply_instmap_delta(InstMap0, InstMapDelta, InstMap1),
|
|
prog_rep__represent_goal(Then, InstMap1, Info, ThenRep),
|
|
prog_rep__represent_goal(Else, InstMap0, Info, ElseRep),
|
|
Rep = ite_rep(CondRep, ThenRep, ElseRep).
|
|
prog_rep__represent_goal_expr(switch(_, _, Cases), _,
|
|
InstMap0, Info, Rep) :-
|
|
prog_rep__represent_cases(Cases, InstMap0, Info, CaseReps),
|
|
Rep = switch_rep(CaseReps).
|
|
prog_rep__represent_goal_expr(some(_, _, Goal), GoalInfo, InstMap0, Info, Rep)
|
|
:-
|
|
prog_rep__represent_goal(Goal, InstMap0, Info, InnerRep),
|
|
Goal = _ - InnerGoalInfo,
|
|
goal_info_get_determinism(GoalInfo, OuterDetism),
|
|
goal_info_get_determinism(InnerGoalInfo, InnerDetism),
|
|
( InnerDetism = OuterDetism ->
|
|
MaybeCut = no_cut
|
|
;
|
|
MaybeCut = cut
|
|
),
|
|
Rep = some_rep(InnerRep, MaybeCut).
|
|
prog_rep__represent_goal_expr(generic_call(GenericCall, Args, _, _),
|
|
GoalInfo, InstMap0, Info, Rep) :-
|
|
list__map(term__var_to_int, Args, ArgsRep),
|
|
(
|
|
GenericCall = higher_order(PredVar, _, _, _),
|
|
term__var_to_int(PredVar, PredVarRep),
|
|
AtomicGoalRep = higher_order_call_rep(PredVarRep, ArgsRep)
|
|
;
|
|
GenericCall = class_method(Var, MethodNum, _, _),
|
|
term__var_to_int(Var, VarRep),
|
|
AtomicGoalRep = method_call_rep(VarRep, MethodNum, ArgsRep)
|
|
;
|
|
GenericCall = unsafe_cast,
|
|
( ArgsRep = [InputArgRep, OutputArgRep] ->
|
|
AtomicGoalRep = unsafe_cast_rep(OutputArgRep,
|
|
InputArgRep)
|
|
;
|
|
error("represent_goal_expr: unsafe_cast arity != 2")
|
|
)
|
|
;
|
|
GenericCall = aditi_builtin(_, _),
|
|
error("Sorry, not yet implemented\n\
|
|
Aditi and declarative debugging")
|
|
),
|
|
prog_rep__represent_atomic_goal(GoalInfo, InstMap0, Info,
|
|
DetismRep, FilenameRep, LinenoRep, ChangedVarsRep),
|
|
Rep = atomic_goal_rep(DetismRep, FilenameRep, LinenoRep,
|
|
ChangedVarsRep, AtomicGoalRep).
|
|
prog_rep__represent_goal_expr(call(PredId, _, Args, _, _, _),
|
|
GoalInfo, InstMap0, Info, Rep) :-
|
|
module_info_pred_info(Info ^ module_info, PredId, PredInfo),
|
|
ModuleSymName = pred_info_module(PredInfo),
|
|
prog_out__sym_name_to_string(ModuleSymName, ModuleName),
|
|
PredName = pred_info_name(PredInfo),
|
|
list__map(term__var_to_int, Args, ArgsRep),
|
|
AtomicGoalRep = plain_call_rep(ModuleName, PredName, ArgsRep),
|
|
prog_rep__represent_atomic_goal(GoalInfo, InstMap0, Info,
|
|
DetismRep, FilenameRep, LinenoRep, ChangedVarsRep),
|
|
Rep = atomic_goal_rep(DetismRep, FilenameRep, LinenoRep,
|
|
ChangedVarsRep, AtomicGoalRep).
|
|
prog_rep__represent_goal_expr(foreign_proc(_,
|
|
_PredId, _, Args, _, _, _),
|
|
GoalInfo, InstMap0, Info, Rep) :-
|
|
list__map(term__var_to_int, Args, ArgsRep),
|
|
AtomicGoalRep = pragma_foreign_code_rep(ArgsRep),
|
|
prog_rep__represent_atomic_goal(GoalInfo, InstMap0, Info,
|
|
DetismRep, FilenameRep, LinenoRep, ChangedVarsRep),
|
|
Rep = atomic_goal_rep(DetismRep, FilenameRep, LinenoRep,
|
|
ChangedVarsRep, AtomicGoalRep).
|
|
prog_rep__represent_goal_expr(shorthand(_), _, _, _, _) :-
|
|
% these should have been expanded out by now
|
|
error("prog_rep__represent_goal: unexpected shorthand").
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- pred prog_rep__represent_conj(hlds_goals::in, instmap::in,
|
|
prog_rep__info::in, list(goal_rep)::out) is det.
|
|
|
|
prog_rep__represent_conj([], _, _, []).
|
|
prog_rep__represent_conj([Goal | Goals], InstMap0, Info, [Rep | Reps]) :-
|
|
prog_rep__represent_goal(Goal, InstMap0, Info, Rep),
|
|
Goal = _ - GoalInfo,
|
|
goal_info_get_instmap_delta(GoalInfo, InstMapDelta),
|
|
instmap__apply_instmap_delta(InstMap0, InstMapDelta, InstMap1),
|
|
prog_rep__represent_conj(Goals, InstMap1, Info, Reps).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- pred prog_rep__represent_disj(hlds_goals::in, instmap::in,
|
|
prog_rep__info::in, list(goal_rep)::out) is det.
|
|
|
|
prog_rep__represent_disj([], _, _, []).
|
|
prog_rep__represent_disj([Goal | Goals], InstMap0, Info, [Rep | Reps]) :-
|
|
prog_rep__represent_goal(Goal, InstMap0, Info, Rep),
|
|
prog_rep__represent_disj(Goals, InstMap0, Info, Reps).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- pred prog_rep__represent_cases(list(case)::in, instmap::in,
|
|
prog_rep__info::in, list(goal_rep)::out) is det.
|
|
|
|
prog_rep__represent_cases([], _, _, []).
|
|
prog_rep__represent_cases([case(_, Goal) | Cases], InstMap0, Info,
|
|
[Rep | Reps]) :-
|
|
prog_rep__represent_goal(Goal, InstMap0, Info, Rep),
|
|
prog_rep__represent_cases(Cases, InstMap0, Info, Reps).
|
|
|
|
%---------------------------------------------------------------------------%
|