Use Levenshtein spelling suggestions in Fortran FE

gcc/fortran/ChangeLog

2017-10-19  Bernhard Reutner-Fischer  <aldot@gcc.gnu.org>

	* gfortran.h (gfc_lookup_function_fuzzy): New declaration.
	(gfc_closest_fuzzy_match): New declaration.
	(vec_push): New definition.
	* misc.c (gfc_closest_fuzzy_match): New definition.
	* resolve.c: Include spellcheck.h.
	(lookup_function_fuzzy_find_candidates): New static function.
	(lookup_uop_fuzzy_find_candidates): Likewise.
	(lookup_uop_fuzzy): Likewise.
	(resolve_operator) <INTRINSIC_USER>: Call lookup_uop_fuzzy.
	(gfc_lookup_function_fuzzy): New definition.
	(resolve_unknown_f): Call gfc_lookup_function_fuzzy.
	* interface.c (check_interface0): Likewise.
	(lookup_arg_fuzzy_find_candidates): New static function.
	(lookup_arg_fuzzy ): Likewise.
	(compare_actual_formal): Call lookup_arg_fuzzy.
	* symbol.c: Include spellcheck.h.
	(lookup_symbol_fuzzy_find_candidates): New static function.
	(lookup_symbol_fuzzy): Likewise.
	(gfc_set_default_type): Call lookup_symbol_fuzzy.
	(lookup_component_fuzzy_find_candidates): New static function.
	(lookup_component_fuzzy): Likewise.
	(gfc_find_component): Call lookup_component_fuzzy.

gcc/testsuite/ChangeLog

2017-10-19  Bernhard Reutner-Fischer  <aldot@gcc.gnu.org>

	* gfortran.dg/spellcheck-operator.f90: New testcase.
	* gfortran.dg/spellcheck-procedure_1.f90: New testcase.
	* gfortran.dg/spellcheck-procedure_2.f90: New testcase.
	* gfortran.dg/spellcheck-structure.f90: New testcase.
	* gfortran.dg/spellcheck-parameter.f90: New testcase.

From-SVN: r253877
This commit is contained in:
Bernhard Reutner-Fischer 2017-10-19 09:24:33 +02:00
parent fba832054d
commit bcc478b964
12 changed files with 483 additions and 17 deletions

View file

@ -1,3 +1,28 @@
2017-10-19 Bernhard Reutner-Fischer <aldot@gcc.gnu.org>
* gfortran.h (gfc_lookup_function_fuzzy): New declaration.
(gfc_closest_fuzzy_match): New declaration.
(vec_push): New definition.
* misc.c (gfc_closest_fuzzy_match): New definition.
* resolve.c: Include spellcheck.h.
(lookup_function_fuzzy_find_candidates): New static function.
(lookup_uop_fuzzy_find_candidates): Likewise.
(lookup_uop_fuzzy): Likewise.
(resolve_operator) <INTRINSIC_USER>: Call lookup_uop_fuzzy.
(gfc_lookup_function_fuzzy): New definition.
(resolve_unknown_f): Call gfc_lookup_function_fuzzy.
* interface.c (check_interface0): Likewise.
(lookup_arg_fuzzy_find_candidates): New static function.
(lookup_arg_fuzzy ): Likewise.
(compare_actual_formal): Call lookup_arg_fuzzy.
* symbol.c: Include spellcheck.h.
(lookup_symbol_fuzzy_find_candidates): New static function.
(lookup_symbol_fuzzy): Likewise.
(gfc_set_default_type): Call lookup_symbol_fuzzy.
(lookup_component_fuzzy_find_candidates): New static function.
(lookup_component_fuzzy): Likewise.
(gfc_find_component): Call lookup_component_fuzzy.
2017-10-18 Thomas Koenig <tkoenig@gcc.gnu.org>
PR fortran/82567

View file

