[m-dev.] Tabling [1/3]

Fergus Henderson fjh at cs.mu.OZ.AU
Tue Mar 10 01:45:33 AEDT 1998


On 09-Mar-1998, Oliver Hutchison <ohutch at students.cs.mu.oz.au> wrote:
> 
> Tom or Zoltan would be the best people to review this diff?

Tom or Zoltan are welcome to review it,
but I couldn't resist having a look myself.

> Add support for tabling.
> 
> This change allows for both deterministic and non deterministic memoing, 
> minimal model semidet code and loop detection.

What about semidet memoing, nondet minimal model code, and
nondet loop detection?  Does it allow those?
(Please clarify this in the log message.)

Also it might be clearer to say "model_det/model_non/model_semi" instead of
"deterministic/nondeterministic/semidet".


You should document your changes in notes/compiler_design.html.

> compiler/modes.m:
> 	Make sure that all procedures with non normal evaluation have 
> 	no unique/partially instantiated modes. Produce error messages 
> 	if they do.

Why?

> compiler/purity.m:
> 	Make sure that only procedures with normal evaluation are 
> 	allowed to be impure/semipure.

Why?

I think it would make perfect sense to use `loopcheck' on an impure predicate.

`memo' and even `minimal_model' could also be very useful
for impure predicates; using these pragmas on impure predicates could
of course change the semantics, but I don't think that is a good reason
for forbidding it.

> compiler/simplify.m:
> 	Only report infinite recursion warning if a procedure has
> 	normal evaluation.

I think it would probably still be useful to issue this warning at
compile time even if there is a `pragma loopcheck', because in general
compile-time warnings are better than run-time errors.

> Index: compiler/det_report.m
> @@ -154,25 +154,79 @@
..
> +		{ proc_info_context(ProcInfo0, Context) },
> +		prog_out__write_context(Context),
> +		{ eval_method_to_string(EvalMethod0, EvalMethodS) },
> +		io__write_string("Error : `pragma "),

s/Error :/Error:/
       ^

> +		io__write_string(EvalMethodS),
> +		io__write_string(
> +"' declaration not allowed for procedure with determinism `"),
> +		mercury_output_det(InferredDetism),
> +		io__write_string("'."), io__nl,

Probably that error message often won't fit on one line,
so it would be better to wrap it over two lines.

> Index: compiler/hlds_pred.m
> --- hlds_pred.m	1998/03/03 17:34:35	1.46
> +++ hlds_pred.m	1998/03/05 02:26:20
...
> +	% The evaluation method that should be used for a pred
> +
> +:- type eval_method	--->	eval_normal		% normal mercury 
> +							% evaluation
> +			;	eval_memo		% memoing evaluation
> +			;	eval_loop_check		% memoing + loop check
> +			;	eval_minimal		% minimal model 
> +							% evaluation 
> +			;	eval_well_founded	% well founded model
> +							% evaluation
> +			;	if_valid(eval_method).	% ignore the eval model
> +							% if the detism of the 
> +							% proc is not valid for 
> +							% the eval model

You should add here a pointer to somewhere that documents
what the various evaluation models are.

> +:- interface.
> +
> +	% check if the given evaluation method is allowed with
> +	% the given code model
> +:- pred valid_code_model_for_eval_method(eval_method, code_model).
> +:- mode valid_code_model_for_eval_method(in, in) is semidet.
> +:- mode valid_code_model_for_eval_method(in, out) is multidet.
> +
> +:- pred get_actual_eval_method(eval_method, eval_method).
> +:- mode get_actual_eval_method(in, out) is det.
> +
> +:- pred eval_method_to_string(eval_method, string).
> +:- mode eval_method_to_string(in, out) is det.
> +
> +:- pred eval_method_need_stratification(eval_method).
> +:- mode eval_method_need_stratification(in) is semidet.
> +
> +:- pred eval_method_change_determinism(eval_method, determinism, 
> +		determinism).
> +:- mode eval_method_change_determinism(in, in, out) is det.

You should document all of these predicates.

