public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs
@ 2012-12-20 16:18 burnus at gcc dot gnu.org
  2012-12-20 16:30 ` [Bug fortran/55763] " burnus at gcc dot gnu.org
                   ` (23 more replies)
  0 siblings, 24 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-12-20 16:18 UTC (permalink / raw)
  To: gcc-bugs


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

             Bug #: 55763
           Summary: Issues with some simpler CLASS(*) programs
    Classification: Unclassified
           Product: gcc
           Version: 4.8.0
            Status: UNCONFIRMED
          Keywords: ice-on-valid-code, rejects-valid
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: burnus@gcc.gnu.org
                CC: pault@gcc.gnu.org


There are some known bigger issues of CLASS(*) which are tracked elsewhere.

This is about simpler issues.



The following program by Reinhold Bader fails with a bogus:

  type is (integer)
           1
alloc_scalar_01_pos.f90:27.15:

  class default
               2
Error: The DEFAULT CASE at (1) cannot be followed by a second DEFAULT CASE at
(2)

!----------------------------
module mod_alloc_scalar_01
contains
  subroutine construct(this)
    class(*), allocatable, intent(out) :: this
    integer :: this_i
    this_i = 4
    allocate(this, source=this_i)
  end subroutine
end module

program alloc_scalar_01
  use mod_alloc_scalar_01
  implicit none
  class(*), allocatable :: mystuff

  call construct(mystuff)
  call construct(mystuff)

  select type(mystuff)
  type is (integer)
    if (mystuff == 4) then
      write(*,*) 'OK'
    else 
      write(*,*) 'FAIL 1'
    end if
  class default
    write(*,*) 'FAIL 2'
  end select
end program
!----------------------------


While the following program by the same author causes an ICE (segmentation
fault) at 

0x5573ac get_unique_type_string
        ../../gcc/fortran/class.c:447
0x557ef8 get_unique_hashed_string
        ../../gcc/fortran/class.c:470
0x558087 gfc_find_derived_vtab(gfc_symbol*)
        ../../gcc/fortran/class.c:1833
0x625d18 gfc_conv_procedure_call(gfc_se*, gfc_symbol*, gfc_actual_arglist*,
gfc_expr*, vec<tree_node*, va_gc, vl_embed>*)
        ../../gcc/fortran/trans-expr.c:4308


!----------------------------
module mod_alloc_scalar_02
contains
  subroutine construct(this)
    class(*), allocatable, intent(out) :: this
    integer :: this_i
    this_i = 4
    allocate(this, source=this_i)
  end subroutine
  subroutine out(this)
    class(*) :: this
    select type(this)
    type is (integer)
      if (this == 4) then
        write(*,*) 'OK'
      else 
        write(*,*) 'FAIL 1'
      end if
    class default
      write(*,*) 'FAIL 2'
    end select
  end subroutine
end module

program alloc_scalar_02
  use mod_alloc_scalar_02
  implicit none
  class(*), allocatable :: mystuff

  call construct(mystuff)
  call out(mystuff)
end program
!----------------------------



And the following MOVE_ALLOC code, which moves TYPE(integer) to CLASS(*) fails
with:

  call move_alloc(i2, i1)
                      1
Error: The FROM and TO arguments of the MOVE_ALLOC intrinsic at (1) must be of
the same kind 4/0

!----------------------------
program mvall_03
  implicit none
  integer, parameter :: n1 = 100, n2 = 200
  class(*), allocatable :: i1(:)
  integer, allocatable :: i2(:)

  allocate(real :: i1(n1))
  allocate(i2(n2))
  i2 = 2
  call move_alloc(i2, i1)
  if (size(i1) /= n2 .or. allocated(i2)) then
     write(*,*) 'FAIL'
  else
     write(*,*) 'OK'
  end if
end program
!----------------------------



And finally, the following program - again by Reinhold Bader - gives an ICE
(segfault) at
             vector_comp => field

0x62d477 gfc_trans_pointer_assignment(gfc_expr*, gfc_expr*)
        ../../gcc/fortran/trans-expr.c:6523

