[m-dev.] for review: Aditi updates[1]

Simon Taylor stayl at cs.mu.OZ.AU
Sat Jun 5 14:46:53 AEST 1999


Index: compiler/base_type_layout.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/base_type_layout.m,v
retrieving revision 1.44
diff -u -u -r1.44 base_type_layout.m
--- base_type_layout.m	1999/05/27 05:14:21	1.44
+++ base_type_layout.m	1999/05/27 05:16:52
@@ -613,8 +613,8 @@
 		base_type_layout__encode_mkword(LayoutInfo, Tag, 
 			const(int_const(Value)), Rval)
 	;
-		ConsTag = pred_closure_tag(_, _),
-		error("type_ctor_layout: Unexpected tag - pred_closure_tag/2")
+		ConsTag = pred_closure_tag(_, _, _),
+		error("base_type_layout: Unexpected tag - pred_closure_tag/3")
 	;
 		ConsTag = code_addr_constant(_, _),
 		error("type_ctor_layout: Unexpected constant - code_addr_constant/2")
@@ -1131,8 +1131,10 @@
 			% argument for their real arity, and then type
 			% arguments according to their types. 
 			% polymorphism.m has a detailed explanation.
-
-			type_is_higher_order(Type, _PredFunc, _TypeArgs)
+			% XXX should the pred_or_func or eval_method fields
+			% change the type name?
+			type_is_higher_order(Type, _PredFunc,
+				_EvalMethod, _TypeArgs)
 		->
 			TypeModule = unqualified(""),
 			TypeName = "pred",
@@ -1247,7 +1249,7 @@
 base_type_layout__tag_type_and_value(string_constant(_), -1, unused). 
 base_type_layout__tag_type_and_value(float_constant(_), -1, unused). 
 base_type_layout__tag_type_and_value(int_constant(_), -1, unused). 
-base_type_layout__tag_type_and_value(pred_closure_tag(_, _), -1, unused). 
+base_type_layout__tag_type_and_value(pred_closure_tag(_, _, _), -1, unused). 
 base_type_layout__tag_type_and_value(code_addr_constant(_, _), -1, unused).
 base_type_layout__tag_type_and_value(type_ctor_info_constant(_, _, _), -1,
 	unused). 
