public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression
@ 2011-05-28 18:15 neil.n.carlson at gmail dot com
  2011-06-16 19:44 ` [Bug fortran/49213] [OOP][F2008] " janus at gcc dot gnu.org
                   ` (31 more replies)
  0 siblings, 32 replies; 33+ messages in thread
From: neil.n.carlson at gmail dot com @ 2011-05-28 18:15 UTC (permalink / raw)
  To: gcc-bugs

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

           Summary: [OOP] gfortran rejects structure constructor
                    expression
           Product: gcc
           Version: 4.7.0
            Status: UNCONFIRMED
          Severity: major
          Priority: P3
         Component: fortran
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: neil.n.carlson@gmail.com


In the following program type-compatible variables are used as an expression in
a structure constructor for an allocatable CLASS(S) component.  In the first
case a TYPE(S) variable is used, and in the second a TYPE(S2), where S2 extends
S.

The program compiles with nagfor 5.2 and (reportedly) with the cray compiler,
but gfortran rejects the code with the error messages:

  Tobj = T(Sobj)
           1
Error: Can't convert TYPE(s) to CLASS(s) at (1)

  Tobj = T(S2obj)
           1
Error: Can't convert TYPE(s2) to CLASS(s) at (1)

===============

>From the F2008 standard:

"For a nonpointer component, the declared type and type parameters of the
component and expr shall conform in the same way as for a variable and expr in
an intrinsic assignment statement (7.2.1.2) [...]" (4.5.10p2)

"if the variable is polymorphic it shall be type compatible with expr; [...]"
(7.2.1.2p1(4))

Also 4.5.10 p6 applies to allocatable components.

===============

program main

  type :: S
    integer :: n
  end type
  type(S) :: Sobj

  type, extends(S) :: S2
    integer :: m
  end type
  type(S2) :: S2obj

  type :: T
    class(S), allocatable :: x
  end type
  type(T) :: Tobj

  Sobj = S(1)
  Tobj = T(Sobj)

  S2obj = S2(1,2)
  Tobj = T(S2obj)

end program


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

* [Bug fortran/49213] [OOP][F2008] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
@ 2011-06-16 19:44 ` janus at gcc dot gnu.org
  2011-06-16 19:50 ` [Bug fortran/49213] [OOP] " janus at gcc dot gnu.org
                   ` (30 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: janus at gcc dot gnu.org @ 2011-06-16 19:44 UTC (permalink / raw)
  To: gcc-bugs

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

janus at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2011.06.16 19:43:45
            Summary|[OOP] gfortran rejects      |[OOP][F2008] gfortran
                   |structure constructor       |rejects structure
                   |expression                  |constructor expression
     Ever Confirmed|0                           |1

--- Comment #1 from janus at gcc dot gnu.org 2011-06-16 19:43:45 UTC ---
Note: Intrinsic assignments to polymorphic variables are forbidden in the
Fortran 2003 standard, and currently not supported by gfortran, cf. PR 43366.

F03:7.4.1.2:
"In an intrinsic assignment statement, variable shall not be polymorphic, and
..."


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
  2011-06-16 19:44 ` [Bug fortran/49213] [OOP][F2008] " janus at gcc dot gnu.org