> +	% XXX : We can't realy use the stratification check as it is to 
> +	% conservative.
> +eval_method_need_stratification(_) :-
> +	semidet_fail.	

s/realy/really/
s/to/too/
s/as/, because/

> --- inlining.m	1998/03/03 17:34:37	1.74
> +++ inlining.m	1998/03/05 02:04:25
> @@ -587,15 +587,26 @@
>  	% don't try to inline imported predicates, since we don't
>  	% have the code for them.
>  
> -	module_info_pred_info(ModuleInfo, PredId, PredInfo),
> +	module_info_pred_proc_info(ModuleInfo, PredId, ProcId, PredInfo, 
> +		ProcInfo),
>  	\+ pred_info_is_imported(PredInfo),
>  		% this next line catches the case of locally defined
>  		% unification predicates for imported types.
> +
>  	\+ (
>  		pred_info_is_pseudo_imported(PredInfo),
> +		
>  		hlds_pred__in_in_unification_proc_id(ProcId)
>  	),

I think the additional blank lines here impede understanding, 
rather than helping, since the code they separate is closely related
(more closely related than the adjacent code which is not separated
by any blank lines).

> +	% Only try to inline procedures which are evaluated using
> +	% normal evaluation. Currently we can't inline procs evaluated
> +	% using any of the other methods because the code genertor for

s/genertor/generator/

