modula2: Simplify REAL/LONGREAL/SHORTREAL node creation.
[official-gcc.git] / gcc / testsuite / gfortran.dg / class_66.f90
blob8ca269b83b184a25758ab2a125ce16b9801b577c
1 ! { dg-do run }
3 ! Test the fix for PR78641 in which an ICE occured on assignment
4 ! of a class array constructor to a derived type array.
6 ! Contributed by Damian Rouson <damian@sourceryinstitute.org>
8 implicit none
9 type foo
10 integer :: i = 99
11 end type
12 type(foo) :: bar(4)
13 class(foo), allocatable :: barfoo
15 allocate(barfoo,source = f(11))
16 bar = [f(33), [f(22), barfoo], f(1)]
17 if (any (bar%i .ne. [33, 22, 11, 1])) STOP 1
18 deallocate (barfoo)
20 contains
22 function f(arg) result(foobar)
23 class(foo), allocatable :: foobar
24 integer :: arg
25 allocate(foobar,source = foo(arg))
26 end function
28 end program