public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/17630] New: Interface procedure not recognized
@ 2004-09-23  9:10 giannozz at nest dot sns dot it
  2004-09-23 17:56 ` [Bug fortran/17630] " tobi at gcc dot gnu dot org
                   ` (2 more replies)
  0 siblings, 3 replies; 4+ messages in thread
From: giannozz at nest dot sns dot it @ 2004-09-23  9:10 UTC (permalink / raw)
  To: gcc-bugs

Linux C daily build, 22 sep: 
$ gfc --version 
GNU Fortran 95 (GCC 4.0.0 20040922 (experimental)) 
 
$ gfc -c wave_base.f90 
 In file wave_base..f90:49 
 
       cnorm = cnorm + dotp(gzero, cgrad(:,i,1), cgrad(:,i,1)) 
                          1 
Error: Symbol 'dotp' at (1) has no IMPLICIT type 
 
'dotp' is defined as an interface procedure. I don't see anything wrong  
in the following piece of code: 
 
!==----------------------------------------------==! 
MODULE wave_base 
  !==----------------------------------------------==! 
 
 
  IMPLICIT NONE 
  INTEGER, PARAMETER :: dbl = selected_real_kind(14,200) 
  INTEGER, PARAMETER :: group = 0 
 
  PUBLIC :: converg_base_gamma 
  INTERFACE dotp 
     MODULE PROCEDURE dotp_gamma, dotp_gamma_n 
  END INTERFACE 
 
  !==----------------------------------------------==! 
CONTAINS 
  !==----------------------------------------------==! 
 
  !==----------------------------------------------==! 
  SUBROUTINE converg_base_gamma(gzero, cgrad, gemax, cnorm) 
  !==----------------------------------------------==! 
 
    IMPLICIT NONE 
 
    ! ...   declare subroutine arguments 
    COMPLEX(dbl) :: cgrad(:,:,:) 
    LOGICAL, INTENT(IN) :: gzero 
    REAL(dbl), INTENT(OUT) :: gemax, cnorm 
 
    ! ...   declare other variables 
    INTEGER    :: imx, izamax, i, nb, ngw 
    REAL(dbl)  :: gemax_l 
 
    ! ...   end of declarations 
    !  ---------------------------------------------- 
 
    ngw     = SIZE( cgrad, 1) 
    nb      = SIZE( cgrad, 2) 
 
    gemax_l = 0.d0 
    cnorm   = 0.d0 
 
    DO i = 1, nb 
       imx = izamax( ngw, cgrad(1, i, 1), 1 ) 
       IF ( gemax_l < ABS( cgrad(imx, i, 1) ) ) THEN 
          gemax_l = ABS ( cgrad(imx, i, 1) ) 
       END IF 
       cnorm = cnorm + dotp(gzero, cgrad(:,i,1), cgrad(:,i,1)) 
    END DO 
 
    CALL mp_max(gemax_l, group) 
    CALL mp_sum(nb, group) 
    CALL mp_sum(ngw, group) 
 
    gemax = gemax_l 
    cnorm = SQRT( cnorm / (nb * ngw) ) 
 
    RETURN 
  !==----------------------------------------------==! 
  END SUBROUTINE converg_base_gamma 
  !==----------------------------------------------==! 
 
  !==----------------------------------------------==! 
  REAL(dbl) FUNCTION dotp_gamma(gzero, ng, a, b) 
  !==----------------------------------------------==! 
 
    REAL(dbl) :: ddot 
    REAL(dbl) :: dot_tmp 
    INTEGER, INTENT(IN) :: ng 
    LOGICAL, INTENT(IN) :: gzero 
 
    COMPLEX(dbl) :: a(:), b(:) 
    INTEGER :: n 
 
    n = MIN( SIZE(a), SIZE(b) ) 
    n = MIN( n, ng ) 
 
    IF ( n < 1 ) & 
         CALL errore( ' dotp_gamma ', ' wrong dimension ', 1 ) 
 
    ! ...       gzero is true on the processor where the first element of the 
    ! ...       input arrays is the coefficient of the G=0 plane wave 
    ! 
    IF (gzero) THEN 
       dot_tmp = ddot( 2*(n-1), a(2), 1, b(2), 1) 
       dot_tmp = 2.0d0 * dot_tmp + REAL( a(1) ) * REAL( b(1) )  
    ELSE 
       dot_tmp = ddot( 2*ng, a(1), 1, b(1), 1) 
       dot_tmp = 2.0d0*dot_tmp 
    END IF 
 
    CALL mp_sum( dot_tmp, group ) 
    dotp_gamma = dot_tmp 
 
    RETURN 
  !==----------------------------------------------==! 
  END FUNCTION dotp_gamma 
  !==----------------------------------------------==! 
  
  !==----------------------------------------------==! 
  REAL(dbl) FUNCTION dotp_gamma_n(gzero, a, b) 
  !==----------------------------------------------==! 
 
    LOGICAL, INTENT(IN) :: gzero 
 
    COMPLEX(dbl) :: a(:), b(:) 
    INTEGER :: n 
 
    n = MIN( SIZE(a), SIZE(b) ) 
 
    IF ( n < 1 ) & 
         CALL errore( ' dotp_gamma_n ', ' wrong dimension ', 1 ) 
 
    dotp_gamma_n = dotp_gamma(gzero, n, a, b) 
 
    RETURN 
  !==----------------------------------------------==! 
  END FUNCTION dotp_gamma_n 
  !==----------------------------------------------==! 
 
 
  !==----------------------------------------------==! 
