* tree-loop-distribution.c (struct partition): New field recording
[official-gcc.git] / gcc / testsuite / gfortran.dg / alloc_comp_assign_13.f08
blobfe697908a2dac780a3fc801ea34f9c2e3df52b71
1 ! { dg-do run }
2 ! Test for allocatable scalar components and deferred length char arrays.
3 ! Check that fix for pr60357 works.
4 ! Contributed by Antony Lewis <antony@cosmologist.info> and
5 !                Andre Vehreschild <vehre@gmx.de>
7 program test_allocatable_components
8     Type A
9         integer :: X
10         integer, allocatable :: y
11         character(len=:), allocatable :: c
12     end type A
13     Type(A) :: Me
14     Type(A) :: Ea
16     Me= A(X= 1, Y= 2, C="correctly allocated")
18     if (Me%X /= 1) call abort()
19     if (.not. allocated(Me%y) .or. Me%y /= 2) call abort()
20     if (.not. allocated(Me%c)) call abort()
21     if (len(Me%c) /= 19) call abort()
22     if (Me%c /= "correctly allocated") call abort()
24     ! Now check explicitly allocated components.
25     Ea%X = 9
26     allocate(Ea%y)
27     Ea%y = 42
28     ! Implicit allocate on assign in the next line
29     Ea%c = "13 characters"
31     if (Ea%X /= 9) call abort()
32     if (.not. allocated(Ea%y) .or. Ea%y /= 42) call abort()
33     if (.not. allocated(Ea%c)) call abort()
34     if (len(Ea%c) /= 13) call abort()
35     if (Ea%c /= "13 characters") call abort()
37     deallocate(Ea%y)
38     deallocate(Ea%c)
39     if (allocated(Ea%y)) call abort()
40     if (allocated(Ea%c)) call abort()
41 end program
43 ! vim:ts=4:sts=4:sw=4: