public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/32634]  New: renamed, use associated generic interface rejected
@ 2007-07-05 15:21 pault at gcc dot gnu dot org
  2007-07-05 15:24 ` [Bug fortran/32634] " pault at gcc dot gnu dot org
                   ` (7 more replies)
  0 siblings, 8 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-07-05 15:21 UTC (permalink / raw)
  To: gcc-bugs

The code below incorrectly gives the error, as reported by Salvatore Filippone:

  Call foo_pwrk(pr,p,f,cd,info,work=aux)
                                       1
Error: There is no specific subroutine for the generic 'bar_pwrk' at (1)

Not only does it look correct but other compilers handle it OK.  module.c is
not finding the "true name" symbol, even though it has been created with the
"use name" symtree. A quick inspection of the .mod file reveals that the
interface is given the true name, which simply is not findable by read_module.

Paul


module foo_base_mod


  type foo_dmt
    real(kind(1.d0)), allocatable  :: rv(:)
    integer, allocatable :: iv1(:), iv2(:)
  end type foo_dmt
  type foo_zmt
    complex(kind(1.d0)), allocatable  :: rv(:)
    integer, allocatable  :: iv1(:), iv2(:)
  end type foo_zmt


  type foo_cdt
     integer, allocatable :: md(:)
     integer, allocatable :: hi(:), ei(:)
  end type foo_cdt


end module foo_base_mod

module bar_prt

  use foo_base_mod, only : foo_dmt, foo_zmt, foo_cdt

  type bar_dbprt
    type(foo_dmt), allocatable :: av(:) 
    real(kind(1.d0)), allocatable      :: d(:)  
    type(foo_cdt)                :: cd 
  end type bar_dbprt


  type bar_dprt
    type(bar_dbprt), allocatable  :: bpv(:) 
  end type bar_dprt

  type bar_zbprt
    type(foo_zmt), allocatable :: av(:) 
    complex(kind(1.d0)), allocatable   :: d(:)  
    type(foo_cdt)                :: cd 
  end type bar_zbprt

  type bar_zprt
    type(bar_zbprt), allocatable  :: bpv(:) 
  end type bar_zprt


end module bar_prt

module bar_pr_mod
  use bar_prt

  interface bar_pwrk
    subroutine bar_dppwrk(pr,x,y,cd,info,trans,work)
      use foo_base_mod
      use bar_prt
      type(foo_cdt),intent(in)    :: cd
      type(bar_dprt), intent(in)  :: pr
      real(kind(0.d0)),intent(inout)    :: x(:), y(:)
      integer, intent(out)              :: info
      character(len=1), optional        :: trans
      real(kind(0.d0)),intent(inout), optional, target :: work(:)
    end subroutine bar_dppwrk
    subroutine bar_zppwrk(pr,x,y,cd,info,trans,work)
      use foo_base_mod
      use bar_prt
      type(foo_cdt),intent(in)    :: cd
      type(bar_zprt), intent(in)  :: pr
      complex(kind(0.d0)),intent(inout) :: x(:), y(:)
      integer, intent(out)              :: info
      character(len=1), optional        :: trans
      complex(kind(0.d0)),intent(inout), optional, target :: work(:)
    end subroutine bar_zppwrk
  end interface

end module bar_pr_mod


module foo_pr_mod

  use bar_prt, &
       & foo_dbprt  => bar_dbprt,&
       & foo_zbprt  => bar_zbprt,&
       & foo_dprt   => bar_dprt,&
       & foo_zprt   => bar_zprt 

  use bar_pr_mod, &
       & foo_pwrk  => bar_pwrk


end module foo_pr_mod


Subroutine foo_sub(a,pr,b,x,eps,cd,info)
  use foo_base_mod
  use foo_pr_mod
  Implicit None
!!$  parameters 
  Type(foo_dmt), Intent(in)  :: a
  Type(foo_dprt), Intent(in)   :: pr 
  Type(foo_cdt), Intent(in)    :: cd
  Real(Kind(1.d0)), Intent(in)       :: b(:)
  Real(Kind(1.d0)), Intent(inout)    :: x(:)
  Real(Kind(1.d0)), Intent(in)       :: eps
  integer, intent(out)               :: info

!!$   Local data
  Real(Kind(1.d0)), allocatable, target   :: aux(:),wwrk(:,:)
  Real(Kind(1.d0)), allocatable   :: p(:), f(:)

  info = 0

  Call foo_pwrk(pr,p,f,cd,info,work=aux)

  return

End Subroutine foo_sub


-- 
           Summary: renamed, use associated generic interface rejected
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          Keywords: rejects-valid
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: pault at gcc dot gnu dot org
        ReportedBy: pault at gcc dot gnu dot org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=32634


^ permalink raw reply	[flat|nested] 9+ messages in thread

* [Bug fortran/32634] renamed, use associated generic interface rejected
  2007-07-05 15:21 [Bug fortran/32634] New: renamed, use associated generic interface rejected pault at gcc dot gnu dot org
