view gcc/testsuite/gfortran.dg/coarray_allocate_6.f08 @ 128:fe568345ddd5

fix CbC-example
author mir3636
date Wed, 11 Apr 2018 19:32:28 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do run }
! { dg-options "-fcoarray=single -fdump-tree-original" }

! Contributed by Tobias Burnus  <burnus@gcc.gnu.org>
! Test fix for pr65795.

implicit none

type t2
  integer, allocatable :: x
end type t2

type t3
  type(t2), allocatable :: caf[:]
end type t3

!type(t3), save, target :: c, d
type(t3), target :: c, d
integer :: stat

allocate(c%caf[*], stat=stat)
end

! Besides checking that the executable does not crash anymore, check
! that the cause has been remove.
! { dg-final { scan-tree-dump-not "c.caf.x = 0B" "original" } }