@ -2796,6 +2796,17 @@ void gfc_done_2 (void);
int get_c_kind (const char *, CInteropKind_t *);
const char *gfc_closest_fuzzy_match (const char *, char **);
static inline void
vec_push (char **&optr, size_t &osz, const char *elt)
{
/* {auto,}vec.safe_push () replacement. Don't ask.. */
// if (strlen (elt) < 4) return; premature optimization: eliminated by cutoff
optr = XRESIZEVEC (char *, optr, osz + 2);
optr[osz] = CONST_CAST (char *, elt);
optr[++osz] = NULL;
}
/* options.c */
unsigned int gfc_option_lang_mask (void);
void gfc_init_options_struct (struct gcc_options *);
@ -3228,6 +3239,7 @@ bool gfc_type_is_extensible (gfc_symbol *);
bool gfc_resolve_intrinsic (gfc_symbol *, locus *);
bool gfc_explicit_interface_required (gfc_symbol *, char *, int);
extern int gfc_do_concurrent_flag;
const char* gfc_lookup_function_fuzzy (const char *, gfc_symtree *);
/* array.c */

View file

@ -1793,13 +1793,27 @@ check_interface0 (gfc_interface *p, const char *interface_name)
|| !p->sym->attr.if_source)
&& !gfc_fl_struct (p->sym->attr.flavor))
{
const char *guessed
= gfc_lookup_function_fuzzy (p->sym->name, p->sym->ns->sym_root);
if (p->sym->attr.external)
gfc_error ("Procedure %qs in %s at %L has no explicit interface",
p->sym->name, interface_name, &p->sym->declared_at);
if (guessed)
gfc_error ("Procedure %qs in %s at %L has no explicit interface"
"; did you mean %qs?",
p->sym->name, interface_name, &p->sym->declared_at,
guessed);
else
gfc_error ("Procedure %qs in %s at %L has no explicit interface",
p->sym->name, interface_name, &p->sym->declared_at);
else
gfc_error ("Procedure %qs in %s at %L is neither function nor "
"subroutine", p->sym->name, interface_name,
&p->sym->declared_at);
if (guessed)
gfc_error ("Procedure %qs in %s at %L is neither function nor "
"subroutine; did you mean %qs?", p->sym->name,
interface_name, &p->sym->declared_at, guessed);
else
gfc_error ("Procedure %qs in %s at %L is neither function nor "
"subroutine", p->sym->name, interface_name,
&p->sym->declared_at);
return true;
}
@ -2778,6 +2792,31 @@ is_procptr_result (gfc_expr *expr)
}
/* Recursively append candidate argument ARG to CANDIDATES. Store the
number of total candidates in CANDIDATES_LEN. */
static void
lookup_arg_fuzzy_find_candidates (gfc_formal_arglist *arg,
char **&candidates,
size_t &candidates_len)
{
for (gfc_formal_arglist *p = arg; p && p->sym; p = p->next)
vec_push (candidates, candidates_len, p->sym->name);
}
/* Lookup argument ARG fuzzily, taking names in ARGUMENTS into account. */
static const char*
lookup_arg_fuzzy (const char *arg, gfc_formal_arglist *arguments)
{
char **candidates = NULL;
size_t candidates_len = 0;
lookup_arg_fuzzy_find_candidates (arguments, candidates, candidates_len);
return gfc_closest_fuzzy_match (arg, candidates);
}
/* Given formal and actual argument lists, see if they are compatible.
If they are compatible, the actual argument list is sorted to
correspond with the formal list, and elements for missing optional
@ -2831,8 +2870,16 @@ compare_actual_formal (gfc_actual_arglist **ap, gfc_formal_arglist *formal,
if (f == NULL)
{
if (where)
gfc_error ("Keyword argument %qs at %L is not in "
"the procedure", a->name, &a->expr->where);
{
const char *guessed = lookup_arg_fuzzy (a->name, formal);
if (guessed)
gfc_error ("Keyword argument %qs at %L is not in "
"the procedure; did you mean %qs?",
a->name, &a->expr->where, guessed);
else
gfc_error ("Keyword argument %qs at %L is not in "
"the procedure", a->name, &a->expr->where);
}
return false;
}
@ -3552,8 +3599,15 @@ gfc_procedure_use (gfc_symbol *sym, gfc_actual_arglist **ap, locus *where)
{
if (sym->ns->has_implicit_none_export && sym->attr.proc == PROC_UNKNOWN)
{
gfc_error ("Procedure %qs called at %L is not explicitly declared",
sym->name, where);
const char *guessed
= gfc_lookup_function_fuzzy (sym->name, sym->ns->sym_root);
if (guessed)
gfc_error ("Procedure %qs called at %L is not explicitly declared"
"; did you mean %qs?",
sym->name, where, guessed);
else
gfc_error ("Procedure %qs called at %L is not explicitly declared",
sym->name, where);
return false;
}
if (warn_implicit_interface)

View file

@ -22,6 +22,7 @@ along with GCC; see the file COPYING3. If not see
#include "system.h"
#include "coretypes.h"
#include "gfortran.h"
#include "spellcheck.h"
/* Initialize a typespec to unknown. */
@ -280,3 +281,43 @@ get_c_kind(const char *c_kind_name, CInteropKind_t kinds_table[])
return ISOCBINDING_INVALID;
}
/* For a given name TYPO, determine the best candidate from CANDIDATES
perusing Levenshtein distance. Frees CANDIDATES before returning. */
const char *
gfc_closest_fuzzy_match (const char *typo, char **candidates)
{
/* Determine closest match. */
const char *best = NULL;
char **cand = candidates;
edit_distance_t best_distance = MAX_EDIT_DISTANCE;
const size_t tl = strlen (typo);
while (cand && *cand)
{
edit_distance_t dist = levenshtein_distance (typo, tl, *cand,
strlen (*cand));
if (dist < best_distance)
{
best_distance = dist;
best = *cand;
}
cand++;
}
/* If more than half of the letters were misspelled, the suggestion is
likely to be meaningless. */
if (best)
{
unsigned int cutoff = MAX (tl, strlen (best)) / 2;
if (best_distance > cutoff)
{
XDELETEVEC (candidates);
return NULL;
}
XDELETEVEC (candidates);
}
return best;
}

