[m-rev.] for review: track subterms through partial unifications

Ian MacLarty maclarty at cs.mu.OZ.AU
Sat Sep 3 22:47:32 AEST 2005


For review by anyone.

PLEASE NOTE: If you check out a workspace between when I commit this and
when it gets installed then you will not be able to do subterm dependency
tracking on the stage1 compiler (the stage2 compiler should be fine).
Also if you compile an old workspace with this new version of the compiler,
then subterm dependency tracking won't work -- you will need to update the
workspace first.

Estimated hours taken: 4
Branches: main

Allow subterms to be tracked through partial unifications in the
declarative debugger.
This involves adding a new type of atomic goal to the program representation
stored with the executable of programs compiled with `--trace rep'.

Remove the ``unsafe'' from the cast goal representation to bring the program
representation up to date with Mark's recent change.

browser/declarative_execution.m:
	Read partial unification atomic goals from bytecode.

browser/declarative_tree.m:
	Handle partial unifications when tracking a subterm.

compiler/prog_rep.m:
	If a construction or deconstruction unification is a partial
	unification then generate the new goal type instead of a construction
	or deconstruction.

	Make atomic_goal_info_to_byte_list return the list of variables bound
	by the atomic goal so we can check if a deconstruction is a
	partial unification (the LHS will be in the list of bound variables).

	Wrap the arguments of the RHS of the partial unification in a maybe
	type, so that we can tell which were input.

mdbcomp/program_representation.m:
	Add a new atomic goal `unify_partial_rep' to represent partial
	unifications.

tests/debugger/declarative/Mmakefile:
tests/debugger/declarative/partial.exp:
tests/debugger/declarative/partial.inp:
tests/debugger/declarative/partial.m:
	Test tracking of subterms through partial unifications.

Index: browser/declarative_execution.m
===================================================================
RCS file: /home/mercury1/repository/mercury/browser/declarative_execution.m,v
retrieving revision 1.44
diff -u -r1.44 declarative_execution.m
--- browser/declarative_execution.m	24 Aug 2005 09:07:07 -0000	1.44
+++ browser/declarative_execution.m	2 Sep 2005 10:53:44 -0000
@@ -1592,6 +1592,15 @@
 			read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
 				Info, AtomicGoal, Goal)
 		;
+			GoalType = goal_partial_unify,
+			read_var(VarNumRep, Bytecode, !Pos, Var),
+			read_cons_id(Bytecode, Label, !Pos, ConsId),
+			read_maybe_vars(VarNumRep, Bytecode, !Pos, MaybeVars),
+			AtomicGoal = unify_partial_rep(Var, ConsId,
+				MaybeVars),
+			read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
+				Info, AtomicGoal, Goal)
+		;
 			GoalType = goal_simple_test,
 			read_var(VarNumRep, Bytecode, !Pos, Var1),
 			read_var(VarNumRep, Bytecode, !Pos, Var2),
@@ -1627,10 +1636,10 @@
 			read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
 				Info, AtomicGoal, Goal)
 		;
-			GoalType = goal_unsafe_cast,
+			GoalType = goal_cast,
 			read_var(VarNumRep, Bytecode, !Pos, OutputVar),
 			read_var(VarNumRep, Bytecode, !Pos, InputVar),
-			AtomicGoal = unsafe_cast_rep(OutputVar, InputVar),
+			AtomicGoal = cast_rep(OutputVar, InputVar),
 			read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
 				Info, AtomicGoal, Goal)
 		;
@@ -1721,6 +1730,33 @@
 		Vars = [Head | Tail]
 	;
 		Vars = []
