flang-compiler / flang

Flang is a Fortran language front-end designed for integration with LLVM.
Other
799 stars 134 forks source link

Problem with conflicting use statements #890

Closed RichBarton-Arm closed 3 years ago

RichBarton-Arm commented 4 years ago

This is similar to issue #889 and from the same BigDFT application.

The below code causes flang to emit the following message:

F90-S-0155-gp is use-associated from modules box and module_defs, and cannot be accessed (big_dft2.f90: 36)

I think that the definition in _moduledefs should be visible because the definition in box is private to the module and the definition from _PoissonSolver is renamed in the USE statement.

module f_precisions
  implicit none
  integer, parameter, public :: f_double = selected_real_kind(15, 307)
end module f_precisions

module box
  use f_precisions, gp=>f_double
  implicit none
  private
end module box

module Poisson_Solver
  use f_precisions
  implicit none
  integer, parameter, public :: gp=f_double
end module Poisson_Solver

module module_defs
  use f_precisions
  implicit none  
  integer, parameter, public :: gp=f_double
end module module_defs

module module_base
  use module_defs
  implicit none  
end module module_base

subroutine PSolver(eh)
  use module_base ! This has a public gp
  ! Removing the next line makes gp visible
  use box ! This has a private gp
  ! Removing the next line makes gp visible
  use Poisson_Solver, except_gp => gp ! This has a public gp
  implicit none
  real(gp), intent(out) :: eh ! Should be able to use gp from module_base
END SUBROUTINE PSolver

The reproducer is slightly unstable in that removing either of box or _PoissonSolver USE statements causes flang to compile this with no error. Removing the USE of _modulebase does correctly cause an error because gp is unknown.

michalpasztamobica commented 4 years ago

I tried to analyze this issue and just wanted to share some findings in case someone more competent will perhaps be able to decide what to do with this report.

The error is coming from sym_in_scope function and the comment is quite explicit about not allowing the same name to be used twice:

if (bestuse && bestuse2 && multiple_use_error && bestuse != bestuse2 &&
      !isSameNameGenericOrProcOrModproc(bestsptr, bestsptrloop) &&
      bestusecount == bestuse2count && sem.which_pass == 1) {
    /* oops; this name is USE-associated from two
     * different modules */
    char msg[200];
    sprintf(msg,
            "is use-associated from modules %s and %s,"
            " and cannot be accessed",
            SYMNAME(bestuse), SYMNAME(bestuse2));
    error(155, 3, gbl.lineno, SYMNAME(first), msg);
  }

At the beginning of the sym_in_scope() function there is also an explanation of this approach. The code is a kind of compromise and might flag false negatives and false positives, but they "should be rare and easy to work around by not overloading names". In my opinion this behaviour is not exactly a bug, it is intentional.

I see a number of ways out of the situation, but by no means do I feel competent to decide which one is best: 1) Redesign the algorithm, providing it with more information, as per the comment, so it doesn't have to make any compromises. 2) Change the error to warning - but this may let some actual errors pass this compilation stage. 3) Leave things as they are and modify the error message to explain the situation better and encourage avoidance of name overloads. The implementation is done this way for a reason and documented in the code.

Breaking backward compatibility should not be an issue. Current algorithm is "oversensitive" and lowering the sensitivity to a more relevant level can only make the situation better.

RichBarton-Arm commented 4 years ago

Thanks for tracking the error down in flang.

I think the Fortran standard shows unambiguously how to interpret the example and shows it is legal Fortran.

s14.2.2: "At the time a USE statement is processed, the public portions of the specified module shall be available."

which should mean the definition of gp from box should never be visible inside PSolver at all.

An accessible entity in the referenced module is associated with one or more accessed entities, each with its own identifier. These identifiers are

  • the identifier of the entity in the referenced module if that identifier appears as an only-use-name or as the defined-operator of a generic-spec in any only for that module,
  • each of the local-names or local-defined-operators that the entity is given in any rename for that module, and
  • the identifier of the entity in the referenced module if that identifier does not appear as a use-name or use-defined-operator in any rename for that module.

The first bullet does not apply as there is no ONLY and I think the second two say that gp should not be available from _PoissonSolver at all as it has been renamed.

So I believe the correct behaviour is for flang to allow this to compile and use the definition from module_base.

I think that means option 1 is the right way to progress.

michalpasztamobica commented 4 years ago

When analyzing the algorithm in more detail I found one peculiarity. The algorithm counts on scope.Private field to be set. We do have a private scope in box module. But when debugging I never saw any scope that would have the Private filed set to true.

I set a breakpoint at the only place where we set this flag and it never triggered.

I noticed there is another place where we check for private scope, but when we hit it, the scope is set to SC_DUMMY.

In summary - seems like we don't take into consideration the fact that the box module has a private scope.

Looking at how the compiler works, it seems to infer the grammar from gram.txt human-readable file and transform it into machine-firendly arrays, which are later used by the algorithms to perform reductions. Nowhere in this file did I find a definition of the private keyword as used in the example. I am very new to this project, but I would expect something like <end> := in the gram.txt file, similar to how END is handled.