@ 2011-06-16 19:50 ` janus at gcc dot gnu.org
  2011-06-16 20:36 ` neil.n.carlson at gmail dot com
                   ` (29 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: janus at gcc dot gnu.org @ 2011-06-16 19:50 UTC (permalink / raw)
  To: gcc-bugs

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

janus at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
            Summary|[OOP][F2008] gfortran       |[OOP] gfortran rejects
                   |rejects structure           |structure constructor
                   |constructor expression      |expression

--- Comment #2 from janus at gcc dot gnu.org 2011-06-16 19:49:33 UTC ---
(In reply to comment #1)
> Note: Intrinsic assignments to polymorphic variables are forbidden in the
> Fortran 2003 standard, and currently not supported by gfortran, cf. PR 43366.


However, the same error message appears for the following variant (with a
defined assignment), which is valid according to F03:


module m

  type :: S
    integer :: n
  contains
    generic :: assignment (=) => assgn
    procedure :: assgn
  end type

  type :: T
    class(S), allocatable :: x
  end type

contains

  subroutine assgn (a, b)
    class (S), intent (inout) :: a
    class (S), intent (in) :: b
  end subroutine

end module


  use m
  type(S) :: Sobj
  type(T) :: Tobj

  Sobj = S(1)
  Tobj = T(Sobj)

end program 



  Tobj = T(Sobj)
           1
Error: Can't convert TYPE(s) to CLASS(s) at (1)


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
  2011-06-16 19:44 ` [Bug fortran/49213] [OOP][F2008] " janus at gcc dot gnu.org
  2011-06-16 19:50 ` [Bug fortran/49213] [OOP] " janus at gcc dot gnu.org
@ 2011-06-16 20:36 ` neil.n.carlson at gmail dot com
  2011-06-16 20:50 ` neil.n.carlson at gmail dot com
                   ` (28 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: neil.n.carlson at gmail dot com @ 2011-06-16 20:36 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from neil.n.carlson at gmail dot com 2011-06-16 20:35:48 UTC ---
(In reply to comment #1)
> Note: Intrinsic assignments to polymorphic variables are forbidden [...]

This was really about the structure constructor; the assignment was
just to do something with the value, so the example was poor.  Here's
a slightly different version that gets to the heart of what I intended:

program main

  type :: S
    integer :: n
  end type
  type(S) :: Sobj

  type, extends(S) :: S2
    integer :: m
  end type
  type(S2) :: S2obj

  type :: T
    class(S), allocatable :: x
  end type

  Sobj = S(1)
  call pass_it (T(Sobj))

  S2obj = S2(1,2)
  call pass_it (T(S2obj))

contains

  subroutine pass_it (foo)
    type(T), intent(in) :: foo
  end subroutine

end program

This gives the same errors:

  call pass_it (T(Sobj))
                  1
Error: Can't convert TYPE(s) to CLASS(s) at (1)

  call pass_it (T(S2obj))
                  1
Error: Can't convert TYPE(s2) to CLASS(s) at (1)


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (2 preceding siblings ...)
  2011-06-16 20:36 ` neil.n.carlson at gmail dot com
@ 2011-06-16 20:50 ` neil.n.carlson at gmail dot com
  2011-06-16 21:29 ` janus at gcc dot gnu.org
                   ` (27 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: neil.n.carlson at gmail dot com @ 2011-06-16 20:50 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #4 from neil.n.carlson at gmail dot com 2011-06-16 20:49:32 UTC ---
An intuitive way of viewing (and maybe even implementing I guess) the process
triggered by a structure constructor is as a sequence of assignment statements
for the components of the structure.  But that's not how the (2008) standard
describes what takes place, and so constraints that apply to assignments (like
assigning to a polymorphic) don't apply in this context.


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (3 preceding siblings ...)
  2011-06-16 20:50 ` neil.n.carlson at gmail dot com
@ 2011-06-16 21:29 ` janus at gcc dot gnu.org
  2011-06-16 22:14 ` neil.n.carlson at gmail dot com
                   ` (26 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: janus at gcc dot gnu.org @ 2011-06-16 21:29 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #5 from janus at gcc dot gnu.org 2011-06-16 21:29:07 UTC ---
(In reply to comment #4)
> An intuitive way of viewing (and maybe even implementing I guess) the process
> triggered by a structure constructor is as a sequence of assignment statements
> for the components of the structure.  But that's not how the (2008) standard
> describes what takes place, and so constraints that apply to assignments (like
> assigning to a polymorphic) don't apply in this context.

I think you are wrong here.

F08:7.2.1.3p13:

"An intrinsic assignment where the variable is of derived type is performed as
if each component of the variable were assigned from the corresponding
component of expr using pointer assignment (7.2.2) for each pointer component,
defined assignment for each nonpointer nonallocatable component of a type that
has a type-bound defined assignment consistent with the component, intrinsic
assignment for each other nonpointer nonallocatable component, and intrinsic
assignment for each allocated coarray component. For unallocated coarray
components, the corresponding component of the variable shall be unallocated.
For a noncoarray allocatable component the following sequence of operations is
applied."

In essence this means that a derived type assignment *is* viewed as a sequence
of component assignments. Therefore I think that the corresponding restrictions
*do* apply.


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (4 preceding siblings ...)
  2011-06-16 21:29 ` janus at gcc dot gnu.org
@ 2011-06-16 22:14 ` neil.n.carlson at gmail dot com
  2011-06-16 22:18 ` neil.n.carlson at gmail dot com
                   ` (25 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: neil.n.carlson at gmail dot com @ 2011-06-16 22:14 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #6 from neil.n.carlson at gmail dot com 2011-06-16 22:12:17 UTC ---
(In reply to comment #5)
> (In reply to comment #4)
> > An intuitive way of viewing (and maybe even implementing I guess) the process
> > triggered by a structure constructor [...]
> 
> I think you are wrong here.
> 
> F08:7.2.1.3p13:
> 
> "An intrinsic assignment where the variable is of derived type [...]

Sorry, I wasn't talking about intrinsic assignment.  I was (unsuccessfully)
trying to talk about what happens when a structure constructor expression,
like T(Sobj) is encountered.  The compiler has to generate a temporary
object of type T and define its components, and what I was trying to say
(and I might be wrong about this) is that this process of defining the
components using the expressions given to the constructor is not like
normal assignment (intrinsic or defined) of derived type objects.
The reason for raising this was that the error messages suggest that
that is how the compiler is viewing it.

Sorry for the confusion.


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (5 preceding siblings ...)
  2011-06-16 22:14 ` neil.n.carlson at gmail dot com
@ 2011-06-16 22:18 ` neil.n.carlson at gmail dot com
  2013-01-10 15:46 ` janus at gcc dot gnu.org
                   ` (24 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: neil.n.carlson at gmail dot com @ 2011-06-16 22:18 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #7 from neil.n.carlson at gmail dot com 2011-06-16 22:18:14 UTC ---
I want to emphasize again that the error I wanted to report was that gfortran
is rejecting valid structure constructor expressions (see comment 3).  It looks
from you example that there is also an error with assignment, but that's
orthogonal to the constructor error.


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (6 preceding siblings ...)
  2011-06-16 22:18 ` neil.n.carlson at gmail dot com
@ 2013-01-10 15:46 ` janus at gcc dot gnu.org
  2013-01-10 16:07 ` janus at gcc dot gnu.org
                   ` (23 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: janus at gcc dot gnu.org @ 2013-01-10 15:46 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #8 from janus at gcc dot gnu.org 2013-01-10 15:46:12 UTC ---
(In reply to comment #7)
> I want to emphasize again that the error I wanted to report was that gfortran
> is rejecting valid structure constructor expressions (see comment 3).

Here is a slightly reduced version of comment 3:

  type :: S
    integer :: n
  end type
  type(S) :: Sobj

  type :: T
    class(S), allocatable :: x
  end type

  Sobj = S(1)
  call pass_it (T(Sobj))

contains

  subroutine pass_it (foo)
    type(T) :: foo
  end subroutine

end



One can get past the error message with the following patch:

Index: gcc/fortran/resolve.c
===================================================================
--- gcc/fortran/resolve.c    (revision 194927)
+++ gcc/fortran/resolve.c    (working copy)
@@ -1103,7 +1103,7 @@ resolve_structure_cons (gfc_expr *expr, int init)
       /* If we don't have the right type, try to convert it.  */

       if (!comp->attr.proc_pointer &&
-      !gfc_compare_types (&cons->expr->ts, &comp->ts))
+      !gfc_compare_types (&comp->ts, &cons->expr->ts))
     {
       t = FAILURE;
       if (strcmp (comp->name, "_extends") == 0)


but the one runs into an ICE:

internal compiler error: in fold_convert_loc, at fold-const.c:1986
   call pass_it (T(Sobj))
 ^
0x845634 fold_convert_loc(unsigned int, tree_node*, tree_node*)
        /home/jweil/gcc48/trunk/gcc/fold-const.c:1986
0x671aa9 gfc_trans_subcomponent_assign
        /home/jweil/gcc48/trunk/gcc/fortran/trans-expr.c:6001
0x671e10 gfc_trans_structure_assign
        /home/jweil/gcc48/trunk/gcc/fortran/trans-expr.c:6068
0x671f46 gfc_conv_structure(gfc_se*, gfc_expr*, int)
        /home/jweil/gcc48/trunk/gcc/fortran/trans-expr.c:6095


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (7 preceding siblings ...)
  2013-01-10 15:46 ` janus at gcc dot gnu.org
@ 2013-01-10 16:07 ` janus at gcc dot gnu.org
  2013-01-10 20:40 ` janus at gcc dot gnu.org
                   ` (22 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: janus at gcc dot gnu.org @ 2013-01-10 16:07 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #9 from janus at gcc dot gnu.org 2013-01-10 16:06:51 UTC ---
In fact one also gets an ICE when replacing "class(S)" with "type(S)" in
comment 8 (already with an unpatched gfortran):


  type :: S
    integer :: n
  end type
  type(S) :: Sobj

  type :: T
    type(S), allocatable :: x
  end type

  Sobj = S(1)
  call pass_it (T(Sobj))

contains

  subroutine pass_it (foo)
    type(T) :: foo
  end subroutine

end



internal compiler error: in fold_convert_loc, at fold-const.c:1864
   call pass_it (T(Sobj))
 ^
0x844efe fold_convert_loc(unsigned int, tree_node*, tree_node*)
        /home/jweil/gcc48/trunk/gcc/fold-const.c:1863
0x671aa9 gfc_trans_subcomponent_assign
        /home/jweil/gcc48/trunk/gcc/fortran/trans-expr.c:6001
0x671e10 gfc_trans_structure_assign
        /home/jweil/gcc48/trunk/gcc/fortran/trans-expr.c:6068
0x671f46 gfc_conv_structure(gfc_se*, gfc_expr*, int)
        /home/jweil/gcc48/trunk/gcc/fortran/trans-expr.c:6095


This is similar, but not identical, to the ICE in comment 8.


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (8 preceding siblings ...)
  2013-01-10 16:07 ` janus at gcc dot gnu.org
@ 2013-01-10 20:40 ` janus at gcc dot gnu.org
  2013-01-11 12:04 ` janus at gcc dot gnu.org
                   ` (21 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: janus at gcc dot gnu.org @ 2013-01-10 20:40 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #10 from janus at gcc dot gnu.org 2013-01-10 20:39:58 UTC ---
The following patch makes comment 8 and 9 compile, but I'm not sure if the
generated code is correct:

Index: gcc/fortran/trans-expr.c
===================================================================
--- gcc/fortran/trans-expr.c    (revision 194927)
+++ gcc/fortran/trans-expr.c    (working copy)
@@ -5990,23 +5990,11 @@ gfc_trans_subcomponent_assign (tree dest, gfc_comp
       gfc_add_expr_to_block (&block, tmp);
     }
     }
-  else if (expr->ts.type == BT_DERIVED)
+  else if (expr->ts.type == BT_DERIVED && expr->expr_type == EXPR_STRUCTURE)
     {
-      if (expr->expr_type != EXPR_STRUCTURE)
-    {
-      gfc_init_se (&se, NULL);
-      gfc_conv_expr (&se, expr);
-      gfc_add_block_to_block (&block, &se.pre);
-      gfc_add_modify (&block, dest,
-                   fold_convert (TREE_TYPE (dest), se.expr));
-      gfc_add_block_to_block (&block, &se.post);
-    }
-      else
-    {
-      /* Nested constructors.  */
-      tmp = gfc_trans_structure_assign (dest, expr);
-      gfc_add_expr_to_block (&block, tmp);
-    }
+      /* Nested constructors.  */
+      tmp = gfc_trans_structure_assign (dest, expr);
+      gfc_add_expr_to_block (&block, tmp);
     }
   else
     {


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (9 preceding siblings ...)
  2013-01-10 20:40 ` janus at gcc dot gnu.org
@ 2013-01-11 12:04 ` janus at gcc dot gnu.org
  2013-08-05  9:08 ` janus at gcc dot gnu.org
                   ` (20 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: janus at gcc dot gnu.org @ 2013-01-11 12:04 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #11 from janus at gcc dot gnu.org 2013-01-11 12:04:26 UTC ---
Note: Neither of the patches in comment 8 and 10 shows any testsuite
regressions.


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (10 preceding siblings ...)
  2013-01-11 12:04 ` janus at gcc dot gnu.org
@ 2013-08-05  9:08 ` janus at gcc dot gnu.org
  2013-08-05  9:22 ` janus at gcc dot gnu.org
                   ` (19 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: janus at gcc dot gnu.org @ 2013-08-05  9:08 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #12 from janus at gcc dot gnu.org ---
Related test case (using unlimited polymorphism) from
http://gcc.gnu.org/ml/fortran/2013-08/msg00011.html:

type t
  class(*), pointer :: x
end type t
type(t), target :: y
integer,target :: z
type(t) :: x = t(y)
type(t) :: x = t(z)
class(*), pointer :: a => y 
end


Unpatched gfortran trunk yields:

tobias2.f90:7.17:

type(t) :: x = t(y)
                 1
Error: Can't convert TYPE(t) to CLASS(*) at (1)
tobias2.f90:8.17:

type(t) :: x = t(z)
                 1
Error: Can't convert INTEGER(4) to CLASS(*) at (1)


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (11 preceding siblings ...)
  2013-08-05  9:08 ` janus at gcc dot gnu.org
@ 2013-08-05  9:22 ` janus at gcc dot gnu.org
  2013-08-05 11:14 ` janus at gcc dot gnu.org
                   ` (18 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: janus at gcc dot gnu.org @ 2013-08-05  9:22 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #13 from janus at gcc dot gnu.org ---
(In reply to janus from comment #12)
> 
> type(t) :: x = t(y)
>                  1
> Error: Can't convert TYPE(t) to CLASS(*) at (1)

The patch in comment 8 turns this error into:

type(t) :: x = t(y)
                 1
Error: Parameter 'y' at (1) has not been declared or is a variable, which does
not reduce to a constant expression


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (12 preceding siblings ...)
  2013-08-05  9:22 ` janus at gcc dot gnu.org
@ 2013-08-05 11:14 ` janus at gcc dot gnu.org
  2013-08-06  8:42 ` janus at gcc dot gnu.org
                   ` (17 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: janus at gcc dot gnu.org @ 2013-08-05 11:14 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #14 from janus at gcc dot gnu.org ---
(In reply to janus from comment #13)
> type(t) :: x = t(y)
>                  1
> Error: Parameter 'y' at (1) has not been declared or is a variable, which
> does not reduce to a constant expression

This error also occurs for the following non-polymorphic version ...

type t
  integer, pointer :: j
end type t
integer, target :: i = 0
type(t) :: x = t(i)
end

... which should be valid at least in F08.


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (13 preceding siblings ...)
  2013-08-05 11:14 ` janus at gcc dot gnu.org
@ 2013-08-06  8:42 ` janus at gcc dot gnu.org
  2013-08-06  9:13 ` janus at gcc dot gnu.org
                   ` (16 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: janus at gcc dot gnu.org @ 2013-08-06  8:42 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #15 from janus at gcc dot gnu.org ---
Another test case related to comment 12 (from
http://gcc.gnu.org/ml/fortran/2013-08/msg00015.html):


integer, target :: tgt
type t2
end type t2
type(t2), target :: tgt2
type t
  class(*), pointer :: a => tgt
  class(*), pointer :: b => tgt2
end type t
type(t) :: x
type(t), SAVE :: y
end


Unpatched gfortran gives:


tobias3.f90:1.22:

integer, target :: tgt
                      1
Internal Error at (1):
tobias3.f90:6.31:

  class(*), pointer :: a => tgt
                               1
Can't convert INTEGER(4) to CLASS(*) at (1)


and also the patches from comment 8 and 10 don't help here.


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (14 preceding siblings ...)
  2013-08-06  8:42 ` janus at gcc dot gnu.org
@ 2013-08-06  9:13 ` janus at gcc dot gnu.org
  2013-08-06 10:50 ` janus at gcc dot gnu.org
                   ` (15 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: janus at gcc dot gnu.org @ 2013-08-06  9:13 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #16 from janus at gcc dot gnu.org ---
(In reply to janus from comment #15)
> and also the patches from comment 8 and 10 don't help here.

... but the following does:


Index: gcc/fortran/expr.c
===================================================================
--- gcc/fortran/expr.c    (revision 201520)
+++ gcc/fortran/expr.c    (working copy)
@@ -3936,8 +3936,7 @@ gfc_default_initializer (gfc_typespec *ts)
       if (comp->initializer)
     {
       ctor->expr = gfc_copy_expr (comp->initializer);
-      if ((comp->ts.type != comp->initializer->ts.type
-           || comp->ts.kind != comp->initializer->ts.kind)
+      if (!gfc_compare_types (&comp->ts, &comp->initializer->ts)
           && !comp->attr.pointer && !comp->attr.proc_pointer)
         gfc_convert_type_warn (ctor->expr, &comp->ts, 2, false);
     }


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (15 preceding siblings ...)
  2013-08-06  9:13 ` janus at gcc dot gnu.org
@ 2013-08-06 10:50 ` janus at gcc dot gnu.org
  2013-08-08 16:54 ` dominiq at lps dot ens.fr
                   ` (14 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: janus at gcc dot gnu.org @ 2013-08-06 10:50 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #17 from janus at gcc dot gnu.org ---
(In reply to janus from comment #16)
> > and also the patches from comment 8 and 10 don't help here.
> 
> ... but the following does:

... without any testsuite failures, btw.


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (16 preceding siblings ...)
  2013-08-06 10:50 ` janus at gcc dot gnu.org
@ 2013-08-08 16:54 ` dominiq at lps dot ens.fr
  2013-08-11 17:03 ` dominiq at lps dot ens.fr
                   ` (13 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-08-08 16:54 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #18 from Dominique d'Humieres <dominiq at lps dot ens.fr> ---
With the patch in comment #16 the 'Internal Error' when compiling the code in
comment #15 disappears, but appears when compiling the test in pr51945 with the
type-declaration line 'type(my_t) :: a' is uncommented.


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (17 preceding siblings ...)
  2013-08-08 16:54 ` dominiq at lps dot ens.fr
@ 2013-08-11 17:03 ` dominiq at lps dot ens.fr
  2015-01-24 11:52 ` dominiq at lps dot ens.fr
                   ` (12 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-08-11 17:03 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #19 from Dominique d'Humieres <dominiq at lps dot ens.fr> ---
Note that the patch in comment #10 no longer applies cleanly due to revision
197053:

@@ -6013,7 +5786,7 @@
       gfc_add_expr_to_block (&block, tmp);
     }
     }
-  else if (expr->ts.type == BT_DERIVED)
+  else if (expr->ts.type == BT_DERIVED && expr->ts.f90_type != BT_VOID)
     {
       if (expr->expr_type != EXPR_STRUCTURE)
     {


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (18 preceding siblings ...)
  2013-08-11 17:03 ` dominiq at lps dot ens.fr
@ 2015-01-24 11:52 ` dominiq at lps dot ens.fr
  2015-01-24 16:32 ` dominiq at lps dot ens.fr
                   ` (11 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: dominiq at lps dot ens.fr @ 2015-01-24 11:52 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

Dominique d'Humieres <dominiq at lps dot ens.fr> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |mike at rilee dot net

--- Comment #20 from Dominique d'Humieres <dominiq at lps dot ens.fr> ---
*** Bug 64757 has been marked as a duplicate of this bug. ***


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (19 preceding siblings ...)
  2015-01-24 11:52 ` dominiq at lps dot ens.fr
@ 2015-01-24 16:32 ` dominiq at lps dot ens.fr
  2015-01-24 19:05 ` janus at gcc dot gnu.org
                   ` (10 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: dominiq at lps dot ens.fr @ 2015-01-24 16:32 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

--- Comment #21 from Dominique d'Humieres <dominiq at lps dot ens.fr> ---
The ICE for the test in comment 8 is now handled by PR64757.


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (20 preceding siblings ...)
  2015-01-24 16:32 ` dominiq at lps dot ens.fr
@ 2015-01-24 19:05 ` janus at gcc dot gnu.org
  2015-02-05  8:09 ` pault at gcc dot gnu.org
                   ` (9 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: janus at gcc dot gnu.org @ 2015-01-24 19:05 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

--- Comment #22 from janus at gcc dot gnu.org ---
The ICE on comment 9 does not occur any more with current trunk:

gcc-Version 5.0.0 20150124 (experimental) [trunk revision 220084] (GCC)


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (21 preceding siblings ...)
  2015-01-24 19:05 ` janus at gcc dot gnu.org
@ 2015-02-05  8:09 ` pault at gcc dot gnu.org
  2020-03-12 11:58 ` jakub at gcc dot gnu.org
                   ` (8 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: pault at gcc dot gnu.org @ 2015-02-05  8:09 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213
Bug 49213 depends on bug 64757, which changed state.

Bug 64757 Summary: [5 Regression] ICE in fold_convert_loc, at fold-const.c:2353
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=64757

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


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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (22 preceding siblings ...)
  2015-02-05  8:09 ` pault at gcc dot gnu.org
@ 2020-03-12 11:58 ` jakub at gcc dot gnu.org
  2021-04-16 20:03 ` vladimir.fuka at gmail dot com
                   ` (7 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: jakub at gcc dot gnu.org @ 2020-03-12 11:58 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

Jakub Jelinek <jakub at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|9.3                         |9.4

--- Comment #32 from Jakub Jelinek <jakub at gcc dot gnu.org> ---
GCC 9.3.0 has been released, adjusting target milestone.

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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (23 preceding siblings ...)
  2020-03-12 11:58 ` jakub at gcc dot gnu.org
@ 2021-04-16 20:03 ` vladimir.fuka at gmail dot com
  2021-06-01  8:05 ` rguenth at gcc dot gnu.org
                   ` (6 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: vladimir.fuka at gmail dot com @ 2021-04-16 20:03 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

Vladimir Fuka <vladimir.fuka at gmail dot com> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |vladimir.fuka at gmail dot com

--- Comment #33 from Vladimir Fuka <vladimir.fuka at gmail dot com> ---
GCC 11 was released and the problem is still present.

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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (24 preceding siblings ...)
  2021-04-16 20:03 ` vladimir.fuka at gmail dot com
@ 2021-06-01  8:05 ` rguenth at gcc dot gnu.org
  2022-05-27  9:12 ` rguenth at gcc dot gnu.org
                   ` (5 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: rguenth at gcc dot gnu.org @ 2021-06-01  8:05 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

Richard Biener <rguenth at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|9.4                         |9.5

--- Comment #34 from Richard Biener <rguenth at gcc dot gnu.org> ---
GCC 9.4 is being released, retargeting bugs to GCC 9.5.

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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (25 preceding siblings ...)
  2021-06-01  8:05 ` rguenth at gcc dot gnu.org
@ 2022-05-27  9:12 ` rguenth at gcc dot gnu.org
  2023-06-22 16:45 ` pault at gcc dot gnu.org
                   ` (4 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: rguenth at gcc dot gnu.org @ 2022-05-27  9:12 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

Richard Biener <rguenth at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|9.5                         |---

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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (26 preceding siblings ...)
  2022-05-27  9:12 ` rguenth at gcc dot gnu.org
@ 2023-06-22 16:45 ` pault at gcc dot gnu.org
  2023-06-28 11:39 ` cvs-commit at gcc dot gnu.org
                   ` (3 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: pault at gcc dot gnu.org @ 2023-06-22 16:45 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

Paul Thomas <pault at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |pault at gcc dot gnu.org
           Assignee|janus at gcc dot gnu.org           |pault at gcc dot gnu.org

--- Comment #35 from Paul Thomas <pault at gcc dot gnu.org> ---
Created attachment 55383
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=55383&action=edit
Fix for this PR

Hello again Neil,

I had a tedious job to do, which I alleviated by fixing this bug :-)

Dejagnu-style testcase below.

Now the earliest surviving bug is gfortran-20160129.f90 and there are 22/64
remaining failures (there might be fewer; my octave test harness doesn't cope
with multiple sources yet).

Regards

Paul

! { dg-do run }
!
! Contributed by Neil Carlson  <neil.n.carlson@gmail.com>
!
program main
  character(2) :: c

  type :: S
    integer :: n
  end type
  type(S) :: Sobj

  type, extends(S) :: S2
    integer :: m
  end type
  type(S2) :: S2obj

  type :: T
    class(S), allocatable :: x
  end type
  type(T) :: Tobj

  Sobj = S(1)
  Tobj = T(Sobj)

  S2obj = S2(1,2)
  Tobj = T(S2obj)            ! Failed here
  select type (x => Tobj%x)
    type is (S2)
      if ((x%n .ne. 1) .or. (x%m .ne. 2)) stop 1
    class default
      stop 2
  end select

  c = "  "
  call pass_it (T(Sobj))
  if (c .ne. "S ") stop 3
  call pass_it (T(S2obj))    ! and here
  if (c .ne. "S2") stop 4

contains

  subroutine pass_it (foo)
    type(T), intent(in) :: foo
    select type (x => foo%x)
      type is (S)
        c = "S "
        if (x%n .ne. 1) stop 5
      type is (S2)
        c = "S2"
        if ((x%n .ne. 1) .or. (x%m .ne. 2)) stop 6
      class default
        stop 7
    end select
  end subroutine

end program

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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (27 preceding siblings ...)
  2023-06-22 16:45 ` pault at gcc dot gnu.org
@ 2023-06-28 11:39 ` cvs-commit at gcc dot gnu.org
  2023-10-31  8:23 ` pault at gcc dot gnu.org
                   ` (2 subsequent siblings)
  31 siblings, 0 replies; 33+ messages in thread
From: cvs-commit at gcc dot gnu.org @ 2023-06-28 11:39 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

--- Comment #36 from CVS Commits <cvs-commit at gcc dot gnu.org> ---
The master branch has been updated by Paul Thomas <pault@gcc.gnu.org>:

https://gcc.gnu.org/g:3521768e8e3c448052c5bd3e8fde412e9cf5d70f

commit r14-2160-g3521768e8e3c448052c5bd3e8fde412e9cf5d70f
Author: Paul Thomas <pault@gcc.gnu.org>
Date:   Wed Jun 28 12:38:58 2023 +0100

    Fortran: Enable class expressions in structure constructors [PR49213]

    2023-06-28  Paul Thomas  <pault@gcc.gnu.org>

    gcc/fortran
            PR fortran/49213
            * expr.cc (gfc_is_ptr_fcn): Remove reference to class_pointer.
            * resolve.cc (resolve_assoc_var): Call gfc_is_ptr_fcn to allow
            associate names with pointer function targets to be used in
            variable definition context.
            * trans-decl.cc (get_symbol_decl): Remove extraneous line.
            * trans-expr.cc (alloc_scalar_allocatable_subcomponent): Obtain
            size of intrinsic and character expressions.
            (gfc_trans_subcomponent_assign): Expand assignment to class
            components to include intrinsic and character expressions.

    gcc/testsuite/
            PR fortran/49213
            * gfortran.dg/pr49213.f90 : New test

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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (28 preceding siblings ...)
  2023-06-28 11:39 ` cvs-commit at gcc dot gnu.org
@ 2023-10-31  8:23 ` pault at gcc dot gnu.org
  2023-10-31  8:24 ` pault at gcc dot gnu.org
  2023-10-31  8:29 ` pault at gcc dot gnu.org
  31 siblings, 0 replies; 33+ messages in thread
From: pault at gcc dot gnu.org @ 2023-10-31  8:23 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

Paul Thomas <pault at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |marxin at gcc dot gnu.org

--- Comment #37 from Paul Thomas <pault at gcc dot gnu.org> ---
This bug has fixed itself on mainline. I thought that it might be
r14-4943-g8d2130a4e5ce369f5884c8522934dc027db6e9d8 but reversion didn't cause a
recurrence.

@Martin - as and when you have the time, could you please find the commit that
fixed this PR.

Paul

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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (29 preceding siblings ...)
  2023-10-31  8:23 ` pault at gcc dot gnu.org
@ 2023-10-31  8:24 ` pault at gcc dot gnu.org
  2023-10-31  8:29 ` pault at gcc dot gnu.org
  31 siblings, 0 replies; 33+ messages in thread
From: pault at gcc dot gnu.org @ 2023-10-31  8:24 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

--- Comment #38 from Paul Thomas <pault at gcc dot gnu.org> ---
This bug has fixed itself on mainline. I thought that it might be
r14-4943-g8d2130a4e5ce369f5884c8522934dc027db6e9d8 but reversion didn't cause a
recurrence.

@Martin - as and when you have the time, could you please find the commit that
fixed this PR.

Paul

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

* [Bug fortran/49213] [OOP] gfortran rejects structure constructor expression
  2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
                   ` (30 preceding siblings ...)
  2023-10-31  8:24 ` pault at gcc dot gnu.org
@ 2023-10-31  8:29 ` pault at gcc dot gnu.org
  31 siblings, 0 replies; 33+ messages in thread
From: pault at gcc dot gnu.org @ 2023-10-31  8:29 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=49213

Paul Thomas <pault at gcc dot gnu.org> changed:

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

--- Comment #39 from Paul Thomas <pault at gcc dot gnu.org> ---
(In reply to Paul Thomas from comment #38)
> This bug has fixed itself on mainline. I thought that it might be
> r14-4943-g8d2130a4e5ce369f5884c8522934dc027db6e9d8 but reversion didn't
> cause a recurrence.
> 
> @Martin - as and when you have the time, could you please find the commit
> that fixed this PR.
> 
> Paul

Martin,

Please forgive the noise and ignore the doubled request. For some reason, when
I first opened the PR, the later comments and my commit were missing.

Fixed on mainline. Thanks for the report and sorry for the long delay in fixing
the bug.

Paul

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

end of thread, other threads:[~2023-10-31  8:29 UTC | newest]

Thread overview: 33+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2011-05-28 18:15 [Bug fortran/49213] New: [OOP] gfortran rejects structure constructor expression neil.n.carlson at gmail dot com
2011-06-16 19:44 ` [Bug fortran/49213] [OOP][F2008] " janus at gcc dot gnu.org
2011-06-16 19:50 ` [Bug fortran/49213] [OOP] " janus at gcc dot gnu.org
2011-06-16 20:36 ` neil.n.carlson at gmail dot com
2011-06-16 20:50 ` neil.n.carlson at gmail dot com
2011-06-16 21:29 ` janus at gcc dot gnu.org
2011-06-16 22:14 ` neil.n.carlson at gmail dot com
2011-06-16 22:18 ` neil.n.carlson at gmail dot com
2013-01-10 15:46 ` janus at gcc dot gnu.org
2013-01-10 16:07 ` janus at gcc dot gnu.org
2013-01-10 20:40 ` janus at gcc dot gnu.org
2013-01-11 12:04 ` janus at gcc dot gnu.org
2013-08-05  9:08 ` janus at gcc dot gnu.org
2013-08-05  9:22 ` janus at gcc dot gnu.org
2013-08-05 11:14 ` janus at gcc dot gnu.org
2013-08-06  8:42 ` janus at gcc dot gnu.org
2013-08-06  9:13 ` janus at gcc dot gnu.org
2013-08-06 10:50 ` janus at gcc dot gnu.org
2013-08-08 16:54 ` dominiq at lps dot ens.fr
2013-08-11 17:03 ` dominiq at lps dot ens.fr
2015-01-24 11:52 ` dominiq at lps dot ens.fr
2015-01-24 16:32 ` dominiq at lps dot ens.fr
2015-01-24 19:05 ` janus at gcc dot gnu.org
2015-02-05  8:09 ` pault at gcc dot gnu.org
2020-03-12 11:58 ` jakub at gcc dot gnu.org
2021-04-16 20:03 ` vladimir.fuka at gmail dot com
2021-06-01  8:05 ` rguenth at gcc dot gnu.org
2022-05-27  9:12 ` rguenth at gcc dot gnu.org
2023-06-22 16:45 ` pault at gcc dot gnu.org
2023-06-28 11:39 ` cvs-commit at gcc dot gnu.org
2023-10-31  8:23 ` pault at gcc dot gnu.org
2023-10-31  8:24 ` pault at gcc dot gnu.org
2023-10-31  8:29 ` pault at gcc dot gnu.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).