Bug 41807 - [4.5/4.4 Regression] data statement with nested type constructors
Summary: [4.5/4.4 Regression] data statement with nested type constructors
Status: RESOLVED FIXED
Alias: None
Product: gcc
Classification: Unclassified
Component: fortran (show other bugs)
Version: 4.5.0
: P4 normal
Target Milestone: 4.4.3
Assignee: Jerry DeLisle
URL:
Keywords: rejects-valid
Depends on:
Blocks:
 
Reported: 2009-10-23 12:26 UTC by Paul Thomas
Modified: 2009-11-27 08:32 UTC (History)
2 users (show)

See Also:
Host:
Target:
Build:
Known to work: 4.3.4
Known to fail: 4.4.1 4.5.0 4.2.4
Last reconfirmed: 2009-11-26 01:08:07


Attachments

Note You need to log in before you can comment on or make changes to this bug.
Description Paul Thomas 2009-10-23 12:26:47 UTC
Reported on clf http://groups.google.com/group/comp.lang.fortran/browse_thread/thread/650b2eeeb8d76213#

w.f90:53.20:

  data(dft_water_nuc(i), i=1,n_nuc) /
&
                    1
Error: non-constant array in DATA statement (1) 

These seems to be variable - I can confirm it but others say that they do not see it.

Source:
=============== w.f90 =================
module w

  implicit none
  save
  private

  real, parameter :: zero = 0.0

  type, public :: charge
     real :: q
     real :: C
     real :: A
  end type charge

  type, public :: multpol
     character*12  :: name
     real :: coor(3)  !!! COMMENT THIS TO MAKE IT COMPILE !!!
     real :: mass
     type(charge)  :: z
  end type multpol

  integer, public, parameter :: n_nuc=3

  type(multpol),      public :: dft_water_nuc(n_nuc)

  real, parameter :: C_i        =zero
  real, parameter :: A_i        =zero

  !names of multipole
  character*12, parameter :: mname1="O1          "
  character*12, parameter :: mname2="H2          "
  character*12, parameter :: mname3="H3          "

  !coordinates of multipole centers
  real, parameter :: mcoor1(3)=(/ zero,     zero, -0.119151/)
  real, parameter :: mcoor2(3)=(/-1.431042, zero,  0.945510/)
  real, parameter :: mcoor3(3)=(/ 1.431042, zero,  0.945510/)

  !mass
  real, parameter :: mass1=15.99491
  real, parameter :: mass2=1.007825
  real, parameter :: mass3=1.007825

  !charges
  real, parameter :: Zn1=8.0
  real, parameter :: Zn2=1.0
  real, parameter :: Zn3=1.0

  integer :: i

  !----------------------------------------------------------------
  data(dft_water_nuc(i), i=1,n_nuc) /
&
                                multpol
(                               &
                                        mname1, &
                                        mcoor1, &  !!! COMMENT THIS TO
MAKE IT COMPILE !!!
                                        mass1,           &
                                        charge(Zn1,C_i,A_i)
&
                                       ),
&
                                multpol
(                               &
                                        mname2, &
                                        mcoor2, &  !!! COMMENT THIS TO
MAKE IT COMPILE !!!
                                        mass2,           &
                                        charge(Zn2,C_i,A_i)
&
                                       ),
&
                                multpol
(                               &
                                        mname3, &
                                        mcoor3, &  !!! COMMENT THIS TO
MAKE IT COMPILE !!!
                                        mass3,           &
                                        charge(Zn3,C_i,A_i)
&
                                       )
&
                                /

end module w
Comment 1 Dominique d'Humieres 2009-10-23 12:46:31 UTC
The code in comment #0 gives errors with gfortran 4.4.1 and 4.5.0 (recent patched trunk), compiles with 4.3.4, and gives an ICE with 4.2.4. Also compiles with ifort and gives an ICE with g95.
Comment 2 Paul Thomas 2009-10-24 09:38:27 UTC
A reduced testcase

module w
  real, parameter :: zero = 0.0

  type, public :: multpol
     real :: coor(3)
  end type multpol

  integer, public, parameter :: n_nuc=2

  type(multpol),      public :: dft_water_nuc(n_nuc)

  real, parameter :: C_i        =zero
  real, parameter :: A_i        =zero

  !coordinates of multipole centers
  real, parameter :: mcoor1(3)=(/ zero,     zero, -0.119151/)
  real, parameter :: mcoor2(3)=(/-1.431042, zero,  0.945510/)

  integer :: i

  !----------------------------------------------------------------
  data(dft_water_nuc(i), i=1,n_nuc) /multpol( mcoor1), multpol( mcoor2)/

