public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/30872]  New: incorrect error message for valid code
@ 2007-02-20  7:50 jv244 at cam dot ac dot uk
  2007-02-20 16:50 ` [Bug fortran/30872] Bogus "size of variable is too large" burnus at gcc dot gnu dot org
                   ` (4 more replies)
  0 siblings, 5 replies; 6+ messages in thread
From: jv244 at cam dot ac dot uk @ 2007-02-20  7:50 UTC (permalink / raw)
  To: gcc-bugs

With recent trunk, gfortran incorrectly generates an error for the following
standard code:
MODULE MOD1
 IMPLICIT NONE
 INTEGER, PARAMETER :: dp=KIND(0.0D0)
CONTAINS
  SUBROUTINE pw_compose_stripe(weights,in_val,in_val_first,in_val_last,&
     out_val,n_el)

    REAL(kind=dp), DIMENSION(0:2), &
      INTENT(in)                             :: weights
    INTEGER                                  :: n_el
    REAL(kind=dp), DIMENSION(1:n_el), &
      INTENT(in)                             :: in_val
    REAL(kind=dp), DIMENSION(1:n_el), &
      INTENT(inout)                          :: out_val
    REAL(kind=dp), INTENT(in)                :: in_val_last, in_val_first
    out_val=in_val
  END SUBROUTINE pw_compose_stripe
  SUBROUTINE pw_nn_compose_r_work(weights,in_val,out_val,bo)
      REAL(kind=dp), DIMENSION(0:2, 0:2, 0:2)  :: weights
      INTEGER, DIMENSION(2, 3)                 :: bo
      REAL(kind=dp), DIMENSION(bo(1, 1):bo(2, &
       1), bo(1, 2):bo(2, 2), bo(1, 3):bo(2, &
       3)), INTENT(inout)                     :: out_val
      REAL(kind=dp), DIMENSION(bo(1, 1):bo(2, &
       1), bo(1, 2):bo(2, 2), bo(1, 3):bo(2, &
       3)), INTENT(in)                        :: in_val
      INTEGER :: n_el,i,j
      REAL(kind=dp)                           :: in_val_f, in_val_l
      INTEGER, DIMENSION(3)                   :: s
      s(1)=bo(2,1)-bo(1,1)+1
      i=1 ; j=1
      CALL pw_compose_stripe(weights=weights(:,i,j),&
              in_val=in_val(:,i,j),&
              in_val_first=in_val_f,in_val_last=in_val_l,&
              out_val=out_val(:,bo(1,2)+i,bo(1,3)+j),n_el=s(1))
  END SUBROUTINE pw_nn_compose_r_work
END MODULE MOD1

USE MOD1
      REAL(kind=dp), DIMENSION(0:2, 0:2, 0:2)  :: weights
      INTEGER, PARAMETER, DIMENSION(2,3) :: bo= &
                          RESHAPE((/-1,1,-1,1,-1,1/),(/2,3/))
      REAL(kind=dp), DIMENSION(bo(1, 1):bo(2, &
       1), bo(1, 2):bo(2, 2), bo(1, 3):bo(2, &
       3))                  :: out_val,in_val
      in_val=1.0
      out_val=0.0
      CALL pw_nn_compose_r_work(weights,in_val,out_val,bo)
!      write(6,'(10F5.1)') in_val
!      write(6,'(10F5.1)') out_val
END


-- 
           Summary: incorrect error message for valid code
           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=30872


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

* [Bug fortran/30872] Bogus "size of variable is too large"
  2007-02-20  7:50 [Bug fortran/30872] New: incorrect error message for valid code jv244 at cam dot ac dot uk
@ 2007-02-20 16:50 ` burnus at gcc dot gnu dot org
  2007-04-01 22:12 ` pault at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  4 siblings, 0 replies; 6+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-02-20 16:50 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from burnus at gcc dot gnu dot org  2007-02-20 16:50 -------
Reduced test case:

 INTEGER, PARAMETER, DIMENSION(2,3) :: bo= &
                    RESHAPE((/-1,1,-1,1,-1,1/),(/2,3/))
 REAL(kind=8), DIMENSION(  &
          bo(1,1):bo(2,1), &
          bo(1,2):bo(2,2), &
          bo(1,3):bo(2,3)) :: out_val
 out_val=0.0
END

gfortran fails with:
bar.f90:6: error: size of variable 'out_val' is too large

Observation: If one replaces the bo(...):bo(...) by "-1:1" gfortran compiles
without errors.

The test case compiles & runs with nagf95, ifort, g95.


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |burnus at gcc dot gnu dot
                   |                            |org
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
           Keywords|                            |rejects-valid
   Last reconfirmed|0000-00-00 00:00:00         |2007-02-20 16:50:46
               date|                            |
            Summary|incorrect error message for |Bogus "size of variable is
                   |valid code                  |too large"


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


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