END MODULE wave_base 
!==----------------------------------------------==!

-- 
           Summary: Interface procedure not recognized
           Product: gcc
           Version: 4.0.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P2
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: giannozz at nest dot sns dot it
                CC: gcc-bugs at gcc dot gnu dot org
  GCC host triplet: i686-pc-linux-gnu


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


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

* [Bug fortran/17630] Interface procedure not recognized
  2004-09-23  9:10 [Bug fortran/17630] New: Interface procedure not recognized giannozz at nest dot sns dot it
@ 2004-09-23 17:56 ` tobi at gcc dot gnu dot org
  2004-09-23 19:46 ` tobi at gcc dot gnu dot org
  2004-09-23 19:46 ` tobi at gcc dot gnu dot org
  2 siblings, 0 replies; 4+ messages in thread
From: tobi at gcc dot gnu dot org @ 2004-09-23 17:56 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2004-09-23 17:56 -------
This also looks like a problem with host association.

*** This bug has been marked as a duplicate of 16940 ***

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


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


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

* [Bug fortran/17630] Interface procedure not recognized
  2004-09-23  9:10 [Bug fortran/17630] New: Interface procedure not recognized giannozz at nest dot sns dot it
  2004-09-23 17:56 ` [Bug fortran/17630] " tobi at gcc dot gnu dot org
@ 2004-09-23 19:46 ` tobi at gcc dot gnu dot org
  2004-09-23 19:46 ` tobi at gcc dot gnu dot org
  2 siblings, 0 replies; 4+ messages in thread
From: tobi at gcc dot gnu dot org @ 2004-09-23 19:46 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2004-09-23 19:46 -------
I reopenend the bug so that I can mark it as dupe of PR17379

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


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


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

* [Bug fortran/17630] Interface procedure not recognized
  2004-09-23  9:10 [Bug fortran/17630] New: Interface procedure not recognized giannozz at nest dot sns dot it
  2004-09-23 17:56 ` [Bug fortran/17630] " tobi at gcc dot gnu dot org
  2004-09-23 19:46 ` tobi at gcc dot gnu dot org
@ 2004-09-23 19:46 ` tobi at gcc dot gnu dot org
  2 siblings, 0 replies; 4+ messages in thread
From: tobi at gcc dot gnu dot org @ 2004-09-23 19:46 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2004-09-23 19:46 -------


*** This bug has been marked as a duplicate of 17379 ***

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


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


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

end of thread, other threads:[~2004-09-23 19:46 UTC | newest]

Thread overview: 4+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2004-09-23  9:10 [Bug fortran/17630] New: Interface procedure not recognized giannozz at nest dot sns dot it
2004-09-23 17:56 ` [Bug fortran/17630] " tobi at gcc dot gnu dot org
2004-09-23 19:46 ` tobi at gcc dot gnu dot org
2004-09-23 19:46 ` tobi 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).