public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/35698]  New: lbound and ubound wrong for allocated run-time zero size array
@ 2008-03-25 20:47 dick dot hendrickson at gmail dot com
  2008-03-25 23:52 ` [Bug fortran/35698] " burnus at gcc dot gnu dot org
                   ` (6 more replies)
  0 siblings, 7 replies; 8+ messages in thread
From: dick dot hendrickson at gmail dot com @ 2008-03-25 20:47 UTC (permalink / raw)
  To: gcc-bugs

The following program gives wrong results for some positions
in LBOUND and UBOUND.  The allocated array has a run-time
computed zero-sized subscript range in the 4th subscript.
LBOUND and UBOUND give incorrect results for the 5th, 6th,
and 7th subscript.  They propagate the zero size (1,0) pair.
the results in subscripts 1, 2, and 3 are correct. 

The results are correct if the 4th subscript is replaced with
10:1 instead of the run-time expression.

Dick Hendrickson


 first test loop
           5  expected lbound =          -2 computed =            1
           6  expected lbound =          -3 computed =            1
           7  expected lbound =          -4 computed =            1
 second test loop
           5  expected ubound =           7 computed =            0
           6  expected ubound =           8 computed =            0
           7  expected ubound =           9 computed =            0



      program try_lf0030
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]

      call LF0030(10)
      end

      SUBROUTINE LF0030(nf10)
      INTEGER ILA1(7)
      INTEGER ILA2(7)
      LOGICAL LLA(:,:,:,:,:,:,:)
      INTEGER ICA(7)
      ALLOCATABLE LLA


      ALLOCATE (LLA(2:3, 4, 0:5,
     $          NF10:1, -2:7, -3:8,
     $          -4:9))

      ILA1 = LBOUND(LLA)
      ILA2 = UBOUND(LLA)
C     CORRECT FOR THE ZERO DIMENSIONED TERM TO ALLOW AN EASIER VERIFY
      ILA1(4) = ILA1(4) - 2    !   1 - 2 = -1
      ILA2(4) = ILA2(4) + 6    !   0 + 6 = 6     

      print *, 'first test loop'
      DO J1 = 1,7
      IVAL = 3-J1
      IF (ILA1(J1) .NE. IVAL) print *, J1, " expected lbound =", 
     $     ival, "computed = ", ila1(j1)
  100 ENDDO

      print *, 'second test loop'
      DO J1 = 1,7
      IVAL = 2+J1
      IF (ILA2(J1) .NE. IVAL) print *, J1, " expected ubound =", 
     $     ival, "computed = ", ila2(j1)
  101 ENDDO

      END SUBROUTINE


-- 
           Summary: lbound and ubound wrong for allocated run-time zero size
                    array
           Product: gcc
           Version: 4.4.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: dick dot hendrickson at gmail dot com


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


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

* [Bug fortran/35698] lbound and ubound wrong for allocated run-time zero size array
  2008-03-25 20:47 [Bug fortran/35698] New: lbound and ubound wrong for allocated run-time zero size array dick dot hendrickson at gmail dot com
@ 2008-03-25 23:52 ` burnus at gcc dot gnu dot org
  2008-03-26 22:21 ` pault at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: burnus at gcc dot gnu dot org @ 2008-03-25 23:52 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from burnus at gcc dot gnu dot org  2008-03-25 23:52 -------
Thanks for testing/reducing/reporting this.

If one looks at the bounds, one sees that for negative lower bounds the output
is wrong. NAG correctly has:
   2   1   0   1  -2  -3  -4
   3   4   5   0   7   8   9
while gfortran wrongly has:
   2   1   0   1   1   1   1
   3   4   5   0   0   0   0

ila1[S.2 + -1] = lla.dim[S.2 + -1].stride >= 0 && lla.dim[S.2 + -1].ubound >=
lla.dim[S.2 + -1].lbound || lla.dim[S.2 + -1].stride < 0 && lla.dim[S.2 +
-1].ubound <= lla.dim[S.2 + -1].lbound ? (integer(kind=4)) lla.dim[S.2 +
-1].lbound : 1;

This looks ok. However, I do not understand the stride calculation:

    lla.dim[3].lbound = (integer(kind=8)) nf10;
    lla.dim[3].ubound = 1;
    lla.dim[3].stride = 48;

so far so good, but why the following?

    D.950 = (2 - (integer(kind=8)) nf10) * 48;
    lla.dim[4].lbound = -2;
    lla.dim[4].ubound = 7;
    lla.dim[4].stride = D.950;

D.950 is (2-10)*48 = -384 ?!?!?


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
OtherBugsDependingO|                            |32834
              nThis|                            |
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
           Keywords|                            |wrong-code
   Last reconfirmed|0000-00-00 00:00:00         |2008-03-25 23:52:07
               date|                            |


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


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

