public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/35152]  New: Implicit procedure with keyword=argument is accepted
@ 2008-02-10  8:36 burnus at gcc dot gnu dot org
  2008-02-10 20:38 ` [Bug fortran/35152] " dfranke at gcc dot gnu dot org
                   ` (6 more replies)
  0 siblings, 7 replies; 8+ messages in thread
From: burnus at gcc dot gnu dot org @ 2008-02-10  8:36 UTC (permalink / raw)
  To: gcc-bugs

external bar
call bar(a=5)
end

The "a=" is invalid as there is no explicit interface.

"12.4 Procedure reference"
"R1220 actual-arg-spec is [ keyword = ] actual-arg"
"C1225 (R1220) The keyword = shall not appear if the interface of the procedure
is implicit in the scoping unit."

Found at:
http://groups.google.com/group/comp.lang.fortran/browse_thread/thread/543563d67446fbea/

Other compilers show:

Error: Procedure with a keyword argument at (1) does not have an explicit
interface
Error: Keyword arguments are invalid without an explicit interface.
Error: Keyword argument requires an explicit interface
Error: An actual argument keyword is being used when an explicit interface is
not known.


-- 
           Summary: Implicit procedure with keyword=argument is accepted
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          Keywords: accepts-invalid
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: burnus at gcc dot gnu dot org


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


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

* [Bug fortran/35152] Implicit procedure with keyword=argument is accepted
  2008-02-10  8:36 [Bug fortran/35152] New: Implicit procedure with keyword=argument is accepted burnus at gcc dot gnu dot org
@ 2008-02-10 20:38 ` dfranke at gcc dot gnu dot org
  2008-03-16 12:52 ` dfranke at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: dfranke at gcc dot gnu dot org @ 2008-02-10 20:38 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from dfranke at gcc dot gnu dot org  2008-02-10 20:37 -------
*** Bug 35157 has been marked as a duplicate of this bug. ***


-- 

dfranke at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |tkoenig at gcc dot gnu dot
                   |                            |org


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


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

