1! { dg-additional-options "-Wall -Wextra" }
2program main
3  use omp_lib
4  use ISO_C_Binding
5  implicit none (external, type)
6  type(c_ptr) :: p
7  integer, pointer, contiguous :: ip(:)
8  type (omp_alloctrait) :: traits(3)
9  integer (omp_allocator_handle_kind) :: a
10  integer (c_ptrdiff_t) :: iptr
11
12  traits = [omp_alloctrait (omp_atk_alignment, 64), &
13            omp_alloctrait (omp_atk_fallback, omp_atv_null_fb), &
14            omp_alloctrait (omp_atk_sync_hint, omp_atv_serialized)]
15  a = omp_init_allocator (omp_default_mem_space, 3, traits)
16  if (a == omp_null_allocator) stop 1
17
18  p = omp_alloc (3 * c_sizeof (0), a)
19  if (.not. c_associated (p)) stop 2
20  call c_f_pointer (p, ip, [3])
21  if (mod (TRANSFER (p, iptr), 64) /= 0) &
22    stop 3
23  ip(1) = 1
24  ip(2) = 2
25  ip(3) = 3
26  call omp_free (p, a)
27  call omp_destroy_allocator (a)
28end program main
29