RISC-V: Regenerate opt urls.
[official-gcc.git] / gcc / testsuite / gfortran.dg / used_dummy_types_2.f90
blobf12d2864d0b560953ed49f14d4418f6c67e582bc
1 ! { dg-do compile }
2 ! This tests that the fix for PR25391 also fixes PR20244. If
3 ! the USE mod1 in subroutine foo were deleted, the code would
4 ! compile fine. With the USE statement, the compiler would
5 ! make new TYPEs for T1 and T2 and bomb out in fold-convert.
6 ! This is a slightly more elaborate test than
7 ! used_dummy_types_1.f90 and came from the PR.
9 ! Contributed by Jakub Jelinek <jakubcc.gnu.org>
10 module mod1
11 type t1
12 real :: f1
13 end type t1
14 type t2
15 type(t1), pointer :: f2(:)
16 real, pointer :: f3(:,:)
17 end type t2
18 end module mod1
20 module mod2
21 use mod1
22 type(t1), pointer, save :: v(:)
23 contains
24 subroutine foo (x)
25 use mod1
26 implicit none
27 type(t2) :: x
28 integer :: d
29 d = size (x%f3, 2)
30 v = x%f2(:)
31 end subroutine foo
32 end module mod2