+	).
+
+:- pred read_maybe_vars(var_num_rep::in, bytecode::in, int::in, int::out,
+	list(maybe(var_rep))::out) is det.
+
+read_maybe_vars(VarNumRep, Bytecode, !Pos, MaybeVars) :-
+	read_length(Bytecode, !Pos, Len),
+	read_maybe_vars_2(VarNumRep, Bytecode, Len, !Pos, MaybeVars).
+
+:- pred read_maybe_vars_2(var_num_rep::in, bytecode::in, int::in, int::in,
+	int::out, list(maybe(var_rep))::out) is det.
+
+read_maybe_vars_2(VarNumRep, Bytecode, N, !Pos, MaybeVars) :-
+	( N > 0 ->
+		read_byte(Bytecode, !Pos, YesOrNo),
+		( YesOrNo = 1 ->
+			read_var(VarNumRep, Bytecode, !Pos, Head),
+			MaybeHead = yes(Head)
+		; YesOrNo = 0 ->
+			MaybeHead = no
+		; throw(internal_error("read_maybe_vars_2",
+			"invalid yes or no flag"))
+		),
+		read_maybe_vars_2(VarNumRep, Bytecode, N - 1, !Pos, Tail),
+		MaybeVars = [MaybeHead | Tail]
+	;
+		MaybeVars = []
 	).

 :- pred read_var(var_num_rep::in, bytecode::in, int::in, int::out,
Index: browser/declarative_tree.m
===================================================================
RCS file: /home/mercury1/repository/mercury/browser/declarative_tree.m,v
retrieving revision 1.32
diff -u -r1.32 declarative_tree.m
--- browser/declarative_tree.m	24 Aug 2005 09:07:07 -0000	1.32
+++ browser/declarative_tree.m	3 Sep 2005 06:25:58 -0000
@@ -1616,6 +1616,43 @@
 				Store, ProcRep, Origin)
 		)
 	;
+		AtomicGoal = unify_partial_rep(_CellVar, _Cons, MaybeFieldVars),
+		( list.member(Var0, BoundVars) ->
+			(
+				TermPath0 = [],
+				Origin = primitive_op(File, Line, unification)
+			;
+				TermPath0 = [TermPathStep0 | TermPath],
+				list.index1_det(MaybeFieldVars, TermPathStep0,
+					MaybeVar),
+				(
+					MaybeVar = yes(Var),
+					%
+					% This partial unification bound the
+					% TermPathStep0'th argument of
+					% Var0.
+					%
+					traverse_primitives(Prims, Var,
+						TermPath, Store, ProcRep,
+						Origin)
+				;
+					MaybeVar = no,
+					%
+					% This partial unfication did not
+					% bind the TermPathStep0'th argument,
+					% so continue looking for the
+					% unification which did.
+					%
+					traverse_primitives(Prims, Var0,
+						TermPath0, Store, ProcRep,
+						Origin)
+				)
+			)
+		;
+			traverse_primitives(Prims, Var0, TermPath0,
+				Store, ProcRep, Origin)
+		)
+	;
 		AtomicGoal = unify_assign_rep(ToVar, FromVar),
 		% We handle assigns the same as we handle unsafe casts.
 		( list.member(Var0, BoundVars) ->
@@ -1628,8 +1665,8 @@
 				Store, ProcRep, Origin)
 		)
 	;