* [Bug fortran/35152] Implicit procedure with keyword=argument is accepted
  2008-02-10  8:36 [Bug fortran/35152] New: Implicit procedure with keyword=argument is accepted burnus at gcc dot gnu dot org
  2008-02-10 20:38 ` [Bug fortran/35152] " dfranke at gcc dot gnu dot org
@ 2008-03-16 12:52 ` dfranke at gcc dot gnu dot org
  2008-03-19 19:15 ` dfranke at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: dfranke at gcc dot gnu dot org @ 2008-03-16 12:52 UTC (permalink / raw)
  To: gcc-bugs



-- 

dfranke at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |dfranke at gcc dot gnu dot
                   |dot org                     |org
                URL|                            |http://gcc.gnu.org/ml/fortra
                   |                            |n/2008-03/msg00103.html
             Status|UNCONFIRMED                 |ASSIGNED
     Ever Confirmed|0                           |1
           Keywords|                            |patch
   Last reconfirmed|0000-00-00 00:00:00         |2008-03-16 12:51:58
               date|                            |


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


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

* [Bug fortran/35152] Implicit procedure with keyword=argument is accepted
  2008-02-10  8:36 [Bug fortran/35152] New: Implicit procedure with keyword=argument is accepted burnus at gcc dot gnu dot org
  2008-02-10 20:38 ` [Bug fortran/35152] " dfranke at gcc dot gnu dot org
  2008-03-16 12:52 ` dfranke at gcc dot gnu dot org
@ 2008-03-19 19:15 ` dfranke at gcc dot gnu dot org
  2008-03-19 19:16 ` dfranke at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: dfranke at gcc dot gnu dot org @ 2008-03-19 19:15 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from dfranke at gcc dot gnu dot org  2008-03-19 19:14 -------
Subject: Bug 35152

Author: dfranke
Date: Wed Mar 19 19:13:48 2008
New Revision: 133347

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=133347
Log:
gcc/fortran:
2008-03-19  Daniel Franke  <franke.daniel@gmail.com>

        PR fortran/35152
        * interface.c (gfc_procedure_use): Check for keyworded arguments in
        procedures without explicit interfaces.

gcc/testsuite:
2008-03-19  Daniel Franke  <franke.daniel@gmail.com>

        PR fortran/35152
        * gfortran.dg/argument_checking_16.f90: New test.



Added:
    trunk/gcc/testsuite/gfortran.dg/argument_checking_16.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/interface.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/35152] Implicit procedure with keyword=argument is accepted
  2008-02-10  8:36 [Bug fortran/35152] New: Implicit procedure with keyword=argument is accepted burnus at gcc dot gnu dot org
                   ` (2 preceding siblings ...)
  2008-03-19 19:15 ` dfranke at gcc dot gnu dot org
@ 2008-03-19 19:16 ` dfranke at gcc dot gnu dot org
  2008-03-20 11:24 ` dominiq at lps dot ens dot fr
                   ` (2 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: dfranke at gcc dot gnu dot org @ 2008-03-19 19:16 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from dfranke at gcc dot gnu dot org  2008-03-19 19:15 -------
Fixed in trunk, no backport as it is not a regression. Closing.


-- 

dfranke at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|ASSIGNED                    |RESOLVED
           Keywords|patch                       |
      Known to fail|                            |4.3.0
      Known to work|                            |4.4.0
         Resolution|                            |FIXED
   Target Milestone|---                         |4.4.0


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


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

* [Bug fortran/35152] Implicit procedure with keyword=argument is accepted
  2008-02-10  8:36 [Bug fortran/35152] New: Implicit procedure with keyword=argument is accepted burnus at gcc dot gnu dot org
                   ` (3 preceding siblings ...)
  2008-03-19 19:16 ` dfranke at gcc dot gnu dot org
@ 2008-03-20 11:24 ` dominiq at lps dot ens dot fr
  2008-03-20 12:15 ` dfranke at gcc dot gnu dot org
  2008-03-20 12:17 ` burnus at gcc dot gnu dot org
  6 siblings, 0 replies; 8+ messages in thread
From: dominiq at lps dot ens dot fr @ 2008-03-20 11:24 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from dominiq at lps dot ens dot fr  2008-03-20 11:24 -------
With this revision the following code gives an error:

[ibook-dhum] f90/bug% cat rename_use_1.f90
! { dg-do compile }
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 bar_pwrk(pr,p,f,cd,info,work=aux)

  return

End Subroutine foo_sub
[ibook-dhum] f90/bug% gfc rename_use_1.f90
rename_use_1.f90:114.36:

  Call bar_pwrk(pr,p,f,cd,info,work=aux)
                                   1
Error: Keyword argument requires explicit interface for procedure 'bar_pwrk' at
(1)

If 'Call bar_pwrk(pr,p,f,cd,info,work=aux)' is replaced by 'Call
foo_pwrk(pr,p,f,cd,info,work=aux)' the error disappears. Note that I did not
write the code, but only kept it and I don't know if the code is valid or not.


-- 


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


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

* [Bug fortran/35152] Implicit procedure with keyword=argument is accepted
  2008-02-10  8:36 [Bug fortran/35152] New: Implicit procedure with keyword=argument is accepted burnus at gcc dot gnu dot org
                   ` (4 preceding siblings ...)
  2008-03-20 11:24 ` dominiq at lps dot ens dot fr
@ 2008-03-20 12:15 ` dfranke at gcc dot gnu dot org
  2008-03-20 12:17 ` burnus at gcc dot gnu dot org
  6 siblings, 0 replies; 8+ messages in thread
From: dfranke at gcc dot gnu dot org @ 2008-03-20 12:15 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from dfranke at gcc dot gnu dot org  2008-03-20 12:15 -------
> I don't know if the code is valid or not

IMO, it is not:

module foo_pr_mod
  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_pr_mod
  ...
  Call bar_pwrk(pr,p,f,cd,info,work=aux)
end subroutine

The module renames 'bar_pwrk' to 'foo_pwrk'. When the subroutine uses the
module it only sees 'foo_pwrk', not 'bar_pwrk'. Hence, 'bar_pwrk' has an
implicit interface within 'foo_sub'.

IMO, the warning is correct and the code ahould be fixed :)


-- 


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


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

* [Bug fortran/35152] Implicit procedure with keyword=argument is accepted
  2008-02-10  8:36 [Bug fortran/35152] New: Implicit procedure with keyword=argument is accepted burnus at gcc dot gnu dot org
                   ` (5 preceding siblings ...)
  2008-03-20 12:15 ` dfranke at gcc dot gnu dot org
@ 2008-03-20 12:17 ` burnus at gcc dot gnu dot org
  6 siblings, 0 replies; 8+ messages in thread
From: burnus at gcc dot gnu dot org @ 2008-03-20 12:17 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from burnus at gcc dot gnu dot org  2008-03-20 12:17 -------
> With this revision the following code gives an error:
>   Call bar_pwrk(pr,p,f,cd,info,work=aux)

The error is correct; bar_pwrk is known in module bar_pr_mod, that module is
then imported in module foo_pr_mod but under the name foo_pwrk. Subroutine
foo_sub now uses the module foo_pr_mod and thus only the symbol foo_pwrk and
not bar_pwrk is use associated. Therefore, bar_pwrk has an implicit interface,
which per C1225 may not use the keyword= syntax.
(All compilers I tried give the same error as gfortran.)

(I have to admit that I miss an option to enforce that the name of a
non-intrinsic subroutine has to be made available before using PROCEDURE,
EXTERNAL, INTERFACE or being use/host associated. Unfortunately, IMPLICIT NONE
does not enforce this.)


-- 


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


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

end of thread, other threads:[~2008-03-20 12:17 UTC | newest]

Thread overview: 8+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-02-10  8:36 [Bug fortran/35152] New: Implicit procedure with keyword=argument is accepted burnus at gcc dot gnu dot org
2008-02-10 20:38 ` [Bug fortran/35152] " dfranke at gcc dot gnu dot org
2008-03-16 12:52 ` dfranke at gcc dot gnu dot org
2008-03-19 19:15 ` dfranke at gcc dot gnu dot org
2008-03-19 19:16 ` dfranke at gcc dot gnu dot org
2008-03-20 11:24 ` dominiq at lps dot ens dot fr
2008-03-20 12:15 ` dfranke at gcc dot gnu dot org
2008-03-20 12:17 ` burnus 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).