public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/39772]  New: add a correctness check for the size intrinsic to -fbounds-check
@ 2009-04-14 21:25 jv244 at cam dot ac dot uk
  2009-04-14 21:26 ` [Bug fortran/39772] " jv244 at cam dot ac dot uk
                   ` (10 more replies)
  0 siblings, 11 replies; 12+ messages in thread
From: jv244 at cam dot ac dot uk @ 2009-04-14 21:25 UTC (permalink / raw)
  To: gcc-bugs

the following program

INTEGER*8 :: N
INTEGER, DIMENSION(:), ALLOCATABLE :: data
N=2_8**32
write(6,*) N
ALLOCATE(data(N))
write(6,*) SIZE(data,1)
END

prints 

           4294967296
           0

It would be useful if a check for overflow of size could be added to e.g.
-fbounds-check (a rather natural place I would say) so that this kind of
undefined behavior could be detected at run time. I'm aware of the fact that
this is fixed more fundamentally with F2003.


-- 
           Summary: add a correctness check for the size intrinsic to -
                    fbounds-check
           Product: gcc
           Version: 4.4.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=39772


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

* [Bug fortran/39772] add a correctness check for the size intrinsic to -fbounds-check
  2009-04-14 21:25 [Bug fortran/39772] New: add a correctness check for the size intrinsic to -fbounds-check jv244 at cam dot ac dot uk
@ 2009-04-14 21:26 ` jv244 at cam dot ac dot uk
  2009-04-15 12:30 ` dfranke at gcc dot gnu dot org
                   ` (9 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: jv244 at cam dot ac dot uk @ 2009-04-14 21:26 UTC (permalink / raw)
  To: gcc-bugs



-- 

jv244 at cam dot ac dot uk changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Severity|normal                      |enhancement


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


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

* [Bug fortran/39772] add a correctness check for the size intrinsic to -fbounds-check
  2009-04-14 21:25 [Bug fortran/39772] New: add a correctness check for the size intrinsic to -fbounds-check jv244 at cam dot ac dot uk
  2009-04-14 21:26 ` [Bug fortran/39772] " jv244 at cam dot ac dot uk