-		AtomicGoal = unsafe_cast_rep(ToVar, FromVar),
-		% We handle unsafe casts the same as we handle assigns.
+		AtomicGoal = cast_rep(ToVar, FromVar),
+		% We handle casts the same as we handle assigns.
 		( list.member(Var0, BoundVars) ->
 			decl_require(unify(Var0, ToVar),
 				"traverse_primitives", "bad unsafe_cast"),
Index: compiler/prog_rep.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_rep.m,v
retrieving revision 1.36
diff -u -r1.36 prog_rep.m
--- compiler/prog_rep.m	12 Aug 2005 05:14:14 -0000	1.36
+++ compiler/prog_rep.m	2 Sep 2005 10:18:55 -0000
@@ -48,6 +48,7 @@
 :- implementation.

 :- import_module backend_libs__bytecode_data.
+:- import_module check_hlds__inst_match.
 :- import_module hlds__code_model.
 :- import_module hlds__hlds_data.
 :- import_module mdbcomp__prim_data.
@@ -151,7 +152,7 @@
 goal_expr_to_byte_list(unify(_, _, _, Uni, _), GoalInfo, InstMap0, Info,
 		!StackInfo, Bytes) :-
 	atomic_goal_info_to_byte_list(GoalInfo, InstMap0, Info, !StackInfo,
-		AtomicBytes),
+		AtomicBytes, BoundVars),
 	(
 		Uni = assign(Target, Source),
 		Bytes = [goal_type_to_byte(goal_assign)] ++
@@ -159,21 +160,39 @@
 			var_to_byte_list(Info, Source) ++
 			AtomicBytes
 	;
-		Uni = construct(Var, ConsId, Args, _, _, _, _),
+		Uni = construct(Var, ConsId, Args, ArgModes, _, _, _),
 		cons_id_to_byte_list(ConsId, !StackInfo, ConsIdBytes),
-		Bytes = [goal_type_to_byte(goal_construct)] ++
-			var_to_byte_list(Info, Var) ++
-			ConsIdBytes ++
-			vars_to_byte_list(Info, Args) ++
-			AtomicBytes
+		( list.all_true(rhs_is_input(Info), ArgModes) ->
+			Bytes = [goal_type_to_byte(goal_construct)] ++
+				var_to_byte_list(Info, Var) ++
+				ConsIdBytes ++
+				vars_to_byte_list(Info, Args) ++
+				AtomicBytes
+		;
+			filter_input_args(Info, ArgModes, Args, MaybeArgs),
+			Bytes = [goal_type_to_byte(goal_partial_unify)] ++
+				var_to_byte_list(Info, Var) ++
+				ConsIdBytes ++
+				maybe_vars_to_byte_list(Info, MaybeArgs) ++
+				AtomicBytes
+		)
 	;
-		Uni = deconstruct(Var, ConsId, Args, _, _, _),
+		Uni = deconstruct(Var, ConsId, Args, ArgModes, _, _),
 		cons_id_to_byte_list(ConsId, !StackInfo, ConsIdBytes),
-		Bytes = [goal_type_to_byte(goal_deconstruct)] ++
-			var_to_byte_list(Info, Var) ++
-			ConsIdBytes ++
-			vars_to_byte_list(Info, Args) ++
-			AtomicBytes
+		( list.member(Var, BoundVars) ->
+			filter_input_args(Info, ArgModes, Args, MaybeArgs),
+			Bytes = [goal_type_to_byte(goal_partial_unify)] ++
+				var_to_byte_list(Info, Var) ++
+				ConsIdBytes ++
+				maybe_vars_to_byte_list(Info, MaybeArgs) ++
+				AtomicBytes
+		;
+			Bytes = [goal_type_to_byte(goal_deconstruct)] ++
+				var_to_byte_list(Info, Var) ++
+				ConsIdBytes ++
+				vars_to_byte_list(Info, Args) ++
+				AtomicBytes
+		)
 	;
 		Uni = simple_test(Var1, Var2),
 		Bytes = [goal_type_to_byte(goal_simple_test)] ++
@@ -205,7 +224,7 @@
 goal_expr_to_byte_list(generic_call(GenericCall, Args, _, _),
 		GoalInfo, InstMap0, Info, !StackInfo, Bytes) :-
 	atomic_goal_info_to_byte_list(GoalInfo, InstMap0, Info, !StackInfo,
-		AtomicBytes),
+		AtomicBytes, _),
 	(
 		GenericCall = higher_order(PredVar, _, _, _),
 		Bytes = [goal_type_to_byte(goal_ho_call)] ++
@@ -222,7 +241,7 @@
 	;
 		GenericCall = cast(_),
 		( Args = [InputArg, OutputArg] ->
-			Bytes = [goal_type_to_byte(goal_unsafe_cast)] ++
+			Bytes = [goal_type_to_byte(goal_cast)] ++
 				var_to_byte_list(Info, OutputArg) ++
 				var_to_byte_list(Info, InputArg) ++
 				AtomicBytes
@@ -237,7 +256,7 @@
 goal_expr_to_byte_list(call(PredId, _, Args, Builtin, _, _),
 		GoalInfo, InstMap0, Info, !StackInfo, Bytes) :-
 	atomic_goal_info_to_byte_list(GoalInfo, InstMap0, Info, !StackInfo,
-		AtomicBytes),
+		AtomicBytes, _),
 	module_info_pred_info(Info ^ module_info, PredId, PredInfo),
 	ModuleSymName = pred_info_module(PredInfo),
 	mdbcomp__prim_data__sym_name_to_string(ModuleSymName, ModuleName),
@@ -261,20 +280,42 @@
 		GoalInfo, InstMap0, Info, !StackInfo, Bytes) :-
 	ArgVars = list__map(foreign_arg_var, Args),
 	atomic_goal_info_to_byte_list(GoalInfo, InstMap0, Info, !StackInfo,
-		AtomicBytes),
+		AtomicBytes, _),
 	Bytes = [goal_type_to_byte(goal_foreign)] ++
 		vars_to_byte_list(Info, ArgVars) ++ AtomicBytes.
 goal_expr_to_byte_list(shorthand(_), _, _, _, !StackInfo, _) :-
 	% these should have been expanded out by now
 	error("goal_expr_to_byte_list: unexpected shorthand").