View file

@ -2801,6 +2801,43 @@ resolve_specific_f (gfc_expr *expr)
return true;
}
/* Recursively append candidate SYM to CANDIDATES. Store the number of
candidates in CANDIDATES_LEN. */
static void
lookup_function_fuzzy_find_candidates (gfc_symtree *sym,
char **&candidates,
size_t &candidates_len)
{
gfc_symtree *p;
if (sym == NULL)
return;
if ((sym->n.sym->ts.type != BT_UNKNOWN || sym->n.sym->attr.external)
&& sym->n.sym->attr.flavor == FL_PROCEDURE)
vec_push (candidates, candidates_len, sym->name);
p = sym->left;
if (p)
lookup_function_fuzzy_find_candidates (p, candidates, candidates_len);
p = sym->right;
if (p)
lookup_function_fuzzy_find_candidates (p, candidates, candidates_len);
}
/* Lookup function FN fuzzily, taking names in SYMROOT into account. */
const char*
gfc_lookup_function_fuzzy (const char *fn, gfc_symtree *symroot)
{
char **candidates = NULL;
size_t candidates_len = 0;
lookup_function_fuzzy_find_candidates (symroot, candidates, candidates_len);
return gfc_closest_fuzzy_match (fn, candidates);
}
/* Resolve a procedure call not known to be generic nor specific. */
@ -2851,8 +2888,15 @@ set_type:
if (ts->type == BT_UNKNOWN)
{
gfc_error ("Function %qs at %L has no IMPLICIT type",
sym->name, &expr->where);
const char *guessed
= gfc_lookup_function_fuzzy (sym->name, sym->ns->sym_root);
if (guessed)
gfc_error ("Function %qs at %L has no IMPLICIT type"
"; did you mean %qs?",
sym->name, &expr->where, guessed);
else
gfc_error ("Function %qs at %L has no IMPLICIT type",
sym->name, &expr->where);
return false;
}
else
@ -3713,6 +3757,46 @@ logical_to_bitwise (gfc_expr *e)
return e;
}
/* Recursively append candidate UOP to CANDIDATES. Store the number of
candidates in CANDIDATES_LEN. */
static void
lookup_uop_fuzzy_find_candidates (gfc_symtree *uop,
char **&candidates,
size_t &candidates_len)
{
gfc_symtree *p;
if (uop == NULL)
return;
/* Not sure how to properly filter here. Use all for a start.
n.uop.op is NULL for empty interface operators (is that legal?) disregard
these as i suppose they don't make terribly sense. */
if (uop->n.uop->op != NULL)
vec_push (candidates, candidates_len, uop->name);
p = uop->left;
if (p)
lookup_uop_fuzzy_find_candidates (p, candidates, candidates_len);
p = uop->right;
if (p)
lookup_uop_fuzzy_find_candidates (p, candidates, candidates_len);
}
/* Lookup user-operator OP fuzzily, taking names in UOP into account. */
static const char*
lookup_uop_fuzzy (const char *op, gfc_symtree *uop)
{
char **candidates = NULL;
size_t candidates_len = 0;
lookup_uop_fuzzy_find_candidates (uop, candidates, candidates_len);
return gfc_closest_fuzzy_match (op, candidates);
}
/* Resolve an operator expression node. This can involve replacing the
operation with a user defined function call. */
@ -3935,8 +4019,16 @@ resolve_operator (gfc_expr *e)
case INTRINSIC_USER:
if (e->value.op.uop->op == NULL)
sprintf (msg, _("Unknown operator %%<%s%%> at %%L"),
e->value.op.uop->name);
{
const char *name = e->value.op.uop->name;
const char *guessed;
guessed = lookup_uop_fuzzy (name, e->value.op.uop->ns->uop_root);
if (guessed)
sprintf (msg, _("Unknown operator %%<%s%%> at %%L; did you mean '%s'?"),
name, guessed);
else
sprintf (msg, _("Unknown operator %%<%s%%> at %%L"), name);
}
else if (op2 == NULL)
sprintf (msg, _("Operand of user operator %%<%s%%> at %%L is %s"),
e->value.op.uop->name, gfc_typename (&op1->ts));