@ 2009-04-15 12:30 ` dfranke at gcc dot gnu dot org
  2009-04-15 13:22 ` jv244 at cam dot ac dot uk
                   ` (8 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: dfranke at gcc dot gnu dot org @ 2009-04-15 12:30 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from dfranke at gcc dot gnu dot org  2009-04-15 12:30 -------


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


-- 

dfranke at gcc dot gnu dot org changed:

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


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


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

* [Bug fortran/39772] add a correctness check for the size intrinsic to -fbounds-check
  2009-04-14 21:25 [Bug fortran/39772] New: add a correctness check for the size intrinsic to -fbounds-check jv244 at cam dot ac dot uk
  2009-04-14 21:26 ` [Bug fortran/39772] " jv244 at cam dot ac dot uk
  2009-04-15 12:30 ` dfranke at gcc dot gnu dot org
@ 2009-04-15 13:22 ` jv244 at cam dot ac dot uk
  2009-04-15 13:57 ` kargl at gcc dot gnu dot org
                   ` (7 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: jv244 at cam dot ac dot uk @ 2009-04-15 13:22 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from jv244 at cam dot ac dot uk  2009-04-15 13:21 -------
not a duplicate of PR28105. The allocate is fine (on an x86_64).


-- 

jv244 at cam dot ac dot uk changed:

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


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


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

* [Bug fortran/39772] add a correctness check for the size intrinsic to -fbounds-check
  2009-04-14 21:25 [Bug fortran/39772] New: add a correctness check for the size intrinsic to -fbounds-check jv244 at cam dot ac dot uk
                   ` (2 preceding siblings ...)
  2009-04-15 13:22 ` jv244 at cam dot ac dot uk
@ 2009-04-15 13:57 ` kargl at gcc dot gnu dot org
  2009-04-15 17:04 ` jv244 at cam dot ac dot uk
                   ` (6 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: kargl at gcc dot gnu dot org @ 2009-04-15 13:57 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from kargl at gcc dot gnu dot org  2009-04-15 13:57 -------
(In reply to comment #2)
> not a duplicate of PR28105. The allocate is fine (on an x86_64).
> 

Actually, the entire program is fine.  But, it does not do
what you expected!  Try using your allocated array in something
other than SIZE().

INTEGER*8 :: N
INTEGER :: M
INTEGER, DIMENSION(:), ALLOCATABLE :: data
N=2_8**32
m = n
write(6,*) N, m
ALLOCATE(data(N))
write(6,*) SIZE(data,1)
data(1) = 1
ENDREMOVE:kargl[53] gfc4x -o z -fbounds-check d.f90
REMOVE:kargl[54] ./z
           4294967296           0
           0
At line 9 of file d.f90
Fortran runtime error: Array reference out of bounds for array 'data', upper
bound of dimension 1 exceeded (1 > 0)


-- 


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


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

* [Bug fortran/39772] add a correctness check for the size intrinsic to -fbounds-check
  2009-04-14 21:25 [Bug fortran/39772] New: add a correctness check for the size intrinsic to -fbounds-check jv244 at cam dot ac dot uk
                   ` (3 preceding siblings ...)
  2009-04-15 13:57 ` kargl at gcc dot gnu dot org
@ 2009-04-15 17:04 ` jv244 at cam dot ac dot uk
  2009-04-15 17:44 ` kargl at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: jv244 at cam dot ac dot uk @ 2009-04-15 17:04 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from jv244 at cam dot ac dot uk  2009-04-15 17:03 -------
> But, it does not do
> what you expected!  Try using your allocated array in something
> other than SIZE().

It's doing exactly what I expect... including the size intrinsic returning a
garbage result because it returns a default integer.

> cat test.f90
INTEGER*8 :: N
INTEGER, DIMENSION(:), ALLOCATABLE :: data
N=2_8**32
write(6,*) N
ALLOCATE(data(N))
data(1:N)=0
write(6,*) SIZE(data,1)
END
> gfortran -O2 -fbounds-check test.f90
> ./a.out
           4294967296
           0


-- 


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


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

* [Bug fortran/39772] add a correctness check for the size intrinsic to -fbounds-check
  2009-04-14 21:25 [Bug fortran/39772] New: add a correctness check for the size intrinsic to -fbounds-check jv244 at cam dot ac dot uk
                   ` (4 preceding siblings ...)
  2009-04-15 17:04 ` jv244 at cam dot ac dot uk
@ 2009-04-15 17:44 ` kargl at gcc dot gnu dot org
  2009-04-16 17:32 ` [Bug fortran/39772] SIZE intrinsic ignores optional KIND argument kargl at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: kargl at gcc dot gnu dot org @ 2009-04-15 17:44 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from kargl at gcc dot gnu dot org  2009-04-15 17:43 -------
(In reply to comment #4)
> > But, it does not do
> > what you expected!  Try using your allocated array in something
> > other than SIZE().
> 
> It's doing exactly what I expect... including the size intrinsic returning a
> garbage result because it returns a default integer.
> 
> > cat test.f90
> INTEGER*8 :: N
> INTEGER, DIMENSION(:), ALLOCATABLE :: data
> N=2_8**32
> write(6,*) N
> ALLOCATE(data(N))
> data(1:N)=0
> write(6,*) SIZE(data,1)
> END
> > gfortran -O2 -fbounds-check test.f90
> > ./a.out
>            4294967296
>            0
> 

Damn.  I was in the wrong xterm, which was a i686 system
not my usual x86_64.  I looked at the wrong dump.  You're
correct that size is doing something stupid.  From the
dump

    logical(kind=4) D.1539;                    <-- This wrong.
    integer(kind=8) size.2;
    integer(kind=8) D.1537;

    data.dtype = 265;
    data.dim[0].lbound = 1;
    data.dim[0].ubound = n;
    data.dim[0].stride = 1;
    D.1537 = NON_LVALUE_EXPR <MAX_EXPR <n, 0>>;
    D.1539 = NON_LVALUE_EXPR <n> <= 0;       <--- because this triggers
    if (D.1539)                              <--- this.
      {
        size.2 = 0;
      }


-- 

kargl at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
   Last reconfirmed|0000-00-00 00:00:00         |2009-04-15 17:43:49
               date|                            |


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


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

* [Bug fortran/39772] SIZE intrinsic ignores optional KIND argument
  2009-04-14 21:25 [Bug fortran/39772] New: add a correctness check for the size intrinsic to -fbounds-check jv244 at cam dot ac dot uk
                   ` (5 preceding siblings ...)
  2009-04-15 17:44 ` kargl at gcc dot gnu dot org
@ 2009-04-16 17:32 ` kargl at gcc dot gnu dot org
  2009-04-16 17:34 ` kargl at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: kargl at gcc dot gnu dot org @ 2009-04-16 17:32 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from kargl at gcc dot gnu dot org  2009-04-16 17:31 -------
well, that was an inconvenient goose chase.  (Note to self:
always check the Standard).

I'm tempted to close this with INVALID because the F95 Standard
explicitly states that SIZE() has a

  "Result Characteristics. Default integer scalar."

and it further states

   A program is prohibited from invoking an intrinsic procedure under
   circumstances where a value to be returned in a subroutine argument
   or function result is outside the range of values representable by
   objects of the specified type and type parameters.

Thus, it is the users' responsibility to catch a possible problem.

INTEGER*8 :: N
INTEGER, DIMENSION(:), ALLOCATABLE :: data
N=2_8**32
write(6,*) N
ALLOCATE(data(N))
if (n, < int(huge(1), 8)) then
  write(6,*) SIZE(data,1)
end if
END

That being said, I'm changing this from an enhancement request to
a wrong-code bug because gfortran has grown support for the F2003
standards' optional kind argument.  F2003 standard has


  Result Characteristics. Integer scalar. If KIND is present, the kind
  type parameter is that specified by the value of KIND; otherwise the
  kind type parameter is that of default integer type.

NTEGER*8 :: N
INTEGER, DIMENSION(:), ALLOCATABLE :: data
N=2_8**32
write(6,*) N
ALLOCATE(data(N))
write(6,*) SIZE(data,kind=8)
END

REMOVE:kargl[253] gfc4x -o z -fdump-tree-original d.f90
REMOVE:kargl[254] ./z
           4294967296
                    0

This is clearly wrong, and -fdump-tree-original shows that
the computation of size is doen in INTEGER*4. 


-- 

kargl at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Severity|enhancement                 |normal
           Priority|P3                          |P4
   Last reconfirmed|2009-04-15 17:43:49         |2009-04-16 17:31:44
               date|                            |
            Summary|add a correctness check for |SIZE intrinsic ignores
                   |the size intrinsic to -     |optional KIND argument
                   |fbounds-check               |


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


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

* [Bug fortran/39772] SIZE intrinsic ignores optional KIND argument
  2009-04-14 21:25 [Bug fortran/39772] New: add a correctness check for the size intrinsic to -fbounds-check jv244 at cam dot ac dot uk
                   ` (6 preceding siblings ...)
  2009-04-16 17:32 ` [Bug fortran/39772] SIZE intrinsic ignores optional KIND argument kargl at gcc dot gnu dot org
@ 2009-04-16 17:34 ` kargl at gcc dot gnu dot org
  2009-04-16 17:38 ` jv244 at cam dot ac dot uk
                   ` (2 subsequent siblings)
  10 siblings, 0 replies; 12+ messages in thread
From: kargl at gcc dot gnu dot org @ 2009-04-16 17:34 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from kargl at gcc dot gnu dot org  2009-04-16 17:33 -------
Add wrong-code keyword


-- 

kargl at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Keywords|                            |wrong-code


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


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

* [Bug fortran/39772] SIZE intrinsic ignores optional KIND argument
  2009-04-14 21:25 [Bug fortran/39772] New: add a correctness check for the size intrinsic to -fbounds-check jv244 at cam dot ac dot uk
                   ` (7 preceding siblings ...)
  2009-04-16 17:34 ` kargl at gcc dot gnu dot org
@ 2009-04-16 17:38 ` jv244 at cam dot ac dot uk
  2009-04-16 19:27 ` [Bug fortran/39772] add a correctness check for the size intrinsic to -fbounds-check kargl at gcc dot gnu dot org
  2009-05-04 20:24 ` mikael at gcc dot gnu dot org
  10 siblings, 0 replies; 12+ messages in thread
From: jv244 at cam dot ac dot uk @ 2009-04-16 17:38 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from jv244 at cam dot ac dot uk  2009-04-16 17:37 -------
(In reply to comment #6)
>   "Result Characteristics. Default integer scalar."

yes, that is what I know. in the initial comment, I asked for an enhancement of
 'bounds-check' which would detect the case where the default integer is
overflowed by the results of size.

BTW, -fdefault-integer-8 works fine.


-- 


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


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

* [Bug fortran/39772] add a correctness check for the size intrinsic to -fbounds-check
  2009-04-14 21:25 [Bug fortran/39772] New: add a correctness check for the size intrinsic to -fbounds-check jv244 at cam dot ac dot uk
                   ` (8 preceding siblings ...)
  2009-04-16 17:38 ` jv244 at cam dot ac dot uk
@ 2009-04-16 19:27 ` kargl at gcc dot gnu dot org
  2009-05-04 20:24 ` mikael at gcc dot gnu dot org
  10 siblings, 0 replies; 12+ messages in thread
From: kargl at gcc dot gnu dot org @ 2009-04-16 19:27 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from kargl at gcc dot gnu dot org  2009-04-16 19:27 -------
Sigh.  Return this to an enhancement request with the
original Summary.

gfortran's behavior is correct.

(Note to self)**2:  Never look at a bug report involving the
allocation of 16 GB of memory on a system limited by a 4 GB
address space.  gfc_array_index_type differs on 32 and 64 bit
systems.


-- 

kargl at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Severity|normal                      |enhancement
           Keywords|wrong-code                  |
           Priority|P4                          |P5
            Summary|SIZE intrinsic ignores      |add a correctness check for
                   |optional KIND argument      |the size intrinsic to -
                   |                            |fbounds-check


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


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

* [Bug fortran/39772] add a correctness check for the size intrinsic to -fbounds-check
  2009-04-14 21:25 [Bug fortran/39772] New: add a correctness check for the size intrinsic to -fbounds-check jv244 at cam dot ac dot uk
                   ` (9 preceding siblings ...)
  2009-04-16 19:27 ` [Bug fortran/39772] add a correctness check for the size intrinsic to -fbounds-check kargl at gcc dot gnu dot org
@ 2009-05-04 20:24 ` mikael at gcc dot gnu dot org
  10 siblings, 0 replies; 12+ messages in thread
From: mikael at gcc dot gnu dot org @ 2009-05-04 20:24 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from mikael at gcc dot gnu dot org  2009-05-04 20:24 -------
cf PR36462


-- 


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


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

end of thread, other threads:[~2009-05-04 20:24 UTC | newest]

Thread overview: 12+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2009-04-14 21:25 [Bug fortran/39772] New: add a correctness check for the size intrinsic to -fbounds-check jv244 at cam dot ac dot uk
2009-04-14 21:26 ` [Bug fortran/39772] " jv244 at cam dot ac dot uk
2009-04-15 12:30 ` dfranke at gcc dot gnu dot org
2009-04-15 13:22 ` jv244 at cam dot ac dot uk
2009-04-15 13:57 ` kargl at gcc dot gnu dot org
2009-04-15 17:04 ` jv244 at cam dot ac dot uk
2009-04-15 17:44 ` kargl at gcc dot gnu dot org
2009-04-16 17:32 ` [Bug fortran/39772] SIZE intrinsic ignores optional KIND argument kargl at gcc dot gnu dot org
2009-04-16 17:34 ` kargl at gcc dot gnu dot org
2009-04-16 17:38 ` jv244 at cam dot ac dot uk
2009-04-16 19:27 ` [Bug fortran/39772] add a correctness check for the size intrinsic to -fbounds-check kargl at gcc dot gnu dot org
2009-05-04 20:24 ` mikael 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).