[m-rev.] for review: improve typeclass constraints error messages

Mark Brown mark at csse.unimelb.edu.au
Wed Aug 19 14:14:20 AEST 2009


On 19-Aug-2009, Peter Wang <novalazy at gmail.com> wrote:
> On 2009-08-18, Julien Fischer <juliensf at csse.unimelb.edu.au> wrote:
> > 
> > One suggestion:
> > 
> > It might be nicer to say what the goals are, for example instead of
> > 
> > 	a goal here, and
> > 	a goal here.
> > 
> > this:
> > 	the call to foo/4, and
> > 	the unification between `X' and `Y'.
> > 
> > 
> > The diff looks fine otherwise.
> 
> That sounds like too much work so I attempted it only for some calls.

That's okay; most types of goal can never be the source of a typeclass
constraint anyway.

> Committed with these changes.
> 
> diff --git a/compiler/post_typecheck.m b/compiler/post_typecheck.m
> index 94eac3e..7d00e4f 100644
> --- a/compiler/post_typecheck.m
> +++ b/compiler/post_typecheck.m
> @@ -373,9 +373,10 @@ report_unsatisfied_constraints(ModuleInfo, PredId, PredInfo, Constraints,
>          "The constraint is due to:",
>          "The constraints are due to:"),
>      ContextMsgStart = error_msg(yes(Context), do_not_treat_as_first, 0,
> -        [always([fixed(DueTo)])]),
> -    Contexts = find_constraint_contexts(PredInfo, Constraints),
> -    ContextMsgs = constraint_contexts_to_error_msgs(Contexts),
> +        [always([words(DueTo)])]),
> +    ConstrainedGoals = find_constrained_goals(PredInfo, Constraints),
> +    ContextMsgs = constrained_goals_to_error_msgs(ModuleInfo,
> +        ConstrainedGoals),
>  
>      Spec = error_spec(severity_error, phase_type_check,
>          [Msg, ContextMsgStart | ContextMsgs]),
> @@ -390,12 +391,12 @@ constraint_to_error_piece(TVarset, Constraint) =
>      % A prog_constraint cannot contain context information (see the comment on
>      % the type definition). However, a constraint_id happens to contain a
>      % goal_path so we can look up a constraint_id for a prog_constraint, then
> -    % use the goal_path to reach the goal to get the context.
> +    % use the goal_path to reach the goal.
>      %
> -:- func find_constraint_contexts(pred_info, list(prog_constraint))
> -    = list(prog_context).
> +:- func find_constrained_goals(pred_info, list(prog_constraint))
> +    = list(hlds_goal).
>  
> -find_constraint_contexts(PredInfo, Constraints) = Contexts :-
> +find_constrained_goals(PredInfo, Constraints) = Goals :-
>      pred_info_get_clauses_info(PredInfo, ClausesInfo),
>      clauses_info_clauses_only(ClausesInfo, Clauses),
>  
> @@ -405,38 +406,80 @@ find_constraint_contexts(PredInfo, Constraints) = Contexts :-
>      ConstraintIds = set.union_list(ConstraintIdSets),
>  
>      % This could be more efficient.
> -    FindContexts = (pred(Context::out) is nondet :-
> +    FindGoals = (pred(Goal::out) is nondet :-
>          set.member(ConstraintId, ConstraintIds),
>          ConstraintId = constraint_id(_, ConstraintGoalPath, _),
> -        promise_equivalent_solutions [Context] (
> +        promise_equivalent_solutions [Goal] (
>              list.member(Clause, Clauses),
>              goal_contains_goal(Clause ^ clause_body, Goal),
>              Goal = hlds_goal(_, GoalInfo),
>              GoalPath = goal_info_get_goal_path(GoalInfo),
> -            GoalPath = ConstraintGoalPath,
> -            Context = goal_info_get_context(GoalInfo)
> +            GoalPath = ConstraintGoalPath
>          )
>      ),
> -    solutions(FindContexts, Contexts).
> +    solutions(FindGoals, Goals).
>  
> -:- func constraint_contexts_to_error_msgs(list(prog_context))
> +:- func constrained_goals_to_error_msgs(module_info, list(hlds_goal))
>      = list(error_msg).
>  
> -constraint_contexts_to_error_msgs([]) = [].
> -constraint_contexts_to_error_msgs([Context | Contexts]) = [Msg | Msgs] :-
> +constrained_goals_to_error_msgs(_, []) = [].
> +constrained_goals_to_error_msgs(ModuleInfo, [Goal | Goals]) = [Msg | Msgs] :-
>      (
> -        Contexts = [_, _ | _],
> -        Words = "a goal here,"
> +        Goals = [_, _ | _],
> +        Words = describe_constrained_goal(ModuleInfo, Goal),
> +        Suffix = suffix(",")
>      ;
> -        Contexts = [_],
> -        Words = "a goal here, and"
> +        Goals = [_],
> +        Words = describe_constrained_goal(ModuleInfo, Goal),
> +        Suffix = suffix(", and")
>      ;
> -        Contexts = [],
> -        Words = "a goal here."
> +        Goals = [],
> +        Words = describe_constrained_goal(ModuleInfo, Goal),
> +        Suffix = suffix(".")
>      ),
> +    Goal = hlds_goal(_, GoalInfo),
> +    Context = goal_info_get_context(GoalInfo),
>      Msg = error_msg(yes(Context), do_not_treat_as_first, 1,
> -        [always([fixed(Words)])]),
> -    Msgs = constraint_contexts_to_error_msgs(Contexts).
> +        [always(Words ++ [Suffix])]),
> +    Msgs = constrained_goals_to_error_msgs(ModuleInfo, Goals).
> +
> +:- func describe_constrained_goal(module_info, hlds_goal)
> +    = list(format_component).
> +
> +describe_constrained_goal(ModuleInfo, Goal) = Pieces :-
> +    Goal = hlds_goal(GoalExpr, _),
> +    (
> +        (
> +            GoalExpr = plain_call(PredId, _, _, _, _, _),
> +            CallPieces = describe_one_pred_name(ModuleInfo,
> +                should_module_qualify, PredId)
> +        ;
> +            GoalExpr = generic_call(GenericCall, _, _, _),
> +            GenericCall = class_method(_, _, _, SimpleCallId),
> +            CallPieces = [simple_call(SimpleCallId)]
> +        ;
> +            GoalExpr = call_foreign_proc(_, PredId, _, _, _, _, _),
> +            CallPieces = describe_one_pred_name(ModuleInfo,
> +                should_module_qualify, PredId)
> +        ),
> +        Pieces = [words("the call to") | CallPieces]
> +    ;
> +        GoalExpr = generic_call(higher_order(_, _, _, _), _, _, _),
> +        Pieces = [words("a higher-order call here")]
> +    ;
> +        ( GoalExpr = generic_call(event_call(_), _, _, _)
> +        ; GoalExpr = generic_call(cast(_), _, _, _)
> +        ; GoalExpr = unify(_, _, _, _, _)
> +        ; GoalExpr = conj(_, _)
> +        ; GoalExpr = disj(_)
> +        ; GoalExpr = switch(_, _, _)
> +        ; GoalExpr = negation(_)
> +        ; GoalExpr = scope(_, _)
> +        ; GoalExpr = if_then_else(_, _, _, _)
> +        ; GoalExpr = shorthand(_)
> +        ),
> +        Pieces = [words("a goal here")]
> +    ).

The only other goals that can be the source of a typeclass constraint are
constructions of closures and constructions of existentially typed terms.
Adding cases for "a closure construction here" and "an existentially typed
construction here" would be useful, I think.  It should be easy to identify
these goals from the unify_rhs.

Otherwise, simply adding a case for "a unification here" would be fine.

This is a great change, BTW.  Thanks!

Cheers,
Mark.

>  
>  %-----------------------------------------------------------------------------%
>  
> diff --git a/tests/invalid/typeclass_test_8.err_exp b/tests/invalid/typeclass_test_8.err_exp
> index d610001..cb58178 100644
> --- a/tests/invalid/typeclass_test_8.err_exp
> +++ b/tests/invalid/typeclass_test_8.err_exp
> @@ -14,5 +14,7 @@ typeclass_test_8.m:004: In predicate `main'/2:
>  typeclass_test_8.m:004:   type error: unsatisfied typeclass constraint:
>  typeclass_test_8.m:004:     `typeclass_test_8.fooable(T)'
>  typeclass_test_8.m:004:   The constraint is due to:
> -typeclass_test_8.m:013:     a goal here, and
> -typeclass_test_8.m:014:     a goal here.
> +typeclass_test_8.m:013:     the call to type class predicate method
> +typeclass_test_8.m:013:     `typeclass_test_8.foo'/1, and
> +typeclass_test_8.m:014:     the call to type class predicate method
> +typeclass_test_8.m:014:     `typeclass_test_8.bar'/1.
> 
> --------------------------------------------------------------------------
> mercury-reviews mailing list
> Post messages to:       mercury-reviews at csse.unimelb.edu.au
> Administrative Queries: owner-mercury-reviews at csse.unimelb.edu.au
> Subscriptions:          mercury-reviews-request at csse.unimelb.edu.au
> --------------------------------------------------------------------------
--------------------------------------------------------------------------
mercury-reviews mailing list
Post messages to:       mercury-reviews at csse.unimelb.edu.au
Administrative Queries: owner-mercury-reviews at csse.unimelb.edu.au
Subscriptions:          mercury-reviews-request at csse.unimelb.edu.au
--------------------------------------------------------------------------



More information about the reviews mailing list