RichBarton-Arm commented 4 years ago

It sounds like you are on the right track with your investigation.

I think you are missing the definition of PRIVATE as an "access spec" on L555 in the grammer. That seems to make it available as a "declaration" on L149 which looks like it would be how the definition of module box would be parsed in the example.

I suggest tracing forwards from the parsing of box to see how PRIVATE is handled in this case and why it is not then setting the scope.Private attribute that you point out.

michalpasztamobica commented 4 years ago

I can see we are hitting L8342 in the semantic analysis, which sets entity_attr.access to 'v' which stands for private. When we hit this line the gbl.lineno is set to 9, which corresponds to the 'private' keyword in module box.

I checked that we never trigger any check for this attribute or the getter for it. I am trying to figure out where would be a good place to potentially do so. Most likely somewhere in the use statement application, but a simple modification

--- a/tools/flang1/flang1exe/module.c
+++ b/tools/flang1/flang1exe/module.c
@@ -712,7 +712,7 @@ apply_use(MODULE_ID m_id)
       onlylist = add_symitem(pr->global, onlylist);
     }
   }
-  if (used->unrestricted) {
+  if (used->unrestricted && get_entity_access() != 'v') {

Makes no difference.

It is a little bit complicated as there are 3 ways of tracking the private scope:

  1. Through the scope.Private attribute
  2. Through a "private bit" using the macro PRIVATEG(sptr)
  3. using the entity_attr.access

Probably because of this the "private" keyword in the box module does not affect the gp's scope correctly causing the multiple use error.

RichBarton-Arm commented 4 years ago

It doesn't surprise me that there are multiple ways of expressing the same information in flang and that they are not lining up correctly!

Tagging in @kiranchandramohan to take a look and see if he can make a suggestion.

michalpasztamobica commented 4 years ago

Found another way of keeping the privet/public information and this one is triggerred in L1240 of module.c.

I tried to set the flag when scope is being pushed to the scope queue:

--- a/tools/flang1/flang1exe/scopestack.c
+++ b/tools/flang1/flang1exe/scopestack.c
@@ -211,6 +211,9 @@ push_scope_level(int sptr, SCOPEKIND kind)
   scope->kind = kind;
   scope->sptr = sptr;
   scope->symavl = stb.stg_avail;
+  scope->Private = get_entity_access() == 'v' ? TRUE : FALSE;
+  scope->Private = sem.accl.type == 'v' ? TRUE : FALSE;
+  scope->Private = IS_TBP(sptr) && PRIVATEG(sptr);

But I still never get any scope->Private set to true when the 36th line is being processes in sym_in_scope() function...

kiranchandramohan commented 4 years ago

Thanks @michalpasztamobica for your investigations. A few comments.

1) PRIVATEG has the following definition in build-flang/tools/flang1/utils/symtab/symtab.h:

define PRIVATEG(s) (stb.stg_base[s].f5)

So the private flag can be set by filling the f5 field. This happens while importing the module in functions import, import_symbol. And the field is set in fillsym (GETBIT(f5)) in file flang/tools/flang1/flang1exe/interf.c.

2) The invocation of sym_in_scope from import_symbol through the function getocsym has PRIVATE set and I can see it entering the following condition and working correctly as expected. Invocation: semant1->apply_use_stmts->apply_use->import_module->import->import_symbol->getocsym->sym_in_scope

       } else if (scope->kind == SCOPE_USE &&
                   (PRIVATEG(sptr) ||
                    PRIVATEG(sptrloop))) {

3) The failing invocation of sym_in_scope is through refsym and does not have PRIVATE set. Invocation: parser-> _parser->semant2->refsym->sym_in_scope

michalpasztamobica commented 4 years ago

Thanks for your comment, @kiranchandramohan . It was very helpful.

I found that between what you described as point 2 (the private flag set to 1 in sym_in_scope() called from getocsym()) and point 3 (sym_in_scope() called from refsym()), the private bit is cleared for SPTR=636 by the find_def_in_most_recent_scope() function called by semant1 (L881)->apply_use_stmts->apply_use.

Actually, when I commented out line 506, which sets the private bit to 0, I got the compilation to pass (or rather - I got it to fail at undefined reference toMAIN_'`):

--- a/tools/flang1/flang1exe/module.c
+++ b/tools/flang1/flang1exe/module.c
@@ -503,7 +503,7 @@ find_def_in_most_recent_scope(int sptr, int save_sem_scope_level)
     if (NMPTRG(sptr1) != NMPTRG(sptr))
       continue;
     if (STYPEG(sptr1) == ST_ALIAS && aliased_sym_visible(sptr1)) {
-      PRIVATEP(sptr1, 0);
+//      PRIVATEP(sptr1, 0);
       HIDDENP(SYMLKG(sptr1), 0);
     }
     if (STYPEG(sptr1) == ST_ALIAS) {

So now we have the exact line to blame, but most likely removing it is not the best idea without understanding why it is being called. Perhaps a better fix would be to store the bit's value and set it back once use statement processing is done?