* [Bug fortran/35698] lbound and ubound wrong for allocated run-time zero size array
  2008-03-25 20:47 [Bug fortran/35698] New: lbound and ubound wrong for allocated run-time zero size array dick dot hendrickson at gmail dot com
  2008-03-25 23:52 ` [Bug fortran/35698] " burnus at gcc dot gnu dot org
@ 2008-03-26 22:21 ` pault at gcc dot gnu dot org
  2008-03-27 11:09 ` dominiq at lps dot ens dot fr
                   ` (4 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-03-26 22:21 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from pault at gcc dot gnu dot org  2008-03-26 22:20 -------
This one is relatively easy:

Index: gcc/fortran/trans-array.c
===================================================================
*** gcc/fortran/trans-array.c   (revision 133278)
--- gcc/fortran/trans-array.c   (working copy)
*************** gfc_conv_loop_setup (gfc_loopinfo * loop
*** 3506,3512 ****
          a.ubound[n] = specified_upper_bound;
          a.stride[n] = stride;
          size = ubound + size; //size = ubound + 1 - lbound
!         stride = stride * size;
        }
      return (stride);
     }  */
--- 3516,3522 ----
          a.ubound[n] = specified_upper_bound;
          a.stride[n] = stride;
          size = ubound + size; //size = ubound + 1 - lbound
!         stride = size >= 0 ? stride * size : 0;
        }
      return (stride);
     }  */
*************** gfc_array_init_size (tree descriptor, in
*** 3605,3610 ****
--- 3615,3623 ----
        else
        or_expr = fold_build2 (TRUTH_OR_EXPR, boolean_type_node, or_expr,
cond);


+       size = fold_build3 (COND_EXPR, gfc_array_index_type, cond,
+                         size, gfc_index_zero_node);
+
        /* Multiply the stride by the number of elements in this dimension.  */
        stride = fold_build2 (MULT_EXPR, gfc_array_index_type, stride, size);
        stride = gfc_evaluate_now (stride, pblock);

I'll put it on to regtest.

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |pault at gcc dot gnu dot org
                   |dot org                     |
             Status|NEW                         |ASSIGNED
   Last reconfirmed|2008-03-25 23:52:07         |2008-03-26 22:20:33
               date|                            |


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


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

* [Bug fortran/35698] lbound and ubound wrong for allocated run-time zero size array
  2008-03-25 20:47 [Bug fortran/35698] New: lbound and ubound wrong for allocated run-time zero size array dick dot hendrickson at gmail dot com
  2008-03-25 23:52 ` [Bug fortran/35698] " burnus at gcc dot gnu dot org
  2008-03-26 22:21 ` pault at gcc dot gnu dot org
@ 2008-03-27 11:09 ` dominiq at lps dot ens dot fr
  2008-03-28  8:33 ` pault at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: dominiq at lps dot ens dot fr @ 2008-03-27 11:09 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from dominiq at lps dot ens dot fr  2008-03-27 11:08 -------
Some comments about the patch in comment #2:

1) If I am not mistaken, the first change is within a commented block (look at
the last line in the diff.:
'     }  */')

2) With the patch I have a lot of regressions on my quick and dirty testsuite.
Among them I have several:

test.exe(65765) malloc: *** error for object 0x2004c0: incorrect checksum for
freed object - object was probably modified after being freed.
*** set a breakpoint in malloc_error_break to debug

one example being:

PROGRAM  testb 
 IMPLICIT none 

 CHARACTER(len=120), DIMENSION(3) :: vect 

 CHARACTER(len=1), DIMENSION(:), ALLOCATABLE :: cvect 

 INTEGER :: length 

!!$----------------------- 

 vect(:)=(/'ippaaa0','ippaaa1','ippaaa2'/) 
 WRITE(*,*) 'Say hi!' 
 length=SIZE(TRANSFER(vect,cvect)) 
 WRITE(*,*) 'Say hi again!', length 
 ALLOCATE(cvect(length)) 
 cvect=TRANSFER(vect,cvect) 

!!$----------------- 

END PROGRAM testb 


-- 


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


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

* [Bug fortran/35698] lbound and ubound wrong for allocated run-time zero size array
  2008-03-25 20:47 [Bug fortran/35698] New: lbound and ubound wrong for allocated run-time zero size array dick dot hendrickson at gmail dot com
                   ` (2 preceding siblings ...)
  2008-03-27 11:09 ` dominiq at lps dot ens dot fr
@ 2008-03-28  8:33 ` pault at gcc dot gnu dot org
  2008-03-29  8:12 ` pault at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-03-28  8:33 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from pault at gcc dot gnu dot org  2008-03-28 08:33 -------
(In reply to comment #3)

> 1) If I am not mistaken, the first change is within a commented block (look at
> the last line in the diff.:
> '     }  */')

Yes, indeed - the comment has been made consistent with the intended patch....

> 
> 2) With the patch I have a lot of regressions on my quick and dirty testsuite.
> Among them I have several:

The patch posted here is in error - the version posted to the lists is correct.
 Please note that I have no idea why what appears here did anything for the
