public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/31683]  New: bogus warnings / miscompilation
@ 2007-04-24 14:42 jv244 at cam dot ac dot uk
  2007-04-24 17:47 ` [Bug fortran/31683] " burnus at gcc dot gnu dot org
                   ` (7 more replies)
  0 siblings, 8 replies; 9+ messages in thread
From: jv244 at cam dot ac dot uk @ 2007-04-24 14:42 UTC (permalink / raw)
  To: gcc-bugs

[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #1: Type: text/plain, Size: 2257 bytes --]

The following generates bogus warnings and is likely miscompiled:

MODULE test
  IMPLICIT NONE
  INTEGER, PARAMETER :: dp=KIND(0.0D0)
  INTEGER, ALLOCATABLE, DIMENSION(:) :: ncoset
  PRIVATE

  PUBLIC :: overlap

CONTAINS

  SUBROUTINE overlap(la_max_set,la_min_set,&
                     lb_max_set,lb_min_set,&
                     s,lds,&
                     pab,force_a)
    INTEGER, INTENT(IN)                      :: la_max_set, la_min_set
    INTEGER, INTENT(IN)                      :: lb_max_set, lb_min_set
    INTEGER, INTENT(IN)                      :: lds
    REAL(KIND=dp), DIMENSION(lds, lds, *), &
      INTENT(INOUT)                          :: s
    REAL(KIND=dp), DIMENSION(:, :), &
      INTENT(IN), OPTIONAL                   :: pab
    REAL(KIND=dp), DIMENSION(3), &
      INTENT(OUT), OPTIONAL                  :: force_a

    INTEGER                                  :: i, j, k, na, nb
    LOGICAL                                  :: calculate_force_a

!   ---------------------------------------------------------------------------

        na = 0
        nb = 0
        calculate_force_a=.TRUE.
        IF (calculate_force_a) THEN
          DO k=1,3
            DO j=ncoset(lb_min_set-1)+1,ncoset(lb_max_set)
              DO i=ncoset(la_min_set-1)+1,ncoset(la_max_set)
                force_a(k) = force_a(k) + pab(na+i,nb+j)*s(i,j,k+1)
              END DO
            END DO
          END DO
        END IF

    END SUBROUTINE

END MODULE test

gfortran -c -O2 -g -Wall test.f90
test.f90: In function ‘overlap’:
test.f90:7: warning: ‘offset.4’ may be used uninitialized in this function
test.f90:7: warning: ‘stride.3’ may be used uninitialized in this function
test.f90:7: warning: ‘stride.1’ may be used uninitialized in this function
test.f90:7: warning: ‘pab.0’ may be used uninitialized in this function

it is a reduced testcase from CP2K


-- 
           Summary: bogus warnings / miscompilation
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: jv244 at cam dot ac dot uk


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


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

* [Bug fortran/31683] bogus warnings / miscompilation
  2007-04-24 14:42 [Bug fortran/31683] New: bogus warnings / miscompilation jv244 at cam dot ac dot uk
@ 2007-04-24 17:47 ` burnus at gcc dot gnu dot org
  2007-04-24 18:07 ` jv244 at cam dot ac dot uk
                   ` (6 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-04-24 17:47 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from burnus at gcc dot gnu dot org  2007-04-24 18:46 -------
This example is not valid. As NAG f95 claims:
Error: foo.f90, line 45: ALLOCATABLE array NCOSET used but never ALLOCATEd

(gfortran actually misses such an error/warning.


-- 


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


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

* [Bug fortran/31683] bogus warnings / miscompilation
  2007-04-24 14:42 [Bug fortran/31683] New: bogus warnings / miscompilation jv244 at cam dot ac dot uk
  2007-04-24 17:47 ` [Bug fortran/31683] " burnus at gcc dot gnu dot org
@ 2007-04-24 18:07 ` jv244 at cam dot ac dot uk
  2007-04-24 18:58 ` burnus at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: jv244 at cam dot ac dot uk @ 2007-04-24 18:07 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from jv244 at cam dot ac dot uk  2007-04-24 19:07 -------
(In reply to comment #1)
> This example is not valid. As NAG f95 claims:

it is not supposed to be a runable example, of course. Just remove the
'PRIVATE' from the module definition.


-- 


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


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

* [Bug fortran/31683] bogus warnings / miscompilation
  2007-04-24 14:42 [Bug fortran/31683] New: bogus warnings / miscompilation jv244 at cam dot ac dot uk
  2007-04-24 17:47 ` [Bug fortran/31683] " burnus at gcc dot gnu dot org
  2007-04-24 18:07 ` jv244 at cam dot ac dot uk
@ 2007-04-24 18:58 ` burnus at gcc dot gnu dot org
  2007-04-24 20:06 ` [Bug fortran/31683] bogus warnings with optional arguments tkoenig at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-04-24 18:58 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from burnus at gcc dot gnu dot org  2007-04-24 19:58 -------
> > This example is not valid. As NAG f95 claims:
> it is not supposed to be a runable example
Well, for hunting miscompilation bugs, a runable example helps.

I think there are at leastfour problems:

a) The program misses something like:
        allocate(ncoset(lb_min_set-1:lb_max_set))
        ncoset = 1
- or as you have suggested - overlap may not be PRIVATE
otherwise the program is it not valid.

b) Since the program is invalid if pad is not present, I added:
        if(.not.present(pab)) return
