]> git.ipfire.org Git - thirdparty/binutils-gdb.git/blob - gdb/testsuite/gdb.fortran/dynamic-ptype-whatis.f90
Update copyright year range in header of all files managed by GDB
[thirdparty/binutils-gdb.git] / gdb / testsuite / gdb.fortran / dynamic-ptype-whatis.f90
1 ! Copyright 2021-2023 Free Software Foundation, Inc.
2 !
3 ! This program is free software; you can redistribute it and/or modify
4 ! it under the terms of the GNU General Public License as published by
5 ! the Free Software Foundation; either version 3 of the License, or
6 ! (at your option) any later version.
7 !
8 ! This program is distributed in the hope that it will be useful,
9 ! but WITHOUT ANY WARRANTY; without even the implied warranty of
10 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
11 ! GNU General Public License for more details.
12 !
13 ! You should have received a copy of the GNU General Public License
14 ! along with this program. If not, see <http://www.gnu.org/licenses/>.
15
16 program main
17
18 ! A non-dynamic type.
19 type type1
20 integer(kind=4) :: spacer
21 integer(kind=4) t1_i
22 end type type1
23
24 ! A first dynamic type. The array is of a static type.
25 type type2
26 integer(kind=4) :: spacer
27 type(type1), allocatable :: t2_array(:)
28 end type type2
29
30 ! Another dynamic type, the array is again a static type.
31 type type3
32 integer(kind=4) :: spacer
33 type(type1), pointer :: t3_array(:)
34 end type type3
35
36 ! A dynamic type, this time the array contains a dynamic type.
37 type type4
38 integer(kind=4) :: spacer
39 type(type2), allocatable :: t4_array(:)
40 end type type4
41
42 ! A static type, the array though contains dynamic types.
43 type type5
44 integer(kind=4) :: spacer
45 type(type2) :: t5_array (4)
46 end type type5
47
48 ! A static type containing pointers to a type that contains a
49 ! dynamic array.
50 type type6
51 type(type2), pointer :: ptr_1
52 type(type2), pointer :: ptr_2
53 end type type6
54
55 real, dimension(:), pointer :: var1
56 real, dimension(:), allocatable :: var2
57 type(type1) :: var3
58 type(type2), target :: var4
59 type(type3) :: var5
60 type(type4) :: var6
61 type(type5) :: var7
62 type(type6) :: var8
63
64 allocate (var1 (3))
65
66 allocate (var2 (4))
67
68 allocate (var4%t2_array(3))
69
70 allocate (var5%t3_array(3))
71
72 allocate (var6%t4_array(3))
73 allocate (var6%t4_array(1)%t2_array(2))
74 allocate (var6%t4_array(2)%t2_array(5))
75 allocate (var6%t4_array(3)%t2_array(4))
76
77 allocate (var7%t5_array(1)%t2_array(2))
78 allocate (var7%t5_array(2)%t2_array(5))
79 allocate (var7%t5_array(3)%t2_array(4))
80 allocate (var7%t5_array(4)%t2_array(1))
81
82 var8%ptr_1 => var4
83 var8%ptr_2 => var4
84
85 print *, var1 ! Break Here
86 print *, var2
87 print *, var3
88 print *, var4%t2_array(1)
89 print *, var5%t3_array(2)
90 print *, var6%t4_array(1)%t2_array(1)
91 print *, var7%t5_array(1)%t2_array(1)
92
93 end program main