end module w


A single element in the data statement or...
  data dft_water_nuc(1),dft_water_nuc(2) /multpol( mcoor1), multpol( mcoor2)/

clears the problem.  There is something wrong with the loop variable that is screwing up data.c(get_array_index) but I cannot see what it is right now.

Paul
Comment 3 Tobias Burnus 2009-11-06 14:07:07 UTC
Working: 2009-06-11-r148366
Failing:
With my 2009-06-15-r148480, which has additionally the patch 2009-06-16-r148519 installed.


Probably caused by the following patch, which has also been backported to 4.4:


r148396 | pault | 2009-06-11 22:11:59 +0200 (Thu, 11 Jun 2009) | 11 lines
http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=148396

2009-06-11  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/40402
        * resolve.c (next_data_value): It is an error if the value is
        not constant.
Comment 4 Dominique d'Humieres 2009-11-06 15:02:43 UTC
Further reduced test case:

  type :: multpol
     real :: coor(3)
  end type multpol
  integer, parameter :: n_nub=2
  type(multpol) :: dft_water_nuc(n_nub)
  real, parameter :: mcoor1(3)=(/ 0.0,      0.0, -0.119151/)
  real, parameter :: mcoor2(3)=(/-1.431042, 0.0,  0.945510/)
  integer :: i, ia(2)

  data(dft_water_nuc(i), i=1,n_nub) /multpol( mcoor1), multpol( mcoor2)/
  data(ia(i), i=1,n_nub) / 1, 2/
end

The error is emitted only for the derived type.
Comment 5 Jerry DeLisle 2009-11-06 16:11:51 UTC
I just started looking into this.  There is a check for array index and start to be EXPR_CONSTANT.  In the case of start it is an EXPR_FUNCTION because there is a conversion from kind 4 to kind 8 function being inlined.  More later.
Comment 6 Jerry DeLisle 2009-11-11 05:20:50 UTC
I have tracked through the matchers and as suspected, the iterator is being initialised correctly. Start, End, and Step are all constants.  This hints at some corruption.  As time  allows  I will follow the iterator through to the array spec and try to see where we are losing it.  By the time we get into resolve.c, start is no longer a constant.
Comment 7 Jerry DeLisle 2009-11-14 18:35:08 UTC
Does anyone recognize this in resolve.c

      /* If we have more than one element left in the repeat count,
	 and we have more than one element left in the target variable,
	 then create a range assignment.  */
      /* FIXME: Only done for full arrays for now, since array sections
	 seem tricky.  */
Comment 8 kargls 2009-11-14 19:30:29 UTC
(In reply to comment #7)
> Does anyone recognize this in resolve.c
> 
>       /* If we have more than one element left in the repeat count,
>          and we have more than one element left in the target variable,
>          then create a range assignment.  */
>       /* FIXME: Only done for full arrays for now, since array sections
>          seem tricky.  */
>

svn annotate resolve.c gives

 86443        rth       /* If we have more than one element left in the repeat count,
 86443        rth        and we have more than one element left in the target variable,
 86443        rth        then create a range assignment.  */
129561      kargl       /* FIXME: Only done for full arrays for now, since array sections
 86443        rth        seem tricky.  */
 86443        rth       if (mark == AR_FULL && ref && ref->next == NULL

Comment 9 kargls 2009-11-14 19:32:18 UTC
which traces to 

REMOVE:kargl[207] svn log -r 86443 resolve.c |more
------------------------------------------------------------------------
r86443 | rth | 2004-08-23 14:53:14 -0700 (Mon, 23 Aug 2004) | 11 lines

        PR 13465
        * data.c (find_con_by_offset): Search ordered list; handle
        elements with repeat counts.
        (gfc_assign_data_value_range): New.
        * gfortran.h (struct gfc_data_value): Make repeat unsigned.
        (gfc_assign_data_value_range): Declare.
        * match.c (top_val_list): Extract repeat count into a temporary.
        * resolve.c (values): Make left unsigned.
        (next_data_value): Don't decrement left.
        (check_data_variable): Use gfc_assign_data_value_range.

Comment 10 Jerry DeLisle 2009-11-14 21:24:28 UTC
Interesting, the following patch allows the test case in comment #4 to compile.

Index: data.c
===================================================================
--- data.c	(revision 154170)
+++ data.c	(working copy)
@@ -55,8 +55,8 @@ get_array_index (gfc_array_ref *ar, mpz_t *offset)
   mpz_init_set_si (delta, 1);
   for (i = 0; i < ar->dimen; i++)
     {
+      re = gfc_simplify_expr (ar->start[i], 1);
       e = gfc_copy_expr (ar->start[i]);
-      re = gfc_simplify_expr (e, 1);
 
       if ((gfc_is_constant_expr (ar->as->lower[i]) == 0)
 	  || (gfc_is_constant_expr (ar->as->upper[i]) == 0)

Simplifying the start expression before the copy rather than simplifying the copy.  I am not sure the resulting executable is correct though.
Comment 11 kargls 2009-11-15 18:38:10 UTC
Jerry, I added 

@@ -56,11 +55,11 @@ get_array_index (gfc_array_ref *ar, mpz_
   for (i = 0; i < ar->dimen; i++)
     {
       e = gfc_copy_expr (ar->start[i]);
-      re = gfc_simplify_expr (e, 1);
+      gfc_simplify_expr (e, 1);
 
       if ((gfc_is_constant_expr (ar->as->lower[i]) == 0)
          || (gfc_is_constant_expr (ar->as->upper[i]) == 0)
-         || (gfc_is_constant_expr (e) == 0))
+         /*|| (gfc_is_constant_expr (e) == 0)*/)
        gfc_error ("non-constant array in DATA statement %L", &ar->where);

@@ -313,6 +314,10 @@ gfc_assign_data_value (gfc_expr *lvalue,
          else
            mpz_set (offset, index);
 
+gmp_printf ("offset: %Zd\n", offset);
+if (lvalue->ts.type == BT_DERIVED)
+  mpz_add_ui (offset, offset, 1);
+

in data.c to see the computed offset values.  The first chunk comments out
a check for a constant ar->start[] value, so that I get back to where 
get_data_index is called.  For this code 

  implicit none

  type :: a
     real :: x(3)
  end type a

  integer, parameter :: n = 3

  type(a) :: b(n)

  real, parameter :: d1(3) = (/1., 2., 3./)
  real, parameter :: d2(3) = (/4., 5., 6./)
  real, parameter :: d3(3) = (/7., 8., 9./)

  integer :: i, z(n)

  data (b(i), i = 1, n) /a(d1), a(d2), a(d3)/
  data (z(i), i = 1, n) / 1, 2, 3/

  print *, z(1), b(1)
  print *, z(2), b(2)
  print *, z(3), b(3)
end

I get

REMOVE:kargl[248] gfc4x -o z pr41807.f90
offset: 0
offset: 1
offset: 2
offset: 0
offset: -1
offset: -1
REMOVE:kargl[249] ./z
           1   7.0000000       8.0000000       9.0000000    
           2   1.0000000       2.0000000       3.0000000    
           3   0.0000000       0.0000000       0.0000000    

The first 3 offset values is from the data statement for the 
z(3) array.  The next 3 are for the array b(3) of the derived
type a.  My conclusion to this point is that the array spec for
an array of a derived type is not properly set, or we're looking
at the wrong array spec.
Comment 12 Jerry DeLisle 2009-11-15 19:04:41 UTC
When we simplify start[i], we turn that expression into a constant.  Then I believe the traverse_data_var can no longer increment the index since we made it a constant.  I don't think the start[i] expression should be used to increment the offset, but I think it is.  I am wondering if we don't need a temporary expression to use for this to traverse for the offset. Still thinking ...
Comment 13 Steve Kargl 2009-11-15 19:26:10 UTC
Subject: Re:  [4.5/4.4 Regression]  data statement with nested type constructors

On Sun, Nov 15, 2009 at 07:04:42PM -0000, jvdelisle at gcc dot gnu dot org wrote:
> 
> 
> ------- Comment #12 from jvdelisle at gcc dot gnu dot org  2009-11-15 19:04 -------
> When we simplify start[i], we turn that expression into a constant.  Then I
> believe the traverse_data_var can no longer increment the index since we made
> it a constant.  I don't think the start[i] expression should be used to
> increment the offset, but I think it is.  I am wondering if we don't need a
> temporary expression to use for this to traverse for the offset. Still thinking
> ...
> 

Changed the instrumentaion of the code a little.  In the for-loop
of get_array_index, I added

printf("i = %d --> ", i);
gmp_printf ("start = %Zd ", e->value.integer);
gmp_printf ("lower = %Zd ", ar->as->lower[i]->value.integer);
gmp_printf ("upper = %Zd ", ar->as->upper[i]->value.integer);
gmp_printf ("offset= %Zd\n", *offset);

REMOVE:kargl[252] gfc4x -o z pr41807.f90 -fdump-tree-original
i = 0 --> start = 1 lower = 1 upper = 3 offset= 0
i = 0 --> start = 2 lower = 1 upper = 3 offset= 1
i = 0 --> start = 3 lower = 1 upper = 3 offset= 2
i = 0 --> start = 1 lower = 1 upper = 3 offset= 0
i = 0 --> start = 0 lower = 1 upper = 3 offset= -1
i = 0 --> start = 0 lower = 1 upper = 3 offset= -1

The first 3 lines are from 

  data (z(i), i = 1, n) / 1, 2, 3/

with z integer.  The next 3 are from the array of derived type b.
So, you appear to be on the right track.  The start value appears
to be junk.  What's disconcerting is that the dump shows (with
the check for /*|| (gfc_is_constant_expr (e) == 0)*/ disabled)


REMOVE:kargl[253] more pr41807.f90.003t.original 
MAIN__ ()
{
  static struct a b[3] = {{.x={7.0e+0, 8.0e+0, 9.0e+0}}, {.x={1.0e+0, 2.0e+0, 3.0e+0}}};
  integer(kind=4) i;
  static integer(kind=4) z[3] = {1, 2, 3};


Comment 14 Jerry DeLisle 2009-11-17 04:17:51 UTC
The offending patch is in 4.4 r148732, r148731 passes the test case.

--- branches/gcc-4_4-branch/gcc/fortran/resolve.c	2009/04/03 20:56:54	145519
+++ branches/gcc-4_4-branch/gcc/fortran/resolve.c	2009/06/19 22:10:45	148732
@@ -9430,9 +9430,12 @@
 static gfc_try
 next_data_value (void)
 {
-
   while (mpz_cmp_ui (values.left, 0) == 0)
     {
+      if (!gfc_is_constant_expr (values.vnode->expr))
+	gfc_error ("non-constant DATA value at %L",
+		   &values.vnode->expr->where);
+
       if (values.vnode->next == NULL)
 	return FAILURE;

I suspect that gfc_is_constant_expr is clobbering something.
Comment 15 Jerry DeLisle 2009-11-17 04:29:56 UTC
I have confirmed on trunk that removing that snippet clears the regression.

Looking at gfc_is_constant_expr we see a call to array.c (gfc_constant_ac) which does indeed modify the expr.  So we have a bad side effect going on here.
Comment 16 Jerry DeLisle 2009-11-17 05:35:33 UTC
I propose fixing this at gfc_consant_ac which has the following comment:

/* Given an array constructor, determine if the constructor is
   constant or not by expanding it and making sure that all elements
   are constants.  This is a bit of a hack since something like (/ (i,
   i=1,100000000) /) will take a while as* opposed to a more clever
   function that traverses the expression tree. FIXME.  */

We should just be able to traverse the expression tree.  I have manually done so with a few test cases and one does indeed end up with a BT_CONSTANT.  I will see what I can come up with.
Comment 17 Steve Kargl 2009-11-17 06:03:44 UTC
Subject: Re:  [4.5/4.4 Regression]  data statement with nested type constructors

On Tue, Nov 17, 2009 at 05:35:33AM -0000, jvdelisle at gcc dot gnu dot org wrote:
> 
>- Comment #16 from jvdelisle at gcc dot gnu dot org  2009-11-17 05:35 -------
> I propose fixing this at gfc_consant_ac which has the following comment:
> 
> /* Given an array constructor, determine if the constructor is
>    constant or not by expanding it and making sure that all elements
>    are constants.  This is a bit of a hack since something like (/ (i,
>    i=1,100000000) /) will take a while as* opposed to a more clever
>    function that traverses the expression tree. FIXME.  */
> 
> We should just be able to traverse the expression tree.  I have
> manually done so with a few test cases and one does indeed end up
> with a BT_CONSTANT.  I will see what I can come up with.
> 

Be careful, if I remember correctly, this can be an O(n**2)
problem.  OTOH, nice sleuthing!

Comment 18 Jerry DeLisle 2009-11-21 22:15:30 UTC
Here is a tentative patch.  I removed the offending code and ran the testsuite to see what would happen.  The only failure was the test case associated with patch that caused the regression.  This failure was an ICE on and assert.  So i thought, why not just replace that assert with the error message, and it appears to work.  It even sort of make sense, its not very intrusive, and it passes regression testing on x86-64.

Any opinions?  Shall we just uuse this?

Index: trans-const.c
===================================================================
--- trans-const.c	(revision 154411)
+++ trans-const.c	(working copy)
@@ -340,7 +340,7 @@ void
 gfc_conv_constant (gfc_se * se, gfc_expr * expr)
 {
   /* We may be receiving an expression for C_NULL_PTR or C_NULL_FUNPTR.  If
-     so, they expr_type will not yet be an EXPR_CONSTANT.  We need to make
+     so, the expr_type will not yet be an EXPR_CONSTANT.  We need to make
      it so here.  */
   if (expr->ts.type == BT_DERIVED && expr->ts.u.derived
       && expr->ts.u.derived->attr.is_iso_c)
@@ -353,7 +353,11 @@ gfc_conv_constant (gfc_se * se, gfc_expr * expr)
         }
     }
 
-  gcc_assert (expr->expr_type == EXPR_CONSTANT);
+  if (expr->expr_type != EXPR_CONSTANT)
+    {
+      gfc_error ("non-constant DATA value at %L", &expr->where);
+      return;
+    }
 
   if (se->ss != NULL)
     {
Index: resolve.c
===================================================================
--- resolve.c	(revision 154411)
+++ resolve.c	(working copy)
@@ -11083,9 +11083,6 @@ next_data_value (void)
 {
   while (mpz_cmp_ui (values.left, 0) == 0)
     {
-      if (!gfc_is_constant_expr (values.vnode->expr))
-	gfc_error ("non-constant DATA value at %L",
-		   &values.vnode->expr->where);
 
       if (values.vnode->next == NULL)
 	return FAILURE;
Comment 19 Jerry DeLisle 2009-11-22 02:05:28 UTC
Subject: Bug 41807

Author: jvdelisle
Date: Sun Nov 22 02:05:12 2009
New Revision: 154419

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=154419
Log:
2009-11-21  Jerry DeLisle  <jvdelisle@gcc.gnu.org>

	PR fortran/41807
	* gfortran.dg/data_value_1.f90: Update test.
	* gfortran.dg/array_constructor_32.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/array_constructor_32.f90
Modified:
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/testsuite/gfortran.dg/data_value_1.f90

Comment 20 Jerry DeLisle 2009-11-22 02:06:46 UTC
Subject: Bug 41807

Author: jvdelisle
Date: Sun Nov 22 02:06:26 2009
New Revision: 154420

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=154420
Log:
2009-11-21  Jerry DeLisle  <jvdelisle@gcc.gnu.org>

	PR fortran/41807
	* trans-const.c (gfc_conv_const): Fix typo in comment. Replace assert
	with error message if not constant.
	* resolve.c (next_data_value): Delete check for constant.

Modified:
    trunk/gcc/fortran/ChangeLog

Comment 21 Jerry DeLisle 2009-11-22 02:10:08 UTC
Fixed on trunk.  Note I inadvertently left off the PR number in the commit.

It was:

Sending        ChangeLog
Sending        resolve.c
Sending        trans-const.c
Transmitting file data ...
Committed revision 154418.

I will backport this to 4.4 in a day.
Comment 22 Jerry DeLisle 2009-11-25 02:38:10 UTC
Subject: Bug 41807

Author: jvdelisle
Date: Wed Nov 25 02:37:57 2009
New Revision: 154529

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=154529
Log:
2009-11-24  Jerry DeLisle  <jvdelisle@gcc.gnu.org>

	PR fortran/41807
	* decl.c (variable_decl): Do not error on initialization within a
	derived type specification of a pure procedure.

Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/decl.c

Comment 23 Jerry DeLisle 2009-11-25 02:44:52 UTC
Disregard comment #22 , wrong PR number.
Comment 24 Jerry DeLisle 2009-11-25 03:34:35 UTC
When attempting to backport the patch to 4.4.3 from mainline data_value_1.f90 test failes with a segmentation fault.

$ gfc44 data_value_1.f90 
data_value_1.f90:12.21:

      DATA P / POINT(1.+X) / ! { dg-error "non-constant DATA value" }
                     1
Error: non-constant initialization expression at (1)
data_value_1.f90:13: internal compiler error: Segmentation fault
Please submit a full bug report,
with preprocessed source if appropriate.
See <http://gcc.gnu.org/bugs.html> for instructions.

Program received signal SIGSEGV, Segmentation fault.
0x00000000007b3c76 in initializer_zerop (init=0x0)
    at ../../gcc44/gcc/tree.c:7954
7954	  STRIP_NOPS (init);

I am stuck at this point, any suggestions?
Comment 25 Jerry DeLisle 2009-11-26 01:08:07 UTC
Since we are dealing with invalid fortran code, we can use gfc_fatal_error and avoid the downstream errors and trying to translate bogus code.  This is the cheap way out of it.
Comment 26 Jerry DeLisle 2009-11-26 02:12:28 UTC
This is better, set the expr to a valid constant 0 before converting to a tree.

Index: trans-const.c
===================================================================
--- trans-const.c	(revision 154660)
+++ trans-const.c	(working copy)
@@ -336,7 +336,7 @@ void
 gfc_conv_constant (gfc_se * se, gfc_expr * expr)
 {
   /* We may be receiving an expression for C_NULL_PTR or C_NULL_FUNPTR.  If
-     so, they expr_type will not yet be an EXPR_CONSTANT.  We need to make
+     so, the expr_type will not yet be an EXPR_CONSTANT.  We need to make
      it so here.  */
   if (expr->ts.type == BT_DERIVED && expr->ts.derived
       && expr->ts.derived->attr.is_iso_c)
@@ -349,7 +349,12 @@ gfc_conv_constant (gfc_se * se, gfc_expr * expr)
         }
     }
 
-  gcc_assert (expr->expr_type == EXPR_CONSTANT);
+  if (expr->expr_type != EXPR_CONSTANT)
+    {
+      gfc_error ("non-constant initialization expression at %L", &expr->where);
+      se->expr = gfc_conv_constant_to_tree (gfc_int_expr (0));
+      return;
+    }
 
   if (se->ss != NULL)
     {
Comment 27 Jerry DeLisle 2009-11-26 21:53:08 UTC
Subject: Bug 41807

Author: jvdelisle
Date: Thu Nov 26 21:52:52 2009
New Revision: 154690

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=154690
Log:
2009-11-26  Jerry DeLisle  <jvdelisle@gcc.gnu.org>

	PR fortran/41807
	* trans-const.c (gfc_conv_const): Set se->expr to a constant on error.

Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-const.c

Comment 28 Jerry DeLisle 2009-11-26 21:57:44 UTC
Subject: Bug 41807

Author: jvdelisle
Date: Thu Nov 26 21:57:32 2009
New Revision: 154691

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=154691
Log:
2009-11-26  Jerry DeLisle  <jvdelisle@gcc.gnu.org>

	PR fortran/41807
	Backport from mainline.
	* trans-const.c (gfc_conv_const): Fix typo in comment. Replace assert
	with error message if not constant. Set se->expr to a constant on error.
	* resolve.c (next_data_value): Delete check for constant.

Modified:
    branches/gcc-4_4-branch/gcc/fortran/ChangeLog
    branches/gcc-4_4-branch/gcc/fortran/resolve.c
    branches/gcc-4_4-branch/gcc/fortran/trans-const.c

Comment 29 Jerry DeLisle 2009-11-26 22:18:50 UTC
Subject: Bug 41807

Author: jvdelisle
Date: Thu Nov 26 22:18:36 2009
New Revision: 154692

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=154692
Log:
2009-11-26  Jerry DeLisle  <jvdelisle@gcc.gnu.org>

	PR fortran/41807
	* gfortran.dg/data_value_1.f90: Update test.
	* gfortran.dg/array_constructor_32.f90: New test.

Added:
    branches/gcc-4_4-branch/gcc/testsuite/gfortran.dg/array_constructor_32.f90
Modified:
    branches/gcc-4_4-branch/gcc/testsuite/ChangeLog
    branches/gcc-4_4-branch/gcc/testsuite/gfortran.dg/data_value_1.f90

Comment 30 Jerry DeLisle 2009-11-26 22:21:31 UTC
Fixed on trunk and 4.4.
Comment 31 Tobias Burnus 2009-11-27 08:32:04 UTC
Crossref: I have opened a follow up PR 42189 as in the review it was stated that "gfc_is_constant_expr has unacceptable side effects".