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

Simon Taylor stayl at cs.mu.OZ.AU
Thu Jul 1 12:24:50 AEST 1999


 
> On 05-Jun-1999, Simon Taylor <stayl at cs.mu.OZ.AU> wrote:
> > Index: compiler/typecheck.m
> ...
> > +	% Filter out pred_ids which could not be used in the call's context.
> > +	% This is used to remove predicates which aren't base relations
> > +	% when typechecking an Aditi update.
> > +:- type filter_pred_ids == pred(module_info, list(pred_id), list(pred_id)).
> > +:- inst filter_pred_ids = (pred(in, in, out) is det).
> 
> There's an interesting design decision here.  There's two possible ways
> of handling that issue -- the check for whether something is a base
> relation could be done either before or after ambiguity resolution.
> I don't think it makes a big difference either way, but this is something
> that should be mentioned in the documentation.  It would also be a good
> idea to have a test case which tests this.

On thinking about this a bit more, I decided it was better to
do the check afterwards, and report an error in post_typecheck.m
if the updated relation is not a base relation, because it is
slightly simpler.

> > +		{ GenericCall0 = aditi_builtin(AditiBuiltin0, PredCallId) },
> > +		typecheck_aditi_builtin(PredCallId,
> > +			AditiBuiltin0, AditiBuiltin, Args),
> > +		{ GenericCall = aditi_builtin(AditiBuiltin, PredCallId) }
> > +	).
> 
> I think you should call `checkpoint' in the aditi_builtin case.

Fixed.

> > +typecheck_aditi_builtin(CallId, Builtin0, Builtin, Args) -->
> 
> The argument ordering here is a bit confusing, because it doesn't really
> match our normal argument ordering conventions.  In particular, all input
> arguments which are not part of an (in, out) or (di, uo) pair should come
> before any output arguments.
> 
> Also some documentation here explaining what this predicate is supposed to
> do would be very helpful.

Fixed.

> > +	{ get_state_args_det(Args, OtherArgs, State0, State) },
> 
> Why is this guaranteed to succeed?
> (Please document this.)

        % This must succeed because make_hlds.m does not add a clause
        % to the clauses_info if it contains Aditi updates with the
        % wrong number of arguments.
        { get_state_args_det(Args, OtherArgs, State0, State) },

> > +typecheck_aditi_builtin_2(CallId, aditi_insert(_),
> > +		aditi_insert(PredId), Args) -->
> > +	% The first `aditi__state' argument is always argument 2.
> > +	typecheck_call_pred(CallId, Args, PredId).
> 
> I don't understand how the comment relates to the code here.
> So I think you should explain things in a bit more detail.

That comment referred to a previous version of the code.
I've changed it to:

        % The tuple to insert has the same argument types
        % as the relation being inserted into.
        typecheck_call_pred(CallId, Args, PredId).

> 
> > +typecheck_aditi_builtin_2(CallId, aditi_delete(_, Syntax),
> > +		aditi_delete(PredId, Syntax), Args) -->
> > +	{ CallId = PredOrFunc - _ },
> > +	typecheck_aditi_builtin_higher_order_arg(CallId, PredOrFunc,
> > +		(aditi_top_down), Args, PredId).
> > +typecheck_aditi_builtin_2(CallId, aditi_bulk_operation(BulkOp, _), 
> > +		aditi_bulk_operation(BulkOp, PredId), Args) -->
> > +	{ CallId = PredOrFunc - _ },
> > +	typecheck_aditi_builtin_higher_order_arg(CallId, PredOrFunc,
> > +		(aditi_bottom_up), Args, PredId).
> 
> Why do you pass PredOrFunc as a separate argument here when it is already
> part of the CallId?

Fixed.

> > +typecheck_aditi_builtin_2(CallId, aditi_modify(_, Syntax),
> > +		aditi_modify(PredId, Syntax), Args) -->
> > +	% `aditi_modify' takes a closure which takes two sets of arguments
> > +	% corresponding to those of the base relation - one set input
> > +	% and one set output.
> > +	{ AdjustArgTypes = 
> > +	    lambda([ArgTypes0::in, ArgTypes::out] is det, (
> > +			list__append(ArgTypes0, ArgTypes0, ArgTypes1),
> > +			construct_higher_order_pred_type((aditi_top_down),
> > +				ArgTypes1, HOType),
> > +			ArgTypes = [HOType]
> > +	    )) },
> > +	typecheck_aditi_builtin_higher_order_arg_2(CallId,
> > +		Args, AdjustArgTypes, PredId).
> 
> Here `ArgTypes0', `ArgTypes1', and `ArgTypes' all have different meanings,
> rather than being related versions of a single data structure at different
> points in its history.  So I think it might be clearer if you used different
> names, e.g. perhaps `RelationArgTypes', `ClosureArgTypes', and
> `AditiModifyArgTypes'.

OK.
 
> In general the suffix `_2' is used for an auxilliary version of a
> predicate that is called only from the main predicate.  So it is not
> good style to call a predicate named foo_2 from anything other than foo.
> Here you call typecheck_aditi_builtin_higher_order_arg_2 from
> typecheck_aditi_builtin_2.