!----------------------------
  program change_field_type
    use, intrinsic :: iso_c_binding
    implicit none
    TYPE, BIND(C) :: scalar_vector
       REAL(kind=c_float) :: scalar
       REAL(kind=c_float) :: vec(3)
    END TYPE
    TYPE, BIND(C) :: scalar_vector_matrix
       REAL(kind=c_float) :: scalar
       REAL(kind=c_float) :: vec(3)
       REAL(kind=c_float) :: mat(3,3)
    END TYPE
    CLASS(*), ALLOCATABLE, TARGET :: one_d_field(:)
    real, pointer :: v1(:)

    allocate(one_d_field(3), &
             source = (/ scalar_vector( 1.0, (/ -1.0, 0.0, 1.0 /) ), &
                         scalar_vector( 1.1, (/ -1.2, 0.2, 0.9 /) ), &
                         scalar_vector( 1.2, (/ -1.4, 0.4, 0.8 /) )  /) )

    call extract_vec(one_d_field, 1, v1, 2)
    print *, v1
    deallocate(one_d_field)   ! v1 becomes undefined

    allocate(one_d_field(1), &
         source = (/ scalar_vector_matrix( 1.0, (/ -1.0, 0.0, 1.0 /), &
         reshape( (/ 1.0, 0.0, 0.0, 0.0, 1.0, 0.0, 0.0, 0.0, 1.0 /), &
                 (/3, 3/) ) ) /) )

    call extract_vec(one_d_field, 2, v1, 1)
    print *, v1
    deallocate(one_d_field)   ! v1 becomes undefined
  contains
    subroutine extract_vec(field, tag, vector_comp, ic) 
        use, intrinsic :: iso_c_binding
        CLASS(*), TARGET :: field(:)
        REAL(kind=c_float), POINTER :: vector_comp(:)
        INTEGER(kind=c_int), value :: tag, ic

        type(scalar_vector), pointer :: sv(:)
        type(scalar_vector_matrix), pointer :: svm(:)

        select type (field)
        type is (real(c_float))
          vector_comp => field
        class default
          select case (tag)
          case (1)
             sv => field
             vector_comp => sv(:)%vec(ic)
          case (2)
             svm => field
             vector_comp => svm(:)%vec(ic)
          end select
        end select
    end subroutine
  end program
!----------------------------


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
@ 2012-12-20 16:30 ` burnus at gcc dot gnu.org
  2012-12-21 14:29 ` pault at gcc dot gnu.org
                   ` (22 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-12-20 16:30 UTC (permalink / raw)
  To: gcc-bugs


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

Tobias Burnus <burnus at gcc dot gnu.org> changed:

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

--- Comment #1 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-12-20 16:30:23 UTC ---
Another follow up: The following code causes an ICE (segfault):

0x5989bc select_type_set_tmp
        ../../gcc/fortran/match.c:5299
0x5a0015 gfc_match_type_is()
        ../../gcc/fortran/match.c:5556


If one changes the commented lines, one gets the bogus error message:

    type is (integer)
                     1
Error: Assumed shape array at (1) must be a dummy argument


!----------------------------
module mpi_f08_f
  implicit none
  abstract interface
    subroutine user_function( inoutvec )
      class(*), dimension(:), intent(inout) :: inoutvec
    end subroutine user_function
  end interface
end module

module mod_test
  use mpi_f08_f
  implicit none
contains
  subroutine my_function( invec )   ! <<< ICE
!   subroutine my_function( inoutvec )  ! <<< BOGUS ERROR
    class(*), dimension(:), intent(inout) :: inoutvec

    select type (inoutvec)
    type is (integer)
         inoutvec = 2*inoutvec
    end select
  end subroutine my_function
end module
!----------------------------


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
  2012-12-20 16:30 ` [Bug fortran/55763] " burnus at gcc dot gnu.org