+:- pred rhs_is_input(prog_rep__info::in, uni_mode::in) is semidet.
+
+rhs_is_input(Info, (_ - RHSInitialInst) -> (_ - _)) :-
+	inst_is_bound(Info ^ module_info, RHSInitialInst).
+
+:- pred filter_input_args(prog_rep__info::in, list(uni_mode)::in,
+	list(prog_var)::in, list(maybe(prog_var))::out) is det.
+
+filter_input_args(_, [], [], []).
+filter_input_args(Info, [Mode | Modes], [Var | Vars], [MaybeVar | MaybeVars])
+		:-
+	( rhs_is_input(Info, Mode) ->
+		MaybeVar = yes(Var)
+	;
+		MaybeVar = no
+	),
+	filter_input_args(Info, Modes, Vars, MaybeVars).
+filter_input_args(_, [], [_ | _], _) :-
+	error("filter_input_args: more vars than modes").
+filter_input_args(_, [_ | _], [], _) :-
+	error("filter_input_args: more modes than vars").
 %---------------------------------------------------------------------------%

 :- pred atomic_goal_info_to_byte_list(hlds_goal_info::in, instmap::in,
 	prog_rep__info::in, stack_layout_info::in, stack_layout_info::out,
-	list(int)::out) is det.
+	list(int)::out, list(prog_var)::out) is det.

-atomic_goal_info_to_byte_list(GoalInfo, InstMap0, Info, !StackInfo, Bytes) :-
+atomic_goal_info_to_byte_list(GoalInfo, InstMap0, Info, !StackInfo, Bytes,
+		BoundVars) :-
 	goal_info_get_determinism(GoalInfo, Detism),
 	goal_info_get_context(GoalInfo, Context),
 	term__context_file(Context, FileName0),
@@ -288,12 +329,12 @@
 	instmap__apply_instmap_delta(InstMap0, InstMapDelta, InstMap),
 	instmap_changed_vars(InstMap0, InstMap, Info ^ vartypes,
 		Info ^ module_info, ChangedVars),
-	set__to_sorted_list(ChangedVars, ChangedVarList),
+	set__to_sorted_list(ChangedVars, BoundVars),
 	string_to_byte_list(FileName, !StackInfo, FileNameBytes),
 	Bytes = [represent_determinism(Detism)] ++
 		FileNameBytes ++
 		lineno_to_byte_list(LineNo) ++
-		vars_to_byte_list(Info, ChangedVarList).
+		vars_to_byte_list(Info, BoundVars).

 :- pred cons_id_to_byte_list(cons_id::in,
 	stack_layout_info::in, stack_layout_info::out, list(int)::out) is det.
@@ -398,6 +439,13 @@
 	length_to_byte_list(Vars) ++
 	list__condense(list__map(var_to_byte_list(Info), Vars)).

+:- func maybe_vars_to_byte_list(prog_rep__info, list(maybe(prog_var))) =
+	list(int).
+
+maybe_vars_to_byte_list(Info, Vars) =
+	length_to_byte_list(Vars) ++
+	list__condense(list__map(maybe_var_to_byte_list(Info), Vars)).
+
 :- func var_to_byte_list(prog_rep__info, prog_var) = list(int).

 var_to_byte_list(Info, Var) = Bytes :-
@@ -408,6 +456,22 @@
 	;
 		Info ^ var_num_rep = short,
 		short_to_byte_list(VarNum, Bytes)
+	).
+
+:- func maybe_var_to_byte_list(prog_rep__info, maybe(prog_var)) = list(int).
+
+maybe_var_to_byte_list(Info, MaybeVar) = Bytes :-
+	%
+	% This is not the most efficient representation, however
+	% maybe(prog_var)'s are only used for partial unifications
+	% which are rare.
+	%
+	(
+		MaybeVar = yes(Var),
+		Bytes = [1 | var_to_byte_list(Info, Var)]
+	;
+		MaybeVar = no,
+		Bytes = [0]
 	).

 :- func length_to_byte_list(list(T)) = list(int).