@ 2007-07-05 15:24 ` pault at gcc dot gnu dot org
  2007-07-06 11:20 ` patchapp at dberlin dot org
                   ` (6 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-07-05 15:24 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from pault at gcc dot gnu dot org  2007-07-05 15:24 -------
This fixes it but is, as yet, unregtested:

Index: gcc/fortran/module.c
===================================================================
*** gcc/fortran/module.c        (revision 126317)
--- gcc/fortran/module.c        (working copy)
*************** write_operator (gfc_user_op *uop)
*** 3943,3948 ****
--- 3943,3951 ----
  static void
  write_generic (gfc_symbol *sym)
  {
+   const char *p;
+   int nuse, j;
+
    if (sym->generic == NULL
        || !gfc_check_access (sym->attr.access, sym->ns->default_access))
      return;
*************** write_generic (gfc_symbol *sym)
*** 3950,3956 ****
    if (sym->module == NULL)
      sym->module = gfc_get_string (module_name);

!   mio_symbol_interface (&sym->name, &sym->module, &sym->generic);
  }


--- 3953,3971 ----
    if (sym->module == NULL)
      sym->module = gfc_get_string (module_name);

!   /* See how many use names there are.  If none, go through the start
!        of the loop at least once.  */
!   nuse = number_use_names (sym->name);
!   if (nuse == 0)
!     nuse = 1;
!
!   for (j = 1; j <= nuse; j++)
!     {
!       /* Get the jth local name for this symbol.  */
!       p = find_use_name_n (sym->name, &j);
!
!       mio_symbol_interface (&p, &sym->module, &sym->generic);
!     }
  }


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=32634


^ permalink raw reply	[flat|nested] 9+ messages in thread

* [Bug fortran/32634] renamed, use associated generic interface rejected
  2007-07-05 15:21 [Bug fortran/32634] New: renamed, use associated generic interface rejected pault at gcc dot gnu dot org
  2007-07-05 15:24 ` [Bug fortran/32634] " pault at gcc dot gnu dot org
@ 2007-07-06 11:20 ` patchapp at dberlin dot org
  2007-07-10  5:11 ` pault at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: patchapp at dberlin dot org @ 2007-07-06 11:20 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from patchapp at dberlin dot org  2007-07-06 11:20 -------
Subject: Bug number PR32634

A patch for this bug has been added to the patch tracker.
The mailing list url for the patch is
http://gcc.gnu.org/ml/gcc-patches/2007-07/msg00561.html


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=32634


^ permalink raw reply	[flat|nested] 9+ messages in thread

* [Bug fortran/32634] renamed, use associated generic interface rejected
  2007-07-05 15:21 [Bug fortran/32634] New: renamed, use associated generic interface rejected pault at gcc dot gnu dot org
  2007-07-05 15:24 ` [Bug fortran/32634] " pault at gcc dot gnu dot org
  2007-07-06 11:20 ` patchapp at dberlin dot org
@ 2007-07-10  5:11 ` pault at gcc dot gnu dot org
  2007-07-10  5:13 ` pault at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-07-10  5:11 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from pault at gcc dot gnu dot org  2007-07-10 05:11 -------
Subject: Bug 32634

Author: pault
Date: Tue Jul 10 05:11:00 2007
New Revision: 126509

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=126509
Log:
2007-07-10  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/32157
        * resolve.c (is_external_proc): New function.  Adds test that
        the symbol is not an intrinsic procedure.
        * (resolve_function, resolve_call): Replace logical statements
        with call to is_external_proc.

        PR fortran/32689
        * simplify.c (gfc_simplify_transfer): If mold has rank, the
        result is an array.

        PR fortran/32634
        * module.c (write_generic): Write the local name of the
        interface. 


2007-07-10  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/32157
        * gfortran.dg/overload_2.f90: New test.

        PR fortran/32689
        * gfortran.dg/transfer_simplify_5.f90

        PR fortran/32634
        * gfortran.dg/interface_15.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/interface_16.f90
    trunk/gcc/testsuite/gfortran.dg/overload_2.f90
    trunk/gcc/testsuite/gfortran.dg/transfer_simplify_5.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/module.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/fortran/simplify.c
    trunk/gcc/testsuite/ChangeLog


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=32634


^ permalink raw reply	[flat|nested] 9+ messages in thread

* [Bug fortran/32634] renamed, use associated generic interface rejected
  2007-07-05 15:21 [Bug fortran/32634] New: renamed, use associated generic interface rejected pault at gcc dot gnu dot org
                   ` (2 preceding siblings ...)
  2007-07-10  5:11 ` pault at gcc dot gnu dot org
@ 2007-07-10  5:13 ` pault at gcc dot gnu dot org
  2007-07-12  6:31 ` dfranke at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-07-10  5:13 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from pault at gcc dot gnu dot org  2007-07-10 05:13 -------