(similarly for force_a)

c) gfortran should detect that the local variable ncoset is never allocated -
as NAG f95 does:
Error: foo.f90, line 45: ALLOCATABLE array NCOSET used but never ALLOCATEd

d) gfortran give the wrong warning about offset.9 being uninitialized.
It is initialized if pad is present and if it isn't, this variable is not
accessed as I explicitly use: "if(.not.present(pab)) return"

For (d) I filled the middle-end PR 31688.

I still miss the place where gfortran miscompiles (if any).


-- 

burnus at gcc dot gnu dot org changed:

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


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


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

* [Bug fortran/31683] bogus warnings with optional arguments
  2007-04-24 14:42 [Bug fortran/31683] New: bogus warnings / miscompilation jv244 at cam dot ac dot uk
                   ` (2 preceding siblings ...)
  2007-04-24 18:58 ` burnus at gcc dot gnu dot org
@ 2007-04-24 20:06 ` tkoenig at gcc dot gnu dot org
  2007-04-25  1:19 ` jv244 at cam dot ac dot uk
                   ` (3 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: tkoenig at gcc dot gnu dot org @ 2007-04-24 20:06 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from tkoenig at gcc dot gnu dot org  2007-04-24 21:06 -------
There is a questionable practice with the original code:  It uses
pab without a check whether it is present.

The compiler tries to guard against this, partially by generating
(from the *.original dump):

  if (pab != 0B)
    {
      {
        int4 D.1054;

        D.1054 = pab->dim[0].stride;
        stride.1 = D.1054 == 0 ? 1 : D.1054;
        pab.0 = (real8[0:D.1055] *) pab->data;
        ubound.0 = (pab->dim[0].ubound - pab->dim[0].lbound) + 1;
        stride.3 = pab->dim[1].stride;
        ubound.2 = (pab->dim[1].ubound - pab->dim[1].lbound) + 1;
        size.5 = stride.3 * NON_LVALUE_EXPR <ubound.2>;
        offset.4 = -stride.1 - NON_LVALUE_EXPR <stride.3>;
        D.1055 = size.5 - 1;
        D.1056 = (bit_size_type) (<unnamed-unsigned:32>) size.5 * 64;
        D.1057 = (<unnamed-unsigned:32>) size.5 * 8;
      }
    }

All these variables are initialized in this block, and nowhere
else.  Later in the loop, they are used, which generates the warnings.

The if(pab) above doesn't really help because the code will crash, or produce
strange results, if pab isn't present.

This is a very misleading diagnostic, but not a wrong-code as far as I can see.


-- 

tkoenig at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
           Keywords|                            |diagnostic
   Last reconfirmed|0000-00-00 00:00:00         |2007-04-24 21:06:01
               date|                            |
            Summary|bogus warnings /            |bogus warnings with optional
                   |miscompilation              |arguments


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


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

* [Bug fortran/31683] bogus warnings with optional arguments
  2007-04-24 14:42 [Bug fortran/31683] New: bogus warnings / miscompilation jv244 at cam dot ac dot uk
                   ` (3 preceding siblings ...)
  2007-04-24 20:06 ` [Bug fortran/31683] bogus warnings with optional arguments tkoenig at gcc dot gnu dot org
@ 2007-04-25  1:19 ` jv244 at cam dot ac dot uk
  2007-04-25 18:50 ` burnus at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  7 siblings, 0 replies; 9+ messages in thread
From: jv244 at cam dot ac dot uk @ 2007-04-25  1:19 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from jv244 at cam dot ac dot uk  2007-04-25 02:18 -------
(In reply to comment #4)
> This is a very misleading diagnostic, but not a wrong-code as far as I can see.

Indeed, I was mislead by the diagnostic in reducing the wrong-code issue to the
above testcase. So that leaves the CP2K sources (see PR 29975) as the
'testcase'. From that PR is clear that the miscompilation happens in
__ai_overlap_new_MOD_overlap
gdb shows a segfault 
__ai_overlap_new_MOD_overlap (la_max_set=@0x1620720, la_min_set=@0x1620630,
npgfa=Variable "npgfa" is not available.
) at ai_overlap_new.f90:389
389                           s(coa,cob,1) = s(coapy,cobmy,1) -
rab(2)*s(coa,cobmy,1)


-- 


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


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

* [Bug fortran/31683] bogus warnings with optional arguments
  2007-04-24 14:42 [Bug fortran/31683] New: bogus warnings / miscompilation jv244 at cam dot ac dot uk
                   ` (4 preceding siblings ...)
  2007-04-25  1:19 ` jv244 at cam dot ac dot uk
@ 2007-04-25 18:50 ` burnus at gcc dot gnu dot org
  2007-04-26  4:54 ` jv244 at cam dot ac dot uk
  2007-06-20 15:20 ` jv244 at cam dot ac dot uk
  7 siblings, 0 replies; 9+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-04-25 18:50 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from burnus at gcc dot gnu dot org  2007-04-25 19:49 -------