* [Bug fortran/30872] Bogus "size of variable is too large"
  2007-02-20  7:50 [Bug fortran/30872] New: incorrect error message for valid code jv244 at cam dot ac dot uk
  2007-02-20 16:50 ` [Bug fortran/30872] Bogus "size of variable is too large" burnus at gcc dot gnu dot org
@ 2007-04-01 22:12 ` pault at gcc dot gnu dot org
  2007-04-05 21:01 ` pault at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  4 siblings, 0 replies; 6+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-04-01 22:12 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from pault at gcc dot gnu dot org  2007-04-01 23:11 -------
This fixes it and regtests on x86_ia64/FC5.  The arithmetic for finding the
offset to a rank>1 element was plain wrong.

I will submit asap.

Paul

Index: gcc/fortran/expr.c
===================================================================
*** gcc/fortran/expr.c  (revision 123382)
--- gcc/fortran/expr.c  (working copy)
*************** find_array_element (gfc_constructor *con
*** 899,904 ****
--- 899,906 ----
    int i;
    mpz_t delta;
    mpz_t offset;
+   mpz_t span;
+   mpz_t tmp;
    gfc_expr *e;
    try t;

*************** find_array_element (gfc_constructor *con
*** 907,912 ****
--- 909,916 ----

    mpz_init_set_ui (offset, 0);
    mpz_init (delta);
+   mpz_init (tmp);
+   mpz_init_set_ui (span, 1);
    for (i = 0; i < ar->dimen; i++)
      {
        e = gfc_copy_expr (ar->start[i]);
*************** find_array_element (gfc_constructor *con
*** 930,936 ****
--- 934,946 ----
        }

        mpz_sub (delta, e->value.integer, ar->as->lower[i]->value.integer);
+       mpz_mul (delta, delta, span);
        mpz_add (offset, offset, delta);
+ 
+       mpz_set_ui (tmp, 1);
+       mpz_add (tmp, tmp, ar->as->upper[i]->value.integer);
+       mpz_sub (tmp, tmp, ar->as->lower[i]->value.integer);
+       mpz_mul (span, span, tmp);
      }

    if (cons)
*************** find_array_element (gfc_constructor *con
*** 949,954 ****
--- 959,966 ----
  depart:
    mpz_clear (delta);
    mpz_clear (offset);
+   mpz_clear (span);
+   mpz_clear (tmp);
    if (e)
      gfc_free_expr (e);
    *rval = cons;


-- 

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|2007-02-20 16:50:46         |2007-04-01 23:11:48
               date|                            |


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


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

* [Bug fortran/30872] Bogus "size of variable is too large"
  2007-02-20  7:50 [Bug fortran/30872] New: incorrect error message for valid code jv244 at cam dot ac dot uk
  2007-02-20 16:50 ` [Bug fortran/30872] Bogus "size of variable is too large" burnus at gcc dot gnu dot org
  2007-04-01 22:12 ` pault at gcc dot gnu dot org
@ 2007-04-05 21:01 ` pault at gcc dot gnu dot org
  2007-04-07 20:24 ` pault at gcc dot gnu dot org
  2007-04-07 20:33 ` pault at gcc dot gnu dot org
  4 siblings, 0 replies; 6+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-04-05 21:01 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from pault at gcc dot gnu dot org  2007-04-05 22:01 -------
I submitted a patch for this in:
http://gcc.gnu.org/ml/fortran/2007-04/msg00016.html

Paul


-- 


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


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

* [Bug fortran/30872] Bogus "size of variable is too large"
  2007-02-20  7:50 [Bug fortran/30872] New: incorrect error message for valid code jv244 at cam dot ac dot uk
                   ` (2 preceding siblings ...)
  2007-04-05 21:01 ` pault at gcc dot gnu dot org
@ 2007-04-07 20:24 ` pault at gcc dot gnu dot org
  2007-04-07 20:33 ` pault at gcc dot gnu dot org
  4 siblings, 0 replies; 6+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-04-07 20:24 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from pault at gcc dot gnu dot org  2007-04-07 21:23 -------
Subject: Bug 30872

Author: pault
Date: Sat Apr  7 21:23:40 2007
New Revision: 123644

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=123644
Log:
2007-04-07  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/30872
        * expr.c (find_array_element): Correct arithmetic for rank > 1.

2007-04-07  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/30872
        * gfortran.dg/parameter_array_element_1.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/parameter_array_element_1.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/expr.c
    trunk/gcc/testsuite/ChangeLog


-- 


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


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

* [Bug fortran/30872] Bogus "size of variable is too large"
  2007-02-20  7:50 [Bug fortran/30872] New: incorrect error message for valid code jv244 at cam dot ac dot uk
                   ` (3 preceding siblings ...)
  2007-04-07 20:24 ` pault at gcc dot gnu dot org
@ 2007-04-07 20:33 ` pault at gcc dot gnu dot org
  4 siblings, 0 replies; 6+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-04-07 20:33 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from pault at gcc dot gnu dot org  2007-04-07 21:33 -------
Fixed on trumk

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=30872


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

end of thread, other threads:[~2007-04-07 20:33 UTC | newest]

Thread overview: 6+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-02-20  7:50 [Bug fortran/30872] New: incorrect error message for valid code jv244 at cam dot ac dot uk
2007-02-20 16:50 ` [Bug fortran/30872] Bogus "size of variable is too large" burnus at gcc dot gnu dot org
2007-04-01 22:12 ` pault at gcc dot gnu dot org
2007-04-05 21:01 ` pault at gcc dot gnu dot org
2007-04-07 20:24 ` pault at gcc dot gnu dot org
2007-04-07 20:33 ` 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).