Fixed on trunk.

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |RESOLVED
         Resolution|                            |FIXED


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=32634


^ permalink raw reply	[flat|nested] 9+ messages in thread

* [Bug fortran/32634] renamed, use associated generic interface rejected
  2007-07-05 15:21 [Bug fortran/32634] New: renamed, use associated generic interface rejected pault at gcc dot gnu dot org
                   ` (3 preceding siblings ...)
  2007-07-10  5:13 ` pault at gcc dot gnu dot org
@ 2007-07-12  6:31 ` dfranke at gcc dot gnu dot org
  2007-07-12  6:35 ` dfranke at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: dfranke at gcc dot gnu dot org @ 2007-07-12  6:31 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from dfranke at gcc dot gnu dot org  2007-07-12 06:31 -------
Subject: Bug 32634

Author: dfranke
Date: Thu Jul 12 06:31:12 2007
New Revision: 126572

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=126572
Log:
2007-07-12  Daniel Franke  <franke.daniel@gmail.com>

        PR fortran/32634
        PR fortran/32727
        * module.c: Reverted Paul's patch from 2007-07-10.


Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/module.c


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=32634


^ permalink raw reply	[flat|nested] 9+ messages in thread

* [Bug fortran/32634] renamed, use associated generic interface rejected
  2007-07-05 15:21 [Bug fortran/32634] New: renamed, use associated generic interface rejected pault at gcc dot gnu dot org
                   ` (4 preceding siblings ...)
  2007-07-12  6:31 ` dfranke at gcc dot gnu dot org
@ 2007-07-12  6:35 ` dfranke at gcc dot gnu dot org
  2007-07-12 20:05 ` pault at gcc dot gnu dot org
  2007-07-12 20:27 ` pault at gcc dot gnu dot org
  7 siblings, 0 replies; 9+ messages in thread
From: dfranke at gcc dot gnu dot org @ 2007-07-12  6:35 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from dfranke at gcc dot gnu dot org  2007-07-12 06:35 -------
Reverted patch and re-opened as requested in PR32727.


-- 

dfranke at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |dfranke at gcc dot gnu dot
                   |                            |org
             Status|RESOLVED                    |UNCONFIRMED
         Resolution|FIXED                       |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=32634


^ permalink raw reply	[flat|nested] 9+ messages in thread

* [Bug fortran/32634] renamed, use associated generic interface rejected
  2007-07-05 15:21 [Bug fortran/32634] New: renamed, use associated generic interface rejected pault at gcc dot gnu dot org
                   ` (5 preceding siblings ...)
  2007-07-12  6:35 ` dfranke at gcc dot gnu dot org
@ 2007-07-12 20:05 ` pault at gcc dot gnu dot org
  2007-07-12 20:27 ` pault at gcc dot gnu dot org
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-07-12 20:05 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from pault at gcc dot gnu dot org  2007-07-12 20:05 -------
Subject: Bug 32634

Author: pault
Date: Thu Jul 12 20:04:59 2007
New Revision: 126600

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=126600
Log:
2007-07-12  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/32634
        PR fortran/32727
        * module.c (write_generic): Restore patch of 2007-07-10 and use
        symbol name if there are no use names. 

2007-07-12  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/32727
        * gfortran.dg/interface_17.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/interface_17.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/module.c
    trunk/gcc/testsuite/ChangeLog


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=32634


^ permalink raw reply	[flat|nested] 9+ messages in thread

* [Bug fortran/32634] renamed, use associated generic interface rejected
  2007-07-05 15:21 [Bug fortran/32634] New: renamed, use associated generic interface rejected pault at gcc dot gnu dot org
                   ` (6 preceding siblings ...)
  2007-07-12 20:05 ` pault at gcc dot gnu dot org
@ 2007-07-12 20:27 ` pault at gcc dot gnu dot org
  7 siblings, 0 replies; 9+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-07-12 20:27 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from pault at gcc dot gnu dot org  2007-07-12 20:27 -------
Fixed... again, I hope.

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |RESOLVED
         Resolution|                            |FIXED


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=32634


^ permalink raw reply	[flat|nested] 9+ messages in thread

end of thread, other threads:[~2007-07-12 20:27 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-07-05 15:21 [Bug fortran/32634] New: renamed, use associated generic interface rejected pault at gcc dot gnu dot org
2007-07-05 15:24 ` [Bug fortran/32634] " pault at gcc dot gnu dot org
2007-07-06 11:20 ` patchapp at dberlin dot org
2007-07-10  5:11 ` pault at gcc dot gnu dot org
2007-07-10  5:13 ` pault at gcc dot gnu dot org
2007-07-12  6:31 ` dfranke at gcc dot gnu dot org
2007-07-12  6:35 ` dfranke at gcc dot gnu dot org
2007-07-12 20:05 ` pault at gcc dot gnu dot org
2007-07-12 20:27 ` pault at gcc dot gnu dot org

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).