Index: compiler/bytecode_gen.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/bytecode_gen.m,v
retrieving revision 1.43
diff -u -u -r1.43 bytecode_gen.m
--- bytecode_gen.m	1999/06/01 09:43:34	1.43
+++ bytecode_gen.m	1999/06/02 01:25:19
@@ -156,15 +156,20 @@
 
 bytecode_gen__goal_expr(GoalExpr, GoalInfo, ByteInfo0, ByteInfo, Code) :-
 	(
-		GoalExpr = higher_order_call(PredVar, ArgVars, ArgTypes,
-			ArgModes, Detism, _IsPredOrFunc),
-		bytecode_gen__higher_order_call(PredVar, ArgVars,
-			ArgTypes, ArgModes, Detism, ByteInfo0, Code),
-		ByteInfo = ByteInfo0
-	;
+		GoalExpr = generic_call(GenericCallType, 
+			ArgVars, ArgModes, Detism),
+		( GenericCallType = higher_order(PredVar, _, _) ->
+			bytecode_gen__higher_order_call(PredVar, ArgVars,
+				ArgModes, Detism, ByteInfo0, Code),
+			ByteInfo = ByteInfo0
+		;
 			% XXX
-		GoalExpr = class_method_call(_, _, _, _, _, _),
-		error("sorry: bytecode not implemented yet for typeclasses")
+			functor(GenericCallType, GenericCallFunctor, _),
+			string__append_list([
+				"sorry: bytecode not yet implemented for ",
+				GenericCallFunctor, " calls"], Msg),
+			error(Msg)
+		)
 	;
 		GoalExpr = call(PredId, ProcId, ArgVars, BuiltinState, _, _),
 		( BuiltinState = not_builtin ->
@@ -188,7 +193,7 @@
 		EndofCode = node([endof_negation, label(EndLabel)]),
 		Code = tree(EnterCode, tree(SomeCode, EndofCode))
 	;
-		GoalExpr = some(_, Goal),
+		GoalExpr = some(_, _, Goal),
 		bytecode_gen__goal(Goal, ByteInfo0, ByteInfo1, SomeCode),
 		bytecode_gen__get_next_temp(ByteInfo1, Temp, ByteInfo),
 		EnterCode = node([enter_commit(Temp)]),
@@ -274,13 +279,13 @@
 	% Generate bytecode for a higher order call.
 
 :- pred bytecode_gen__higher_order_call(prog_var::in, list(prog_var)::in,
-	list(type)::in, list(mode)::in, determinism::in,
-	byte_info::in, byte_tree::out) is det.
+	list(mode)::in, determinism::in, byte_info::in, byte_tree::out) is det.
 
-bytecode_gen__higher_order_call(PredVar, ArgVars, ArgTypes, ArgModes, Detism,
+bytecode_gen__higher_order_call(PredVar, ArgVars, ArgModes, Detism,
 		ByteInfo, Code) :-
 	determinism_to_code_model(Detism, CodeModel),
 	bytecode_gen__get_module_info(ByteInfo, ModuleInfo),
+	list__map(bytecode_gen__get_var_type(ByteInfo), ArgVars, ArgTypes),
 	make_arg_infos(ArgTypes, ArgModes, CodeModel, ModuleInfo, ArgInfo),
 	assoc_list__from_corresponding_lists(ArgVars, ArgInfo, ArgVarsInfos),
 
@@ -418,8 +423,8 @@
 :- pred bytecode_gen__unify(unification::in, prog_var::in, unify_rhs::in,
 	byte_info::in, byte_tree::out) is det.
 
-bytecode_gen__unify(construct(Var, ConsId, Args, UniModes), _, _, ByteInfo,
-		Code) :-
+bytecode_gen__unify(construct(Var, ConsId, Args, UniModes, _, _, _),
+		_, _, ByteInfo, Code) :-
 	bytecode_gen__map_var(ByteInfo, Var, ByteVar),
 	bytecode_gen__map_vars(ByteInfo, Args, ByteArgs),
 	bytecode_gen__map_cons_id(ByteInfo, Var, ConsId, ByteConsId),
@@ -610,10 +615,18 @@
 		ConsId = float_const(FloatVal),
 		ByteConsId = float_const(FloatVal)
 	;
-		ConsId = pred_const(PredId, ProcId),
-		predicate_id(ModuleInfo, PredId, ModuleName, PredName, Arity),
-		proc_id_to_int(ProcId, ProcInt),
-		ByteConsId = pred_const(ModuleName, PredName, Arity, ProcInt)
+		ConsId = pred_const(PredId, ProcId, EvalMethod),
+		( EvalMethod = normal ->
+			predicate_id(ModuleInfo, PredId,
+				ModuleName, PredName, Arity),
+			proc_id_to_int(ProcId, ProcInt),
+			ByteConsId = pred_const(ModuleName,
+				PredName, Arity, ProcInt)
+		;
+			% XXX
+			error(
+	"sorry: bytecode not yet implemented for Aditi lambda expressions")
+		)
 	;
 		ConsId = code_addr_const(PredId, ProcId),
 		predicate_id(ModuleInfo, PredId, ModuleName, PredName, Arity),
@@ -647,7 +660,7 @@
 bytecode_gen__map_cons_tag(int_constant(IntVal), enum_tag(IntVal)).
 bytecode_gen__map_cons_tag(float_constant(_), _) :-
 	error("float_constant cons tag for non-float_constant cons id").
-bytecode_gen__map_cons_tag(pred_closure_tag(_, _), _) :-
+bytecode_gen__map_cons_tag(pred_closure_tag(_, _, _), _) :-
 	error("pred_closure_tag cons tag for non-pred_const cons id").
 bytecode_gen__map_cons_tag(code_addr_constant(_, _), _) :-
 	error("code_addr_constant cons tag for non-address_const cons id").
Index: compiler/call_gen.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/call_gen.m,v
retrieving revision 1.131
diff -u -u -r1.131 call_gen.m
--- call_gen.m	1999/06/01 09:43:35	1.131
+++ call_gen.m	1999/06/02 02:00:17
@@ -21,17 +21,11 @@
 :- import_module prog_data, hlds_pred, hlds_data, hlds_goal, llds, code_info.
 :- import_module list, set, assoc_list.
 
-:- pred call_gen__generate_higher_order_call(code_model, prog_var,
-			list(prog_var), list(type), list(mode), determinism,
+:- pred call_gen__generate_generic_call(code_model, generic_call,
+			list(prog_var), list(mode), determinism,
 			hlds_goal_info, code_tree, code_info, code_info).
-:- mode call_gen__generate_higher_order_call(in, in, in, in, in, in, in, out,
-				in, out) is det.
-
-:- pred call_gen__generate_class_method_call(code_model, prog_var, int,
-			list(prog_var), list(type), list(mode), determinism,
-			hlds_goal_info, code_tree, code_info, code_info).
-:- mode call_gen__generate_class_method_call(in, in, in, in, in, in, in, in,
-				out, in, out) is det.
+:- mode call_gen__generate_generic_call(in, in, in, in, in, in,
+			out, in, out) is det.
 
 :- pred call_gen__generate_call(code_model, pred_id, proc_id, list(prog_var),
 			hlds_goal_info, code_tree, code_info, code_info).
@@ -61,11 +55,11 @@
 
 :- implementation.
 
-:- import_module hlds_module, code_util.
+:- import_module hlds_module, code_util, rl.
 :- import_module arg_info, type_util, mode_util, unify_proc, instmap.
 :- import_module trace, globals, options.
 :- import_module std_util, bool, int, tree, map.
-:- import_module varset, require.
+:- import_module varset, require, string.
 
 %---------------------------------------------------------------------------%
 
@@ -115,26 +109,7 @@
 		% Make the call.
 	code_info__get_module_info(ModuleInfo),
 
-	{ module_info_pred_info(ModuleInfo, PredId, PredInfo) },
-	{ pred_info_get_markers(PredInfo, Markers) },
-	( { check_marker(Markers, aditi_interface) } ->
-		% For a call to an Aditi procedure, just pass all the
-		% arguments to do_*_aditi_call, which is defined in
-		% extras/aditi/aditi.m.
-		{
-			CodeModel = model_det,
-			Address = do_det_aditi_call
-		;
-			CodeModel = model_semi,
-			Address = do_semidet_aditi_call
-		;
-			CodeModel = model_non,
-			Address = do_nondet_aditi_call
-		}
-	;
-		code_info__make_entry_label(ModuleInfo,
-			PredId, ModeId, yes, Address)
-	),
+	code_info__make_entry_label(ModuleInfo, PredId, ModeId, yes, Address),
 	code_info__get_next_label(ReturnLabel),
 	{ call_gen__call_comment(CodeModel, CallComment) },
 	{ CallCode = node([
@@ -159,21 +134,17 @@
 %---------------------------------------------------------------------------%
 
 	%
-	% For a higher-order call,
+	% For a generic_call,
 	% we split the arguments into inputs and outputs, put the inputs
 	% in the locations expected by mercury__do_call_closure in
 	% runtime/mercury_ho_call.c, generate the call to that code,
 	% and pick up the outputs from the locations that we know
 	% the runtime system leaves them in.
 	%
-	% Lambda.m transforms the generated lambda predicates to
-	% make sure that all inputs come before all outputs, so that
-	% the code in the runtime system doesn't have trouble figuring out
-	% which registers the arguments go in.
-	%
 
-call_gen__generate_higher_order_call(_OuterCodeModel, PredVar, Args, Types,
+call_gen__generate_generic_call(_OuterCodeModel, GenericCall, Args,
 		Modes, Det, GoalInfo, Code) -->
+	list__map_foldl(code_info__variable_type, Args, Types),
 	{ determinism_to_code_model(Det, CodeModel) },
 	code_info__get_module_info(ModuleInfo),
 	{ make_arg_infos(Types, Modes, CodeModel, ModuleInfo, ArgInfos) },
@@ -184,45 +155,33 @@
 
 	call_gen__prepare_for_call(CodeModel, FlushCode, CallModel),
 
+	{ call_gen__generic_call_info(CodeModel, GenericCall,
+		CodeAddr, FirstInput) },
+
 		% place the immediate input arguments in registers
-		% starting at r4.
-	call_gen__generate_immediate_args(InVars, 4, InLocs, ImmediateCode),
+	call_gen__generate_immediate_args(InVars, FirstInput,
+		InLocs, ImmediateCode),
 	code_info__generate_call_stack_vn_livevals(OutArgs, LiveVals0),
-	{ set__insert_list(LiveVals0,
-		[reg(r, 1), reg(r, 2), reg(r, 3) | InLocs], LiveVals) },
-	(
-		{ CodeModel = model_semi }
-	->
-		{ FirstArg = 2 }
-	;
-		{ FirstArg = 1 }
-	),
+	{ call_gen__extra_livevals(FirstInput, ExtraLiveVals) },
+	{ set__insert_list(LiveVals0, ExtraLiveVals, LiveVals1) },
+	{ set__insert_list(LiveVals1, InLocs, LiveVals) },
 
-	{ call_gen__outvars_to_outargs(OutVars, FirstArg, OutArguments) },
+	{ CodeModel = model_semi ->
+		FirstOutput = 2
+	;
+		FirstOutput = 1
+	},
+	{ call_gen__outvars_to_outargs(OutVars, FirstOutput, OutArguments) },
 	{ call_gen__output_arg_locs(OutArguments, OutputArgLocs) },
+
 	code_info__get_instmap(InstMap),
 	{ goal_info_get_instmap_delta(GoalInfo, InstMapDelta) },
 	{ instmap__apply_instmap_delta(InstMap, InstMapDelta, ReturnInstMap) },
 
-	code_info__produce_variable(PredVar, PredVarCode, PredRVal),
-	(
-		{ PredRVal = lval(reg(r, 1)) }
-	->
-		{ CopyCode = empty }
-	;
-		{ CopyCode = node([
-			assign(reg(r, 1), PredRVal) - "Copy pred-term"
-		]) }
-	),
-
-	{ list__length(InVars, NInVars) },
-	{ list__length(OutVars, NOutVars) },
-	{ ArgNumCode = node([
-		assign(reg(r, 2), const(int_const(NInVars))) -
-			"Assign number of immediate input arguments",
-		assign(reg(r, 3), const(int_const(NOutVars))) -
-			"Assign number of output arguments"
-	]) },
+		% Doing this after generating the immediate input arguments,
+		% results in slightly more efficient code by not moving
+		% the immediate arguments twice.
+	call_gen__generic_call_setup(GenericCall, InVars, OutVars, SetupCode),
 
 	trace__prepare_for_call(TraceCode),
 
@@ -238,9 +197,9 @@
 	{ CallCode = node([
 		livevals(LiveVals)
 			- "",
-		call(do_call_closure, label(ReturnLabel), ReturnLiveLvalues,
+		call(CodeAddr, label(ReturnLabel), ReturnLiveLvalues,
 			CallModel)
-			- "Setup and call higher order pred",
+			- "Setup and call",
 		label(ReturnLabel)
 			- "Continuation label"
 	]) },
@@ -251,113 +210,171 @@
 		tree(SaveCode,
 		tree(FlushCode,
 		tree(ImmediateCode,
-		tree(PredVarCode,
-		tree(CopyCode,
-		tree(ArgNumCode,
+		tree(SetupCode,
 		tree(TraceCode,
 		tree(CallCode,
-		     FailHandlingCode))))))))
+		     FailHandlingCode))))))
 	}.
 
-%---------------------------------------------------------------------------%
-
-	%
-	% For a class method call,
-	% we split the arguments into inputs and outputs, put the inputs
-	% in the locations expected by mercury__do_call_class_method in
-	% runtime/mercury_ho_call.c, generate the call to that code,
-	% and pick up the outputs from the locations that we know
-	% the runtime system leaves them in.
-	%
-
-call_gen__generate_class_method_call(_OuterCodeModel, TCVar, MethodNum, Args,
-		Types, Modes, Det, GoalInfo, Code) -->
-	{ determinism_to_code_model(Det, CodeModel) },
-	code_info__get_module_info(ModuleInfo),
-
-	{ make_arg_infos(Types, Modes, CodeModel, ModuleInfo, ArgInfo) },
-	{ assoc_list__from_corresponding_lists(Args, ArgInfo, ArgsAndArgInfo) },
-	{ call_gen__partition_args(ArgsAndArgInfo, InVars, OutVars) },
-	{ set__list_to_set(OutVars, OutArgs) },
-	call_gen__save_variables(OutArgs, SaveCode),
-	call_gen__prepare_for_call(CodeModel, FlushCode, CallModel),
-
-		% place the immediate input arguments in registers
-		% starting at r5.
-	call_gen__generate_immediate_args(InVars, 5, InLocs, ImmediateCode),
-	code_info__generate_call_stack_vn_livevals(OutArgs, LiveVals0),
-	{ set__insert_list(LiveVals0,
-		[reg(r, 1), reg(r, 2), reg(r, 3), reg(r, 4) | InLocs], 
-			LiveVals) },
-	(
-		{ CodeModel = model_semi }
-	->
-		{ FirstArg = 2 }
+	% The registers before the first input argument are all live.
+:- pred call_gen__extra_livevals(int, list(lval)).
+:- mode call_gen__extra_livevals(in, out) is det.
+
+call_gen__extra_livevals(FirstInput, ExtraLiveVals) :-
+	call_gen__extra_livevals(1, FirstInput, ExtraLiveVals). 
+
+:- pred call_gen__extra_livevals(int, int, list(lval)).
+:- mode call_gen__extra_livevals(in, in, out) is det.
+
+call_gen__extra_livevals(Reg, FirstInput, ExtraLiveVals) :-
+	( Reg < FirstInput ->
+		ExtraLiveVals = [reg(r, Reg) | ExtraLiveVals1],
+		NextReg is Reg + 1,
+		call_gen__extra_livevals(NextReg, FirstInput, ExtraLiveVals1)
 	;
-		{ FirstArg = 1 }
-	),
-	{ call_gen__outvars_to_outargs(OutVars, FirstArg, OutArguments) },
-	{ call_gen__output_arg_locs(OutArguments, OutputArgLocs) },
-	code_info__get_instmap(InstMap),
-	{ goal_info_get_instmap_delta(GoalInfo, InstMapDelta) },
-	{ instmap__apply_instmap_delta(InstMap, InstMapDelta, ReturnInstMap) },
+		ExtraLiveVals = []
+	).
 
-	code_info__produce_variable(TCVar, TCVarCode, TCVarRVal),
-	(
-		{ TCVarRVal = lval(reg(r, 1)) }
-	->
-		{ CopyCode = empty }
-	;
-		{ CopyCode = node([
-			assign(reg(r, 1), TCVarRVal)
-				- "Copy typeclass info"
-		]) }
+	% call_gen__generic_call_info(CodeModel, GenericCall,
+	% 	CodeAddr, FirstImmediateInputReg).
+:- pred call_gen__generic_call_info(code_model, generic_call, code_addr, int).
+:- mode call_gen__generic_call_info(in, in, out, out) is det.
+
+call_gen__generic_call_info(_, higher_order(_, _, _), do_call_closure, 4).
+call_gen__generic_call_info(_, class_method(_, _, _, _),
+		do_call_class_method, 5).
+call_gen__generic_call_info(CodeModel, aditi_builtin(aditi_call(_,_,_,_),_),
+		CodeAddr, 5) :-
+	( CodeModel = model_det, CodeAddr = do_det_aditi_call
+	; CodeModel = model_semi, CodeAddr = do_semidet_aditi_call
+	; CodeModel = model_non, CodeAddr = do_nondet_aditi_call
+	).
+call_gen__generic_call_info(CodeModel, aditi_builtin(aditi_insert(_), _),
+		do_aditi_insert, 3) :-
+	require(unify(CodeModel, model_det), "aditi_insert not model_det").
+call_gen__generic_call_info(CodeModel, aditi_builtin(aditi_delete(_,_), _),
+		do_aditi_delete, 2) :-
+	require(unify(CodeModel, model_det), "aditi_delete not model_det").
+call_gen__generic_call_info(CodeModel,
+		aditi_builtin(aditi_bulk_operation(BulkOp, _), _),
+		CodeAddr, 2) :-
+	( BulkOp = insert, CodeAddr = do_aditi_bulk_insert
+	; BulkOp = delete, CodeAddr = do_aditi_bulk_delete
 	),
+	require(unify(CodeModel, model_det),
+		"aditi_bulk_operation not model_det").
+call_gen__generic_call_info(CodeModel, aditi_builtin(aditi_modify(_,_), _),
+		do_aditi_modify, 2) :-
+	require(unify(CodeModel, model_det), "aditi_modify not model_det").
+
+	% Produce code to set up the arguments to a generic call
+	% that are always present, such as the closure for a higher-order call,
+	% the typeclass_info for a class method call or the relation
+	% name for an Aditi update operation.
+:- pred call_gen__generic_call_setup(generic_call, list(prog_var),
+	list(prog_var), code_tree, code_info, code_info).
+:- mode call_gen__generic_call_setup(in, in, in, out, in, out) is det.
+
+call_gen__generic_call_setup(higher_order(PredVar, _, _),
+		InVars, OutVars, SetupCode) -->
+	call_gen__place_generic_call_var(PredVar, "closure", PredVarCode),
 	{ list__length(InVars, NInVars) },
 	{ list__length(OutVars, NOutVars) },
-	{ SetupCode = node([
-		assign(reg(r, 2), const(int_const(MethodNum))) -
+	{ NumArgCode = node([
+		assign(reg(r, 2), const(int_const(NInVars))) -
+			"Assign number of immediate input arguments",
+		assign(reg(r, 3), const(int_const(NOutVars))) -
+			"Assign number of output arguments"
+	]) },
+	{ SetupCode = tree(PredVarCode, NumArgCode) }.
+call_gen__generic_call_setup(class_method(TCVar, Method, _, _),
+		InVars, OutVars, SetupCode) -->
+	call_gen__place_generic_call_var(TCVar, "typeclass_info", TCVarCode),
+	{ list__length(InVars, NInVars) },
+	{ list__length(OutVars, NOutVars) },
+	{ ArgsCode = node([
+		assign(reg(r, 2), const(int_const(Method))) -
 			"Index of class method in typeclass info",
 		assign(reg(r, 3), const(int_const(NInVars))) -
 			"Assign number of immediate input arguments",
 		assign(reg(r, 4), const(int_const(NOutVars))) -
 			"Assign number of output arguments"
 	]) },
+	{ SetupCode = tree(TCVarCode, ArgsCode) }.
+call_gen__generic_call_setup(aditi_builtin(Builtin, _),
+		InVars, OutVars, SetupCode) -->
+	call_gen__aditi_builtin_setup(Builtin, InVars, OutVars,
+		SetupCode).
+
+:- pred call_gen__place_generic_call_var(prog_var, string, code_tree,
+		code_info, code_info).
+:- mode call_gen__place_generic_call_var(in, in, out, in, out) is det.
+
+call_gen__place_generic_call_var(Var, Description, Code) -->
+	code_info__produce_variable(Var, VarCode, VarRVal),
+	{ VarRVal = lval(reg(r, 1)) ->
+               CopyCode = empty
+	;
+	       % We don't need to clear r1 first - the arguments
+	       % should have been moved into their proper positions and
+	       % all other variables should have been saved by now.
+	       string__append("Copy ", Description, Comment),
+               CopyCode = node([
+                       assign(reg(r, 1), VarRVal) - Comment
+               ])
+	},
+	{ Code = tree(VarCode, CopyCode) }.
+
+:- pred call_gen__aditi_builtin_setup(aditi_builtin,
+	list(prog_var), list(prog_var), code_tree, code_info, code_info).
+:- mode call_gen__aditi_builtin_setup(in, in, in, out, in, out) is det.
+
+call_gen__aditi_builtin_setup(
+		aditi_call(PredProcId, NumInputs, InputTypes, NumOutputs),
+		_, _, SetupCode) -->
+	code_info__get_module_info(ModuleInfo),
+	{ rl__get_entry_proc_name(ModuleInfo, PredProcId, ProcName) },
+	{ rl__proc_name_to_string(ProcName, ProcStr) },
+	{ rl__schema_to_string(ModuleInfo, InputTypes, InputSchema) },
+	{ SetupCode = node([
+		assign(reg(r, 1), const(string_const(ProcStr))) -
+			"Assign name of procedure to call",
+		assign(reg(r, 2), const(int_const(NumInputs))) -
+			"Assign number of input arguments",
+		assign(reg(r, 3), const(string_const(InputSchema))) -
+			"Assign schema of input arguments",
+		assign(reg(r, 4), const(int_const(NumOutputs))) -
+			"Assign number of output arguments"
+	]) }.
+call_gen__aditi_builtin_setup(aditi_insert(PredId), Inputs, _, SetupCode) -->
+	call_gen__setup_base_relation_name(PredId, NameCode),
+	{ list__length(Inputs, NumInputs) },
+	{ SetupCode =
+		tree(NameCode,
+		node([
+			assign(reg(r, 2), const(int_const(NumInputs))) -
+				"Assign arity of relation to insert into"
+		])
+	) }.
+call_gen__aditi_builtin_setup(aditi_delete(PredId, _), _, _, SetupCode) -->
+	call_gen__setup_base_relation_name(PredId, SetupCode).
+call_gen__aditi_builtin_setup(aditi_bulk_operation(_, PredId), _, _,
+		SetupCode) -->
+	call_gen__setup_base_relation_name(PredId, SetupCode).
+call_gen__aditi_builtin_setup(aditi_modify(PredId, _), _, _, SetupCode) -->
+	call_gen__setup_base_relation_name(PredId, SetupCode).
+
+:- pred call_gen__setup_base_relation_name(pred_id,
+		code_tree, code_info, code_info).
+:- mode call_gen__setup_base_relation_name(in, out, in, out) is det.
 
-	trace__prepare_for_call(TraceCode),
-
-		% We must update the code generator state to reflect
-		% the situation after the call before building
-		% the return liveness info. No later code in this
-		% predicate depends on the old state.
-	call_gen__rebuild_registers(OutArguments),
-	code_info__generate_return_live_lvalues(OutputArgLocs, ReturnInstMap,
-		ReturnLiveLvalues),
-
-	code_info__get_next_label(ReturnLabel),
-	{ CallCode = node([
-		livevals(LiveVals)
-			- "",
-		call(do_call_class_method, label(ReturnLabel),
-			ReturnLiveLvalues, CallModel)
-			- "Setup and call class method",
-		label(ReturnLabel)
-			- "Continuation label"
-	]) },
-
-	call_gen__handle_failure(CodeModel, FailHandlingCode),
-
-	{ Code =
-		tree(SaveCode,
-		tree(FlushCode,
-		tree(ImmediateCode,
-		tree(TCVarCode,
-		tree(CopyCode,
-		tree(SetupCode,
-		tree(TraceCode,
-		tree(CallCode,
-		     FailHandlingCode))))))))
-	}.
+call_gen__setup_base_relation_name(PredId, SetupCode) -->
+	code_info__get_module_info(ModuleInfo),
+	{ rl__permanent_relation_name(ModuleInfo, PredId, ProcStr) },
+	{ SetupCode = node([
+		assign(reg(r, 1), const(string_const(ProcStr))) -
+			"Assign name of base relation"
+	]) }.
 
 %---------------------------------------------------------------------------%
 
Index: compiler/code_aux.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/code_aux.m,v
retrieving revision 1.55
diff -u -u -r1.55 code_aux.m
--- code_aux.m	1998/11/20 04:07:05	1.55
+++ code_aux.m	1999/05/14 04:37:01
@@ -70,7 +70,7 @@
 	code_aux__contains_only_builtins_cases(Cases).
 code_aux__contains_only_builtins_2(not(Goal)) :-
 	code_aux__contains_only_builtins(Goal).
-code_aux__contains_only_builtins_2(some(_Vars, Goal)) :-
+code_aux__contains_only_builtins_2(some(_Vars, _, Goal)) :-
 	code_aux__contains_only_builtins(Goal).
 code_aux__contains_only_builtins_2(if_then_else(_Vars, Cond, Then, Else, _)) :-
 	code_aux__contains_only_builtins(Cond),
@@ -84,7 +84,7 @@
 	;
 		Uni = simple_test(_, _)
 	;
-		Uni = construct(_, _, _, _)
+		Uni = construct(_, _, _, _, _, _, _)
 	;
 		Uni = deconstruct(_, _, _, _, _)
 	).
@@ -133,7 +133,7 @@
 	).
 code_aux__goal_cannot_loop_2(ModuleInfo, not(Goal)) :-
 	code_aux__goal_cannot_loop(ModuleInfo, Goal).
-code_aux__goal_cannot_loop_2(ModuleInfo, some(_Vars, Goal)) :-
+code_aux__goal_cannot_loop_2(ModuleInfo, some(_Vars, _, Goal)) :-
 	code_aux__goal_cannot_loop(ModuleInfo, Goal).
 code_aux__goal_cannot_loop_2(ModuleInfo,
 		if_then_else(_Vars, Cond, Then, Else, _)) :-
@@ -150,7 +150,7 @@
 	;
 		Uni = simple_test(_, _)
 	;
-		Uni = construct(_, _, _, _)
+		Uni = construct(_, _, _, _, _, _, _)
 	;
 		Uni = deconstruct(_, _, _, _, _)
 	).
@@ -169,9 +169,9 @@
 	code_aux__goal_is_flat_list(Goals).
 code_aux__goal_is_flat_2(not(Goal)) :-
 	code_aux__goal_is_flat(Goal).
-code_aux__goal_is_flat_2(some(_Vars, Goal)) :-
+code_aux__goal_is_flat_2(some(_Vars, _, Goal)) :-
 	code_aux__goal_is_flat(Goal).
-code_aux__goal_is_flat_2(higher_order_call(_, _, _, _, _, _)).
+code_aux__goal_is_flat_2(generic_call(_, _, _, _)).
 code_aux__goal_is_flat_2(call(_, _, _, _, _, _)).
 code_aux__goal_is_flat_2(unify(_, _, _, _, _)).
 code_aux__goal_is_flat_2(pragma_c_code(_, _, _, _, _, _, _)).
Index: compiler/code_gen.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/code_gen.m,v
retrieving revision 1.64
diff -u -u -r1.64 code_gen.m
--- code_gen.m	1999/04/30 08:23:42	1.64
+++ code_gen.m	1999/05/14 04:34:08
@@ -807,16 +807,13 @@
 		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) -->
+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(generic_call(GenericCall, Args, Modes, Det),
+		GoalInfo, CodeModel, Code) -->
+	call_gen__generate_generic_call(CodeModel, GenericCall, Args,
+		Modes, Det, GoalInfo, Code).
+		
 code_gen__generate_goal_2(call(PredId, ProcId, Args, BuiltinState, _, _),
 		GoalInfo, CodeModel, Code) -->
 	(
Index: compiler/code_util.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/code_util.m,v
retrieving revision 1.108
diff -u -u -r1.108 code_util.m
--- code_util.m	1999/04/30 06:19:16	1.108
+++ code_util.m	1999/05/14 04:36:49
@@ -592,12 +592,13 @@
 :- pred code_util__goal_may_allocate_heap_2(hlds_goal_expr).
 :- mode code_util__goal_may_allocate_heap_2(in) is semidet.
 
-code_util__goal_may_allocate_heap_2(higher_order_call(_, _, _, _, _, _)).
+code_util__goal_may_allocate_heap_2(generic_call(_, _, _, _)).
 code_util__goal_may_allocate_heap_2(call(_, _, _, Builtin, _, _)) :-
 	Builtin \= inline_builtin.
-code_util__goal_may_allocate_heap_2(unify(_, _, _, construct(_,_,Args,_), _)) :-
+code_util__goal_may_allocate_heap_2(
+		unify(_, _, _, construct(_,_,Args,_,_,_,_), _)) :-
 	Args = [_|_].
-code_util__goal_may_allocate_heap_2(some(_Vars, Goal)) :-
+code_util__goal_may_allocate_heap_2(some(_Vars, _, Goal)) :-
 	code_util__goal_may_allocate_heap(Goal).
 code_util__goal_may_allocate_heap_2(not(Goal)) :-
 	code_util__goal_may_allocate_heap(Goal).
@@ -693,7 +694,7 @@
 code_util__cons_id_to_tag(float_const(X), _, _, float_constant(X)).
 code_util__cons_id_to_tag(string_const(X), _, _, string_constant(X)).
 code_util__cons_id_to_tag(code_addr_const(P,M), _, _, code_addr_constant(P,M)).
-code_util__cons_id_to_tag(pred_const(P,M), _, _, pred_closure_tag(P,M)).
+code_util__cons_id_to_tag(pred_const(P,M,E), _, _, pred_closure_tag(P,M,E)).
 code_util__cons_id_to_tag(type_ctor_info_const(M,T,A), _, _,
 		type_ctor_info_constant(M,T,A)).
 code_util__cons_id_to_tag(base_typeclass_info_const(M,C,_,N), _, _,
@@ -798,7 +799,7 @@
 			GoalExpr = call(_, _, _, BuiltinState, _, _),
 			BuiltinState \= inline_builtin
 		;
-			GoalExpr = higher_order_call(_, _, _, _, _, _)
+			GoalExpr = generic_call(_, _, _, _)
 		)
 	->
 		true
@@ -822,12 +823,11 @@
 
 code_util__count_recursive_calls_2(not(Goal), PredId, ProcId, Min, Max) :-
 	code_util__count_recursive_calls(Goal, PredId, ProcId, Min, Max).
-code_util__count_recursive_calls_2(some(_, Goal), PredId, ProcId, Min, Max) :-
+code_util__count_recursive_calls_2(some(_, _, Goal),
+		PredId, ProcId, Min, Max) :-
 	code_util__count_recursive_calls(Goal, PredId, ProcId, Min, Max).
 code_util__count_recursive_calls_2(unify(_, _, _, _, _), _, _, 0, 0).
-code_util__count_recursive_calls_2(higher_order_call(_, _,_, _, _, _), _, _,
-		0, 0).
-code_util__count_recursive_calls_2(class_method_call(_, _,_, _, _, _), _, _, 
+code_util__count_recursive_calls_2(generic_call(_, _, _, _), _, _,
 		0, 0).
 code_util__count_recursive_calls_2(pragma_c_code(_,_,_, _, _, _, _), _, _,
 		0, 0).
Index: compiler/common.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/common.m,v
retrieving revision 1.52
diff -u -u -r1.52 common.m
--- common.m	1998/11/20 04:07:13	1.52
+++ common.m	1998/12/11 03:58:50
@@ -123,7 +123,7 @@
 common__optimise_unification(Unification0, _Left0, _Right0, Mode, _Context,
 		Goal0, GoalInfo0, Goal, GoalInfo, Info0, Info) :-
 	(
-		Unification0 = construct(Var, ConsId, ArgVars, _),
+		Unification0 = construct(Var, ConsId, ArgVars, _, _, _, _),
 		(
 			% common__generate_assign assumes that the
 			% output variable is in the instmap_delta, which
Index: compiler/continuation_info.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/continuation_info.m,v
retrieving revision 1.21
diff -u -u -r1.21 continuation_info.m
--- continuation_info.m	1999/05/28 05:26:12	1.21
+++ continuation_info.m	1999/05/29 02:10:41
@@ -411,7 +411,7 @@
 	pred_info_arg_types(PredInfo, ArgTypes),
 	some([Type], (
 		list__member(Type, ArgTypes),
-		type_is_higher_order(Type, _, _)
+		type_is_higher_order(Type, _, _, _)
 	)).
 
 %-----------------------------------------------------------------------------%
Index: compiler/cse_detection.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/cse_detection.m,v
retrieving revision 1.56
diff -u -u -r1.56 cse_detection.m
--- cse_detection.m	1998/11/20 04:07:17	1.56
+++ cse_detection.m	1999/05/27 06:06:33
@@ -206,11 +206,8 @@
 detect_cse_in_goal_2(pragma_c_code(A,B,C,D,E,F,G), _, _, CseInfo, CseInfo,
 	no, pragma_c_code(A,B,C,D,E,F,G)).
 
-detect_cse_in_goal_2(higher_order_call(A,B,C,D,E,F), _, _, CseInfo, CseInfo,
-	no, higher_order_call(A,B,C,D,E,F)).
-
-detect_cse_in_goal_2(class_method_call(A,B,C,D,E,F), _, _, CseInfo, CseInfo, 
-	no, class_method_call(A,B,C,D,E,F)).
+detect_cse_in_goal_2(generic_call(A,B,C,D), _, _, CseInfo, CseInfo,
+	no, generic_call(A,B,C,D)).
 
 detect_cse_in_goal_2(call(A,B,C,D,E,F), _, _, CseInfo, CseInfo, no,
 	call(A,B,C,D,E,F)).
@@ -218,16 +215,16 @@
 detect_cse_in_goal_2(unify(A,B0,C,D,E), _, InstMap0, CseInfo0, CseInfo, Redo,
 		unify(A,B,C,D,E)) :-
 	( 
-		B0 = lambda_goal(PredOrFunc, NonLocalVars,
-			Vars, Modes, Det, Goal0)
+		B0 = lambda_goal(PredOrFunc, EvalMethod, FixModes,
+			NonLocalVars, Vars, Modes, Det, Goal0)
 	->
 		CseInfo0 = cse_info(_, _, ModuleInfo),
 		instmap__pre_lambda_update(ModuleInfo, 
 			Vars, Modes, InstMap0, InstMap),
 		detect_cse_in_goal(Goal0, InstMap, CseInfo0, CseInfo, Redo,
 			Goal),
-		B = lambda_goal(PredOrFunc, NonLocalVars, 
-			Vars, Modes, Det, Goal)
+		B = lambda_goal(PredOrFunc, EvalMethod, FixModes,
+			NonLocalVars, Vars, Modes, Det, Goal)
 	;
 		B = B0,
 		CseInfo = CseInfo0,
@@ -238,8 +235,8 @@
 		Redo, not(Goal)) :-
 	detect_cse_in_goal(Goal0, InstMap, CseInfo0, CseInfo, Redo, Goal).
 
-detect_cse_in_goal_2(some(Vars, Goal0), _GoalInfo, InstMap, CseInfo0, CseInfo,
-		Redo, some(Vars, Goal)) :-
+detect_cse_in_goal_2(some(Vars, CanRemove, Goal0), _GoalInfo, InstMap,
+		CseInfo0, CseInfo, Redo, some(Vars, CanRemove, Goal)) :-
 	detect_cse_in_goal(Goal0, InstMap, CseInfo0, CseInfo, Redo, Goal).
 
 detect_cse_in_goal_2(conj(Goals0), _GoalInfo, InstMap, CseInfo0, CseInfo,
Index: compiler/dead_proc_elim.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/dead_proc_elim.m,v
retrieving revision 1.46
diff -u -u -r1.46 dead_proc_elim.m
--- dead_proc_elim.m	1999/04/23 01:02:36	1.46
+++ dead_proc_elim.m	1999/05/27 06:07:07
@@ -419,7 +419,7 @@
 		Needed0, Needed) :-
 	dead_proc_elim__examine_goal(Goal, CurrProc, Queue0, Queue,
 		Needed0, Needed).
-dead_proc_elim__examine_expr(some(_, Goal), CurrProc, Queue0, Queue,
+dead_proc_elim__examine_expr(some(_, _, Goal), CurrProc, Queue0, Queue,
 		Needed0, Needed) :-
 	dead_proc_elim__examine_goal(Goal, CurrProc, Queue0, Queue,
 		Needed0, Needed).
@@ -435,9 +435,7 @@
 		Needed1, Needed2),
 	dead_proc_elim__examine_goal(Else, CurrProc, Queue2, Queue,
 		Needed2, Needed).
-dead_proc_elim__examine_expr(higher_order_call(_,_,_,_,_,_), _,
-		Queue, Queue, Needed, Needed).
-dead_proc_elim__examine_expr(class_method_call(_,_,_,_,_,_), _,
+dead_proc_elim__examine_expr(generic_call(_,_,_,_), _,
 		Queue, Queue, Needed, Needed).
 dead_proc_elim__examine_expr(call(PredId, ProcId, _,_,_,_),
 		CurrProc, Queue0, Queue, Needed0, Needed) :-
@@ -469,9 +467,9 @@
 dead_proc_elim__examine_expr(unify(_,_,_, Uni, _), _CurrProc, Queue0, Queue,
 		Needed0, Needed) :-
 	(
-		Uni = construct(_, ConsId, _, _),
+		Uni = construct(_, ConsId, _, _, _, _, _),
 		(
-			ConsId = pred_const(PredId, ProcId),
+			ConsId = pred_const(PredId, ProcId, _),
 			Entity = proc(PredId, ProcId)
 		;
 			ConsId = code_addr_const(PredId, ProcId),
@@ -820,11 +818,10 @@
 		pre_modecheck_examine_goal(Goal, Info0, Info)
 	)) },
 	list__foldl(ExamineCase, Cases).
-pre_modecheck_examine_goal(higher_order_call(_,_,_,_,_,_) - _) --> [].
-pre_modecheck_examine_goal(class_method_call(_,_,_,_,_,_) - _) --> [].
+pre_modecheck_examine_goal(generic_call(_,_,_,_) - _) --> [].
 pre_modecheck_examine_goal(not(Goal) - _) -->
 	pre_modecheck_examine_goal(Goal).
-pre_modecheck_examine_goal(some(_, Goal) - _) -->
+pre_modecheck_examine_goal(some(_, _, Goal) - _) -->
 	pre_modecheck_examine_goal(Goal).
 pre_modecheck_examine_goal(call(_, _, _, _, _, PredName) - _) -->
 	dead_pred_info_add_pred_name(PredName).
@@ -842,7 +839,7 @@
 	;
 		[]
 	).
-pre_modecheck_examine_unify_rhs(lambda_goal(_, _, _, _, _, Goal)) -->
+pre_modecheck_examine_unify_rhs(lambda_goal(_, _, _, _, _, _, _, Goal)) -->
 	pre_modecheck_examine_goal(Goal).
 
 :- pred dead_pred_info_add_pred_name(sym_name::in, dead_pred_info::in, 
Index: compiler/deforest.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/deforest.m,v
retrieving revision 1.9
diff -u -u -r1.9 deforest.m
--- deforest.m	1998/11/20 04:07:18	1.9
+++ deforest.m	1999/05/14 04:40:02
@@ -202,15 +202,13 @@
 	{ Goal = pragma_c_code(_, _, _, _, _, _, _) - _ }.
 
 deforest__goal(Goal, Goal) -->
-	{ Goal = higher_order_call(_, _, _, _, _, _) - _ }.
-
-deforest__goal(Goal, Goal) -->
-	{ Goal = class_method_call(_, _, _, _, _, _) - _ }.
+	{ Goal = generic_call(_, _, _, _) - _ }.
 
 deforest__goal(not(Goal0) - Info, not(Goal) - Info) -->
 	deforest__goal(Goal0, Goal).
 
-deforest__goal(some(Vs, Goal0) - Info, some(Vs, Goal) - Info) -->
+deforest__goal(some(Vs, CanRemove, Goal0) - Info,
+		some(Vs, CanRemove, Goal) - Info) -->
 	deforest__goal(Goal0, Goal).
 
 deforest__goal(Goal0, Goal) -->
Index: compiler/dependency_graph.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/dependency_graph.m,v
retrieving revision 1.40
diff -u -u -r1.40 dependency_graph.m
--- dependency_graph.m	1999/03/22 08:07:07	1.40
+++ dependency_graph.m	1999/05/14 05:21:54
@@ -229,14 +229,11 @@
 dependency_graph__add_arcs_in_goal_2(not(Goal), Caller, DepGraph0, DepGraph) :-
 	dependency_graph__add_arcs_in_goal(Goal, Caller, DepGraph0, DepGraph).
 
-dependency_graph__add_arcs_in_goal_2(some(_Vars, Goal), Caller, 
+dependency_graph__add_arcs_in_goal_2(some(_Vars, _, Goal), Caller, 
 					DepGraph0, DepGraph) :-
 	dependency_graph__add_arcs_in_goal(Goal, Caller, DepGraph0, DepGraph).
 
-dependency_graph__add_arcs_in_goal_2(higher_order_call(_, _, _, _, _, _),
-		_Caller, DepGraph, DepGraph).
-
-dependency_graph__add_arcs_in_goal_2(class_method_call(_, _, _, _, _, _),
+dependency_graph__add_arcs_in_goal_2(generic_call(_, _, _, _),
 		_Caller, DepGraph, DepGraph).
 
 dependency_graph__add_arcs_in_goal_2(call(PredId, ProcId, _, Builtin, _, _),
@@ -265,7 +262,7 @@
 	    DepGraph0 = DepGraph
 	; Unify = simple_test(_, _),
 	    DepGraph0 = DepGraph
-	; Unify = construct(_, Cons, _, _),
+	; Unify = construct(_, Cons, _, _, _, _, _),
 	    dependency_graph__add_arcs_in_cons(Cons, Caller,
 				DepGraph0, DepGraph)
 	; Unify = deconstruct(_, Cons, _, _, _),
@@ -316,7 +313,7 @@
 				DepGraph, DepGraph).
 dependency_graph__add_arcs_in_cons(float_const(_), _Caller,
 				DepGraph, DepGraph).
-dependency_graph__add_arcs_in_cons(pred_const(Pred, Proc), Caller,
+dependency_graph__add_arcs_in_cons(pred_const(Pred, Proc, _), Caller,
 				DepGraph0, DepGraph) :-
 	(
 			% If the node isn't in the relation, then
@@ -669,7 +666,7 @@
 	process_aditi_goal(yes, Cond, Map0, Map1),
 	process_aditi_goal(IsNeg, Then, Map1, Map2),
 	process_aditi_goal(IsNeg, Else, Map2, Map).
-process_aditi_goal(IsNeg, some(_, Goal) - _, Map0, Map) -->
+process_aditi_goal(IsNeg, some(_, _, Goal) - _, Map0, Map) -->
 	process_aditi_goal(IsNeg, Goal, Map0, Map).
 process_aditi_goal(_IsNeg, not(Goal) - _, Map0, Map) -->
 	process_aditi_goal(yes, Goal, Map0, Map).
@@ -679,15 +676,16 @@
 
 process_aditi_goal(_IsNeg, unify(Var, _, _, Unify, _) - _, 
 		Map0, Map) -->
-	( { Unify = construct(_, pred_const(PredId, ProcId), _, _) } ->
+	(
+		{ Unify = construct(_, pred_const(PredId, ProcId, _),
+			_, _, _, _, _) }
+	->
 		aditi_scc_info_add_closure(Var, 
 			proc(PredId, ProcId), Map0, Map)
 	;
 		{ Map = Map0 }
 	).
-process_aditi_goal(_IsNeg, higher_order_call(_, _, _, _, _, _) - _, 
-		Map, Map) --> [].
-process_aditi_goal(_IsNeg, class_method_call(_, _, _, _, _, _) - _, 
+process_aditi_goal(_IsNeg, generic_call(_, _, _, _) - _, 
 		Map, Map) --> [].
 process_aditi_goal(_IsNeg, pragma_c_code(_, _, _, _, _, _, _) - _,
 		Map, Map) --> [].
Index: compiler/det_analysis.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/det_analysis.m,v
retrieving revision 1.138
diff -u -u -r1.138 det_analysis.m
--- det_analysis.m	1998/11/20 04:07:23	1.138
+++ det_analysis.m	1999/05/27 06:07:33
@@ -366,13 +366,13 @@
 		Goal1 \= disj(_, _),	
 
 		% do we already have a commit?
-		Goal1 \= some(_, _)
+		Goal1 \= some(_, _, _)
 	->
 		% a commit needed - we must introduce an explicit `some'
 		% so that the code generator knows to insert the appropriate
 		% code for pruning
 		goal_info_set_determinism(GoalInfo0, InternalDetism, InnerInfo),
-		Goal = some([], Goal1 - InnerInfo),
+		Goal = some([], can_remove, Goal1 - InnerInfo),
 		Msgs = Msgs1
 	;
 		% either no commit needed, or a `some' already present
@@ -488,42 +488,20 @@
 		Detism = Detism0
 	).
 
-det_infer_goal_2(higher_order_call(PredVar, ArgVars, Types, Modes, Det0,
-			IsPredOrFunc),
+det_infer_goal_2(generic_call(GenericCall, ArgVars, Modes, Det0),
 		GoalInfo, _InstMap0, SolnContext,
 		_MiscInfo, _NonLocalVars, _DeltaInstMap,
-		higher_order_call(PredVar, ArgVars, Types, Modes, Det0,
-			IsPredOrFunc),
+		generic_call(GenericCall, ArgVars, Modes, Det0),
 		Det, Msgs) :-
 	determinism_components(Det0, CanFail, NumSolns),
 	(
 		NumSolns = at_most_many_cc,
 		SolnContext \= first_soln
 	->
-		Msgs = [higher_order_cc_pred_in_wrong_context(GoalInfo, Det0)],
-		% Code elsewhere relies on the assumption that
-		% SolnContext \= first_soln => NumSolns \= at_most_many_cc,
-		% so we need to enforce that here.
-		determinism_components(Det, CanFail, at_most_many)
-	;
-		Msgs = [],
-		Det = Det0
-	).
-
-det_infer_goal_2(class_method_call(TCVar, Num, ArgVars, Types, Modes, Det0),
-		GoalInfo, _InstMap0, SolnContext,
-		_MiscInfo, _NonLocalVars, _DeltaInstMap,
-		class_method_call(TCVar, Num, ArgVars, Types, Modes, Det0),
-		Det, Msgs) :-
-	determinism_components(Det0, CanFail, NumSolns),
-	(
-		NumSolns = at_most_many_cc,
-		SolnContext \= first_soln
-	->
-			% If called, this would give a slightly misleading
-			% error message. class_method_calls are introduced
-			% after det_analysis, though, so it doesn't really
-			% matter.
+		% This error can only occur for higher-order calls.
+		% class_method calls are only introduced by polymorphism,
+		% and the aditi_builtins are all det (for the updates)
+		% or introduced later (for calls).
 		Msgs = [higher_order_cc_pred_in_wrong_context(GoalInfo, Det0)],
 		% Code elsewhere relies on the assumption that
 		% SolnContext \= first_soln => NumSolns \= at_most_many_cc,
@@ -539,8 +517,8 @@
 det_infer_goal_2(unify(LT, RT0, M, U, C), GoalInfo, InstMap0, SolnContext,
 		DetInfo, _, _, unify(LT, RT, M, U, C), UnifyDet, Msgs) :-
 	(
-		RT0 = lambda_goal(PredOrFunc, NonLocalVars, Vars,
-			Modes, LambdaDeclaredDet, Goal0)
+		RT0 = lambda_goal(PredOrFunc, EvalMethod, FixModes,
+			NonLocalVars, Vars, Modes, LambdaDeclaredDet, Goal0)
 	->
 		(
 			determinism_components(LambdaDeclaredDet, _,
@@ -558,8 +536,8 @@
 		det_check_lambda(LambdaDeclaredDet, LambdaInferredDet,
 				Goal, GoalInfo, DetInfo, Msgs2),
 		list__append(Msgs1, Msgs2, Msgs3),
-		RT = lambda_goal(PredOrFunc, NonLocalVars, Vars,
-			Modes, LambdaDeclaredDet, Goal)
+		RT = lambda_goal(PredOrFunc, EvalMethod, FixModes,
+			NonLocalVars, Vars, Modes, LambdaDeclaredDet, Goal)
 	;
 		RT = RT0,
 		Msgs3 = []
@@ -656,8 +634,8 @@
 	% but we cannot rely on explicit quantification to detect this.
 	% Therefore cuts are handled in det_infer_goal.
 
-det_infer_goal_2(some(Vars, Goal0), _, InstMap0, SolnContext, DetInfo, _, _,
-		some(Vars, Goal), Det, Msgs) :-
+det_infer_goal_2(some(Vars, CanRemove, Goal0), _, InstMap0, SolnContext,
+		DetInfo, _, _, some(Vars, CanRemove, Goal), Det, Msgs) :-
 	det_infer_goal(Goal0, InstMap0, SolnContext, DetInfo,
 		Goal, Det, Msgs).
 
@@ -922,7 +900,7 @@
 % the concrete representation of the abstract values involved.
 :- pred det_infer_unify_examines_rep(unification::in, bool::out) is det.
 det_infer_unify_examines_rep(assign(_, _), no).
-det_infer_unify_examines_rep(construct(_, _, _, _), no).
+det_infer_unify_examines_rep(construct(_, _, _, _, _, _, _), no).
 det_infer_unify_examines_rep(deconstruct(_, _, _, _, _), yes).
 det_infer_unify_examines_rep(simple_test(_, _), yes).
 det_infer_unify_examines_rep(complicated_unify(_, _), no).
@@ -947,7 +925,7 @@
 
 det_infer_unify_canfail(deconstruct(_, _, _, _, CanFail), CanFail).
 det_infer_unify_canfail(assign(_, _), cannot_fail).
-det_infer_unify_canfail(construct(_, _, _, _), cannot_fail).
+det_infer_unify_canfail(construct(_, _, _, _, _, _, _), cannot_fail).
 det_infer_unify_canfail(simple_test(_, _), can_fail).
 det_infer_unify_canfail(complicated_unify(_, CanFail), CanFail).
 
Index: compiler/det_report.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/det_report.m,v
retrieving revision 1.54
diff -u -u -r1.54 det_report.m
--- det_report.m	1998/11/20 04:07:27	1.54
+++ det_report.m	1999/05/27 02:52:18
@@ -530,21 +530,12 @@
 			PredId, ModeId),
 		Context).
 
-det_diagnose_goal_2(higher_order_call(_, _, _, _, _, _), GoalInfo,
+det_diagnose_goal_2(generic_call(GenericCall, _, _, _), GoalInfo,
 		Desired, Actual, _, _DetInfo, yes) -->
 	{ goal_info_get_context(GoalInfo, Context) },
 	det_diagnose_atomic_goal(Desired, Actual,
-		report_higher_order_call_context(Context), Context).
-
-	% There's probably no point in this code being here: we only
-	% insert class_method_calls by hand, so they're gauranteed to be right,
-	% and in any case, we insert them after determinism analysis.
-	% Nonetheless, it's probably safer to include the code.
-det_diagnose_goal_2(class_method_call(_, _, _, _, _, _), GoalInfo,
-		Desired, Actual, _, _MiscInfo, yes) -->
-	{ goal_info_get_context(GoalInfo, Context) },
-	det_diagnose_atomic_goal(Desired, Actual,
-		report_higher_order_call_context(Context), Context).
+		report_generic_call_context(Context, GenericCall),
+		Context).
 
 det_diagnose_goal_2(unify(LT, RT, _, _, UnifyContext), GoalInfo,
 		Desired, Actual, _, DetInfo, yes) -->
@@ -600,7 +591,7 @@
 		{ Diagnosed = no }
 	).
 
-det_diagnose_goal_2(some(_Vars, Goal), _, Desired, Actual,
+det_diagnose_goal_2(some(_Vars, _, Goal), _, Desired, Actual,
 		SwitchContext, DetInfo, Diagnosed) -->
 	{ Goal = _ - GoalInfo },
 	{ goal_info_get_determinism(GoalInfo, Internal) },
@@ -630,11 +621,13 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred report_higher_order_call_context(prog_context::in,
-		io__state::di, io__state::uo) is det.
-report_higher_order_call_context(Context) -->
+:- pred report_generic_call_context(prog_context::in,
+		generic_call::in, io__state::di, io__state::uo) is det.
+report_generic_call_context(Context, CallType) -->
 	prog_out__write_context(Context),
-	io__write_string("  Higher-order call").
+	io__write_string("  "),
+	{ hlds_goal__generic_call_id(CallType, CallId) },
+	hlds_out__write_call_id(CallId).
 
 %-----------------------------------------------------------------------------%
 
@@ -682,9 +675,6 @@
 		hlds_out__write_determinism(Actual),
 		io__write_string(".\n")
 	).
-
-	% det_diagnose_conj is used for both normal [sequential]
-	% conjunction and parallel conjunction.
 
 	% det_diagnose_conj is used for both normal [sequential]
 	% conjunction and parallel conjunction.
Index: compiler/det_util.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/det_util.m,v
retrieving revision 1.17
diff -u -u -r1.17 det_util.m
--- det_util.m	1998/11/20 04:07:28	1.17
+++ det_util.m	1999/05/27 06:07:42
@@ -116,8 +116,8 @@
 	term__var_list_to_term_list(ArgVars, ArgTerms),
 	cons_id_and_args_to_term(ConsId, ArgTerms, RhsTerm),
 	term__unify(term__variable(X), RhsTerm, Subst0, Subst).
-interpret_unify(_X, lambda_goal(_POrF, _NonLocals, _Vars, _Modes, _Det, _Goal),
-		Subst0, Subst) :-
+interpret_unify(_X, lambda_goal(_POrF, _Method, _Fix, _NonLocals,
+			_Vars, _Modes, _Det, _Goal), Subst0, Subst) :-
 		% For ease of implementation we just ignore unifications with
 		% lambda terms.  This is a safe approximation, it just
 		% prevents us from optimizing them as well as we would like.
Index: compiler/dnf.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/dnf.m,v
retrieving revision 1.36
diff -u -u -r1.36 dnf.m
--- dnf.m	1999/06/01 09:43:40	1.36
+++ dnf.m	1999/06/02 01:20:57
@@ -190,11 +190,11 @@
 		GoalExpr0 = par_conj(_Goals0, _SM),
 		error("sorry, dnf of parallel conjunction not implemented")
 	;
-		GoalExpr0 = some(Vars, SomeGoal0),
+		GoalExpr0 = some(Vars, CanRemove, SomeGoal0),
 		dnf__make_goal_literal(SomeGoal0, InstMap0, MaybeNonAtomic,
 			ModuleInfo0, ModuleInfo, no, yes, Base, 0, _, 
 			DnfInfo, SomeGoal, NewPredIds0, NewPredIds),
-		Goal = some(Vars, SomeGoal) - GoalInfo
+		Goal = some(Vars, CanRemove, SomeGoal) - GoalInfo
 	;
 		GoalExpr0 = not(NegGoal0),
 		dnf__make_goal_literal(NegGoal0, InstMap0, MaybeNonAtomic,
@@ -221,12 +221,7 @@
 			DnfInfo, Cond, Then, Else, NewPredIds0, NewPredIds),
 		Goal = if_then_else(Vars, Cond, Then, Else, SM) - GoalInfo
 	;
-		GoalExpr0 = higher_order_call(_, _, _, _, _, _),
-		ModuleInfo = ModuleInfo0,
-		NewPredIds = NewPredIds0,
-		Goal = Goal0
-	;
-		GoalExpr0 = class_method_call(_, _, _, _, _, _),
+		GoalExpr0 = generic_call(_, _, _, _),
 		ModuleInfo = ModuleInfo0,
 		NewPredIds = NewPredIds0,
 		Goal = Goal0
@@ -450,7 +445,7 @@
 		IsAtomic = no
 	).
 dnf__is_atomic_expr(_, _, _, par_conj(_, _), no).
-dnf__is_atomic_expr(_, _, _, higher_order_call(_, _, _, _, _, _), yes).
+dnf__is_atomic_expr(_, _, _, generic_call(_, _, _, _), yes).
 dnf__is_atomic_expr(_, _, _, call(_, _, _, _, _, _), yes).
 dnf__is_atomic_expr(_, _, _, switch(_, _, _, _), no).
 dnf__is_atomic_expr(_, _, _, unify(_, _, _, _, _), yes).
@@ -464,7 +459,7 @@
 		IsAtomic = no
 	).
 dnf__is_atomic_expr(MaybeNonAtomic, InNeg, InSome,
-		some(_, GoalExpr - _), IsAtomic) :-
+		some(_, _, GoalExpr - _), IsAtomic) :-
 	( InSome = no ->
 		dnf__is_atomic_expr(MaybeNonAtomic, InNeg, yes,
 			GoalExpr, IsAtomic)
@@ -473,7 +468,6 @@
 	).
 dnf__is_atomic_expr(_, _, _, if_then_else(_, _, _, _, _), no).
 dnf__is_atomic_expr(_, _, _, pragma_c_code(_, _, _, _, _, _, _), yes).
-dnf__is_atomic_expr(_, _, _, class_method_call(_, _, _, _, _, _), yes).
 
 :- pred dnf__free_of_nonatomic(hlds_goal::in,
 	set(pred_proc_id)::in) is semidet.
@@ -488,7 +482,8 @@
 	dnf__cases_free_of_nonatomic(Cases, NonAtomic).
 dnf__free_of_nonatomic(unify(_, _, _, Uni, _) - _, NonAtomic) :-
 	\+ (
-		Uni = construct(_, pred_const(PredId, ProcId), _, _),
+		Uni = construct(_, pred_const(PredId, ProcId, _),
+			_, _, _, _, _),
 		set__member(proc(PredId, ProcId), NonAtomic)
 	).
 dnf__free_of_nonatomic(disj(Goals, _) - GoalInfo, NonAtomic) :-
@@ -499,7 +494,7 @@
 	dnf__goals_free_of_nonatomic(Goals, NonAtomic).
 dnf__free_of_nonatomic(not(Goal) - _, NonAtomic) :-
 	dnf__free_of_nonatomic(Goal, NonAtomic).
-dnf__free_of_nonatomic(some(_, Goal) - _, NonAtomic) :-
+dnf__free_of_nonatomic(some(_, _, Goal) - _, NonAtomic) :-
 	dnf__free_of_nonatomic(Goal, NonAtomic).
 dnf__free_of_nonatomic(if_then_else(_, Cond, Then, Else, _) - GoalInfo, 
 		NonAtomic) :-
Index: compiler/dupelim.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/dupelim.m,v
retrieving revision 1.40
diff -u -u -r1.40 dupelim.m
--- dupelim.m	1999/05/28 05:26:14	1.40
+++ dupelim.m	1999/05/29 02:10:43
@@ -956,6 +956,13 @@
 		do_semidet_aditi_call).
 dupelim__replace_labels_code_addr(do_nondet_aditi_call, _,
 		do_nondet_aditi_call).
+dupelim__replace_labels_code_addr(do_aditi_insert, _, do_aditi_insert).
+dupelim__replace_labels_code_addr(do_aditi_delete, _, do_aditi_delete).
+dupelim__replace_labels_code_addr(do_aditi_bulk_insert, _,
+		do_aditi_bulk_insert).
+dupelim__replace_labels_code_addr(do_aditi_bulk_delete, _,
+		do_aditi_bulk_delete).
+dupelim__replace_labels_code_addr(do_aditi_modify, _, do_aditi_modify).
 dupelim__replace_labels_code_addr(do_not_reached, _, do_not_reached).
 
 :- pred dupelim__replace_labels_label_list(list(label)::in,
Index: compiler/excess.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/excess.m,v
retrieving revision 1.30
diff -u -u -r1.30 excess.m
--- excess.m	1998/11/20 04:07:34	1.30
+++ excess.m	1999/05/14 04:40:54
@@ -117,16 +117,12 @@
 		excess_assignments_in_goal(Else0, ElimVars2, Else, ElimVars),
 		Goal = if_then_else(Vars, Cond, Then, Else, SM) - GoalInfo0
 	;
-		GoalExpr0 = some(Var, SubGoal0),
+		GoalExpr0 = some(Var, CanRemove, SubGoal0),
 		excess_assignments_in_goal(SubGoal0, ElimVars0,
 					   SubGoal, ElimVars),
-		Goal = some(Var, SubGoal) - GoalInfo0
+		Goal = some(Var, CanRemove, SubGoal) - GoalInfo0
 	;
-		GoalExpr0 = higher_order_call(_, _, _, _, _, _),
-		Goal = GoalExpr0 - GoalInfo0,
-		ElimVars = ElimVars0
-	;
-		GoalExpr0 = class_method_call(_, _, _, _, _, _),
+		GoalExpr0 = generic_call(_, _, _, _),
 		Goal = GoalExpr0 - GoalInfo0,
 		ElimVars = ElimVars0
 	;
Index: compiler/exprn_aux.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/exprn_aux.m,v
retrieving revision 1.35
diff -u -u -r1.35 exprn_aux.m
--- exprn_aux.m	1999/05/28 05:26:15	1.35
+++ exprn_aux.m	1999/05/29 02:10:44
@@ -155,6 +155,11 @@
 exprn_aux__addr_is_constant(do_det_aditi_call, _, no).
 exprn_aux__addr_is_constant(do_semidet_aditi_call, _, no).
 exprn_aux__addr_is_constant(do_nondet_aditi_call, _, no).
+exprn_aux__addr_is_constant(do_aditi_insert, _, no).
+exprn_aux__addr_is_constant(do_aditi_delete, _, no).
+exprn_aux__addr_is_constant(do_aditi_bulk_insert, _, no).
+exprn_aux__addr_is_constant(do_aditi_bulk_delete, _, no).
+exprn_aux__addr_is_constant(do_aditi_modify, _, no).
 exprn_aux__addr_is_constant(do_not_reached, _, no).
 
 :- pred exprn_aux__label_is_constant(label, bool, bool, bool).
Index: compiler/follow_code.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/follow_code.m,v
retrieving revision 1.50
diff -u -u -r1.50 follow_code.m
--- follow_code.m	1998/11/20 04:07:39	1.50
+++ follow_code.m	1999/05/14 04:57:53
@@ -111,14 +111,12 @@
 	move_follow_code_in_goal(Then0, Then, Flags, R1, R2),
 	move_follow_code_in_goal(Else0, Else, Flags, R2, R).
 
-move_follow_code_in_goal_2(some(Vars, Goal0), some(Vars, Goal), Flags, R0, R) :-
+move_follow_code_in_goal_2(some(Vars, CanRemove, Goal0),
+		some(Vars, CanRemove, Goal), Flags, R0, R) :-
 	move_follow_code_in_goal(Goal0, Goal, Flags, R0, R).
 
-move_follow_code_in_goal_2(higher_order_call(A,B,C,D,E,F),
-			higher_order_call(A,B,C,D,E,F), _, R, R).
-
-move_follow_code_in_goal_2(class_method_call(A,B,C,D,E,F),
-			class_method_call(A,B,C,D,E,F), _, R, R).
+move_follow_code_in_goal_2(generic_call(A,B,C,D),
+			generic_call(A,B,C,D), _, R, R).
 
 move_follow_code_in_goal_2(call(A,B,C,D,E,F), call(A,B,C,D,E,F), _, R, R).
 
Index: compiler/follow_vars.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/follow_vars.m,v
retrieving revision 1.52
diff -u -u -r1.52 follow_vars.m
--- follow_vars.m	1999/06/01 09:43:43	1.52
+++ follow_vars.m	1999/06/02 01:26:32
@@ -29,14 +29,15 @@
 
 :- interface.
 
-:- import_module hlds_module, hlds_pred, hlds_goal.
+:- import_module hlds_module, hlds_pred, hlds_goal, prog_data.
+:- import_module map.
 
 :- pred find_final_follow_vars(proc_info, follow_vars).
 :- mode find_final_follow_vars(in, out) is det.
 
-:- pred find_follow_vars_in_goal(hlds_goal, module_info,
+:- pred find_follow_vars_in_goal(hlds_goal, map(prog_var, type), module_info,
 				follow_vars, hlds_goal, follow_vars).
-:- mode find_follow_vars_in_goal(in, in, in, out, out) is det.
+:- mode find_follow_vars_in_goal(in, in, in, in, out, out) is det.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -79,51 +80,52 @@
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
-find_follow_vars_in_goal(Goal0 - GoalInfo, ModuleInfo, FollowVars0,
+find_follow_vars_in_goal(Goal0 - GoalInfo, VarTypes, ModuleInfo, FollowVars0,
 					Goal - GoalInfo, FollowVars) :-
-	find_follow_vars_in_goal_2(Goal0, ModuleInfo, FollowVars0,
+	find_follow_vars_in_goal_2(Goal0, VarTypes, ModuleInfo, FollowVars0,
 					Goal, FollowVars).
 
 %-----------------------------------------------------------------------------%
 
-:- pred find_follow_vars_in_goal_2(hlds_goal_expr, module_info,
-		follow_vars, hlds_goal_expr, follow_vars).
-:- mode find_follow_vars_in_goal_2(in, in, in, out, out) is det.
+:- pred find_follow_vars_in_goal_2(hlds_goal_expr, map(prog_var, type),
+		module_info, follow_vars, hlds_goal_expr, follow_vars).
+:- mode find_follow_vars_in_goal_2(in, in, in, in, out, out) is det.
 
-find_follow_vars_in_goal_2(conj(Goals0), ModuleInfo, FollowVars0,
+find_follow_vars_in_goal_2(conj(Goals0), VarTypes, ModuleInfo, FollowVars0,
 		conj(Goals), FollowVars) :-
-	find_follow_vars_in_conj(Goals0, ModuleInfo, FollowVars0,
+	find_follow_vars_in_conj(Goals0, VarTypes, ModuleInfo, FollowVars0,
 		no, Goals, FollowVars).
 
-find_follow_vars_in_goal_2(par_conj(Goals0, SM), ModuleInfo,
+find_follow_vars_in_goal_2(par_conj(Goals0, SM), VarTypes, ModuleInfo,
 		FollowVars0, par_conj(Goals, SM), FollowVars) :-
 		% find_follow_vars_in_disj treats its list of goals as a
 		% series of independent goals, so we can use it to process
 		% independent parallel conjunction.
-	find_follow_vars_in_disj(Goals0, ModuleInfo, FollowVars0,
+	find_follow_vars_in_disj(Goals0, VarTypes, ModuleInfo, FollowVars0,
 		Goals, FollowVars).
 
 	% We record that at the end of each disjunct, live variables should
 	% be in the locations given by the initial follow_vars, which reflects
 	% the requirements of the code following the disjunction.
 
-find_follow_vars_in_goal_2(disj(Goals0, _), ModuleInfo, FollowVars0,
+find_follow_vars_in_goal_2(disj(Goals0, _), VarTypes, ModuleInfo, FollowVars0,
 		disj(Goals, FollowVars0), FollowVars) :-
-	find_follow_vars_in_disj(Goals0, ModuleInfo, FollowVars0,
+	find_follow_vars_in_disj(Goals0, VarTypes, ModuleInfo, FollowVars0,
 		Goals, FollowVars).
 
-find_follow_vars_in_goal_2(not(Goal0), ModuleInfo, FollowVars0,
+find_follow_vars_in_goal_2(not(Goal0), VarTypes, ModuleInfo, FollowVars0,
 		not(Goal), FollowVars) :-
-	find_follow_vars_in_goal(Goal0, ModuleInfo, FollowVars0,
+	find_follow_vars_in_goal(Goal0, VarTypes, ModuleInfo, FollowVars0,
 		Goal, FollowVars).
 
 	% We record that at the end of each arm of the switch, live variables
 	% should be in the locations given by the initial follow_vars, which
 	% reflects the requirements of the code following the switch.
 
-find_follow_vars_in_goal_2(switch(Var, Det, Cases0, _), ModuleInfo, FollowVars0,
-		switch(Var, Det, Cases, FollowVars0), FollowVars) :-
-	find_follow_vars_in_cases(Cases0, ModuleInfo, FollowVars0,
+find_follow_vars_in_goal_2(switch(Var, Det, Cases0, _), VarTypes, ModuleInfo,
+		FollowVars0, switch(Var, Det, Cases, FollowVars0),
+		FollowVars) :-
+	find_follow_vars_in_cases(Cases0, VarTypes, ModuleInfo, FollowVars0,
 		Cases, FollowVars).
 
 	% Set the follow_vars field for the condition, the then-part and the
@@ -144,53 +146,38 @@
 	% following the if-then-else.
 
 find_follow_vars_in_goal_2(if_then_else(Vars, Cond0, Then0, Else0, _),
-		ModuleInfo, FollowVars0,
+		VarTypes, ModuleInfo, FollowVars0,
 		if_then_else(Vars, Cond, Then, Else, FollowVars0),
 		FollowVarsCond) :-
-	find_follow_vars_in_goal(Then0, ModuleInfo, FollowVars0,
+	find_follow_vars_in_goal(Then0, VarTypes, ModuleInfo, FollowVars0,
 		Then1, FollowVarsThen),
 	goal_set_follow_vars(Then1, yes(FollowVarsThen), Then),
-	find_follow_vars_in_goal(Cond0, ModuleInfo, FollowVarsThen,
+	find_follow_vars_in_goal(Cond0, VarTypes, ModuleInfo, FollowVarsThen,
 		Cond1, FollowVarsCond),
 	goal_set_follow_vars(Cond1, yes(FollowVarsCond), Cond),
-	find_follow_vars_in_goal(Else0, ModuleInfo, FollowVars0,
+	find_follow_vars_in_goal(Else0, VarTypes, ModuleInfo, FollowVars0,
 		Else1, FollowVarsElse),
 	goal_set_follow_vars(Else1, yes(FollowVarsElse), Else).
 
-find_follow_vars_in_goal_2(some(Vars, Goal0), ModuleInfo,
-		FollowVars0, some(Vars, Goal), FollowVars) :-
-	find_follow_vars_in_goal(Goal0, ModuleInfo, FollowVars0,
+find_follow_vars_in_goal_2(some(Vars, CanRemove, Goal0), VarTypes, ModuleInfo,
+		FollowVars0, some(Vars, CanRemove, Goal), FollowVars) :-
+	find_follow_vars_in_goal(Goal0, VarTypes, ModuleInfo, FollowVars0,
 		Goal, FollowVars).
 
 	% XXX These follow-vars aren't correct since the desired positions for
 	% XXX the arguments are different from an ordinary call --- they are
-	% XXX as required by do_call_{det,semidet,nondet}_closure
-find_follow_vars_in_goal_2(
-		higher_order_call(PredVar, Args, Types, Modes, Det,
-			IsPredOrFunc),
-		ModuleInfo, _FollowVars0,
-		higher_order_call(PredVar, Args, Types, Modes, Det,
-			IsPredOrFunc),
-		FollowVars) :-
-	determinism_to_code_model(Det, CodeModel),
-	make_arg_infos(Types, Modes, CodeModel, ModuleInfo, ArgInfo),
-	find_follow_vars_from_arginfo(ArgInfo, Args, FollowVars).
-
-	% XXX These follow-vars aren't correct since the desired positions for
-	% XXX the arguments are different from an ordinary call --- they are
-	% XXX as required by do_call_{det,semidet,nondet}_class_method
+	% XXX as required by the builtin operation.
 find_follow_vars_in_goal_2(
-		class_method_call(TypeClassInfoVar, Num, Args, Types, Modes,
-			Det),
-		ModuleInfo, _FollowVars0,
-		class_method_call(TypeClassInfoVar, Num, Args, Types, Modes,
-			Det),
+		generic_call(GenericCall, Args, Modes, Det),
+		VarTypes, ModuleInfo, _FollowVars0,
+		generic_call(GenericCall, Args, Modes, Det),
 		FollowVars) :-
 	determinism_to_code_model(Det, CodeModel),
+	map__apply_to_list(Args, VarTypes, Types),
 	make_arg_infos(Types, Modes, CodeModel, ModuleInfo, ArgInfo),
 	find_follow_vars_from_arginfo(ArgInfo, Args, FollowVars).
 
-find_follow_vars_in_goal_2(call(A,B,C,D,E,F), ModuleInfo,
+find_follow_vars_in_goal_2(call(A,B,C,D,E,F), _, ModuleInfo,
 		FollowVars0, call(A,B,C,D,E,F), FollowVars) :-
 	(
 		D = inline_builtin
@@ -200,7 +187,7 @@
 		find_follow_vars_in_call(A, B, C, ModuleInfo, FollowVars)
 	).
 
-find_follow_vars_in_goal_2(unify(A,B,C,D,E), _ModuleInfo,
+find_follow_vars_in_goal_2(unify(A,B,C,D,E), _, _ModuleInfo,
 		FollowVars0, unify(A,B,C,D,E), FollowVars) :-
 	(
 		D = assign(LVar, RVar),
@@ -212,7 +199,7 @@
 	).
 
 find_follow_vars_in_goal_2(pragma_c_code(A,B,C,D,E,F,G), 
-		_ModuleInfo, FollowVars,
+		_, _ModuleInfo, FollowVars,
 		pragma_c_code(A,B,C,D,E,F,G), FollowVars).
 
 %-----------------------------------------------------------------------------%
@@ -282,18 +269,18 @@
 	%
 	% This code is used both for disjunction and parallel conjunction.
 
-:- pred find_follow_vars_in_disj(list(hlds_goal), module_info,
-				follow_vars, list(hlds_goal), follow_vars).
-:- mode find_follow_vars_in_disj(in, in, in, out, out) is det.
+:- pred find_follow_vars_in_disj(list(hlds_goal), map(prog_var, type),
+		module_info, follow_vars, list(hlds_goal), follow_vars).
+:- mode find_follow_vars_in_disj(in, in, in, in, out, out) is det.
 
-find_follow_vars_in_disj([], _ModuleInfo, FollowVars,
+find_follow_vars_in_disj([], _, _ModuleInfo, FollowVars,
 			[], FollowVars).
-find_follow_vars_in_disj([Goal0 | Goals0], ModuleInfo, FollowVars0,
+find_follow_vars_in_disj([Goal0 | Goals0], VarTypes, ModuleInfo, FollowVars0,
 						[Goal | Goals], FollowVars) :-
-	find_follow_vars_in_goal(Goal0, ModuleInfo, FollowVars0,
+	find_follow_vars_in_goal(Goal0, VarTypes, ModuleInfo, FollowVars0,
 		Goal1, FollowVars),
 	goal_set_follow_vars(Goal1, yes(FollowVars), Goal),
-	find_follow_vars_in_disj(Goals0, ModuleInfo, FollowVars0,
+	find_follow_vars_in_disj(Goals0, VarTypes, ModuleInfo, FollowVars0,
 		Goals, _FollowVars1).
 
 %-----------------------------------------------------------------------------%
@@ -309,17 +296,17 @@
 	% its follow_vars) and to let different branches "vote" on
 	% what should be in registers.
 
-:- pred find_follow_vars_in_cases(list(case), module_info,
+:- pred find_follow_vars_in_cases(list(case), map(prog_var, type), module_info,
 				follow_vars, list(case), follow_vars).
-:- mode find_follow_vars_in_cases(in, in, in, out, out) is det.
+:- mode find_follow_vars_in_cases(in, in, in, in, out, out) is det.
 
-find_follow_vars_in_cases([], _ModuleInfo, FollowVars, [], FollowVars).
-find_follow_vars_in_cases([case(Cons, Goal0) | Goals0], ModuleInfo,
+find_follow_vars_in_cases([], _, _ModuleInfo, FollowVars, [], FollowVars).
+find_follow_vars_in_cases([case(Cons, Goal0) | Goals0], VarTypes, ModuleInfo,
 			FollowVars0, [case(Cons, Goal) | Goals], FollowVars) :-
-	find_follow_vars_in_goal(Goal0, ModuleInfo, FollowVars0,
+	find_follow_vars_in_goal(Goal0, VarTypes, ModuleInfo, FollowVars0,
 		Goal1, FollowVars),
 	goal_set_follow_vars(Goal1, yes(FollowVars), Goal),
-	find_follow_vars_in_cases(Goals0, ModuleInfo, FollowVars0,
+	find_follow_vars_in_cases(Goals0, VarTypes, ModuleInfo, FollowVars0,
 		Goals, _FollowVars1).
 
 %-----------------------------------------------------------------------------%
@@ -327,13 +314,13 @@
 	% We attach the follow_vars to each goal that follows a goal
 	% that is not cachable by the code generator.
 
-:- pred find_follow_vars_in_conj(list(hlds_goal), module_info,
-			follow_vars, bool, list(hlds_goal), follow_vars).
-:- mode find_follow_vars_in_conj(in, in, in, in, out, out) is det.
+:- pred find_follow_vars_in_conj(list(hlds_goal), map(prog_var, type),
+		module_info, follow_vars, bool, list(hlds_goal), follow_vars).
+:- mode find_follow_vars_in_conj(in, in, in, in, in, out, out) is det.
 
-find_follow_vars_in_conj([], _ModuleInfo, FollowVars,
+find_follow_vars_in_conj([], _, _ModuleInfo, FollowVars,
 		_AttachToFirst, [], FollowVars).
-find_follow_vars_in_conj([Goal0 | Goals0], ModuleInfo, FollowVars0,
+find_follow_vars_in_conj([Goal0 | Goals0], VarTypes, ModuleInfo, FollowVars0,
 		AttachToFirst, [Goal | Goals], FollowVars) :-
 	(
 		Goal0 = GoalExpr0 - _,
@@ -349,9 +336,9 @@
 	;
 		AttachToNext = yes
 	),
-	find_follow_vars_in_conj(Goals0, ModuleInfo, FollowVars0,
+	find_follow_vars_in_conj(Goals0, VarTypes, ModuleInfo, FollowVars0,
 		AttachToNext, Goals, FollowVars1),
-	find_follow_vars_in_goal(Goal0, ModuleInfo, FollowVars1,
+	find_follow_vars_in_goal(Goal0, VarTypes, ModuleInfo, FollowVars1,
 		Goal1, FollowVars),
 	(
 		AttachToFirst = yes,
Index: compiler/goal_path.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/goal_path.m,v
retrieving revision 1.5
diff -u -u -r1.5 goal_path.m
--- goal_path.m	1998/06/09 02:12:42	1.5
+++ goal_path.m	1999/05/14 04:47:37
@@ -48,7 +48,7 @@
 	fill_switch_slots(Cases0, Path0, 0, Cases).
 fill_expr_slots(not(Goal0), Path0, not(Goal)) :-
 	fill_goal_slots(Goal0, [neg | Path0], Goal).
-fill_expr_slots(some(A, Goal0), Path0, some(A, Goal)) :-
+fill_expr_slots(some(A, B, Goal0), Path0, some(A, B, Goal)) :-
 	fill_goal_slots(Goal0, [exist | Path0], Goal).
 fill_expr_slots(if_then_else(A, Cond0, Then0, Else0, E), Path0,
 		if_then_else(A, Cond, Then, Else, E)) :-
@@ -56,10 +56,7 @@
 	fill_goal_slots(Then0, [ite_then | Path0], Then),
 	fill_goal_slots(Else0, [ite_else | Path0], Else).
 fill_expr_slots(call(A,B,C,D,E,F), _Path0, call(A,B,C,D,E,F)).
-fill_expr_slots(higher_order_call(A,B,C,D,E,F), _Path0,
-		higher_order_call(A,B,C,D,E,F)).
-fill_expr_slots(class_method_call(A,B,C,D,E,F), _Path0,
-		class_method_call(A,B,C,D,E,F)).
+fill_expr_slots(generic_call(A,B,C,D), _Path0, generic_call(A,B,C,D)).
 fill_expr_slots(unify(A,B,C,D,E), _Path0, unify(A,B,C,D,E)).
 fill_expr_slots(pragma_c_code(A,B,C,D,E,F,G), _Path0,
 		pragma_c_code(A,B,C,D,E,F,G)).
Index: compiler/goal_util.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/goal_util.m,v
retrieving revision 1.50
diff -u -u -r1.50 goal_util.m
--- goal_util.m	1998/12/06 23:43:12	1.50
+++ goal_util.m	1999/05/27 06:08:01
@@ -73,6 +73,10 @@
 		set(prog_var)).
 :- mode goal_util__goals_goal_vars(in, in, out) is det.
 
+	% Return all the variables in a generic call.
+:- pred goal_util__generic_call_vars(generic_call, list(prog_var)).
+:- mode goal_util__generic_call_vars(in, out) is det.
+
 	%
 	% goal_util__extra_nonlocal_typeinfos(TypeInfoMap, TypeClassInfoMap,
 	%		VarTypes, ExistQVars, NonLocals, NonLocalTypeInfos):
@@ -292,26 +296,16 @@
 goal_util__name_apart_2(not(Goal0), Must, Subn, not(Goal)) :-
 	goal_util__rename_vars_in_goal(Goal0, Must, Subn, Goal).
 
-goal_util__name_apart_2(some(Vars0, Goal0), Must, Subn, some(Vars, Goal)) :-
+goal_util__name_apart_2(some(Vars0, CanRemove, Goal0), Must, Subn,
+		some(Vars, CanRemove, Goal)) :-
 	goal_util__rename_var_list(Vars0, Must, Subn, Vars),
 	goal_util__rename_vars_in_goal(Goal0, Must, Subn, Goal).
 
 goal_util__name_apart_2(
-		higher_order_call(PredVar0, Args0, Types, Modes, Det,
-			IsPredOrFunc),
-		Must, Subn,
-		higher_order_call(PredVar, Args, Types, Modes, Det,
-			IsPredOrFunc)) :-
-	goal_util__rename_var(PredVar0, Must, Subn, PredVar),
-	goal_util__rename_var_list(Args0, Must, Subn, Args).
-
-goal_util__name_apart_2(
-		class_method_call(TypeClassInfoVar0, Num, Args0, Types, Modes,
-			Det),
+		generic_call(GenericCall0, Args0, Modes, Det),
 		Must, Subn,
-		class_method_call(TypeClassInfoVar, Num, Args, Types, Modes,
-			Det)) :-
-	goal_util__rename_var(TypeClassInfoVar0, Must, Subn, TypeClassInfoVar),
+		generic_call(GenericCall, Args, Modes, Det)) :-
+	goal_util__rename_generic_call(GenericCall0, Must, Subn, GenericCall),
 	goal_util__rename_var_list(Args0, Must, Subn, Args).
 
 goal_util__name_apart_2(
@@ -365,9 +359,11 @@
 			functor(Functor, ArgVars)) :-
 	goal_util__rename_var_list(ArgVars0, Must, Subn, ArgVars).
 goal_util__rename_unify_rhs(
-	    lambda_goal(PredOrFunc, NonLocals0, Vars0, Modes, Det, Goal0),
+	    lambda_goal(PredOrFunc, EvalMethod, FixModes, NonLocals0,
+	    		Vars0, Modes, Det, Goal0),
 	    Must, Subn, 
-	    lambda_goal(PredOrFunc, NonLocals, Vars, Modes, Det, Goal)) :-
+	    lambda_goal(PredOrFunc, EvalMethod, FixModes, NonLocals,
+	    		Vars, Modes, Det, Goal)) :-
 	goal_util__rename_var_list(NonLocals0, Must, Subn, NonLocals),
 	goal_util__rename_var_list(Vars0, Must, Subn, Vars),
 	goal_util__rename_vars_in_goal(Goal0, Must, Subn, Goal).
@@ -376,10 +372,18 @@
 		unification).
 :- mode goal_util__rename_unify(in, in, in, out) is det.
 
-goal_util__rename_unify(construct(Var0, ConsId, Vars0, Modes), Must, Subn,
-			construct(Var, ConsId, Vars, Modes)) :-
+goal_util__rename_unify(
+		construct(Var0, ConsId, Vars0, Modes, Reuse0, Uniq, Aditi),
+		Must, Subn,
+		construct(Var, ConsId, Vars, Modes, Reuse, Uniq, Aditi)) :-
 	goal_util__rename_var(Var0, Must, Subn, Var),
-	goal_util__rename_var_list(Vars0, Must, Subn, Vars).
+	goal_util__rename_var_list(Vars0, Must, Subn, Vars),
+	( Reuse0 = yes(cell_to_reuse(ReuseVar0, B, C)) ->
+		goal_util__rename_var(ReuseVar0, Must, Subn, ReuseVar),
+		Reuse = yes(cell_to_reuse(ReuseVar, B, C))
+	;
+		Reuse = no
+	).
 goal_util__rename_unify(deconstruct(Var0, ConsId, Vars0, Modes, Cat),
 		Must, Subn, deconstruct(Var, ConsId, Vars, Modes, Cat)) :-
 	goal_util__rename_var(Var0, Must, Subn, Var),
@@ -395,6 +399,21 @@
 
 %-----------------------------------------------------------------------------%
 
+:- pred goal_util__rename_generic_call(generic_call, bool,
+		map(prog_var, prog_var), generic_call).
+:- mode goal_util__rename_generic_call(in, in, in, out) is det.
+
+goal_util__rename_generic_call(higher_order(Var0, PredOrFunc, Arity),
+		Must, Subn, higher_order(Var, PredOrFunc, Arity)) :-
+	goal_util__rename_var(Var0, Must, Subn, Var).
+goal_util__rename_generic_call(class_method(Var0, Method, ClassId, MethodId),
+		Must, Subn, class_method(Var, Method, ClassId, MethodId)) :-
+	goal_util__rename_var(Var0, Must, Subn, Var).
+goal_util__rename_generic_call(aditi_builtin(Builtin, PredCallId),
+		_Must, _Subn, aditi_builtin(Builtin, PredCallId)).
+
+%-----------------------------------------------------------------------------%
+
 :- pred goal_util__rename_var_maps(map(prog_var, T), bool,
 				map(prog_var, prog_var), map(prog_var, T)).
 :- mode goal_util__rename_var_maps(in, in, in, out) is det.
@@ -475,17 +494,24 @@
 :- pred goal_util__goal_vars_2(hlds_goal_expr, set(prog_var), set(prog_var)).
 :- mode goal_util__goal_vars_2(in, in, out) is det.
 
-goal_util__goal_vars_2(unify(Var, RHS, _, _, _), Set0, Set) :-
+goal_util__goal_vars_2(unify(Var, RHS, _, Unif, _), Set0, Set) :-
 	set__insert(Set0, Var, Set1),
-	goal_util__rhs_goal_vars(RHS, Set1, Set).
-
-goal_util__goal_vars_2(higher_order_call(PredVar, ArgVars, _, _, _, _),
-		Set0, Set) :-
-	set__insert_list(Set0, [PredVar | ArgVars], Set).
+	( Unif = construct(_, _, _, _, CellToReuse, _, _) ->
+		( CellToReuse = yes(cell_to_reuse(Var, _, _)) ->
+			set__insert(Set1, Var, Set2)
+		;
+			Set2 = Set1
+		)
+	;
+		Set2 = Set1
+	),	
+	goal_util__rhs_goal_vars(RHS, Set2, Set).
 
-goal_util__goal_vars_2(class_method_call(PredVar, _, ArgVars, _, _, _),
+goal_util__goal_vars_2(generic_call(GenericCall, ArgVars, _, _),
 		Set0, Set) :-
-	set__insert_list(Set0, [PredVar | ArgVars], Set).
+	goal_util__generic_call_vars(GenericCall, Vars0),
+	set__insert_list(Set0, Vars0, Set1),
+	set__insert_list(Set1, ArgVars, Set).
 
 goal_util__goal_vars_2(call(_, _, ArgVars, _, _, _), Set0, Set) :-
 	set__insert_list(Set0, ArgVars, Set).
@@ -503,7 +529,7 @@
 	set__insert(Set0, Var, Set1),
 	goal_util__cases_goal_vars(Cases, Set1, Set).
 
-goal_util__goal_vars_2(some(Vars, Goal - _), Set0, Set) :-
+goal_util__goal_vars_2(some(Vars, _, Goal - _), Set0, Set) :-
 	set__insert_list(Set0, Vars, Set1),
 	goal_util__goal_vars_2(Goal, Set1, Set).
 
@@ -541,12 +567,16 @@
 goal_util__rhs_goal_vars(functor(_Functor, ArgVars), Set0, Set) :-
 	set__insert_list(Set0, ArgVars, Set).
 goal_util__rhs_goal_vars(
-		lambda_goal(_POrF, NonLocals, LambdaVars, _M, _D, Goal - _), 
+		lambda_goal(_, _, _, NonLocals, LambdaVars, _M, _D, Goal - _), 
 		Set0, Set) :-
 	set__insert_list(Set0, NonLocals, Set1),
 	set__insert_list(Set1, LambdaVars, Set2),
 	goal_util__goal_vars_2(Goal, Set2, Set).
 
+goal_util__generic_call_vars(higher_order(Var, _, _), [Var]).
+goal_util__generic_call_vars(class_method(Var, _, _, _), [Var]).
+goal_util__generic_call_vars(aditi_builtin(_, _), []).
+
 %-----------------------------------------------------------------------------%
 
 goal_util__extra_nonlocal_typeinfos(TypeVarMap, TypeClassVarMap, VarTypes,
@@ -631,12 +661,11 @@
 goal_expr_size(not(Goal), Size) :-
 	goal_size(Goal, Size1),
 	Size is Size1 + 1.
-goal_expr_size(some(_, Goal), Size) :-
+goal_expr_size(some(_, _, Goal), Size) :-
 	goal_size(Goal, Size1),
 	Size is Size1 + 1.
 goal_expr_size(call(_, _, _, _, _, _), 1).
-goal_expr_size(higher_order_call(_, _, _, _, _, _), 1).
-goal_expr_size(class_method_call(_, _, _, _, _, _), 1).
+goal_expr_size(generic_call(_, _, _, _), 1).
 goal_expr_size(unify(_, _, _, _, _), 1).
 goal_expr_size(pragma_c_code(_, _, _, _, _, _, _), 1).
 
@@ -687,7 +716,7 @@
 	).
 goal_expr_calls(not(Goal), PredProcId) :-
 	goal_calls(Goal, PredProcId).
-goal_expr_calls(some(_, Goal), PredProcId) :-
+goal_expr_calls(some(_, _, Goal), PredProcId) :-
 	goal_calls(Goal, PredProcId).
 goal_expr_calls(call(PredId, ProcId, _, _, _, _), proc(PredId, ProcId)).
 
@@ -735,7 +764,7 @@
 	).
 goal_expr_calls_pred_id(not(Goal), PredId) :-
 	goal_calls_pred_id(Goal, PredId).
-goal_expr_calls_pred_id(some(_, Goal), PredId) :-
+goal_expr_calls_pred_id(some(_, _, Goal), PredId) :-
 	goal_calls_pred_id(Goal, PredId).
 goal_expr_calls_pred_id(call(PredId, _, _, _, _, _), PredId).
 
Index: compiler/higher_order.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/higher_order.m,v
retrieving revision 1.51
diff -u -u -r1.51 higher_order.m
--- higher_order.m	1999/04/23 01:02:40	1.51
+++ higher_order.m	1999/05/14 04:48:21
@@ -416,17 +416,22 @@
 
 		% check whether this call could be specialized
 traverse_goal(Goal0, Goal) -->
-	{ Goal0 = higher_order_call(Var, Args, _,_,_,_) - GoalInfo }, 
-	maybe_specialize_higher_order_call(Var, no, Args, Goal0, Goals),
-	{ conj_list_to_goal(Goals, GoalInfo, Goal) }.
-
-		% class_method_calls are treated similarly to
-		% higher_order_calls.
-traverse_goal(Goal0, Goal) -->
-	{ Goal0 = class_method_call(Var, Method, Args,_,_,_) - GoalInfo },
-	maybe_specialize_higher_order_call(Var, yes(Method), Args,
-		Goal0, Goals),
-	{ conj_list_to_goal(Goals, GoalInfo, Goal) }.
+	{ Goal0 = generic_call(GenericCall, Args, _, _) - GoalInfo }, 
+	(
+		{
+			GenericCall = higher_order(Var, _, _),
+			MaybeMethod = no
+		;
+			GenericCall = class_method(Var, Method, _, _),
+			MaybeMethod = yes(Method)
+		}
+	->
+		maybe_specialize_higher_order_call(Var, MaybeMethod,
+			Args, Goal0, Goals),
+		{ conj_list_to_goal(Goals, GoalInfo, Goal) }
+	;
+		{ Goal = Goal0 }
+	).
 
 		% check whether this call could be specialized
 traverse_goal(Goal0, Goal) -->
@@ -445,7 +450,8 @@
 traverse_goal(not(NegGoal0) - Info, not(NegGoal) - Info) -->
 	traverse_goal(NegGoal0, NegGoal).
 
-traverse_goal(some(Vars, Goal0) - Info, some(Vars, Goal) - Info) -->
+traverse_goal(some(Vars, CanRemove, Goal0) - Info,
+		some(Vars, CanRemove, Goal) - Info) -->
 	traverse_goal(Goal0, Goal).
 
 traverse_goal(Goal, Goal) -->
@@ -578,7 +584,7 @@
 	% deconstructing a higher order term is not allowed
 check_unify(deconstruct(_, _, _, _, _)) --> [].
 	
-check_unify(construct(LVar, ConsId, Args, _Modes), Info0, Info) :- 
+check_unify(construct(LVar, ConsId, Args, _Modes, _, _, _), Info0, Info) :- 
 	Info0 = info(PredVars0, Requests, NewPreds, PredProcId,
 		PredInfo, ProcInfo, ModuleInfo, Params, Changed),
 	( is_interesting_cons_id(Params, ConsId) ->
@@ -618,7 +624,7 @@
 	( Name = "type_info"
 	; Name = "typeclass_info"
 	).
-is_interesting_cons_id(ho_params(yes, _, _, _, _), pred_const(_, _)).
+is_interesting_cons_id(ho_params(yes, _, _, _, _), pred_const(_, _, _)).
 is_interesting_cons_id(ho_params(_, _, yes, _, _),
 		type_ctor_info_const(_, _, _)).
 is_interesting_cons_id(ho_params(_, _, yes, _, _),
@@ -644,7 +650,7 @@
 	(
 		map__search(PredVars, PredVar, constant(ConsId, CurriedArgs)),
 		(
-			ConsId = pred_const(PredId0, ProcId0),
+			ConsId = pred_const(PredId0, ProcId0, _),
 			MaybeMethod = no
 		->
 			PredId = PredId0,
@@ -1003,12 +1009,12 @@
 		% extract fields from typeclass_infos).
 		ConsId \= int_const(_),
 
-		( ConsId = pred_const(_, _) ->
+		( ConsId = pred_const(_, _, _) ->
 			% If we don't have clauses for the callee, we can't
 			% specialize any higher-order arguments. We may be
 			% able to do user guided type specialization.
 			CalleeStatus \= imported,
-			type_is_higher_order(CalleeArgType, _, _)
+			type_is_higher_order(CalleeArgType, _, _, _)
 		;
 			true
 		)
@@ -1016,7 +1022,7 @@
 		% Find any known higher-order arguments
 		% in the list of curried arguments.
 		map__apply_to_list(CurriedArgs, VarTypes, CurriedArgTypes),
-		( ConsId = pred_const(PredId, _) ->
+		( ConsId = pred_const(PredId, _, _) ->
 			module_info_pred_info(ModuleInfo, PredId, PredInfo),
 			pred_info_arg_types(PredInfo, CurriedCalleeArgTypes)
 		;
@@ -1155,7 +1161,7 @@
 			;
 				HigherOrder = yes,
 				list__member(HOArg, HigherOrderArgs),
-				HOArg = higher_order_arg(pred_const(_, _),
+				HOArg = higher_order_arg(pred_const(_, _, _),
 					_, _, _, _, _)
 			;
 				TypeSpec = yes
@@ -1390,7 +1396,7 @@
 
 		% All the higher-order arguments must be present in the
 		% version otherwise we should create a new one.
-		ConsId1 \= pred_const(_, _),
+		ConsId1 \= pred_const(_, _, _),
 		PartialMatch = yes,
 		higher_order_args_match(Args1, [VersionArg | Args2], Args, _)
 	).
@@ -1792,7 +1798,7 @@
 output_higher_order_args(_, _, []) --> [].
 output_higher_order_args(ModuleInfo, NumToDrop, [HOArg | HOArgs]) -->
 	{ HOArg = higher_order_arg(ConsId, ArgNo, NumArgs, _, _, _) },
-	( { ConsId = pred_const(PredId, _ProcId) } ->
+	( { ConsId = pred_const(PredId, _ProcId, _) } ->
 		{ module_info_pred_info(ModuleInfo, PredId, PredInfo) },
 		{ pred_info_name(PredInfo, Name) },
 		{ pred_info_arity(PredInfo, Arity) },
@@ -2079,7 +2085,7 @@
 
 	list__index1_det(HeadVars0, Index, LVar),
 	(
-		( ConsId = pred_const(PredId, ProcId)
+		( ConsId = pred_const(PredId, ProcId, _)
 		; ConsId = code_addr_const(PredId, ProcId)
 		)
 	->
Index: compiler/hlds_data.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/hlds_data.m,v
retrieving revision 1.34
diff -u -u -r1.34 hlds_data.m
--- hlds_data.m	1999/04/22 01:04:08	1.34
+++ hlds_data.m	1999/05/27 02:56:46
@@ -29,7 +29,8 @@
 			;	int_const(int)
 			;	string_const(string)
 			;	float_const(float)
-			;	pred_const(pred_id, proc_id)
+			;	pred_const(pred_id, proc_id,
+					lambda_eval_method)
 			;	code_addr_const(pred_id, proc_id)
 				% Used for constructing type_infos.
 				% Note that a pred_const is for a closure
@@ -52,6 +53,18 @@
 				% model semantics for the given procedure.
 			.
 
+	% Markers other than `normal' are used for lambda expressions
+	% constructed for arguments of the builtin Aditi update constructs.
+	% `aditi_top_down' expressions are used by the builtin deletion
+	% predicate to determine whether a tuple should be deleted.
+	% `aditi_bottom_up' expressions are used as database queries to
+	% produce a set of tuples to be inserted or deleted.
+:- type lambda_eval_method
+	--->	normal
+	;	(aditi_top_down)
+	;	(aditi_bottom_up)
+	.
+
 	% A cons_defn is the definition of a constructor (i.e. a constant
 	% or a functor) for a particular type.
 
@@ -124,7 +137,7 @@
 cons_id_arity(int_const(_), 0).
 cons_id_arity(string_const(_), 0).
 cons_id_arity(float_const(_), 0).
-cons_id_arity(pred_const(_, _), _) :-
+cons_id_arity(pred_const(_, _, _), _) :-
 	error("cons_id_arity: can't get arity of pred_const").
 cons_id_arity(code_addr_const(_, _), _) :-
 	error("cons_id_arity: can't get arity of code_addr_const").
@@ -249,11 +262,12 @@
 			% a word containing the specified integer value.
 			% This is used for enumerations and character
 			% constants as well as for int constants.
-	;	pred_closure_tag(pred_id, proc_id)
+	;	pred_closure_tag(pred_id, proc_id, lambda_eval_method)
 			% Higher-order pred closures tags.
 			% These are represented as a pointer to
 			% an argument vector.
-			% The first two words of the argument vector
+			% For closures with lambda_eval_method `normal',
+			% the first two words of the argument vector
 			% hold the number of args and the address of
 			% the procedure respectively.
 			% The remaining words hold the arguments.
Index: compiler/hlds_goal.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/hlds_goal.m,v
retrieving revision 1.59
diff -u -u -r1.59 hlds_goal.m
--- hlds_goal.m	1999/04/23 01:02:41	1.59
+++ hlds_goal.m	1999/06/03 02:34:09
@@ -12,8 +12,8 @@
 
 :- interface.
 
-:- import_module hlds_data, hlds_pred, llds, prog_data, (inst), instmap.
-:- import_module char, list, set, map, std_util.
+:- import_module hlds_data, hlds_pred, llds, prog_data, (inst), instmap, rl.
+:- import_module bool, char, list, set, map, std_util.
 
 	% Here is how goals are represented
 
@@ -47,23 +47,23 @@
 			sym_name	% the name of the predicate
 		)
 
-	;	higher_order_call(
-			prog_var,	% the predicate to call
+		% A generic call implements operations which are too
+		% polymorphic to be written as ordinary predicates in Mercury
+		% and require special casing, either because their arity
+		% is variable, or they take higher-order arguments of
+		% variable arity.
+		% This currently includes higher-order calls, class-method
+		% calls, Aditi calls and the Aditi update predicates.
+	
+	;	generic_call(
+			generic_call,
 			list(prog_var),	% the list of argument variables
-			list(type),	% the types of the argument variables
-			list(mode),	% the modes of the argument variables
-			determinism,	% the determinism of the called pred
-			pred_or_func	% call/N (pred) or apply/N (func)
-		)
-
-	;	class_method_call(
-			prog_var,	% the typeclass_info for the instance
-			int,		% the number of the method to call
-			list(prog_var),	% the list of argument variables (other
-					% than this instance's typeclass_info)
-			list(type),	% the types of the argument variables
-			list(mode),	% the modes of the argument variables
-			determinism	% the determinism of the called pred
+			list(mode),	% The modes of the argument variables.
+					% For higher_order calls, this field
+					% is junk until after mode analysis.
+					% For aditi_builtins, this field
+					% is junk until after purity checking.
+			determinism	% the determinism of the call
 		)
 
 		% Deterministic disjunctions are converted
@@ -124,8 +124,15 @@
 		% field of the goal_info, so these get ignored
 		% (except to recompute the goal_info quantification).
 		% `all Vs' gets converted to `not some Vs not'.
-
-	;	{ some(list(prog_var), hlds_goal) }
+		% The second argument is `can_remove' if the quantification
+		% is allowed to be removed. A non-removable explicit
+		% quantification may be introduced to keep related goals
+		% together where optimizations that separate the goals
+		% can only result in worse behaviour. An example is the
+		% closures for the builtin aditi update predicates -
+		% they should be kept close to the update call where
+		% possible to make it easier to use indexes for the update.
+	;	{ some(list(prog_var), can_remove, hlds_goal) }
 
 		% An if-then-else,
 		% `if some <Vars> <Condition> then <Then> else <Else>'.
@@ -180,17 +187,109 @@
 					% conjunction.
 	.
 
-	% Given the variable info field from a pragma c_code, get all the
-	% variable names.
-:- pred get_pragma_c_var_names(list(maybe(pair(string, mode))), list(string)).
-:- mode get_pragma_c_var_names(in, out) is det.
+:- type generic_call
+	--->	higher_order(
+			prog_var,
+			pred_or_func,	% call/N (pred) or apply/N (func)
+			arity		% number of arguments (including the
+					% higher-order term)
+		)
+
+	;	class_method(
+			prog_var,	% typeclass_info for the instance
+			int,		% number of the called method
+			class_id,	% name and arity of the class
+			simple_call_id	% name of the called method
+		)
+
+	;	aditi_builtin(
+			aditi_builtin,
+			simple_call_id
+		)
+	.
+
+	% Builtin Aditi operations. 
+:- type aditi_builtin
+	--->
+		% Call an Aditi predicate from Mercury compiled to C.
+		% This is introduced by magic.m.
+		% Arguments: 
+		%   type-infos for the input arguments
+		%   the input arguments
+		%   type-infos for the output arguments
+		%   the output arguments
+		aditi_call(
+			pred_proc_id,	% procedure to call
+			int,		% number of inputs
+			list(type),	% types of input arguments
+			int		% number of outputs
+		)
+
+		% Insert a single tuple into a predicate.
+		% Arguments:
+		%   type-infos for the arguments of the tuple to insert
+		%   the arguments of tuple to insert
+		% aditi__state::di, aditi__state::uo
+	;	aditi_insert(
+			pred_id		% base relation to insert into
+		)
+
+		% Apply a filter to a relation.
+		% Arguments:
+		%   deletion condition (semidet `aditi_top_down' closure). 
+		%   aditi__state::di, aditi__state::uo
+	;	aditi_delete(
+			pred_id,	% base relation to delete from
+			aditi_builtin_syntax
+		)
+
+		% Insert or delete the tuples returned by a query.
+		% Arguments:
+		%   query to generate tuples to insert or delete
+		% 	(nondet `aditi_bottom_up' closure).
+		%   aditi__state::di, aditi__state::uo
+	;	aditi_bulk_operation(
+			aditi_bulk_operation,
+			pred_id		% base relation to insert into
+		)
+
+		% Modify the tuples in a relation.
+		% Arguments:
+		%   `det' or `semidet' `aditi_top_down' closure to
+		%       construct a new tuple from an old. This is
+ 		%   aditi__state::di, aditi__state::uo.
+	;	aditi_modify(
+			pred_id,	% base relation to modify
+			aditi_builtin_syntax
+		)
+	.
+
+	% Which syntax was used for an aditi_delete or aditi_modify
+	% call. The first syntax is prettier, the second is used
+	% where the closure to be passed in is not known at the call site.
+:- type aditi_builtin_syntax
+	--->	pred_term		% e.g.	aditi_delete(p(_, X) :- X = 1).
+	;	sym_name_and_closure	% e.g.	aditi_delete(p/2,
+					%	    (pred(X::in) is semidet :-
+					%		X = 1)
+					%	)
+	.
+
+:- type aditi_bulk_operation
+	--->	insert
+	;	delete
+	.
+
+:- type can_remove
+	--->	can_remove
+	;	cannot_remove.
 
 	% There may be two sorts of "builtin" predicates - those that we
 	% open-code using inline instructions (e.g. arithmetic predicates),
 	% and those which are still "internal", but for which we generate
 	% a call to an out-of-line procedure. At the moment there are no
 	% builtins of the second sort, although we used to handle call/N
-	% that wayay.
+	% that way.
 
 :- type builtin_state	--->	inline_builtin
 			;	out_of_line_builtin
@@ -233,6 +332,10 @@
 	;	functor(cons_id, list(prog_var))
 	;	lambda_goal(
 			pred_or_func, 
+			lambda_eval_method,
+					% should be `normal' except for
+					% closures executed by Aditi.
+			fix_aditi_state_modes,
 			list(prog_var),	% non-locals of the goal excluding
 					% the lambda quantified variables
 			list(prog_var),	% lambda quantified variables
@@ -242,6 +345,16 @@
 			hlds_goal
 		).
 
+	% For lambda expressions built automatically for Aditi updates
+	% the modes of `aditi__state' arguments may need to be fixed
+	% by purity.m because make_hlds.m does not know which relation
+	% is being updated, so it doesn't know which are the `aditi__state'
+	% arguments.
+:- type fix_aditi_state_modes
+	--->	modes_need_fixing
+	;	modes_are_ok
+	.
+
 :- type unification
 		% A construction unification is a unification with a functor
 		% or lambda expression which binds the LHS variable,
@@ -259,12 +372,22 @@
 					% expression, this is the list of
 					% the non-local variables of the
 					% lambda expression.
-			list(uni_mode)	% The list of modes of the arguments
+			list(uni_mode),	% The list of modes of the arguments
 					% sub-unifications.
 					% For a unification with a lambda
 					% expression, this is the list of
 					% modes of the non-local variables
 					% of the lambda expression.
+			maybe(cell_to_reuse),
+					% Cell to destructively update.
+			cell_is_unique,	% Can the cell be allocated
+					% in shared data.
+			maybe(rl_exprn_id)
+					% Index of the RL expression used to
+					% extract the relevant tuples
+					% from a relation using an index
+					% in the list of expressions for
+					% this module.
 		)
 
 		% A deconstruction unification is a unification with a functor
@@ -337,7 +460,7 @@
 
 		% a unification in an argument of a predicate call
 	;	call(
-			pred_call_id,	% the name and arity of the predicate
+			call_id,	% the name and arity of the predicate
 			int		% the argument number (first arg == 1)
 		).
 
@@ -365,6 +488,26 @@
 			unify_context	% the context of the unification
 		).
 
+	% Information used to perform structure reuse on a cell.
+:- type cell_to_reuse
+	---> cell_to_reuse(
+		prog_var,
+		cons_id,
+		list(bool)      % A `no' entry means that the corresponding
+				% argument already has the correct value
+				% and does not need to be filled in.
+	).
+
+	% Shared constant cells can be allocated in static data.
+	% Others must be created on the heap.
+	% `cell_is_unique' is always a safe approximation.
+:- type cell_is_unique
+	--->	cell_is_unique		% a unique copy of the cell must
+					% be created by the construction
+	;	cell_is_shared		% the construction may use a shared
+					% copy of the cell
+	.
+
 :- type hlds_goals == list(hlds_goal).
 
 :- type hlds_goal_info.
@@ -404,6 +547,17 @@
 
 :- type goal_path == list(goal_path_step).
 
+	% Given the variable info field from a pragma c_code, get all the
+	% variable names.
+:- pred get_pragma_c_var_names(list(maybe(pair(string, mode))), list(string)).
+:- mode get_pragma_c_var_names(in, out) is det.
+
+	% Get a description of a generic_call goal.
+:- pred hlds_goal__generic_call_id(generic_call, call_id).
+:- mode hlds_goal__generic_call_id(in, out) is det.
+
+%-----------------------------------------------------------------------------%
+
 :- implementation.
 
 	% NB. Don't forget to check goal_util__name_apart_goalinfo
@@ -493,6 +647,16 @@
 	),
 	get_pragma_c_var_names_2(MaybeNames, Names1, Names).
 
+hlds_goal__generic_call_id(higher_order(_, PorF, Arity),
+		generic_call(higher_order(PorF, Arity))).
+hlds_goal__generic_call_id(
+		class_method(_, _, ClassId, MethodId),
+		generic_call(class_method(ClassId, MethodId))).
+hlds_goal__generic_call_id(aditi_builtin(Builtin, Name),
+		generic_call(aditi_builtin(Builtin, Name))).
+
+%-----------------------------------------------------------------------------%
+
 :- interface.
 
 :- type unify_mode	==	pair(mode, mode).
@@ -1039,8 +1203,7 @@
 
 goal_is_atomic(conj([])).
 goal_is_atomic(disj([], _)).
-goal_is_atomic(higher_order_call(_,_,_,_,_,_)).
-goal_is_atomic(class_method_call(_,_,_,_,_,_)).
+goal_is_atomic(generic_call(_,_,_,_)).
 goal_is_atomic(call(_,_,_,_,_,_)).
 goal_is_atomic(unify(_,_,_,_,_)).
 goal_is_atomic(pragma_c_code(_,_,_,_,_,_,_)).
@@ -1169,7 +1332,7 @@
 	RHS = functor(ConsId, []),
 	Inst = bound(unique, [functor(ConsId, [])]),
 	Mode = (free -> Inst) - (Inst -> Inst),
-	Unification = construct(Var, ConsId, [], []),
+	Unification = construct(Var, ConsId, [], [], no, cell_is_unique, no),
 	Context = unify_context(explicit, []),
 	Goal = unify(Var, RHS, Mode, Unification, Context),
 	set__singleton_set(NonLocals, Var),
Index: compiler/hlds_module.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/hlds_module.m,v
retrieving revision 1.44
diff -u -u -r1.44 hlds_module.m
--- hlds_module.m	1999/04/30 08:23:46	1.44
+++ hlds_module.m	1999/05/16 02:17:35
@@ -1482,6 +1482,13 @@
 				sym_name, arity, list(pred_id)) is semidet.
 :- mode predicate_table_search_pf_sym_arity(in, in, in, in, out) is semidet.
 
+	% Search the table for predicates or functions matching
+	% this pred_or_func category and sym_name.
+
+:- pred predicate_table_search_pf_sym(predicate_table, pred_or_func,
+				sym_name, list(pred_id)) is semidet.
+:- mode predicate_table_search_pf_sym(in, in, in, out) is semidet.
+
 	% predicate_table_insert(PredTable0, PredInfo, NeedQual, PredId,
 	% 		PredTable).
 	% 
@@ -1915,6 +1922,12 @@
 		unqualified(Name), Arity, PredIdList) :-
 	predicate_table_search_pf_name_arity(PredicateTable, PredOrFunc,
 		Name, Arity, PredIdList).
+
+predicate_table_search_pf_sym(PredicateTable, predicate,
+		SymName, PredIdList) :-
+	predicate_table_search_pred_sym(PredicateTable, SymName, PredIdList).
+predicate_table_search_pf_sym(PredicateTable, function, SymName, PredIdList) :-
+	predicate_table_search_func_sym(PredicateTable, SymName, PredIdList).
 
 %-----------------------------------------------------------------------------%
 
--------------------------------------------------------------------------
mercury-developers mailing list
Post messages to:       mercury-developers at cs.mu.oz.au
Administrative Queries: owner-mercury-developers at cs.mu.oz.au
Subscriptions:          mercury-developers-request at cs.mu.oz.au
--------------------------------------------------------------------------



More information about the developers mailing list