>  		module_add_pragma_fact_table(Pred, Arity, File, 
>  			Status, Context, Module0, Module, Info0, Info)
>  	;
> -		% don't worry about any pragma decs but c_code
> +		{ Pragma = tabled(Type, Name, Arity, PredOrFunc, Mode) }
> +	->
> +		globals__io_lookup_bool_option(type_layout, TypeLayout),
> +		(
> +			{ TypeLayout = yes }
> +		->
> +			module_add_pragma_tabled(Type, Name, Arity, PredOrFunc,
> +				Mode, Context, Module0, Module)
> +		;
> +			% XXX this is an error
> +			{ module_info_incr_errors(Module0, Module) }

You should fix this XXX by printing out an error message here.

> +module_add_pragma_tabled(EvalMethod, PredName, Arity0, MaybePredOrFunc, 
> +		MaybeModes,  Context, ModuleInfo0, ModuleInfo) --> 
> +	io__stderr_stream(StdErr),
> +	
> +	{ module_info_get_predicate_table(ModuleInfo0, PredicateTable0) }, 
> + 	
> +	% Find out if we are tabling a predicate or a function 
> +	(
> +		{ MaybePredOrFunc = yes(PredOrFunc0) }
> +	->
> +		{ PredOrFunc = PredOrFunc0 }
> +	;
> +		(
> +			{ predicate_table_search_sym_arity(PredicateTable0,
> +				PredName, Arity0, [PredId0]) }
> +		->
> +			{ predicate_table_get_preds(PredicateTable0, Preds0) },
> +			{ map__lookup(Preds0, PredId0, PredInfo0) },
> +			{ pred_info_get_is_pred_or_func(PredInfo0, PredOrFunc) }
> +		;
> +				% XXX Fix this when we fix all the other 
> +				% XXX pragmas that dont properly support this
> +				% XXX case
> +			{ error(
> +"module_add_pragma_tabled: predicate and function with same name/arity") }
> +		)
> +	),

You should not call error/1 here.
What you ought to do to handle the XXX case is the same as
what all the other similar pragmas do: if there are multiple matching
names, apply the pragma to all of them.   (You can do this easily
by making the rest of this predicate into a separate predicate, and
calling that predicate for each element of the list of pred_ids returned
from predicate_table_search_sym_arity, perhaps using list__foldl2.)

Make sure that you handle the case of a `pragma tabled' declaration
for a non-existant predicate properly (i.e. it would be a good idea
to include this one in a test case in tests/invalid).

> +++ modes.m	1998/03/05 23:42:13
...
> +proc_check_eval_methods([ProcId|Rest], PredId, ModuleInfo0, ModuleInfo) --> 
> +	{ module_info_pred_proc_info(ModuleInfo0, PredId, ProcId, 
> +		_, ProcInfo) },
> +	{ proc_info_eval_method(ProcInfo, EvalMethod) },
> +	( \+ { EvalMethod = eval_normal } ->

I think it would be simpler (and clearer) to write

	( { EvalMethod \= eval_normal } ->

> +			( { VerboseErrors = yes } ->
> +				io__write_string(
> +"	Perhaps there sould be a good message at this point?\n")

Yes, indeed there should!

> +:- pred only_fully_in_out_nonunique_modes(list(mode), module_info).
> +:- mode only_fully_in_out_nonunique_modes(in, in) is semidet.
> +
> +only_fully_in_out_nonunique_modes([], _).
> +only_fully_in_out_nonunique_modes([Mode|Rest], ModuleInfo) :-
> +	mode_get_insts(ModuleInfo, Mode, InitialInst, FinalInst),
> +	inst_is_not_partly_unique(ModuleInfo, InitialInst),
> +	inst_is_not_partly_unique(ModuleInfo, FinalInst),
> +	(
> +		inst_is_ground(ModuleInfo, InitialInst)	
> +	;
> +		inst_is_free(ModuleInfo, InitialInst),
> +		inst_is_ground(ModuleInfo, FinalInst)
> +	),
> +	only_fully_in_out_nonunique_modes(Rest, ModuleInfo).

Any particular reason to disallow free->free modes here?

> Index: compiler/prog_io_pragma.m
> ===================================================================
> RCS file: /home/staff/zs/imp/mercury/compiler/prog_io_pragma.m,v
> retrieving revision 1.13
> diff -u -r1.13 prog_io_pragma.m
> --- prog_io_pragma.m	1998/03/03 17:35:47	1.13
> +++ prog_io_pragma.m	1998/03/05 02:04:43
> @@ -431,10 +431,42 @@
>  
>  parse_pragma_type(ModuleName, "memo", PragmaTerms,
>  			ErrorTerm, _VarSet, Result) :-
> -	parse_simple_pragma(ModuleName, "memo",
> -		lambda([Name::in, Arity::in, Pragma::out] is det,
> -			Pragma = memo(Name, Arity)),
> -		PragmaTerms, ErrorTerm, Result).
> +	(
> +		PragmaTerms = [PragmaTerm]
> +	->
> +		parse_tabling_pragma(ModuleName, "memo", eval_memo, 
> +			PragmaTerm, Result)
> +	;
> +		Result = error(
> +	"wrong number of arguments in `pragma memo(...)' declaration",
> +			ErrorTerm)
> +				
> +	).
> +parse_pragma_type(ModuleName, "loop_check", PragmaTerms,
> +			ErrorTerm, _VarSet, Result) :-
> +	(
> +		PragmaTerms = [PragmaTerm]
> +	->
> +		parse_tabling_pragma(ModuleName, "loop_check", 
> +			eval_loop_check, PragmaTerm, Result)
> +	;
> +		Result = error(
> +	"wrong number of arguments in `pragma loop_check(...)' declaration",
> +			ErrorTerm)
> +	).				
> +parse_pragma_type(ModuleName, "minimal", PragmaTerms,
> +			ErrorTerm, _VarSet, Result) :-
> +	(
> +		PragmaTerms = [PragmaTerm]
> +	->
> +		parse_tabling_pragma(ModuleName, "minimal", 
> +			eval_minimal, PragmaTerm, Result)
> +	;
> +		Result = error(
> +	"wrong number of arguments in `pragma minimal(...)' declaration",
> +			ErrorTerm)
> +				
> +	).

