diff: tabling code (compiler only)

Fergus Henderson fjh at mundook.cs.mu.OZ.AU
Thu Sep 25 17:50:54 AEST 1997


Oliver Hutchison <ohutch at students.cs.mu.OZ.AU> writes:

>Added code to handle tabling pragmas and to generate tabling code for the
>memo and loop_check cases. 
>The changes to the runtime are not included in this diff.

First, I should out that the design we chose for this is possibly
a suboptimal design.  We decided to handle tabling at code generation
(HLDS -> LLDS) time, rather than via a HLDS transformation.
The reason for this decision was that the code resulting from the
tabling transformation is internally non-logical, even though it has
a logical interface.

However, Peter Schachte is doing some work to add support to the compiler
for being able to optimize impure code, by keeping an `impure' flag in
every goal_info, and being careful to apply optimizations that require
purity only to pure goals.  The reason for this is so that we can apply
optimizations such as inlining, specialization and so forth, that don't
require purity.  This will for example allow us to avoid the overhead of
higher-order calls for solutions/2.

Nevertheless, the current design is OK, even if not optimal.
So I'm not suggesting we change it at this point.
But we might want to revisit it after Peter's stuff is in.

>compiler/prog_io_pragma.m :
>	Removed code to parse memo pragmas.
>	Added code to parse tabled pragmas. The tabling pragmas can be
>	defined in two ways 1) you can use pred name + modes 2) you can
>	use pred name + arity. If pred name and arity is given then only 
>	the procs with modes for which the tabling model are valid will 
>	be generated with tables.

I think that it would be a good idea to report at least a warning
if a tabling model declaration is not appropriate for all modes of
a predicate.

>Index: compiler/code_gen.m
>+:- pred generate_category_code(code_model, eval_model, hlds_goal, code_tree, 
>+		maybe(int), code_info, code_info).
>+:- mode generate_category_code(in, in, in, out, out, in, out) is det.
> 
>-generate_category_code(model_det, Goal, Instrs, Used) -->
>+generate_category_code(model_det, EvalModel, Goal, Instrs, Used) -->
> 		% generate the code for the body of the clause
> 	(
>+		{ EvalModel = model_memo 
>+		; EvalModel = model_loop_check }
>+	->

I think it would be clearer to use `model_foo' only for code models,
and to use `eval_foo' for evaluation models.  I think it might
also be clearer to use the term "evaluation method" rather than
"evaluation model".

>+		% Now see if the evaluation model can change the detism
>+	proc_info_eval_model(Proc0, EvalModel),
>+	eval_model_change_to_determinism(EvalModel, Detism2, Detism),		

I think `change_determinism' would make more sense than
`change_to_determinism'.

>+		prog_out__write_context(Context),
>+		{ eval_model_to_string(EvalModel0, EvalModelS) },
>+		{ string__append_list([
>+			"Error: Invalid determinism for 'pragma ",
>+			EvalModelS,
>+			"(...)'\n"], ErrorMessage) },
>+		io__write_string(ErrorMessage),
>+		{ module_info_incr_errors(ModuleInfo1, ModuleInfo) }

The first ' should be ` instead.
The "I" in "Invalid" should not be capitalized.

I think the message would be clearer if phrased as

	Error: `pragma foo' declaration not allowed
	for procedure with determinism `bar'.

Another point is that it might be best to say "Sorry, not implemented:"
rather than "Error:".

Also, it would be helpful to print out a more informative
message if --verbose-errors was specified, saying which
determinisms were valid for that EvalModel.

>+	% The evaluation model that should be used for a pred
>+
>+:- type eval_model	--->	model_normal		% normal mercury 
>+							% evaluation
>+			;	model_memo		% memoing evaluation
>+			;	model_loop_check	% memoing + loop check
>+			;	model_minimal		% minimal model 
>+							% evaluation
>+			;	model_well_founded	% well founded model
>+							% evaluation
>+			;	if_valid(eval_model).	% ignore the eval model
>+							% if the detism of the 
>+							% proc is not valid for 
>+							% the eval model