View file

@ -245,6 +245,44 @@ gfc_get_default_type (const char *name, gfc_namespace *ns)
}
/* Recursively append candidate SYM to CANDIDATES. Store the number of
candidates in CANDIDATES_LEN. */
static void
lookup_symbol_fuzzy_find_candidates (gfc_symtree *sym,
char **&candidates,
size_t &candidates_len)
{
gfc_symtree *p;
if (sym == NULL)
return;
if (sym->n.sym->ts.type != BT_UNKNOWN && sym->n.sym->ts.type != BT_PROCEDURE)
vec_push (candidates, candidates_len, sym->name);
p = sym->left;
if (p)
lookup_symbol_fuzzy_find_candidates (p, candidates, candidates_len);
p = sym->right;
if (p)
lookup_symbol_fuzzy_find_candidates (p, candidates, candidates_len);
}
/* Lookup symbol SYM_NAME fuzzily, taking names in SYMBOL into account. */
static const char*
lookup_symbol_fuzzy (const char *sym_name, gfc_symbol *symbol)
{
char **candidates = NULL;
size_t candidates_len = 0;
lookup_symbol_fuzzy_find_candidates (symbol->ns->sym_root, candidates,
candidates_len);
return gfc_closest_fuzzy_match (sym_name, candidates);
}
/* Given a pointer to a symbol, set its type according to the first
letter of its name. Fails if the letter in question has no default
type. */
@ -263,8 +301,14 @@ gfc_set_default_type (gfc_symbol *sym, int error_flag, gfc_namespace *ns)
{
if (error_flag && !sym->attr.untyped)
{
gfc_error ("Symbol %qs at %L has no IMPLICIT type",
sym->name, &sym->declared_at);
const char *guessed = lookup_symbol_fuzzy (sym->name, sym);
if (guessed)
gfc_error ("Symbol %qs at %L has no IMPLICIT type"
"; did you mean %qs?",
sym->name, &sym->declared_at, guessed);
else
gfc_error ("Symbol %qs at %L has no IMPLICIT type",
sym->name, &sym->declared_at);
sym->attr.untyped = 1; /* Ensure we only give an error once. */
}
@ -2336,6 +2380,32 @@ find_union_component (gfc_symbol *un, const char *name,
}
/* Recursively append candidate COMPONENT structures to CANDIDATES. Store
the number of total candidates in CANDIDATES_LEN. */
static void
lookup_component_fuzzy_find_candidates (gfc_component *component,
char **&candidates,
size_t &candidates_len)
{
for (gfc_component *p = component; p; p = p->next)
vec_push (candidates, candidates_len, p->name);
}
/* Lookup component MEMBER fuzzily, taking names in COMPONENT into account. */
static const char*
lookup_component_fuzzy (const char *member, gfc_component *component)
{
char **candidates = NULL;
size_t candidates_len = 0;
lookup_component_fuzzy_find_candidates (component, candidates,
candidates_len);
return gfc_closest_fuzzy_match (member, candidates);
}
/* Given a derived type node and a component name, try to locate the
component structure. Returns the NULL pointer if the component is
not found or the components are private. If noaccess is set, no access
@ -2433,8 +2503,16 @@ gfc_find_component (gfc_symbol *sym, const char *name,
}
if (p == NULL && !silent)
gfc_error ("%qs at %C is not a member of the %qs structure",
name, sym->name);
{
const char *guessed = lookup_component_fuzzy (name, sym->components);
if (guessed)
gfc_error ("%qs at %C is not a member of the %qs structure"
"; did you mean %qs?",
name, sym->name, guessed);
else
gfc_error ("%qs at %C is not a member of the %qs structure",
name, sym->name);
}
/* Component was found; build the ultimate component reference. */
if (p != NULL && ref)

View file

@ -1,3 +1,11 @@
2017-10-19 Bernhard Reutner-Fischer <aldot@gcc.gnu.org>
* gfortran.dg/spellcheck-operator.f90: New testcase.
* gfortran.dg/spellcheck-procedure_1.f90: New testcase.
* gfortran.dg/spellcheck-procedure_2.f90: New testcase.
* gfortran.dg/spellcheck-structure.f90: New testcase.
* gfortran.dg/spellcheck-parameter.f90: New testcase.
2017-10-18 Thomas Koenig <tkoenig@gcc.gnu.org>
PR fortran/82567

View file

@ -0,0 +1,30 @@
! { dg-do compile }
! test levenshtein based spelling suggestions
module mymod1
implicit none
contains
function something_good (iarg1)
integer :: something_good
integer, intent(in) :: iarg1
something_good = iarg1 + 42
end function something_good
end module mymod1
program spellchekc
use mymod1
implicit none
interface operator (.mywrong.)
module procedure something_wring ! { dg-error "Procedure .something_wring. in operator interface .mywrong. at .1. is neither function nor subroutine; did you mean .something_good.\\?|User operator procedure .something_wring. at .1. must be a FUNCTION" }
end interface
interface operator (.mygood.)
module procedure something_good
end interface
integer :: i, j, added
i = 0
j = 0
added = .mygoof. j ! { dg-error "Unknown operator .mygoof. at .1.; did you mean .mygood.\\?" }
end program spellchekc

View file

@ -0,0 +1,15 @@
! { dg-do compile }
! Contributed by Joost VandeVondele
! test levenshtein based spelling suggestions for keyword arguments
module test
contains
subroutine mysub(iarg1)
integer :: iarg1
end subroutine
end module
use test
call mysub(iarg=1) ! { dg-error "Keyword argument .iarg. at .1. is not in the procedure; did you mean .iarg1.\\?" }
end

View file

@ -0,0 +1,41 @@
! { dg-do compile }
! test levenshtein based spelling suggestions
module mymod1
implicit none
contains
function something_else (iarg1)
integer :: something_else
integer, intent(in) :: iarg1
something_else = iarg1 + 42
end function something_else
function add_fourtytwo (iarg1)
integer :: add_fourtytwo
integer, intent(in) :: iarg1
add_fourtytwo = iarg1 + 42
end function add_fourtytwo
end module mymod1
function myadd(iarg1, iarg2)
implicit none
integer :: myadd
integer, intent(in) :: iarg1, iarg2
myadd = iarg1 + iarg2
end function myadd
program spellchekc
use mymod1, something_good => something_else
implicit none
integer :: myadd, i, j, myvar
i = 0
j = 0
j = something_goof(j) ! { dg-error "no IMPLICIT type; did you mean .something_good.\\?" }
j = myaddd(i, j) ! { dg-error "no IMPLICIT type; did you mean .myadd.\\?" }
if (j /= 42) call abort
j = add_fourtytow(i, j) ! { dg-error "no IMPLICIT type; did you mean .add_fourtytwo.\\?" }
myval = myadd(i, j) ! { dg-error "no IMPLICIT type; did you mean .myvar.\\?" }
if (j /= 42 * 2) call abort
end program spellchekc

View file

@ -0,0 +1,35 @@
! { dg-do compile }
! test levenshtein based spelling suggestions
program spellchekc
implicit none (external) ! { dg-warning "GNU Extension: IMPORT NONE with spec list" }
interface
subroutine bark_unless_zero(iarg)
implicit none
integer, intent(in) :: iarg
end subroutine bark_unless_zero
end interface
integer :: i
i = 0
if (i /= 1) call abort
call bark_unless_0(i) ! { dg-error "not explicitly declared; did you mean .bark_unless_zero.\\?" }
! call complain_about_0(i) ! { -dg-error "not explicitly declared; did you mean .complain_about_zero.\\?" }
contains
! We cannot reliably see this ATM, would need an unambiguous bit somewhere
subroutine complain_about_zero(iarg)
integer, intent(in) :: iarg
if (iarg /= 0) call abort
end subroutine complain_about_zero
end program spellchekc
subroutine bark_unless_zero(iarg)
implicit none
integer, intent(in) :: iarg
if (iarg /= 0) call abort
end subroutine bark_unless_zero

View file

@ -0,0 +1,35 @@
! { dg-do compile }
! test levenshtein based spelling suggestions
implicit none
!!!!!!!!!!!!!! structure tests !!!!!!!!!!!!!!
type type1
real :: radius
integer :: i
end type type1
type type2
integer :: myint
type(type1) :: mytype
end type type2
type type3
type(type2) :: type_2
end type type3
type type4
type(type3) :: type_3
end type type4
type(type1) :: t1
t1%radiuz = .0 ! { dg-error ".radiuz. at .1. is not a member of the .type1. structure; did you mean .radius.\\?" }
t1%x = .0 ! { dg-error ".x. at .1. is not a member of the .type1. structure" }
type(type2) :: t2
t2%mytape%radius = .0 ! { dg-error ".mytape. at .1. is not a member of the .type2. structure; did you mean .mytype.\\?" }
t2%mytype%radious = .0 ! { dg-error ".radious. at .1. is not a member of the .type1. structure; did you mean .radius.\\?" }
type(type4) :: t4
t4%type_3%type_2%mytype%radium = 88.0 ! { dg-error ".radium. at .1. is not a member of the .type1. structure; did you mean .radius.\\?" }
!!!!!!!!!!!!!! symbol tests !!!!!!!!!!!!!!
integer :: iarg1
iarg2 = 1 ! { dg-error "Symbol .iarg2. at .1. has no IMPLICIT type; did you mean .iarg1.\\?" }
end