reporter's testcase!

+       size = fold_build3 (COND_EXPR, gfc_array_index_type, cond,
+                         size, gfc_index_zero_node);

has the last two arguments the wrong way round *sorry*

Cheers

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |dominiq at lps dot ens dot
                   |                            |fr


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


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

* [Bug fortran/35698] lbound and ubound wrong for allocated run-time zero size array
  2008-03-25 20:47 [Bug fortran/35698] New: lbound and ubound wrong for allocated run-time zero size array dick dot hendrickson at gmail dot com
                   ` (3 preceding siblings ...)
  2008-03-28  8:33 ` pault at gcc dot gnu dot org
@ 2008-03-29  8:12 ` pault at gcc dot gnu dot org
  2008-03-29  8:19 ` pault at gcc dot gnu dot org
  2008-03-29  8:20 ` pault at gcc dot gnu dot org
  6 siblings, 0 replies; 8+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-03-29  8:12 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from pault at gcc dot gnu dot org  2008-03-29 08:11 -------
Subject: Bug 35698

Author: pault
Date: Sat Mar 29 08:11:02 2008
New Revision: 133710

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=133710
Log:
2008-03-29  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/35698
        * trans-array.c (gfc_array_init_size): Set 'size' zero if
        negative in one dimension.

        PR fortran/35702
        * trans-expr.c (gfc_trans_string_copy): Only assign a char
        directly if the lhs and rhs types are the same.

2008-03-29  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/35698
        * gfortran.dg/allocate_zerosize_3.f: New test.

        PR fortran/35702
        * gfortran.dg/character_assign_1.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/allocate_zerosize_3.f
    trunk/gcc/testsuite/gfortran.dg/character_assign_1.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/35698] lbound and ubound wrong for allocated run-time zero size array
  2008-03-25 20:47 [Bug fortran/35698] New: lbound and ubound wrong for allocated run-time zero size array dick dot hendrickson at gmail dot com
                   ` (4 preceding siblings ...)
  2008-03-29  8:12 ` pault at gcc dot gnu dot org
@ 2008-03-29  8:19 ` pault at gcc dot gnu dot org
  2008-03-29  8:20 ` pault at gcc dot gnu dot org
  6 siblings, 0 replies; 8+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-03-29  8:19 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from pault at gcc dot gnu dot org  2008-03-29 08:18 -------
Subject: Bug 35698

Author: pault
Date: Sat Mar 29 08:17:36 2008
New Revision: 133711

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=133711
Log:
2008-03-29  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/35698
        * trans-array.c (gfc_array_init_size): Set 'size' zero if
        negative in one dimension.

        PR fortran/35702
        * trans-expr.c (gfc_trans_string_copy): Only assign a char
        directly if the lhs and rhs types are the same.

2008-03-29  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/35698
        * gfortran.dg/allocate_zerosize_3.f: New test.

        PR fortran/35702
        * gfortran.dg/character_assign_1.f90: New test.

Added:
    branches/gcc-4_3-branch/gcc/testsuite/gfortran.dg/allocate_zerosize_3.f
    branches/gcc-4_3-branch/gcc/testsuite/gfortran.dg/character_assign_1.f90
Modified:
    branches/gcc-4_3-branch/gcc/fortran/ChangeLog
    branches/gcc-4_3-branch/gcc/fortran/trans-array.c
    branches/gcc-4_3-branch/gcc/fortran/trans-expr.c
    branches/gcc-4_3-branch/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/35698] lbound and ubound wrong for allocated run-time zero size array
  2008-03-25 20:47 [Bug fortran/35698] New: lbound and ubound wrong for allocated run-time zero size array dick dot hendrickson at gmail dot com
                   ` (5 preceding siblings ...)
  2008-03-29  8:19 ` pault at gcc dot gnu dot org
@ 2008-03-29  8:20 ` pault at gcc dot gnu dot org
  6 siblings, 0 replies; 8+ messages in thread
From: pault at gcc dot gnu dot org @ 2008-03-29  8:20 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from pault at gcc dot gnu dot org  2008-03-29 08:19 -------
Fixed on trunk and 4.3

Paul


-- 

pault at gcc dot gnu dot org changed:

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


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


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

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

Thread overview: 8+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-03-25 20:47 [Bug fortran/35698] New: lbound and ubound wrong for allocated run-time zero size array dick dot hendrickson at gmail dot com
2008-03-25 23:52 ` [Bug fortran/35698] " burnus at gcc dot gnu dot org
2008-03-26 22:21 ` pault at gcc dot gnu dot org
2008-03-27 11:09 ` dominiq at lps dot ens dot fr
2008-03-28  8:33 ` pault at gcc dot gnu dot org
2008-03-29  8:12 ` pault at gcc dot gnu dot org
2008-03-29  8:19 ` pault at gcc dot gnu dot org
2008-03-29  8:20 ` 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).