Daily bump.
[gcc-git-mirror.git] / libgomp / testsuite / libgomp.fortran / allocate-5.f90
blobde9cd5a302e7f1df00d5a29204fcaf1084b13778
1 ! { dg-additional-options "-fdump-tree-gimple" }
3 ! { dg-final { scan-tree-dump-times "__builtin_GOMP_alloc \\(" 5 "gimple" } }
4 ! { dg-final { scan-tree-dump-times "__builtin_GOMP_free \\(" 5 "gimple" } }
7 module m
8 use omp_lib
9 use iso_c_binding
10 implicit none (type, external)
11 integer(c_intptr_t) :: intptr
12 contains
14 integer function one ()
15 integer :: sum, i
16 !$omp allocate(sum)
17 ! { dg-final { scan-tree-dump-times "sum\\.\[0-9\]+ = __builtin_GOMP_alloc \\(4, 4, 0B\\);" 1 "gimple" } }
18 ! { dg-final { scan-tree-dump-times "__builtin_GOMP_free \\(sum\\.\[0-9\]+, 0B\\);" 1 "gimple" } }
20 ! NOTE: Initializer cannot be omp_init_allocator - as 'A' is
21 ! in the same scope and the auto-omp_free comes later than
22 ! any omp_destroy_allocator.
23 integer(omp_allocator_handle_kind) :: my_allocator = omp_low_lat_mem_alloc
24 integer :: n = 25
25 sum = 0
26 block
27 type(omp_alloctrait) :: traits(1) = [ omp_alloctrait(omp_atk_alignment, 64) ]
28 integer :: A(n)
29 !$omp allocate(A) align(128) allocator(my_allocator)
30 ! { dg-final { scan-tree-dump-times "a = __builtin_GOMP_alloc \\(128, D\\.\[0-9\]+, D\\.\[0-9\]+\\);" 1 "gimple" } }
31 ! { dg-final { scan-tree-dump-times "__builtin_GOMP_free \\(a, 0B\\);" 1 "gimple" } }
33 if (mod (transfer(loc(A), intptr), 128_c_intptr_t) /= 0) &
34 stop 2
35 do i = 1, n
36 A(i) = i
37 end do
39 my_allocator = omp_init_allocator(omp_low_lat_mem_space,1,traits)
40 block
41 integer B(n)
42 integer C(5)
43 !$omp allocate(B,C) allocator(my_allocator)
44 ! { dg-final { scan-tree-dump-times "b = __builtin_GOMP_alloc \\(\[0-9\]+, D\\.\[0-9\]+, D\\.\[0-9\]+\\);" 1 "gimple" } }
45 ! { dg-final { scan-tree-dump-times "c\\.\[0-9\]+ = __builtin_GOMP_alloc \\(\[0-9\]+, 20, D\\.\[0-9\]+\\);" 1 "gimple" } }
46 ! { dg-final { scan-tree-dump-times "__builtin_GOMP_free \\(b, 0B\\);" 1 "gimple" } }
47 ! { dg-final { scan-tree-dump-times "__builtin_GOMP_free \\(c\\.\[0-9\]+, 0B\\);" 1 "gimple" } }
49 integer :: D(5)
50 !$omp allocate(D) align(256)
51 ! { dg-final { scan-tree-dump-times "d\\.\[0-9\]+ = __builtin_GOMP_alloc \\(256, 20, 0B\\);" 1 "gimple" } }
52 ! { dg-final { scan-tree-dump-times "__builtin_GOMP_free \\(d\\.\[0-9\]+, 0B\\);" 1 "gimple" } }
54 B = 0
55 C = [1,2,3,4,5]
56 D = [11,22,33,44,55]
58 if (mod (transfer(loc(B), intptr), 64_c_intptr_t) /= 0) &
59 stop 3
60 if (mod (transfer(loc(C), intptr), 64_c_intptr_t) /= 0) &
61 stop 4
62 if (mod (transfer(loc(D), intptr), 256_c_intptr_t) /= 0) &
63 stop 5
65 do i = 1, 5
66 if (C(i) /= i) &
67 stop 6
68 if (D(i) /= i + 10*i) &
69 stop 7
70 end do
72 do i = 1, n
73 if (B(i) /= 0) &
74 stop 9
75 sum = sum + A(i)+B(i)+C(mod(i,5)+1)+D(mod(i,5)+1)
76 end do
77 end block
78 call omp_destroy_allocator (my_allocator)
79 end block
80 one = sum
81 end
82 end module
84 use m
85 if (one () /= 1225) &
86 stop 1
87 end