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" } }
10 implicit none (type, external)
11 integer(c_intptr_t
) :: intptr
14 integer function one ()
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
27 type(omp_alloctrait
) :: traits(1) = [ omp_alloctrait(omp_atk_alignment
, 64) ]
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) &
39 my_allocator
= omp_init_allocator(omp_low_lat_mem_space
,1,traits
)
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" } }
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" } }
58 if (mod (transfer(loc(B
), intptr
), 64_c_intptr_t
) /= 0) &
60 if (mod (transfer(loc(C
), intptr
), 64_c_intptr_t
) /= 0) &
62 if (mod (transfer(loc(D
), intptr
), 256_c_intptr_t
) /= 0) &
68 if (D(i
) /= i
+ 10*i
) &
75 sum
= sum
+ A(i
)+B(i
)+C(mod(i
,5)+1)+D(mod(i
,5)+1)
78 call omp_destroy_allocator (my_allocator
)