@ 2012-12-21 14:29 ` pault at gcc dot gnu.org
  2012-12-21 14:32 ` pault at gcc dot gnu.org
                   ` (21 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: pault at gcc dot gnu.org @ 2012-12-21 14:29 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #2 from Paul Thomas <pault at gcc dot gnu.org> 2012-12-21 14:29:40 UTC ---
Author: pault
Date: Fri Dec 21 14:29:34 2012
New Revision: 194663

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=194663
Log:
2012-12-21  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/55763
    * match.c (select_type_set_tmp): Return is a derived type or
    class typespec has no derived type.
    * resolve.c (resolve_fl_var_and_proc): Exclude select type
    temporaries from 'pointer'.
    (resolve_symbol): Exclude select type temporaries from tests
    for assumed size and assumed rank.

2012-12-21  Paul Thomas  <pault@gcc.gnu.org>

    PR fortran/55763
    * gfortran.dg/unlimited_polymorphic_4.f03: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/unlimited_polymorphic_4.f03
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/match.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/testsuite/ChangeLog


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
  2012-12-20 16:30 ` [Bug fortran/55763] " burnus at gcc dot gnu.org
  2012-12-21 14:29 ` pault at gcc dot gnu.org
@ 2012-12-21 14:32 ` pault at gcc dot gnu.org
  2012-12-21 14:43 ` burnus at gcc dot gnu.org
                   ` (20 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: pault at gcc dot gnu.org @ 2012-12-21 14:32 UTC (permalink / raw)
  To: gcc-bugs


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

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

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

--- Comment #3 from Paul Thomas <pault at gcc dot gnu.org> 2012-12-21 14:32:07 UTC ---
Fixed on trunk... and blow me if I did not remember to attribute the testcase
properly.  Blast!

Paul


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (2 preceding siblings ...)
  2012-12-21 14:32 ` pault at gcc dot gnu.org
@ 2012-12-21 14:43 ` burnus at gcc dot gnu.org
  2012-12-21 16:52 ` pault at gcc dot gnu.org
                   ` (19 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-12-21 14:43 UTC (permalink / raw)
  To: gcc-bugs


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

Tobias Burnus <burnus at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|RESOLVED                    |NEW
   Last reconfirmed|                            |2012-12-21
         Resolution|FIXED                       |
     Ever Confirmed|0                           |1

--- Comment #4 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-12-21 14:42:56 UTC ---
REOPEN. 'Only' the two issues of the follow up (comment 1) are fixed. None of
the 4 issues of comment 0. (Additionally MOVE_ALLOC for two CLASS(*) variables
fails, which I hadn't tested before.)


(In reply to comment #3)
> Fixed on trunk...
Thanks for fixing the issues quickly!

> blow me if I did not remember to attribute the testcase properly.  Blast!
Well, you have still the chance to do so for the other test cases ;-)


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (3 preceding siblings ...)
  2012-12-21 14:43 ` burnus at gcc dot gnu.org
@ 2012-12-21 16:52 ` pault at gcc dot gnu.org
  2012-12-21 22:59 ` burnus at gcc dot gnu.org
                   ` (18 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: pault at gcc dot gnu.org @ 2012-12-21 16:52 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #5 from Paul Thomas <pault at gcc dot gnu.org> 2012-12-21 16:51:41 UTC ---
Sorry, I didn't look down the PR - I thought that we were just at the stage of
your opening email :-(

Paul


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (4 preceding siblings ...)
  2012-12-21 16:52 ` pault at gcc dot gnu.org
@ 2012-12-21 22:59 ` burnus at gcc dot gnu.org
  2012-12-22 17:27 ` burnus at gcc dot gnu.org
                   ` (17 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-12-21 22:59 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #6 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-12-21 22:59:27 UTC ---
To the last test case of comment 0:

> gives an ICE (segfault) at
>              vector_comp => field
> 
> 0x62d477 gfc_trans_pointer_assignment(gfc_expr*, gfc_expr*)
>         ../../gcc/fortran/trans-expr.c:6523

The problem is that the LHS is:
  expr1->symtree->n.sym->attr.subref_array_pointer

The ICE occurs for:
              gfc_add_modify (&lse.post, GFC_DECL_SPAN(decl), tmp);

The problem is that DECL_LANG_SPECIFIC(decl) is NULL; hence,
DECL_LANG_SPECIFIC(decl)->span causes the ICE.

In principle, gfc_get_symbol_decl takes care of that. However, as the symbol is
a dummy argument, the backend_decl is already set and gfc_get_symbol_decl
returns early.


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (5 preceding siblings ...)
  2012-12-21 22:59 ` burnus at gcc dot gnu.org
@ 2012-12-22 17:27 ` burnus at gcc dot gnu.org
  2012-12-28 11:22 ` burnus at gcc dot gnu.org
                   ` (16 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-12-22 17:27 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #7 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-12-22 17:27:06 UTC ---
Author: burnus
Date: Sat Dec 22 17:27:03 2012
New Revision: 194696

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=194696
Log:
2012-12-21  Tobias Burnus  <burnus@net-b.de>

        PR fortran/55763
        * module.c (mio_component): Don't skip _hash's initializer.
        * resolve.c (resolve_select_type): Add an assert.
        * trans-expr.c (gfc_conv_procedure_call): Handle
        INTENT(OUT) for UNLIMIT_POLY.

2012-12-21  Tobias Burnus  <burnus@net-b.de>

        PR fortran/55763
        * gfortran.dg/unlimited_polymorphic_6.f90: New.


Added:
    trunk/gcc/testsuite/gfortran.dg/unlimited_polymorphic_6.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/module.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/testsuite/ChangeLog


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (6 preceding siblings ...)
  2012-12-22 17:27 ` burnus at gcc dot gnu.org
@ 2012-12-28 11:22 ` burnus at gcc dot gnu.org
  2012-12-28 12:26 ` burnus at gcc dot gnu.org
                   ` (15 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-12-28 11:22 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #8 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-12-28 11:22:20 UTC ---
Author: burnus
Date: Fri Dec 28 11:22:14 2012
New Revision: 194743

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=194743
Log:
2012-12-28  Tobias Burnus  <burnus@net-b.de>

        PR fortran/55763
        * check.c (gfc_check_move_alloc): Handle unlimited polymorphic.
        * trans-intrinsic.c (conv_intrinsic_move_alloc): Ditto.

2012-12-28  Tobias Burnus  <burnus@net-b.de>

        PR fortran/55763
        * gfortran.dg/unlimited_polymorphic_5.f90


Added:
    trunk/gcc/testsuite/gfortran.dg/unlimited_polymorphic_5.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/check.c
    trunk/gcc/fortran/trans-intrinsic.c
    trunk/gcc/testsuite/ChangeLog


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (7 preceding siblings ...)
  2012-12-28 11:22 ` burnus at gcc dot gnu.org
@ 2012-12-28 12:26 ` burnus at gcc dot gnu.org
  2012-12-29 23:06 ` anlauf at gmx dot de
                   ` (14 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-12-28 12:26 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #9 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-12-28 12:26:15 UTC ---
I think all issues have been fixed, except for the sub-pointer issue, i.e. last
example of comment 0 - see also comment 6.


The following modified version of the last example of comment 0 also uses
sub-pointers, however, it compiles but produces the wrong result. I think one
should quickly check whether that's a bug in CLASS(*) or just a problem with
subpointers. - If the former, we should fix it, if the latter, we can regard
this as WONTFIX (before the new array descriptor) - and close this PR.


With gfortran, it prints:
   0.00000000       1.00000000       1.10000002    
  -1.00000000    
while with crayftn it prints:
 0.,  0.200000003,  0.400000006
 -1.


  program change_field_type
    use, intrinsic :: iso_c_binding
    implicit none
    REAL(kind=c_float), POINTER :: vector_comp(:)
    TYPE, BIND(C) :: scalar_vector
       REAL(kind=c_float) :: scalar
       REAL(kind=c_float) :: vec(3)
    END TYPE
    TYPE, BIND(C) :: scalar_vector_matrix
       REAL(kind=c_float) :: scalar
       REAL(kind=c_float) :: vec(3)
       REAL(kind=c_float) :: mat(3,3)
    END TYPE
    CLASS(*), ALLOCATABLE, TARGET :: one_d_field(:)
    real, pointer :: v1(:)

    allocate(one_d_field(3), &
             source = (/ scalar_vector( 1.0, (/ -1.0, 0.0, 1.0 /) ), &
                         scalar_vector( 1.1, (/ -1.2, 0.2, 0.9 /) ), &
                         scalar_vector( 1.2, (/ -1.4, 0.4, 0.8 /) )  /) )

    call extract_vec(one_d_field, 1, 2)
    print *, vector_comp
    deallocate(one_d_field)   ! v1 becomes undefined

    allocate(one_d_field(1), &
         source = (/ scalar_vector_matrix( 1.0, (/ -1.0, 0.0, 1.0 /), &
         reshape( (/ 1.0, 0.0, 0.0, 0.0, 1.0, 0.0, 0.0, 0.0, 1.0 /), &
                 (/3, 3/) ) ) /) )

    call extract_vec(one_d_field, 2, 1)
    print *, vector_comp
    deallocate(one_d_field)   ! v1 becomes undefined
  contains
    subroutine extract_vec(field, tag, ic)
        use, intrinsic :: iso_c_binding
        CLASS(*), TARGET :: field(:)
        INTEGER(kind=c_int), value :: tag, ic

        type(scalar_vector), pointer :: sv(:)
        type(scalar_vector_matrix), pointer :: svm(:)

        select type (field)
        type is (real(c_float))
          vector_comp => field
        class default
          select case (tag)
          case (1)
             sv => field
             vector_comp => sv(:)%vec(ic)
          case (2)
             svm => field
             vector_comp => svm(:)%vec(ic)
          end select
        end select
    end subroutine
  end program


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (8 preceding siblings ...)
  2012-12-28 12:26 ` burnus at gcc dot gnu.org
@ 2012-12-29 23:06 ` anlauf at gmx dot de
  2013-01-01 14:09 ` burnus at gcc dot gnu.org
                   ` (13 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: anlauf at gmx dot de @ 2012-12-29 23:06 UTC (permalink / raw)
  To: gcc-bugs


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

Harald Anlauf <anlauf at gmx dot de> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |anlauf at gmx dot de

--- Comment #10 from Harald Anlauf <anlauf at gmx dot de> 2012-12-29 23:05:45 UTC ---
I have a simple case where CLASS(*) leads to an ICE.
If it doesn't fit here, please feel free to move it elsewhere.

module gfcbug121
  implicit none
  type myobj
     class(*), allocatable :: x
   contains
     procedure :: print
  end type myobj
contains
  subroutine print(this)
    class(myobj) :: this
  end subroutine print
end module gfcbug121

I get:
% gfc-trunk gfcbug121.f90 -c
f951: internal compiler error: Segmentation fault
0x8621590 crash_signal
        ../../trunk/gcc/toplev.c:334
0x8198ffb gfc_default_initializer(gfc_typespec*)
        ../../trunk/gcc/fortran/expr.c:3870
0x817ef24 gfc_find_intrinsic_vtab(gfc_typespec*)
        ../../trunk/gcc/fortran/class.c:2315
0x817f642 gfc_class_null_initializer(gfc_typespec*, gfc_expr*)
        ../../trunk/gcc/fortran/class.c:417
0x82639a0 gfc_conv_initializer(gfc_expr*, gfc_typespec*, tree_node*, bool,
bool, bool)
        ../../trunk/gcc/fortran/trans-expr.c:5665
0x825436e gfc_conv_structure(gfc_se*, gfc_expr*, int)
        ../../trunk/gcc/fortran/trans-expr.c:6132
0x826394d gfc_conv_initializer(gfc_expr*, gfc_typespec*, tree_node*, bool,
bool, bool)
        ../../trunk/gcc/fortran/trans-expr.c:5667
0x8248b8d gfc_get_symbol_decl(gfc_symbol*)
        ../../trunk/gcc/fortran/trans-decl.c:1494
0x8249d45 gfc_create_module_variable
        ../../trunk/gcc/fortran/trans-decl.c:4086
0x8249d45 gfc_create_module_variable
        ../../trunk/gcc/fortran/trans-decl.c:4016
0x82085e3 do_traverse_symtree
        ../../trunk/gcc/fortran/symbol.c:3451
0x8243e05 gfc_generate_module_vars(gfc_namespace*)
        ../../trunk/gcc/fortran/trans-decl.c:4485
0x8221232 gfc_generate_module_code(gfc_namespace*)
        ../../trunk/gcc/fortran/trans.c:1620
0x81dc72d translate_all_program_units
        ../../trunk/gcc/fortran/parse.c:4452
0x81dc72d gfc_parse_file()
        ../../trunk/gcc/fortran/parse.c:4679
0x821ba1f gfc_be_parse_file
        ../../trunk/gcc/fortran/f95-lang.c:191


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (9 preceding siblings ...)
  2012-12-29 23:06 ` anlauf at gmx dot de
@ 2013-01-01 14:09 ` burnus at gcc dot gnu.org
  2013-01-03 12:55 ` burnus at gcc dot gnu.org
                   ` (12 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-01-01 14:09 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #11 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-01-01 14:09:09 UTC ---
(In reply to comment #10)
> I have a simple case where CLASS(*) leads to an ICE.
> If it doesn't fit here, please feel free to move it elsewhere.

The segfault occurs for comp == "_extends" in gfc_default_initializer. The
problem is that  comp->ts.type  is BT_CLASS, which is not handled. As one has
CLASS(*), ts.u.derived == NULL, which breaks the following check:

      if (comp->attr.allocatable
          || (comp->ts.type == BT_CLASS && CLASS_DATA
(comp)->attr.allocatable))

>From class.c's gfc_find_intrinsic_vtab
              if (gfc_add_component (vtype, "_extends", &c) == FAILURE)
              ...
              /* Avoid segfaults because due to character length.   */
              c->ts.type = ts->type == BT_CHARACTER ? BT_VOID : ts->type;
              c->ts.kind = ts->kind;

Thus, either BT_CLASS shouldn't be used - or ts.u.derived has to be used.



By the way, class.c's gfc_find_derived_vtab uses the following if there is no
parent - or for unlimited polymorphic:
                  c->ts.type = BT_DERIVED;
                  c->ts.u.derived = vtype;
                  c->initializer = gfc_get_null_expr (NULL);


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (10 preceding siblings ...)
  2013-01-01 14:09 ` burnus at gcc dot gnu.org
@ 2013-01-03 12:55 ` burnus at gcc dot gnu.org
  2013-01-03 13:03 ` burnus at gcc dot gnu.org
                   ` (11 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-01-03 12:55 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #12 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-01-03 12:55:23 UTC ---
For another failure, see PR 55854.

(In reply to comment #10)
> I have a simple case where CLASS(*) leads to an ICE.
> If it doesn't fit here, please feel free to move it elsewhere.

Proposed patch:

--- a/gcc/fortran/class.c
+++ b/gcc/fortran/class.c
@@ -2227,3 +2227 @@ gfc_find_intrinsic_vtab (gfc_typespec *ts)
-             /* Avoid segfaults because due to character length.   */
-             c->ts.type = ts->type == BT_CHARACTER ? BT_VOID : ts->type;
-             c->ts.kind = ts->kind;
+             c->ts.type = BT_VOID;
@@ -2237,3 +2235 @@ gfc_find_intrinsic_vtab (gfc_typespec *ts)
-             /* Avoid segfaults due to missing character length.   */
-             c->ts.type = ts->type == BT_CHARACTER ? BT_VOID : ts->type;
-             c->ts.kind = ts->kind;
+             c->ts.type = ts->type = BT_VOID;


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (11 preceding siblings ...)
  2013-01-03 12:55 ` burnus at gcc dot gnu.org
@ 2013-01-03 13:03 ` burnus at gcc dot gnu.org
  2013-01-03 15:44 ` burnus at gcc dot gnu.org
                   ` (10 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-01-03 13:03 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #13 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-01-03 13:03:24 UTC ---
(In reply to comment #12)
> Proposed patch:

Which fails with
  gfc_typename(): Undefined type
for

contains
subroutine foo
 type t
 end type t
 class(*), allocatable :: x
 integer, target :: y
 x => y
end subroutine foo
end


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (12 preceding siblings ...)
  2013-01-03 13:03 ` burnus at gcc dot gnu.org
@ 2013-01-03 15:44 ` burnus at gcc dot gnu.org
  2013-01-03 16:54 ` burnus at gcc dot gnu.org
                   ` (9 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-01-03 15:44 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #14 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-01-03 15:44:24 UTC ---
(In reply to comment #12)
> +             c->ts.type = ts->type = BT_VOID;

Ups. The "ts->type =" has to be deleted to fix the failure of comment 13.

 * * *

The following valid code gives an ICE:

    type t
    end type t
    type(t), target :: x
    class(*), pointer :: ptr2 => x
    if (same_type_as (ptr2, x) .neqv. .TRUE.) call abort()
  end


 * * *

The following (currently used in gfortran.dg/unlimited_polymorphic_3.f03) is
invalid:
  class(*), pointer :: ptr2 => null(x)

C512 (R506) The function-reference shall be a reference to the intrinsic
function NULL with no arguments.


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (13 preceding siblings ...)
  2013-01-03 15:44 ` burnus at gcc dot gnu.org
@ 2013-01-03 16:54 ` burnus at gcc dot gnu.org
  2013-01-03 23:51 ` burnus at gcc dot gnu.org
                   ` (8 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-01-03 16:54 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #15 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-01-03 16:54:03 UTC ---
(In reply to comment #14)
>     type(t), target :: x
>     class(*), pointer :: ptr2 => x

TODO: Check whether that would be also valid if "x" is not SAVE (here it is as
"x" is in the main program) and whether one should reject a pointer as
data-target. (Cf. also PR51076, PR45290 and PR50410 comment 9.)


(In reply to comment #14)
> The following (currently used in gfortran.dg/unlimited_polymorphic_3.f03) is
> invalid:
>   class(*), pointer :: ptr2 => null(x)

Note that
  ptr => null(x)
is valid. In any case same_type_as (ptr,x) will be .false. as "ptr" has the
declared type (which doesn't exist) and "x" has a declared type. Presumably,
even same_type_as(ptr,ptr) would be false?!?


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (14 preceding siblings ...)
  2013-01-03 16:54 ` burnus at gcc dot gnu.org
@ 2013-01-03 23:51 ` burnus at gcc dot gnu.org
  2013-01-04  8:58 ` burnus at gcc dot gnu.org
                   ` (7 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-01-03 23:51 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #16 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-01-03 23:51:11 UTC ---
(In reply to comment #12)

The patch has been submitted:
http://gcc.gnu.org/ml/fortran/2013-01/msg00017.html


(In reply to comment #13)
> C512 (R506) The function-reference shall be a reference to the intrinsic
> function NULL with no arguments.

The patch has been submitted:
http://gcc.gnu.org/ml/fortran/2013-01/msg00020.html


> The following valid code gives an ICE:
>     class(*), pointer :: ptr2 => x

Patch for the checking part below. TODO: Fixing the ICE for both CLASS(t) and
CLASS(*).

--- a/gcc/fortran/expr.c
+++ b/gcc/fortran/expr.c
@@ -3765 +3765,4 @@ gfc_check_assign_symbol (gfc_symbol *sym,
-  if (sym->attr.pointer && rvalue->expr_type != EXPR_NULL)
+  if ((sym->attr.pointer
+       || (sym->ts.type == BT_CLASS && CLASS_DATA (sym)
+          && CLASS_DATA (sym)->attr.class_pointer))
+      && rvalue->expr_type != EXPR_NULL)
@@ -3772,2 +3775,2 @@ gfc_check_assign_symbol (gfc_symbol *sym, gfc_expr
-         gfc_error ("Pointer initialization target at %C "
-                    "must not be ALLOCATABLE ");
+         gfc_error ("Pointer initialization target at %L "
+                    "must not be ALLOCATABLE", &rvalue->where);
@@ -3778,2 +3781,2 @@ gfc_check_assign_symbol (gfc_symbol *sym, gfc_expr
-         gfc_error ("Pointer initialization target at %C "
-                    "must have the TARGET attribute");
+         gfc_error ("Pointer initialization target at %L "
+                    "must have the TARGET attribute", &rvalue->where);
@@ -3781,0 +3785,9 @@ gfc_check_assign_symbol (gfc_symbol *sym, gfc_expr
+
+      if (!attr.save && rvalue->expr_type == EXPR_VARIABLE
+         && rvalue->symtree->n.sym->ns->proc_name
+         && rvalue->symtree->n.sym->ns->proc_name->attr.is_main_program)
+       {
+         rvalue->symtree->n.sym->ns->proc_name->attr.save = SAVE_IMPLICIT;
+         attr.save = SAVE_IMPLICIT;
+       }
+
@@ -3784,2 +3796,2 @@ gfc_check_assign_symbol (gfc_symbol *sym, gfc_expr
-         gfc_error ("Pointer initialization target at %C "
-                    "must have the SAVE attribute");
+         gfc_error ("Pointer initialization target at %L "
+                    "must have the SAVE attribute", &rvalue->where);


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (15 preceding siblings ...)
  2013-01-03 23:51 ` burnus at gcc dot gnu.org
@ 2013-01-04  8:58 ` burnus at gcc dot gnu.org
  2013-01-04  9:00 ` burnus at gcc dot gnu.org
                   ` (6 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-01-04  8:58 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #17 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-01-04 08:58:05 UTC ---
Author: burnus
Date: Fri Jan  4 08:57:58 2013
New Revision: 194885

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=194885
Log:
2013-01-03  Tobias Burnus  <burnus@net-b.de>

        PR fortran/55854
        PR fortran/55763
        * class.c (gfc_class_null_initializer): Fix finding the vtab.
        (gfc_find_intrinsic_vtab): Use BT_VOID for some components.

2013-01-03  Tobias Burnus  <burnus@net-b.de>

        PR fortran/55854
        PR fortran/55763
        * gfortran.dg/unlimited_polymorphic_3.f03: Remove invalid code.
        * gfortran.dg/unlimited_polymorphic_7.f90: New.
        * gfortran.dg/unlimited_polymorphic_8.f90: New.


Added:
    trunk/gcc/testsuite/gfortran.dg/unlimited_polymorphic_7.f90
    trunk/gcc/testsuite/gfortran.dg/unlimited_polymorphic_8.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/class.c
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/testsuite/gfortran.dg/unlimited_polymorphic_3.f03


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (16 preceding siblings ...)
  2013-01-04  8:58 ` burnus at gcc dot gnu.org
@ 2013-01-04  9:00 ` burnus at gcc dot gnu.org
  2013-01-04 23:58 ` anlauf at gmx dot de
                   ` (5 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-01-04  9:00 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #18 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-01-04 08:59:53 UTC ---
Author: burnus
Date: Fri Jan  4 08:59:47 2013
New Revision: 194886

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=194886
Log:
2014-01-04  Tobias Burnus  <burnus@net-b.de>

        PR fortran/55763
        * decl.c (gfc_match_null): Parse and reject MOLD.

2014-01-04  Tobias Burnus  <burnus@net-b.de>

        PR fortran/55763
        * gfortran.dg/null_7.f90: New.


Added:
    trunk/gcc/testsuite/gfortran.dg/null_7.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/decl.c
    trunk/gcc/testsuite/ChangeLog


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (17 preceding siblings ...)
  2013-01-04  9:00 ` burnus at gcc dot gnu.org
@ 2013-01-04 23:58 ` anlauf at gmx dot de
  2013-01-05 13:12 ` anlauf at gmx dot de
                   ` (4 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: anlauf at gmx dot de @ 2013-01-04 23:58 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #19 from Harald Anlauf <anlauf at gmx dot de> 2013-01-04 23:57:40 UTC ---
(In reply to comment #17)
> Author: burnus
> Date: Fri Jan  4 08:57:58 2013
> New Revision: 194885

Great!  I extended the example from comment #10 to find:

module gfcbug122
  implicit none
  type myobj
     class(*), allocatable :: x
   contains
     procedure :: print
  end type myobj
contains
  subroutine print(this)
    class(myobj) :: this
    select type (this)
    type is (integer)
    type is (real)
    type is (complex)
    type is (character(len=*))
    end select
  end subroutine print
end module gfcbug122

gfcbug122.f90: In function 'print':
gfcbug122.f90:18:0: internal compiler error: in trans_associate_var, at
fortran/trans-stmt.c:1304
 end module gfcbug122
 ^
0x8289b53 trans_associate_var
        ../../trunk/gcc/fortran/trans-stmt.c:1304
0x8289b53 gfc_trans_block_construct(gfc_code*)
        ../../trunk/gcc/fortran/trans-stmt.c:1351
0x822197f trans_code
        ../../trunk/gcc/fortran/trans.c:1418
0x828df26 gfc_trans_integer_select
        ../../trunk/gcc/fortran/trans-stmt.c:1986
0x828df26 gfc_trans_select(gfc_code*)
        ../../trunk/gcc/fortran/trans-stmt.c:2480
0x8221997 trans_code
        ../../trunk/gcc/fortran/trans.c:1434
0x8289327 gfc_trans_block_construct(gfc_code*)
        ../../trunk/gcc/fortran/trans-stmt.c:1344
0x822197f trans_code
        ../../trunk/gcc/fortran/trans.c:1418
0x824d499 gfc_generate_function_code(gfc_namespace*)
        ../../trunk/gcc/fortran/trans-decl.c:5385
0x8222189 gfc_generate_module_code(gfc_namespace*)
        ../../trunk/gcc/fortran/trans.c:1646
0x81dd52d translate_all_program_units
        ../../trunk/gcc/fortran/parse.c:4452
0x81dd52d gfc_parse_file()
        ../../trunk/gcc/fortran/parse.c:4679
0x821c85f gfc_be_parse_file
        ../../trunk/gcc/fortran/f95-lang.c:191


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (18 preceding siblings ...)
  2013-01-04 23:58 ` anlauf at gmx dot de
@ 2013-01-05 13:12 ` anlauf at gmx dot de
  2013-01-06 15:34 ` burnus at gcc dot gnu.org
                   ` (3 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: anlauf at gmx dot de @ 2013-01-05 13:12 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #20 from Harald Anlauf <anlauf at gmx dot de> 2013-01-05 13:12:30 UTC ---
(In reply to comment #19)

Sorry for the invalid code:

>     select type (this)

should have been:

    select type (x => this% x)

which compiles (no ICE).

;-)


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (19 preceding siblings ...)
  2013-01-05 13:12 ` anlauf at gmx dot de
@ 2013-01-06 15:34 ` burnus at gcc dot gnu.org
  2013-01-07  8:36 ` burnus at gcc dot gnu.org
                   ` (2 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-01-06 15:34 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #21 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-01-06 15:33:24 UTC ---
(In reply to comment #6)
> To the last test case of comment 0:

I mentioned this example in the array-descriptor/subpointer PR 40737 to make
sure it is not forgotten.


(In reply to comment #14)
> The following valid code gives an ICE:
>     class(*), pointer :: ptr2 => x

That's now PR 55887. For the diagnostic part, see patch
http://gcc.gnu.org/ml/fortran/2013-01/msg00025.html


(In reply to comment #19)
> Great!  I extended the example from comment #10 to find:

>     class(myobj) :: this
>     select type (this)
>     type is (integer)


Thanks for reporting the ICE on invalid code; I submitted a patch for this at
http://gcc.gnu.org/ml/fortran/2013-01/msg00046.html


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (20 preceding siblings ...)
  2013-01-06 15:34 ` burnus at gcc dot gnu.org
@ 2013-01-07  8:36 ` burnus at gcc dot gnu.org
  2013-01-07 18:31 ` burnus at gcc dot gnu.org
  2013-01-07 18:37 ` burnus at gcc dot gnu.org
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-01-07  8:36 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #22 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-01-07 08:36:24 UTC ---
Author: burnus
Date: Mon Jan  7 08:36:16 2013
New Revision: 194962

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=194962
Log:
2012-01-07  Tobias Burnus  <burnus@net-b.de>

        PR fortran/55763
        * resolve.c (resolve_select_type): Reject intrinsic types for
        a non-unlimited-polymorphic selector.

2012-01-07  Tobias Burnus  <burnus@net-b.de>

        PR fortran/55763
        * gfortran.dg/select_type_32.f90: New.


Added:
    trunk/gcc/testsuite/gfortran.dg/select_type_32.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/resolve.c
    trunk/gcc/testsuite/ChangeLog


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (21 preceding siblings ...)
  2013-01-07  8:36 ` burnus at gcc dot gnu.org
@ 2013-01-07 18:31 ` burnus at gcc dot gnu.org
  2013-01-07 18:37 ` burnus at gcc dot gnu.org
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-01-07 18:31 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #23 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-01-07 18:30:25 UTC ---
Author: burnus
Date: Mon Jan  7 18:30:11 2013
New Revision: 194990

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=194990
Log:
2013-01-07  Tobias Burnus  <burnus@net-b.de>

        PR fortran/55763
        * gfortran.h (gfc_check_assign_symbol): Update prototype.
        * decl.c (add_init_expr_to_sym, do_parm): Update call.
        * expr.c (gfc_check_assign_symbol): Handle BT_CLASS and
        improve error location; support components.
        (gfc_check_pointer_assign): Handle component assignments.
        * resolve.c (resolve_fl_derived0): Call gfc_check_assign_symbol.
        (resolve_values): Update call.
        (resolve_structure_cons): Avoid double diagnostic.

2013-01-07  Tobias Burnus  <burnus@net-b.de>

        PR fortran/55763
        * gfortran.dg/pointer_init_2.f90: Update dg-error.
        * gfortran.dg/pointer_init_7.f90: New.


Added:
    trunk/gcc/testsuite/gfortran.dg/pointer_init_7.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/decl.c
    trunk/gcc/fortran/expr.c
    trunk/gcc/fortran/gfortran.h
    trunk/gcc/fortran/resolve.c
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/testsuite/gfortran.dg/pointer_init_2.f90


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

* [Bug fortran/55763] Issues with some simpler CLASS(*) programs
  2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
                   ` (22 preceding siblings ...)
  2013-01-07 18:31 ` burnus at gcc dot gnu.org
@ 2013-01-07 18:37 ` burnus at gcc dot gnu.org
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-01-07 18:37 UTC (permalink / raw)
  To: gcc-bugs


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

Tobias Burnus <burnus at gcc dot gnu.org> changed:

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

--- Comment #24 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-01-07 18:36:49 UTC ---
Close as FIXED. - Thanks to all bug-reporters/test-case providers.

All issues are now fixed - except for the issues mentioned in comment 21, which
are tracked elsewher. If you find a new bug, please fill a new PR.


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

end of thread, other threads:[~2013-01-07 18:37 UTC | newest]

Thread overview: 25+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2012-12-20 16:18 [Bug fortran/55763] New: Issues with some simpler CLASS(*) programs burnus at gcc dot gnu.org
2012-12-20 16:30 ` [Bug fortran/55763] " burnus at gcc dot gnu.org
2012-12-21 14:29 ` pault at gcc dot gnu.org
2012-12-21 14:32 ` pault at gcc dot gnu.org
2012-12-21 14:43 ` burnus at gcc dot gnu.org
2012-12-21 16:52 ` pault at gcc dot gnu.org
2012-12-21 22:59 ` burnus at gcc dot gnu.org
2012-12-22 17:27 ` burnus at gcc dot gnu.org
2012-12-28 11:22 ` burnus at gcc dot gnu.org
2012-12-28 12:26 ` burnus at gcc dot gnu.org
2012-12-29 23:06 ` anlauf at gmx dot de
2013-01-01 14:09 ` burnus at gcc dot gnu.org
2013-01-03 12:55 ` burnus at gcc dot gnu.org
2013-01-03 13:03 ` burnus at gcc dot gnu.org
2013-01-03 15:44 ` burnus at gcc dot gnu.org
2013-01-03 16:54 ` burnus at gcc dot gnu.org
2013-01-03 23:51 ` burnus at gcc dot gnu.org
2013-01-04  8:58 ` burnus at gcc dot gnu.org
2013-01-04  9:00 ` burnus at gcc dot gnu.org
2013-01-04 23:58 ` anlauf at gmx dot de
2013-01-05 13:12 ` anlauf at gmx dot de
2013-01-06 15:34 ` burnus at gcc dot gnu.org
2013-01-07  8:36 ` burnus at gcc dot gnu.org
2013-01-07 18:31 ` burnus at gcc dot gnu.org
2013-01-07 18:37 ` burnus 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).