Index: mdbcomp/program_representation.m
===================================================================
RCS file: /home/mercury1/repository/mercury/mdbcomp/program_representation.m,v
retrieving revision 1.7
diff -u -r1.7 program_representation.m
--- mdbcomp/program_representation.m	24 Aug 2005 09:07:10 -0000	1.7
+++ mdbcomp/program_representation.m	3 Sep 2005 08:46:00 -0000
@@ -95,11 +95,25 @@
 			cons_id_rep,
 			list(var_rep)
 		)
+			%
+			% A partial unification of the form
+			% X = f(Y_1, Y_2, ..., Y_n)
+			% Where some of the Y_i are free after the unification
+			% and X is more instanciated after the unification.
+			%
+	;	unify_partial_rep(
+			var_rep,		% X
+			cons_id_rep,		% f
+				% The list of Y_i's.  Y_i's which are
+				% input are wrapped in `yes', while the other
+				% Y_i positions are `no'.
+			list(maybe(var_rep))
+		)
 	;	unify_assign_rep(
 			var_rep,		% target
 			var_rep			% source
 		)
-	;	unsafe_cast_rep(
+	;	cast_rep(
 			var_rep,		% target
 			var_rep			% source
 		)
@@ -263,8 +277,9 @@
 	;	goal_scope
 	;	goal_construct
 	;	goal_deconstruct
+	;	goal_partial_unify
 	;	goal_assign
-	;	goal_unsafe_cast
+	;	goal_cast
 	;	goal_simple_test
 	;	goal_foreign
 	;	goal_ho_call
@@ -299,9 +314,10 @@

 atomic_goal_generates_event(unify_construct_rep(_, _, _)) = no.
 atomic_goal_generates_event(unify_deconstruct_rep(_, _, _)) = no.
+atomic_goal_generates_event(unify_partial_rep(_, _, _)) = no.
 atomic_goal_generates_event(unify_assign_rep(_, _)) = no.
 atomic_goal_generates_event(unify_simple_test_rep(_, _)) = no.
-atomic_goal_generates_event(unsafe_cast_rep(_, _)) = no.
+atomic_goal_generates_event(cast_rep(_, _)) = no.
 atomic_goal_generates_event(pragma_foreign_code_rep(_)) = no.
 atomic_goal_generates_event(higher_order_call_rep(_, Args)) = yes(Args).
 atomic_goal_generates_event(method_call_rep(_, _, Args)) = yes(Args).
@@ -342,9 +358,10 @@

 atomic_goal_identifiable(unify_construct_rep(_, _, _)) = no.
 atomic_goal_identifiable(unify_deconstruct_rep(_, _, _)) = no.
+atomic_goal_identifiable(unify_partial_rep(_, _, _)) = no.
 atomic_goal_identifiable(unify_assign_rep(_, _)) = no.
 atomic_goal_identifiable(unify_simple_test_rep(_, _)) = no.
-atomic_goal_identifiable(unsafe_cast_rep(_, _)) = no.
+atomic_goal_identifiable(cast_rep(_, _)) = no.
 atomic_goal_identifiable(pragma_foreign_code_rep(_)) = no.
 atomic_goal_identifiable(higher_order_call_rep(_, _)) = no.
 atomic_goal_identifiable(method_call_rep(_, _, _)) = no.
@@ -454,14 +471,15 @@
 goal_type_byte(6, goal_scope).
 goal_type_byte(7, goal_construct).
 goal_type_byte(8, goal_deconstruct).
-goal_type_byte(9, goal_assign).
-goal_type_byte(10, goal_unsafe_cast).
-goal_type_byte(11, goal_simple_test).
-goal_type_byte(12, goal_foreign).
-goal_type_byte(13, goal_ho_call).
-goal_type_byte(14, goal_method_call).
-goal_type_byte(15, goal_plain_call).
-goal_type_byte(16, goal_builtin_call).
+goal_type_byte(9, goal_partial_unify).
+goal_type_byte(10, goal_assign).
+goal_type_byte(11, goal_cast).
+goal_type_byte(12, goal_simple_test).
+goal_type_byte(13, goal_foreign).
+goal_type_byte(14, goal_ho_call).
+goal_type_byte(15, goal_method_call).
+goal_type_byte(16, goal_plain_call).
+goal_type_byte(17, goal_builtin_call).

 %-----------------------------------------------------------------------------%

Index: tests/debugger/declarative/Mmakefile
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/declarative/Mmakefile,v
retrieving revision 1.80
diff -u -r1.80 Mmakefile
--- tests/debugger/declarative/Mmakefile	24 Aug 2005 09:07:12 -0000	1.80
+++ tests/debugger/declarative/Mmakefile	2 Sep 2005 11:09:19 -0000
@@ -52,6 +52,7 @@
 	neg_conj		\
 	oracle_db		\
 	output_term_dep		\
+	partial			\
 	pd			\
 	propositional		\
 	queens			\
@@ -396,6 +397,10 @@
 output_term_dep.out: output_term_dep output_term_dep.inp
 	$(MDB_STD) ./output_term_dep < output_term_dep.inp	\
 			> output_term_dep.out 2>&1 \
+	|| { grep . $@ /dev/null; exit 1; }
+
+partial.out: partial partial.inp
+	$(MDB_STD) ./partial < partial.inp > partial.out 2>&1 \
 	|| { grep . $@ /dev/null; exit 1; }

 pd.out: pd pd.inp
Index: tests/debugger/declarative/partial.exp
===================================================================
RCS file: tests/debugger/declarative/partial.exp
diff -N tests/debugger/declarative/partial.exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/debugger/declarative/partial.exp	2 Sep 2005 11:07:23 -0000
@@ -0,0 +1,36 @@
+      E1:     C1 CALL pred partial.main/2-0 (det) partial.m:11
+mdb> mdb> Contexts will not be printed.
+mdb> echo on
+Command echo enabled.
+mdb> step
+      E2:     C2 CALL pred partial.p/1-0 (det)
+mdb> finish
+      E3:     C2 EXIT pred partial.p/1-0 (det)
+mdb> dd
+p(t(1, 2))
+Valid? browse 1
+browser> cd 1
+browser> mark
+a(1)
+Valid? info
+Context of current question : partial.m:32 (partial.m:25)
+Search mode                 : top down
+The current question was chosen because the marked subterm was bound by
+the unification inside the predicate partial.a/1 (partial.m:32). The
+path to the subterm in the atom is 1.
+dd> undo
+p(t(1, 2))
+Valid? browse 1
+browser> cd 2
+browser> mark
+b(2)
+Valid? info
+Context of current question : partial.m:36 (partial.m:26)
+Search mode                 : top down
+The current question was chosen because the marked subterm was bound by
+the unification inside the predicate partial.b/1 (partial.m:36). The
+path to the subterm in the atom is 1.
+dd> quit
+Diagnosis aborted.
+      E3:     C2 EXIT pred partial.p/1-0 (det)
+mdb> quit -y
Index: tests/debugger/declarative/partial.inp
===================================================================
RCS file: tests/debugger/declarative/partial.inp
diff -N tests/debugger/declarative/partial.inp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/debugger/declarative/partial.inp	2 Sep 2005 11:06:48 -0000
@@ -0,0 +1,17 @@
+register --quiet
+context none
+echo on
+step
+finish
+dd
+browse 1
+cd 1
+mark
+info
+undo
+browse 1
+cd 2
+mark
+info
+quit
+quit -y
Index: tests/debugger/declarative/partial.m
===================================================================
RCS file: tests/debugger/declarative/partial.m
diff -N tests/debugger/declarative/partial.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/debugger/declarative/partial.m	2 Sep 2005 11:03:06 -0000
@@ -0,0 +1,36 @@
+:- module partial.
+
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is det.
+
+:- implementation.
+
+main(!IO) :-
+	p(X),
+	io.write(X, !IO),
+	nl(!IO).
+
+:- type t
+	--->	t(
+			a :: int,
+			b :: int
+		).
+
+:- pred p(t::out) is det.
+
+p(X) :-
+	a(A),
+	b(B),
+	X = t(A, _),
+	X = t(_, B).
+
+:- pred a(int::out) is det.
+
+a(1).
+
+:- pred b(int::out) is det.
+
+b(2).

--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list