I detect some duplicate code here.  It would be better to factor
the common code into `parse_tabling_pragma'.

> +parse_tabling_pragma(ModuleName, PragmaName, TablingType, 
> +		PredAndModesTerm0, Result) :-
> +    (
> +    		% Is this a simple pred/arity pragma
> +    	PredAndModesTerm0 = term__functor(term__atom("/"),
> +	    [PredNameTerm, ArityTerm], _)
> +    ->
> +	(
> +	    parse_qualified_term(ModuleName, PredNameTerm, PredAndModesTerm0, 
> +	    	"", ok(PredName, [])),

You should call parse_implicitly_qualified_term here, not
parse_qualified_term.  (I think this is just because you
haven't merged my recent changes into your version yet.)

> +	parse_qualified_term(ModuleName, PredAndModesTerm, PredAndModesTerm0,
> +			"tabled pragma declaration", PredNameResult),

The user won't necessarily know what a "tabled pragma declaration" is,
I think.  Better to use "`pragma <foo>' declaration", for the
appropriate value of <foo>.

> +	    (
> +	    	convert_mode_list(ModeList, Modes)
> +	    ->
> +	    	list__length(Modes, Arity0),
> +		(
> +			PredOrFunc = function
> +		->
> +			Arity is Arity0 - 1
> +		;
> +			Arity = Arity0
> +		),
> +		Result = ok(pragma(tabled(TablingType, PredName, Arity, 
> +			yes(PredOrFunc), yes(Modes))))
> +	    ;
> +		string__append("unknown mode in pragma ", PragmaName, 
> +			ErrorMessage),

When convert_mode_list fails, this indicates a syntax error in the modes,
not an "unknown mode".

> +:- pred error_invalid_eval_model_for_purity2(list(proc_id), proc_table,
> +		pred_or_func, module_info, purity, int, io__state, io__state).
> +:- mode error_invalid_eval_model_for_purity2(in, in, in, in, in, out, 
> +		di, uo) is det.
> +
> +error_invalid_eval_model_for_purity2([], _, _, _, _, 0) --> [].
> +error_invalid_eval_model_for_purity2([ProcId|Rest], Procs, PredOrFunc, Module, 

s/purity2/purity_2/g

> +		Purity, Errors) -->
> +	{ map__lookup(Procs, ProcId, ProcInfo) },
> +	{ proc_info_eval_method(ProcInfo, EvalMethod) },
> +	(
> +		{ EvalMethod \= eval_normal }
> +	->
> +		{ proc_info_context(ProcInfo, Context) },
> +		{ eval_method_to_string(EvalMethod, EvalMethodS) },
> +		prog_out__write_context(Context),
> +		io__write_string("Error: pragma "),
> +		io__write_string(EvalMethodS),
> +		io__write_string(" not allowed for "),
> +		hlds_out__write_pred_or_func(PredOrFunc),
> +		io__write_string(" with purity "),
> +		write_purity(Purity),
> +		io__write_string(".\n"),

You should put the EvalMethodS and the Purity inside single-quotes.
Also, the message is likely to not fit on one line, so it would be
better to wrap it over two lines.

Or alternatively, it may be better to change the message from

	Error: pragma `minimal_model' not allowed for predicate with purity
	`semipure'.

to

	Error: pragma `memo' not allowed for semipure predicate.


Also, it should say "predicates" rather than "predicate".
                              ^

> +		{ Errors0 =  1 }

s/  1/ 1/
  ^^  ^

> Index: compiler/switch_detection.m
> ===================================================================
> RCS file: /home/staff/zs/imp/mercury/compiler/switch_detection.m,v
> retrieving revision 1.80
> diff -u -r1.80 switch_detection.m
> --- switch_detection.m	1998/02/12 01:17:49	1.80
> +++ switch_detection.m	1998/02/19 00:51:48
> @@ -538,8 +538,10 @@
>  :- mode fix_case_list(in, in, out) is det.
>  
>  fix_case_list([], _, []).
> -fix_case_list([Functor - DisjList | Cases0], GoalInfo,
> +fix_case_list([Functor - DisjList0 | Cases0], GoalInfo,
>  		[case(Functor, Goal) | Cases]) :-
> +		% We need to put the list back the right way around.
> +	list__reverse(DisjList0, DisjList),
>  	disj_list_to_goal(DisjList, GoalInfo, Goal),
>  	fix_case_list(Cases0, GoalInfo, Cases).

That change wasn't mentioned in the log message.

-- 
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