Fix gcc.c-torture/execute/ieee/cdivchkf.c on hpux
[official-gcc.git] / libgomp / testsuite / libgomp.fortran / allocators-4.f90
blob12689ea41ac0fcf9b822bb083fb0189072fed6b0
1 ! { dg-additional-options "-fopenmp-allocators" }
2 module m
3 implicit none
4 type t
5 integer, allocatable :: Acomp, Bcomp(:)
6 class(*), allocatable :: Ccomp, Dcomp(:)
7 end type t
8 contains
10 subroutine intout(c,d,e,f)
11 implicit none
12 class(t), intent(out) :: c,d(4)
13 class(t), allocatable, intent(out) :: e,f(:)
14 end
16 subroutine q(c,d,e,f)
17 implicit none
18 class(t) :: c,d(4)
19 class(t), allocatable :: e,f(:)
20 call intout(c,d,e,f)
21 end subroutine q
23 subroutine s
24 implicit none
25 type(t) :: xx
26 class(t), allocatable :: yy
27 integer :: i, iiiiii
28 i = 4
29 !$omp allocate
30 allocate(xx%Acomp, xx%Bcomp(4))
31 deallocate(xx%Acomp, xx%Bcomp)
33 !$omp allocate
34 allocate(integer :: xx%Ccomp, xx%Dcomp(4))
35 deallocate(xx%Ccomp, xx%Dcomp)
37 !$omp allocators allocate(yy)
38 allocate(t :: yy)
40 !$omp allocate
41 allocate(real :: xx%Ccomp, xx%Dcomp(4))
42 deallocate(xx%Ccomp, xx%Dcomp)
44 !$omp allocate
45 allocate(xx%Acomp, xx%Bcomp(4))
46 !$omp allocate
47 allocate(logical :: xx%Ccomp, xx%Dcomp(4))
49 iiiiii = 555
50 xx = t(1, [1,2])
51 end
53 end module
55 use m
56 call s
57 end