Has anyone any objection if I change the purpose of this PR to:
---------
gfortran should detect that the local variable ncoset is never allocated -
as NAG f95 does:
Error: foo.f90, line 45: ALLOCATABLE array NCOSET used but never ALLOCATEd
This includes 
---------

Regarding the original problem with CP2k: A dependence on the optimization
options usually indicates a middle-end problem rather than a (Fortran)
front-end problem. As it occurred around the time I got core-dumps for the
Polyhedron test cases, the easiest is probably to wait until PR 31699 and PR
31697 are fixed. If we are lucky, CP2k is then fixed as well. If not, well,
then one can still dig for the problem.


-- 


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


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

* [Bug fortran/31683] bogus warnings with optional arguments
  2007-04-24 14:42 [Bug fortran/31683] New: bogus warnings / miscompilation jv244 at cam dot ac dot uk
                   ` (5 preceding siblings ...)
  2007-04-25 18:50 ` burnus at gcc dot gnu dot org
@ 2007-04-26  4:54 ` jv244 at cam dot ac dot uk
  2007-06-20 15:20 ` jv244 at cam dot ac dot uk
  7 siblings, 0 replies; 9+ messages in thread
From: jv244 at cam dot ac dot uk @ 2007-04-26  4:54 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from jv244 at cam dot ac dot uk  2007-04-26 05:54 -------
(In reply to comment #6)

> Regarding the original problem with CP2k: A dependence on the optimization
> options usually indicates a middle-end problem rather than a (Fortran)
> front-end problem. As it occurred around the time I got core-dumps for the
> Polyhedron test cases, the easiest is probably to wait until PR 31699 and PR
> 31697 are fixed. If we are lucky, CP2k is then fixed as well. If not, well,
> then one can still dig for the problem.

I'm rather sure the CP2K problem is identical to your PR 31699 and PR 31697.
So, from this point of view you can even close this PR what concerns me, and
add 31699 and 31967 as blockers for PR 29975

You can also leave this open so that gfortran, one day, produces the NAG error
for the unallocated ncoset, but I think that this error is low priority, in
this case you can remove that it blocks PR 29975

Furthermore, I think you should consider to reopen PR 31688. There really
should be no such warnings about frontend generated variables, this is
different from false positives for user variables


-- 


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


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

* [Bug fortran/31683] bogus warnings with optional arguments
  2007-04-24 14:42 [Bug fortran/31683] New: bogus warnings / miscompilation jv244 at cam dot ac dot uk
                   ` (6 preceding siblings ...)
  2007-04-26  4:54 ` jv244 at cam dot ac dot uk
@ 2007-06-20 15:20 ` jv244 at cam dot ac dot uk
  7 siblings, 0 replies; 9+ messages in thread
From: jv244 at cam dot ac dot uk @ 2007-06-20 15:20 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from jv244 at cam dot ac dot uk  2007-06-20 15:20 -------
this really seems a duplicate of PR 31688, so I'll close this PR and reopen
31688.  If one wants to get the error message mentioned in comment #6, I
suggest to open a new PR.

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


-- 

jv244 at cam dot ac dot uk changed:

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


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


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

end of thread, other threads:[~2007-06-20 15:20 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-04-24 14:42 [Bug fortran/31683] New: bogus warnings / miscompilation jv244 at cam dot ac dot uk
2007-04-24 17:47 ` [Bug fortran/31683] " burnus at gcc dot gnu dot org
2007-04-24 18:07 ` jv244 at cam dot ac dot uk
2007-04-24 18:58 ` burnus at gcc dot gnu dot org
2007-04-24 20:06 ` [Bug fortran/31683] bogus warnings with optional arguments tkoenig at gcc dot gnu dot org
2007-04-25  1:19 ` jv244 at cam dot ac dot uk
2007-04-25 18:50 ` burnus at gcc dot gnu dot org
2007-04-26  4:54 ` jv244 at cam dot ac dot uk
2007-06-20 15:20 ` jv244 at cam dot ac dot uk

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).