Update ChangeLog and version files for release
[official-gcc.git] / gcc / testsuite / gfortran.dg / alloc_comp_initializer_4.f03
blob66a5553dec43d4a21c57c6d8fb95bd0eed85a327
1 ! { dg-do run }
2 ! Fixed by the patch for PRs 60357 and 61275
4 ! Contributed by Stefan Mauerberger  <stefan.mauerberger@gmail.com>
6 PROGRAM main
7   IMPLICIT NONE
8   TYPE :: test_typ
9     REAL, ALLOCATABLE :: a
10   END TYPE
11   TYPE(test_typ) :: my_test_typ
12   my_test_typ = test_typ (a = 1.0)
13   if (abs (my_test_typ%a - 1.0) .gt. 1e-6) call abort
14 END PROGRAM main