nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / intent_out_14.f90
blobe59946350086916cee36d307ddaf18ba7aca2e6c
1 ! { dg-do run }
2 ! PR fortran/102287 - optional allocatable DT array arguments (intent out)
4 module m
5 type t
6 integer, allocatable :: a
7 end type t
8 contains
9 subroutine a (x, v)
10 type(t), optional, allocatable, intent(out) :: x(:)
11 type(t), optional, intent(out) :: v(:)
12 call b (x, v)
13 end subroutine a
15 subroutine b (y, w)
16 type(t), optional, allocatable, intent(out) :: y(:)
17 type(t), optional, intent(out) :: w(:)
18 end subroutine b
19 end module m
21 program p
22 use m
23 call a ()
24 end