I've changed the name of `typecheck_aditi_builtin_higher_order_arg'
to `typecheck_aditi_delete_or_bulk_operation_closure'.
`typecheck_aditi_builtin_higher_order_arg_2' is now called
`typecheck_aditi_builtin_closure'.

> > +:- func aditi_builtin_first_state_arg(aditi_builtin, simple_call_id) = int.
> 
> A brief comment explaining what this function does would be helpful.

        % Return the index in the argument list of the first 
        % `aditi__state' DCG argument.

> > +:- pred typecheck_aditi_builtin_higher_order_arg(simple_call_id, pred_or_func,
> > +		lambda_eval_method, list(prog_var), pred_id,
> > +		typecheck_info, typecheck_info).
> > +:- mode typecheck_aditi_builtin_higher_order_arg(in, in, in, in, out,
> > +		typecheck_info_di, typecheck_info_uo) is det.
> 
> Likewise here.

        % Typecheck the closure passed to an `aditi_delete',
        % `aditi_bulk_insert' or `aditi_bulk_delete' which
        % determines which tuples are inserted or deleted.
        % The argument types of the closure are the same as the
        % argument types of the base relation being updated.

> > +typecheck_aditi_builtin_higher_order_arg(CallId, PredOrFunc,
> > +		EvalMethod, Args, PredId) -->
> > +	{ AdjustArgTypes = 
> > +	    lambda([ArgTypes0::in, ArgTypes::out] is det, (
> > +			construct_higher_order_type(PredOrFunc,
> > +				EvalMethod, ArgTypes0, HOType),
> > +			ArgTypes = [HOType]
> > +	    )) },
> > +	typecheck_aditi_builtin_higher_order_arg_2(CallId,
> > +		Args, AdjustArgTypes, PredId).
> > +
> > +:- pred typecheck_aditi_builtin_higher_order_arg_2(simple_call_id,
> > +		list(prog_var), adjust_arg_types, pred_id,
> > +		typecheck_info, typecheck_info).
> > +:- mode typecheck_aditi_builtin_higher_order_arg_2(in,
> > +		in, in(adjust_arg_types), out,
> > +		typecheck_info_di, typecheck_info_uo) is det.
> > +
> > +typecheck_aditi_builtin_higher_order_arg_2(CallId,
> > +		OtherArgs, AdjustArgTypes, PredId) -->
> > +	( { OtherArgs = [HOArg] } ->
> > +		{ FilterPredIds =
> > +		    lambda([Module::in, PredIds0::in, PredIds::out] is det, (
> > +			list__filter(hlds_pred__is_base_relation(Module),
> > +				PredIds0, PredIds)
> > +		    )) },
> > +		typecheck_call_pred_2(CallId, [HOArg],
> > +			FilterPredIds, AdjustArgTypes, PredId)
> 
> Here again you're calling a `_2' version of a predicate.

I've changed the name to `typecheck_call_pred_adjust_args_types'.
This predicate no longer filters the pred_ids.

> > +	;
> > +		{ error(
> > +		"typecheck_aditi_builtin: incorrect arity for aditi_delete") }
> > +	).
> 
> Are you sure that can only get called for aditi_delete builtins?

No, that was a cut-and paste error.

                % An error should have been reported by make_hlds.m.
                { error(
                "typecheck_aditi_builtin: incorrect arity for builtin") }

> 
> > +:- pred check_aditi_state_args(int, prog_var, prog_var,
> > +		typecheck_info, typecheck_info).
> > +:- mode check_aditi_state_args(in, in, in,
> > +		typecheck_info_di, typecheck_info_uo) is det.
> > +
> > +check_aditi_state_args(FirstStateIndex, AditiState0, AditiState) -->
> > +	{ construct_type(qualified(unqualified("aditi"), "state") - 0,
> > +		[], StateType) },
> > +	typecheck_var_has_type_list([AditiState0, AditiState],
> > +		[StateType, StateType], FirstStateIndex).
> 
> The variable names `AditiState0' and `AditiState' are a little confusing,
> partly because these variables stand for variables, not for states, and
> partly because the `Foo0'/`Foo' convention normally suggests that `Foo'
> has an output mode, whereas here both have mode `in'.  I suggest using
> `AditiState0Var' and `AditiStateVar',
> or `AditiStateVarA' and `AditiStateVarB',
> or `AditiOldStateVar' and `AditiNewStateVar',
> or something like that.

Fixed (I've also done this in other modules such as make_hlds.m).
 
> unique_modes.m:

> > +		% Setting the context to `higher_order_call(...)' for
> > +		% class method calls is a little white lie. 
> > +		% However, since there can't really be a unique 
> >  		% mode error in a class_method_call, this lie will never be
> >  		% used. There can't be an error because the class_method_call 
> >  		% is introduced by the compiler as the body of a class method.
> > -	mode_info_set_call_context(higher_order_call(predicate)),
> > +	mode_info_set_call_context(call(CallId)),
> 
> I think that comment is obsolete now, isn't it?

Yes.

> > +	{ mode_info_get_module_info(ModeInfo, ModuleInfo) },
> > +	{ module_info_pred_info(ModuleInfo, PredId, PredInfo) },
> > +	{ pred_info_get_call_id(PredInfo, CallId) },	
> 
> Those three lines occurred about four times in modes.m and unique_modes.m;
> I think that is enough times to make it worthwhile adding a new subroutine.

I've added `mode_info_get_call_id'.

> unused_args.m:
> > +traverse_goal(_, generic_call(GenericCall,Args,_,_), UseInf0, UseInf) :-
> 
> s/,Args,_,_/, Args, _, _/

Fixed.

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