I think you should document what is meant by these different terms,
"memoing evaluation", "well founded model evaluation", etc.,

>+eval_model_change_to_determinism(model_minimal, det, semidet).
...
>+eval_model_change_to_determinism(model_minimal, multidet, multidet).
>+eval_model_change_to_determinism(model_minimal, cc_multidet, cc_multidet).
>+eval_model_change_to_determinism(model_minimal, erroneous, erroneous).

Aren't the entries for multidet, cc_multidet, and erroneous wrong?
Should they produce a determinism of nondet, cc_nondet, and failure
respectively?

It is probably best to write this as

	eval_model_change_to_determinism(model_minimal, Det0, Det) :-
		det_conjunction_detism(semidet, Det0, Det).

>+	% Only try to inline procedures which are evaluated using
>+	% normal evlaluation
>+
>+	proc_info_eval_model(ProcInfo, model_normal),

You misspelt "evaluation".

Also, it would be good to put a comment here explaining _why_
we don't try inlining predicates with abnormal evaluation methods.

>+module_add_pragma_tabled(TableModel, PredName, Arity, PredOrFunc, MModes,  
>+			Status, Context, ModuleInfo0, ModuleInfo) --> 
...
>+		io__write_string(TableModelS),
>+		io__write_string("' for "),
>+		hlds_out__write_call_id(PredOrFunc, PredName/Arity),
>+		io__write_string("...\n")

>+		(
>+			% if we know the modes we know the pred/func too
>+			{ MModes = yes(_),
>+			predicate_table_search_pf_sym_arity(PredicateTable0,
>+				PredOrFunc, PredName, Arity, [PredId0]) }
>+		;
>+			{ MModes = no,
>+			predicate_table_search_sym_arity(PredicateTable0,
>+				PredName, Arity, [PredId0]) }
>+		)

If MModes = no, does that mean that the PredOrFunc value printed out
in the progress message may be wrong?

>+		io__write_string("declaration for imported "),
>+		hlds_out__write_call_id(PredOrFunc, PredName/Arity),
>+		io__write_string(".\n"),
>+                io__set_output_stream(OldStream2, _)

Inconsistent use of spaces & tabs.

>+		% we have to make sure the tabled preds are stratified

Is that true?  Why?

I don't see any need to check stratification for `pragma loop_check'
preds, for example.

>+:- pred parse_tabling_pragma(module_name, string, eval_model, term, 
>+	maybe1(item)).
>+:- mode parse_tabling_pragma(in, in, in, in, out) is det.
>+
>+parse_tabling_pragma(ModuleName, PragmaName, TablingType, 
>+		PredAndModesTerm0, Result) :-
...
>+	Result = error("unexpected variable in pragma(tabled, ...)",
>+						PredAndModesTerm0)

You should use PragmaName rather than "tabled" in that error message.
Also it should be `pragma foo(...)', or perhaps just `pragma foo',
rather than `pragma (foo, ...)'.

> :- module table_gen.
...
> :- implementation.
>
> :- import_module type_util, code_aux.
> :- import_module bool.
...
> :- import_module bool, char, int, string, list, term.
> :- import_module map, tree, std_util, require, set, varset.

The first `import_module bool' is redundant -- delete it.

