[m-rev.] diff: "preceding" vs. "corresponding" in error messages

Julien Fischer jfischer at opturion.com
Mon Aug 25 15:00:52 AEST 2014


Improve the wording of some error messages.

Use the word "corresponding" instead of "preceding" in error messages like:

     Error: clause for predicate `foo'/0 without preceding `:- pred'
     declaration.

The language imposes no ordering on declarations so there is no sense in which
the `:- pred' declaration has to precede the clause.  This is doubly true for
`:- typeclass' and `:- instance' declarations, which may also occur in
different source files from each other.

compiler/make_hlds_error.m:
compiler/add_class.m:
 	Make the above change.

 	Delete a comment regarding this issue.

tests/invalid/*/.err_exp:
 	Update expected error outputs.

Julien.

diff --git a/compiler/add_class.m b/compiler/add_class.m
index eea02d2..930048c 100644
--- a/compiler/add_class.m
+++ b/compiler/add_class.m
@@ -709,7 +709,7 @@ pred_method_with_no_modes_error(PredInfo, !Specs) :-
  undefined_type_class_error(ClassName, Arity, Context, Description, !Specs) :-
      Pieces = [words("Error:"), words(Description), words("for"),
          sym_name_and_arity(ClassName / Arity),
-        words("without preceding"), decl("typeclass"), words("declaration."),
+        words("without corresponding"), decl("typeclass"), words("declaration."),
          nl],
      Msg = simple_msg(Context, [always(Pieces)]),
      Spec = error_spec(severity_error, phase_parse_tree_to_hlds, [Msg]),
diff --git a/compiler/make_hlds_error.m b/compiler/make_hlds_error.m
index 260cabf..4d664ea 100644
--- a/compiler/make_hlds_error.m
+++ b/compiler/make_hlds_error.m
@@ -106,8 +106,6 @@ multiple_def_error(Status, Name, Arity, DefType, Context, OrigContext,
      ).

  undefined_pred_or_func_error(Name, Arity, Context, DescPieces, !Specs) :-
-    % This used to say `preceding' instead of `corresponding.'
-    % Which is more correct?
      Pieces = [words("Error:") | DescPieces] ++ [words("for"),
          sym_name_and_arity(Name / Arity),
          words("without corresponding"), decl("pred"), words("or"),
@@ -193,8 +191,8 @@ maybe_undefined_pred_error(Globals, Name, Arity, PredOrFunc, Status,
      ;
          Pieces = [words("Error:") | DescPieces] ++ [words("for"),
              simple_call(simple_call_id(PredOrFunc, Name, Arity)), nl,
-            words("without preceding"), decl(pred_or_func_to_str(PredOrFunc)),
-            words("declaration."), nl],
+            words("without corresponding"),
+            decl(pred_or_func_to_str(PredOrFunc)), words("declaration."), nl],
          Msg = simple_msg(Context, [always(Pieces)]),
          Spec = error_spec(severity_error, phase_parse_tree_to_hlds, [Msg]),
          !:Specs = [Spec | !.Specs]
diff --git a/tests/invalid/bigtest.err_exp b/tests/invalid/bigtest.err_exp
index b69a891..166a173 100644
--- a/tests/invalid/bigtest.err_exp
+++ b/tests/invalid/bigtest.err_exp
@@ -13,7 +13,7 @@ bigtest.m:002:   export_pred(((append / 3) , member)).
  bigtest.m:003: Error: unrecognized declaration:
  bigtest.m:003:   export_type(((list / 1) , bag)).
  bigtest.m:005: Error: clause for predicate `bigtest.fact'/0
-bigtest.m:005:   without preceding `:- pred' declaration.
+bigtest.m:005:   without corresponding `:- pred' declaration.
  bigtest.m:005: Error: no mode declaration for predicate `fact'/0.
  bigtest.m:005:   (Use `--infer-modes' to enable mode inference.)
  bigtest.m:005: Inferred :- pred fact.
diff --git a/tests/invalid/bug113.err_exp b/tests/invalid/bug113.err_exp
index f09c360..8180d98 100644
--- a/tests/invalid/bug113.err_exp
+++ b/tests/invalid/bug113.err_exp
@@ -2,10 +2,10 @@ bug113.m:001: In module `bug113':
  bug113.m:001:   warning: module `list' is imported in the interface, but is not
  bug113.m:001:   used in the interface.
  bug113.m:036: Error: clause for function `bug113.new'/1
-bug113.m:036:   without preceding `:- func' declaration.
+bug113.m:036:   without corresponding `:- func' declaration.
  bug113.m:036: Inferred :- func new(T1) = T2.
  bug113.m:038: Error: clause for function `bug113.new'/2
-bug113.m:038:   without preceding `:- func' declaration.
+bug113.m:038:   without corresponding `:- func' declaration.
  bug113.m:040: In clause for function `new'/2:
  bug113.m:040:   error: undefined symbol `throw_bitmap_error/1'.
  bug113.m:042: In clause for function `new'/2:
diff --git a/tests/invalid/bug197.err_exp b/tests/invalid/bug197.err_exp
index ee7d959..8c0d6be 100644
--- a/tests/invalid/bug197.err_exp
+++ b/tests/invalid/bug197.err_exp
@@ -1,6 +1,6 @@
  bug197.m:020: Error: no clauses for predicate `foo'/4.
  bug197.m:022: Error: clause for predicate `bug197.foo'/3
-bug197.m:022:   without preceding `:- pred' declaration.
+bug197.m:022:   without corresponding `:- pred' declaration.
  bug197.m:023: In clause for predicate `foo'/3:
  bug197.m:023:   in argument 1 of call to predicate `list.foldl'/4:
  bug197.m:023:   type error: argument has type `pred(string, T, V_6, V_6)',
diff --git a/tests/invalid/constrained_poly_insts.err_exp b/tests/invalid/constrained_poly_insts.err_exp
index 41f4b02..c880779 100644
--- a/tests/invalid/constrained_poly_insts.err_exp
+++ b/tests/invalid/constrained_poly_insts.err_exp
@@ -16,12 +16,12 @@ constrained_poly_insts.m:014:   (s((T :: in((I =< ground)))) = (T :: out((I =<
  constrained_poly_insts.m:014:   unique)))).
  constrained_poly_insts.m:023: Error: clause for predicate
  constrained_poly_insts.m:023:   `constrained_poly_insts.q'/2
-constrained_poly_insts.m:023:   without preceding `:- pred' declaration.
+constrained_poly_insts.m:023:   without corresponding `:- pred' declaration.
  constrained_poly_insts.m:023: Error: no mode declaration for predicate `q'/2.
  constrained_poly_insts.m:023: Inferred :- pred q(T1, T1).
  constrained_poly_insts.m:025: Error: clause for function
  constrained_poly_insts.m:025:   `constrained_poly_insts.s'/1
-constrained_poly_insts.m:025:   without preceding `:- func' declaration.
+constrained_poly_insts.m:025:   without corresponding `:- func' declaration.
  constrained_poly_insts.m:025: Inferred :- func s(T1) = T1.
  constrained_poly_insts.m:027: In clause for `t(in((I =< ground)), out((I =<
  constrained_poly_insts.m:027:   ground)))':
diff --git a/tests/invalid/errors.err_exp b/tests/invalid/errors.err_exp
index 01caddb..8b805d1 100644
--- a/tests/invalid/errors.err_exp
+++ b/tests/invalid/errors.err_exp
@@ -4,13 +4,13 @@ errors.m:001:   and `:- use_module' declarations.
  errors.m:010: Error: module must start with a `:- module' declaration.
  errors.m:028: Error: `:- mode' declaration for predicate
  errors.m:028:   `errors.mode_declaration_without_pred_declaration'/0
-errors.m:028:   without preceding `:- pred' declaration.
+errors.m:028:   without corresponding `:- pred' declaration.
  errors.m:032: Error: `:- mode' declaration for predicate
  errors.m:032:   `errors.missing_pred_declaration'/0
-errors.m:032:   without preceding `:- pred' declaration.
+errors.m:032:   without corresponding `:- pred' declaration.
  errors.m:038: Error: clause for predicate
  errors.m:038:   `errors.clause_without_pred_or_mode_declaration'/0
-errors.m:038:   without preceding `:- pred' declaration.
+errors.m:038:   without corresponding `:- pred' declaration.
  errors.m:049: Error: constructor `errors.a/0' for type
  errors.m:049:   `errors.type_with_multiply_defined_ctors/0' multiply defined.
  errors.m:049: Error: constructor `errors.f/1' for type
diff --git a/tests/invalid/errors1.err_exp b/tests/invalid/errors1.err_exp
index 799be00..b4bc5e2 100644
--- a/tests/invalid/errors1.err_exp
+++ b/tests/invalid/errors1.err_exp
@@ -2,13 +2,13 @@ errors1.m:001: Warning: interface for module `errors1' does not export
  errors1.m:001:   anything.
  errors1.m:028: Error: `:- mode' declaration for predicate
  errors1.m:028:   `errors1.mode_declaration_without_pred_declaration'/0
-errors1.m:028:   without preceding `:- pred' declaration.
+errors1.m:028:   without corresponding `:- pred' declaration.
  errors1.m:032: Error: `:- mode' declaration for predicate
  errors1.m:032:   `errors1.missing_pred_declaration'/0
-errors1.m:032:   without preceding `:- pred' declaration.
+errors1.m:032:   without corresponding `:- pred' declaration.
  errors1.m:038: Error: clause for predicate
  errors1.m:038:   `errors1.clause_without_pred_or_mode_declaration'/0
-errors1.m:038:   without preceding `:- pred' declaration.
+errors1.m:038:   without corresponding `:- pred' declaration.
  errors1.m:049: Error: constructor `errors1.a/0' for type
  errors1.m:049:   `errors1.type_with_multiply_defined_ctors/0' multiply defined.
  errors1.m:049: Error: constructor `errors1.f/1' for type
diff --git a/tests/invalid/errors2.err_exp b/tests/invalid/errors2.err_exp
index c584898..28527d0 100644
--- a/tests/invalid/errors2.err_exp
+++ b/tests/invalid/errors2.err_exp
@@ -7,7 +7,7 @@ errors2.m:001:   `:- pred', `:- func', `:- type', `:- inst' or `:- mode'
  errors2.m:001:   declaration.
  errors2.m:007: Error: no clauses for predicate `bind_type_param'/2.
  errors2.m:009: Error: clause for predicate `errors2.bind_type_param'/1
-errors2.m:009:   without preceding `:- pred' declaration.
+errors2.m:009:   without corresponding `:- pred' declaration.
  errors2.m:009: Inferred :- pred bind_type_param(int).
  errors2.m:023: Error: no clauses for predicate `produce_string'/1.
  errors2.m:025: Error: no clauses for predicate `expect_int'/1.
diff --git a/tests/invalid/exported_mode.err_exp b/tests/invalid/exported_mode.err_exp
index 33a992d..4d134b1 100644
--- a/tests/invalid/exported_mode.err_exp
+++ b/tests/invalid/exported_mode.err_exp
@@ -1,4 +1,4 @@
  exported_mode.m:004: Error: `:- mode' declaration for predicate
  exported_mode.m:004:   `exported_mode.p'/2
-exported_mode.m:004:   without preceding `:- pred' declaration.
+exported_mode.m:004:   without corresponding `:- pred' declaration.
  exported_mode.m:004: Inferred :- pred p(T1, string).
diff --git a/tests/invalid/funcs_as_preds.err_exp b/tests/invalid/funcs_as_preds.err_exp
index 4bcd9bf..d4b294c 100644
--- a/tests/invalid/funcs_as_preds.err_exp
+++ b/tests/invalid/funcs_as_preds.err_exp
@@ -1,23 +1,23 @@
  funcs_as_preds.m:001: Warning: interface for module `funcs_as_preds' does not
  funcs_as_preds.m:001:   export anything.
  funcs_as_preds.m:017: Error: clause for function `funcs_as_preds.null'/1
-funcs_as_preds.m:017:   without preceding `:- func' declaration.
+funcs_as_preds.m:017:   without corresponding `:- func' declaration.
  funcs_as_preds.m:017: In clause for function `null'/1:
  funcs_as_preds.m:017:   in function result term of clause head:
  funcs_as_preds.m:017:   error: the language construct `='/2 should be used as a
  funcs_as_preds.m:017:   goal, not as an expression.
  funcs_as_preds.m:021: Error: clause for function `funcs_as_preds.car'/1
-funcs_as_preds.m:021:   without preceding `:- func' declaration.
+funcs_as_preds.m:021:   without corresponding `:- func' declaration.
  funcs_as_preds.m:021: Inferred :- func car(list.list(list.list(T))) =
  funcs_as_preds.m:021:   list.list(T).
  funcs_as_preds.m:024: Error: clause for function `funcs_as_preds.cdr'/1
-funcs_as_preds.m:024:   without preceding `:- func' declaration.
+funcs_as_preds.m:024:   without corresponding `:- func' declaration.
  funcs_as_preds.m:024: Inferred :- func cdr(list.list(T)) = list.list(T).
  funcs_as_preds.m:027: Error: clause for function `funcs_as_preds.cons'/2
-funcs_as_preds.m:027:   without preceding `:- func' declaration.
+funcs_as_preds.m:027:   without corresponding `:- func' declaration.
  funcs_as_preds.m:027: Inferred :- func cons(T, list.list(T)) = list.list(T).
  funcs_as_preds.m:030: Error: clause for function `funcs_as_preds.ap'/2
-funcs_as_preds.m:030:   without preceding `:- func' declaration.
+funcs_as_preds.m:030:   without corresponding `:- func' declaration.
  funcs_as_preds.m:030: In clause for function `ap'/2:
  funcs_as_preds.m:030:   error: undefined predicate `null'/1.
  funcs_as_preds.m:030:   (There is a *function* with that name, however.
diff --git a/tests/invalid/fundeps_vars.err_exp b/tests/invalid/fundeps_vars.err_exp
index 922773d..0388f87 100644
--- a/tests/invalid/fundeps_vars.err_exp
+++ b/tests/invalid/fundeps_vars.err_exp
@@ -2,8 +2,8 @@ fundeps_vars.m:020: Error: the domain and range of a functional dependency must
  fundeps_vars.m:020:   be comma-separated lists of variables.
  fundeps_vars.m:027: Error: type variable F in the functional dependency is not
  fundeps_vars.m:027:   a parameter of this type class.
-fundeps_vars.m:035: Error: instance declaration for `coll'/2 without preceding
-fundeps_vars.m:035:   `:- typeclass' declaration.
+fundeps_vars.m:035: Error: instance declaration for `coll'/2 without
+fundeps_vars.m:035:   corresponding `:- typeclass' declaration.
  fundeps_vars.m:035: In declaration of instance of typeclass `coll'/2:
  fundeps_vars.m:035:   error: undefined typeclass `coll'/2.
  fundeps_vars.m:042: In definition of predicate `fundeps_vars.test'/2:
diff --git a/tests/invalid/imported_mode.err_exp b/tests/invalid/imported_mode.err_exp
index cd44c2f..66b64ef 100644
--- a/tests/invalid/imported_mode.err_exp
+++ b/tests/invalid/imported_mode.err_exp
@@ -1,4 +1,4 @@
  exported_mode.int:003: Error: `:- mode' declaration for predicate
  exported_mode.int:003:   `exported_mode.p'/2
-exported_mode.int:003:   without preceding `:- pred' declaration.
+exported_mode.int:003:   without corresponding `:- pred' declaration.
  exported_mode.int:003: Inferred :- pred p(T1, T2).
diff --git a/tests/invalid/multimode_syntax.err_exp b/tests/invalid/multimode_syntax.err_exp
index 2d7bc94..082c3f0 100644
--- a/tests/invalid/multimode_syntax.err_exp
+++ b/tests/invalid/multimode_syntax.err_exp
@@ -1,6 +1,6 @@
  multimode_syntax.m:011: Error: no clauses for function `func0'/0.
  multimode_syntax.m:013: Error: clause for predicate `multimode_syntax.::'/2
-multimode_syntax.m:013:   without preceding `:- pred' declaration.
+multimode_syntax.m:013:   without corresponding `:- pred' declaration.
  multimode_syntax.m:013: In clause for predicate `::'/2:
  multimode_syntax.m:013:   in argument 1 of clause head:
  multimode_syntax.m:013:   error: the language construct `='/2 should be used as
diff --git a/tests/invalid/null_char.err_exp b/tests/invalid/null_char.err_exp
index b24007d..9a62ff6 100644
--- a/tests/invalid/null_char.err_exp
+++ b/tests/invalid/null_char.err_exp
@@ -1,6 +1,6 @@
  null_char.m:012: Syntax error: null character is illegal in strings and names.
  null_char.m:012: Error: clause for predicate `null_char.int'/0
-null_char.m:012:   without preceding `:- pred' declaration.
+null_char.m:012:   without corresponding `:- pred' declaration.
  null_char.m:012: Inferred :- pred int.
  null_char.m:014: In clause head: error: atom expected at 1.
  null_char.m:014: Syntax error: null character is illegal in strings and names.
diff --git a/tests/invalid/purity/purity_nonsense.err_exp b/tests/invalid/purity/purity_nonsense.err_exp
index b9aff46..7f468d2 100644
--- a/tests/invalid/purity/purity_nonsense.err_exp
+++ b/tests/invalid/purity/purity_nonsense.err_exp
@@ -1,5 +1,5 @@
  purity_nonsense.m:012: Error: clause for predicate `purity_nonsense.e12'/0
-purity_nonsense.m:012:   without preceding `:- pred' declaration.
+purity_nonsense.m:012:   without corresponding `:- pred' declaration.
  purity_nonsense.m:012: In clause for predicate `e12'/0:
  purity_nonsense.m:012:   error: `impure' marker in an inappropriate place.
  purity_nonsense.m:012: In clause for predicate `e12'/0:
@@ -17,7 +17,7 @@ purity_nonsense.m:012:   in argument 1 of functor `\\+/1':
  purity_nonsense.m:012:   in argument 1 of functor `impure/1':
  purity_nonsense.m:012:   error: undefined symbol `imp/0'.
  purity_nonsense.m:013: Error: clause for predicate `purity_nonsense.e13'/0
-purity_nonsense.m:013:   without preceding `:- pred' declaration.
+purity_nonsense.m:013:   without corresponding `:- pred' declaration.
  purity_nonsense.m:013: In clause for predicate `e13'/0:
  purity_nonsense.m:013:   error: `semipure' marker in an inappropriate place.
  purity_nonsense.m:013: In clause for predicate `e13'/0:
diff --git a/tests/invalid/purity/purity_nonsense2.err_exp b/tests/invalid/purity/purity_nonsense2.err_exp
index 498565e..83d0d08 100644
--- a/tests/invalid/purity/purity_nonsense2.err_exp
+++ b/tests/invalid/purity/purity_nonsense2.err_exp
@@ -6,6 +6,6 @@ purity_nonsense2.m:010: Error: `:- pragma promise_pure' declaration for
  purity_nonsense2.m:010:   `purity_nonsense2.undefined2'/0 without corresponding
  purity_nonsense2.m:010:   `:- pred' or `:- func' declaration.
  purity_nonsense2.m:012: Error: clause for predicate `purity_nonsense2.e12'/0
-purity_nonsense2.m:012:   without preceding `:- pred' declaration.
+purity_nonsense2.m:012:   without corresponding `:- pred' declaration.
  purity_nonsense2.m:013: Error: clause for predicate `purity_nonsense2.e13'/0
-purity_nonsense2.m:013:   without preceding `:- pred' declaration.
+purity_nonsense2.m:013:   without corresponding `:- pred' declaration.
diff --git a/tests/invalid/record_syntax_errors.err_exp b/tests/invalid/record_syntax_errors.err_exp
index 8bf36f1..a80f18b 100644
--- a/tests/invalid/record_syntax_errors.err_exp
+++ b/tests/invalid/record_syntax_errors.err_exp
@@ -2,7 +2,7 @@ record_syntax_errors.m:014: Error: no clauses for predicate `dcg_syntax'/2.
  record_syntax_errors.m:016: Error: no clauses for predicate `dcg_syntax_2'/2.
  record_syntax_errors.m:023: Error: `:- mode' declaration for function
  record_syntax_errors.m:023:   `record_syntax_errors.field8'/1
-record_syntax_errors.m:023:   without preceding `:- func' declaration.
+record_syntax_errors.m:023:   without corresponding `:- func' declaration.
  record_syntax_errors.m:023: Inferred :- func field8(record_syntax_errors.cons2)
  record_syntax_errors.m:023:   = int.
  record_syntax_errors.m:028: In DCG field update goal:
@@ -27,7 +27,7 @@ record_syntax_errors.m:046:   Argument 2 has type `string',
  record_syntax_errors.m:046:   expected type was `int'.
  record_syntax_errors.m:048: Error: clause for predicate
  record_syntax_errors.m:048:   `record_syntax_errors.term_type_error'/1
-record_syntax_errors.m:048:   without preceding `:- pred' declaration.
+record_syntax_errors.m:048:   without corresponding `:- pred' declaration.
  record_syntax_errors.m:050: In clause for predicate `term_type_error'/1:
  record_syntax_errors.m:050:   in argument 2 of functor `field6 :=/2':
  record_syntax_errors.m:050:   in unification of argument
diff --git a/tests/invalid/ref_to_implicit_pred.err_exp b/tests/invalid/ref_to_implicit_pred.err_exp
index 29038df..72cff6c 100644
--- a/tests/invalid/ref_to_implicit_pred.err_exp
+++ b/tests/invalid/ref_to_implicit_pred.err_exp
@@ -3,7 +3,7 @@ ref_to_implicit_pred.m:004:   error: determinism declaration not satisfied.
  ref_to_implicit_pred.m:004:   Declared `det', inferred `failure'.
  ref_to_implicit_pred.m:009: Error: clause for predicate
  ref_to_implicit_pred.m:009:   `ref_to_implicit_pred.p'/2
-ref_to_implicit_pred.m:009:   without preceding `:- pred' declaration.
+ref_to_implicit_pred.m:009:   without corresponding `:- pred' declaration.
  ref_to_implicit_pred.m:009: Error: no mode declaration for predicate `p'/2.
  ref_to_implicit_pred.m:009: Inferred :- pred p((pred), (pred)).
  ref_to_implicit_pred.m:010: Error: reference to undeclared function or
diff --git a/tests/invalid/state_vars_test3.err_exp b/tests/invalid/state_vars_test3.err_exp
index d0bbccf..2754249 100644
--- a/tests/invalid/state_vars_test3.err_exp
+++ b/tests/invalid/state_vars_test3.err_exp
@@ -2,5 +2,5 @@ state_vars_test3.m:015: Error: no clauses for function `f'/1.
  state_vars_test3.m:021: Error: !Y cannot be a function result.
  state_vars_test3.m:021:   You probably meant !.Y or !:Y.
  state_vars_test3.m:021: Error: clause for function `state_vars_test3.f'/2
-state_vars_test3.m:021:   without preceding `:- func' declaration.
+state_vars_test3.m:021:   without corresponding `:- func' declaration.
  state_vars_test3.m:021: Error: no clauses for function `f'/2.
diff --git a/tests/invalid/type_inf_loop.err_exp b/tests/invalid/type_inf_loop.err_exp
index aaa8e75..a4be8bc 100644
--- a/tests/invalid/type_inf_loop.err_exp
+++ b/tests/invalid/type_inf_loop.err_exp
@@ -5,7 +5,7 @@ Type inference iteration limit exceeded. This probably indicates that your
  type_inf_loop.m:001: Warning: interface for module `type_inf_loop' does not
  type_inf_loop.m:001:   export anything.
  type_inf_loop.m:004: Error: clause for predicate `type_inf_loop.loop'/1
-type_inf_loop.m:004:   without preceding `:- pred' declaration.
+type_inf_loop.m:004:   without corresponding `:- pred' declaration.
  type_inf_loop.m:004: Inferred :- pred loop((pred (pred (pred (pred (pred (pred
  type_inf_loop.m:004:   (pred (pred (pred (pred (pred (pred (pred (pred (pred
  type_inf_loop.m:004:   (pred (pred (pred (pred (pred (pred (pred (pred (pred
diff --git a/tests/invalid/typeclass_mode_2.err_exp b/tests/invalid/typeclass_mode_2.err_exp
index 460afee..c1198a5 100644
--- a/tests/invalid/typeclass_mode_2.err_exp
+++ b/tests/invalid/typeclass_mode_2.err_exp
@@ -2,7 +2,7 @@ typeclass_mode_2.m:005: Error: mode declaration for type class method
  typeclass_mode_2.m:005:   `typeclass_mode_2.p'/1 without corresponding
  typeclass_mode_2.m:005:   predicate method declaration.
  typeclass_mode_2.m:010: Error: clause for predicate `typeclass_mode_2.p'/1
-typeclass_mode_2.m:010:   without preceding `:- pred' declaration.
+typeclass_mode_2.m:010:   without corresponding `:- pred' declaration.
  typeclass_mode_2.m:010: Error: no mode declaration for predicate `p'/1.
  typeclass_mode_2.m:010: Inferred :- pred p(T1).
  For more information, recompile with `-E'.
diff --git a/tests/invalid/typeclass_test_2.err_exp b/tests/invalid/typeclass_test_2.err_exp
index e7cafe0..1a73561 100644
--- a/tests/invalid/typeclass_test_2.err_exp
+++ b/tests/invalid/typeclass_test_2.err_exp
@@ -7,5 +7,5 @@ typeclass_test_2.m:020:   `func(<Name> / <Arity>) is <InstanceName>', not
  typeclass_test_2.m:020:   ((type_num / 0) is foo_type_num).
  typeclass_test_2.m:023: Error: clause for function
  typeclass_test_2.m:023:   `typeclass_test_2.foo_type_num'/1
-typeclass_test_2.m:023:   without preceding `:- func' declaration.
+typeclass_test_2.m:023:   without corresponding `:- func' declaration.
  typeclass_test_2.m:023: Inferred :- func foo_type_num(T1) = int.
diff --git a/tests/invalid/types.err_exp b/tests/invalid/types.err_exp
index c32f561..c391bf8 100644
--- a/tests/invalid/types.err_exp
+++ b/tests/invalid/types.err_exp
@@ -8,6 +8,6 @@ types.m:003:   defined.
  types.m:003: Error: constructor `types.f/1' for type `types.t/0' multiply
  types.m:003:   defined.
  types.m:017: Error: clause for predicate `types.r'/0
-types.m:017:   without preceding `:- pred' declaration.
+types.m:017:   without corresponding `:- pred' declaration.
  types.m:020: Error: clause for predicate `types.a'/1
-types.m:020:   without preceding `:- pred' declaration.
+types.m:020:   without corresponding `:- pred' declaration.
diff --git a/tests/invalid/types2.err_exp b/tests/invalid/types2.err_exp
index 832d352..f2f9592 100644
--- a/tests/invalid/types2.err_exp
+++ b/tests/invalid/types2.err_exp
@@ -12,14 +12,14 @@ types2.m:014: In clause for predicate `q'/0:
  types2.m:014:   error: wrong number of arguments (0; should be 1)
  types2.m:014:   in call to predicate `p'.
  types2.m:017: Error: clause for predicate `types2.r'/0
-types2.m:017:   without preceding `:- pred' declaration.
+types2.m:017:   without corresponding `:- pred' declaration.
  types2.m:017: Warning: non-contiguous clauses for predicate `r'/0.
  types2.m:017:   Gap in clauses of predicate `r'/0 starts after this clause.
  types2.m:022:   Gap in clauses of predicate `r'/0 ends with this clause.
  types2.m:018: In clause for predicate `r'/0:
  types2.m:018:   error: undefined predicate `s'/0.
  types2.m:020: Error: clause for predicate `types2.a'/1
-types2.m:020:   without preceding `:- pred' declaration.
+types2.m:020:   without corresponding `:- pred' declaration.
  types2.m:020: In clause for predicate `a'/1:
  types2.m:020:   error: undefined predicate `b'/1.
  types2.m:039: In clause for predicate `bar'/1:
diff --git a/tests/invalid/with_type.err_exp b/tests/invalid/with_type.err_exp
index d8f64b1..23048e7 100644
--- a/tests/invalid/with_type.err_exp
+++ b/tests/invalid/with_type.err_exp
@@ -8,7 +8,7 @@ with_type.m:018:   error: expected higher order function type after
  with_type.m:018:   `with_type`.
  with_type.m:019: Error: `:- mode' declaration for function
  with_type.m:019:   `with_type.with_type_2'/3
-with_type.m:019:   without preceding `:- func' declaration.
+with_type.m:019:   without corresponding `:- func' declaration.
  with_type.m:021: In type declaration for predicate `with_type.with_type_3':
  with_type.m:021:   error: the `with_type` and `with_inst` annotations are
  with_type.m:021:   incompatible.



More information about the reviews mailing list