>	% generate code to save table address
>	{ CodeC2 = node([assign(stackvar(NS+1), lval(TempReg)) -
>		"Save table address"]) },
...
>		tree(node([incr_sp(NS+1, PredName) - "Allocate stack frame"]),

Can you please use

	NS1 is NS + 1

rather than using `NS+1' inline?
Otherwise it won't work as Prolog code.

>	gen_save_answers(NS+1, CodeE),
>	{ CodeB1 = node([ goto(succip) - "Return from procedure call"]) },
>	{ CodeB0 = node([ decr_sp(NS+1) - "Deallocate stack frame" ]) }, 

Ditto.

>	% generate code to save table address
>	{ CodeC2 = node([assign(stackvar(NS+1), lval(TempReg)) -
>		"Save table address"]) },
>	
>	% Allocate stack frame with one extra slot for the table address
>	{ CodeB = tree(
>		CodeC1,
>		tree(node([incr_sp(NS+1, PredName) - "Allocate stack frame"]),
>			CodeC2) 
>		)},

Ditto.

>        { UnLink = tree(
>        	CodeC,
>                node([
>                	decr_sp(NS+1) - "Deallocate stack frame"
>                ])
>        ) },
>	gen_save_answers(NS+1, SaveAnswers),
>	gen_save_failure(NS+1, SaveFailure),

Ditto.

>"{
>		static Word %s = (Word)NULL;
>		%s = (Word)&%s;
>	}
>", 

Please insert a space after the ')', e.g. "(Word) NULL"
rather than "(Word)NULL".

>gen_answer_check(TempReg, OutputArgs, CanFail, LoopCheck, Code) :-
>	(
>		LoopCheck = yes
>	->
>		string__format(
>"	if (MEMO_WORKING_ON_ANS(%s))
>		MEMO_DIE_IN_HELL();
>", 

I think it would be a good idea to say which predicate was looping,
i.e. you should pass the predicate name as a string to the
MEMO_DIE_IN_HELL() macro.

Also, could you please rename all the MEMO_* macros as
MR_MEMO_*?

>		"MEMO_TABLE_INT((Word**)%s, (Integer)%s);\n",

Insert a space after the cast operators.

>		error("gen_lookup: unexpected type")
>	).
>
>gen_lookup(pred_type, _, _Reg, _TempReg, _, _Code) :-
>	error("gen_lookup: pred_type unsupported").
>
>gen_lookup(polymorphic_type, _Type, _Reg, _TempReg, _Module, _Code) :-
>	error("gen_lookup: polymorphic types unsupported").

These sorts of errors should be detected at semantic analysis
time (i.e. in the compiler front-end, not the back-end)
and reported there.

> :- pred reg_to_string(lval, string).
> :- mode reg_to_string(in, out) is det.
>
>reg_to_string(Reg, RegString) :-
>	(
>		Reg = reg(r, N)
>	->
>        	(  N > 32 ->
>			string__format("r(%u)", [i(N)], RegString)
>        	;
>			string__format("r%u", [i(N)], RegString)
>        	)
>	;
>        	error("reg_to_string: unsupported reg type")
>	).
>
>
> :- pred get_free_reg(exprn_info, list(lval), pair(lval, string)).
> :- mode get_free_reg(in, in, out) is det.
>
>get_free_reg(ExprnInfo0, LiveRegs, FreeReg) :-
>	mark_regs_as_live(LiveRegs, ExprnInfo0, ExprnInfo),
>	code_exprn__acquire_reg_prefer_given(r, 1, FreeRegN, ExprnInfo, _),
>	reg_to_string(FreeRegN, FreeRegS),
>	FreeReg = FreeRegN - FreeRegS.
>
>
> :- pred mark_regs_as_live(list(lval), exprn_info, exprn_info).
> :- mode mark_regs_as_live(in, in, out) is det.
>
>mark_regs_as_live([], ExprnInfo, ExprnInfo).
>mark_regs_as_live([Reg|Regs]) -->
>	code_exprn__lock_reg(Reg),
>	mark_regs_as_live(Regs).

These should probably go in code_util.m or llds_util.m or somewhere
like that.

When do the locked registers get unlocked?

--
Fergus Henderson <fjh at cs.mu.oz.au>   |  "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh>   |  of excellence is a lethal habit"
PGP: finger fjh at 128.250.37.3         |     -- the last words of T. S. Garp.



More information about the developers mailing list