diff mbox series

[OpenMP,Fortran] Fix trans-openmp.c, add use_device_addr run-time test case (has known issues with actual offloading)

Message ID 4a155db7-d761-824a-519e-f65463478325@codesourcery.com
State New
Headers show
Series [OpenMP,Fortran] Fix trans-openmp.c, add use_device_addr run-time test case (has known issues with actual offloading) | expand

Commit Message

Tobias Burnus Oct. 4, 2019, 1:54 p.m. UTC
This use_device_addr patch does:
* Add trivial but crucial missing change to "fortran/trans-openmp.c (Ups!)
* Add a comprehensive set of test cases (only scalars and 
non-array-descriptor arrays)

Remarks:

* The test cases are known to mishandle "cc/dd/ee/ff" (= scalars with 
allocatable + pointer attribute). That's only visible with actual 
offloading as with shared memory the errors cancel and it works.

* OpenMP spec: As the test case shows, "is_device_ptr" with 
"type(c_ptr), VALUE" would be nice; but OpenMP's spec for is_device_ptr 
only permits dummy arguments without VALUE attribute.

* Known shortcomings (omp-low.c implementation; not tested for): arrays 
with descriptor (alloctable/pointer arrays), absent optional variables, 
polymorphic variables. [For the first two, draft patches exist.]

Comments, esp. to the test case?

Tobias

PS: My next planned task is to fix the "scalars with allocatable + 
pointer attribute" issue revealed in this case.
diff mbox series

Patch

	gcc/fortran/
	* trans-openmp.c (gfc_trans_omp_clauses): Handle
	OMP_LIST_USE_DEVICE_ADDR.

	libgomp/
	* testsuite/libgomp.fortran/use_device_addr-1.f90: New.

diff --git a/gcc/fortran/trans-openmp.c b/gcc/fortran/trans-openmp.c
index f83bab4850e..35c2f280fb6 100644
--- a/gcc/fortran/trans-openmp.c
+++ b/gcc/fortran/trans-openmp.c
@@ -1887,6 +1887,9 @@  gfc_trans_omp_clauses (stmtblock_t *block, gfc_omp_clauses *clauses,
 	case OMP_LIST_USE_DEVICE_PTR:
 	  clause_code = OMP_CLAUSE_USE_DEVICE_PTR;
 	  goto add_clause;
+	case OMP_LIST_USE_DEVICE_ADDR:
+	  clause_code = OMP_CLAUSE_USE_DEVICE_ADDR;
+	  goto add_clause;
 	case OMP_LIST_IS_DEVICE_PTR:
 	  clause_code = OMP_CLAUSE_IS_DEVICE_PTR;
 	  goto add_clause;
diff --git a/libgomp/testsuite/libgomp.fortran/use_device_addr-1.f90 b/libgomp/testsuite/libgomp.fortran/use_device_addr-1.f90
new file mode 100644
index 00000000000..7a45c989ad5
--- /dev/null
+++ b/libgomp/testsuite/libgomp.fortran/use_device_addr-1.f90
@@ -0,0 +1,1196 @@ 
+! Comprehensive run-time test for use_device_addr
+!
+! Untested:
+! - arrays with array descriptor
+! - polymorphic variables
+! - absent optional arguments
+!
+module target_procs
+  use iso_c_binding
+  implicit none
+  private
+  public :: copy3_array, copy3_scalar
+contains
+  subroutine copy3_array_int(from_intptr, to_intptr, N)
+    !$omp declare target
+    !type(c_ptr), value :: from, to
+    integer(c_intptr_t), value :: from_intptr, to_intptr  ! VALUE issue, cf. copy3_array
+    type(c_ptr) :: from, to
+    integer, value :: N
+
+    real(c_double), pointer :: from_ptr(:)
+    real(c_double), pointer :: to_ptr(:)
+    integer :: i
+
+    from = transfer(from_intptr, mold=from)
+    to = transfer(to_intptr, mold=to)
+    call c_f_pointer(from, from_ptr, shape=[N])
+    call c_f_pointer(to, to_ptr, shape=[N])
+
+    !$omp parallel do
+    do i = 1, N
+      to_ptr(i) = 3 * from_ptr(i)
+    end do
+    !$omp end parallel do
+  end subroutine copy3_array_int
+
+  subroutine copy3_scalar_int(from_intptr, to_intptr)
+    !$omp declare target
+    !type(c_ptr), value :: from, to
+    integer(c_intptr_t), value :: from_intptr, to_intptr  ! VALUE issue, cf. copy3_array
+    type(c_ptr) :: from, to
+
+    real(c_double), pointer :: from_ptr
+    real(c_double), pointer :: to_ptr
+
+    from = transfer(from_intptr, mold=from)
+    to = transfer(to_intptr, mold=to)
+    call c_f_pointer(from, from_ptr)
+    call c_f_pointer(to, to_ptr)
+
+    to_ptr = 3 * from_ptr
+  end subroutine copy3_scalar_int
+
+
+  subroutine copy3_array(from, to, N)
+    type(c_ptr) :: from, to
+    integer, value :: N
+! [OpenMP issue:] Would like to use the following but it is not permitted due to VALUE.
+!     !$omp target is_device_ptr(from, to)
+!     call copy3_array_int(from, to, N)
+!     !$omp end target
+! Hence:
+    integer(c_intptr_t) :: from_intptr, to_intptr
+
+    from_intptr = transfer(from, mold=from_intptr)
+    to_intptr = transfer(to, mold=to_intptr)
+
+    !$omp target
+    call copy3_array_int(from_intptr, to_intptr, N)
+    !$omp end target
+  end subroutine copy3_array
+
+  subroutine copy3_scalar(from, to)
+    type(c_ptr), value :: from, to  ! VALUE issue, cf. copy3_array above
+    integer(c_intptr_t) :: from_intptr, to_intptr
+
+    from_intptr = transfer(from, mold=from_intptr)
+    to_intptr = transfer(to, mold=to_intptr)
+
+    !$omp target
+    call copy3_scalar_int(from_intptr, to_intptr)
+    !$omp end target
+  end subroutine copy3_scalar
+end module target_procs
+
+
+
+! Test local dummy arguments (w/o optional)
+module test_dummies
+  use iso_c_binding
+  use target_procs
+  implicit none
+  private
+  public :: test_dummy_call_1, test_dummy_call_2
+contains
+  subroutine test_dummy_call_1()
+     integer, parameter :: N = 1000
+    
+     ! scalars
+     real(c_double), target :: aa, bb
+     real(c_double), target, allocatable :: cc, dd
+     real(c_double), pointer :: ee, ff
+
+     ! non-descriptor arrays
+     real(c_double), target :: gg(N), hh(N)
+
+     allocate(cc, dd, ee, ff)
+
+     aa = 11.0_c_double
+     bb = 22.0_c_double
+     cc = 33.0_c_double
+     dd = 44.0_c_double
+     ee = 55.0_c_double
+     ff = 66.0_c_double
+     gg = 77.0_c_double
+     hh = 88.0_c_double
+
+     call test_dummy_callee_1(aa, bb, cc, dd, ee, ff, gg, hh, N)
+     deallocate(ee, ff) ! pointers, only
+  end subroutine test_dummy_call_1
+
+  subroutine test_dummy_callee_1(aa, bb, cc, dd, ee, ff, gg, hh, N)
+     ! scalars
+     real(c_double), target :: aa, bb
+     real(c_double), target, allocatable :: cc, dd
+     real(c_double), pointer :: ee, ff
+
+     ! non-descriptor arrays
+     real(c_double), target :: gg(N), hh(N)
+     integer, value :: N
+
+     !$omp target data map(to:aa) map(from:bb) use_device_addr(aa,bb)
+     call copy3_scalar(c_loc(aa), c_loc(bb))
+     !$omp end target data
+     if (abs(aa - 11.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+     !$omp target data map(to:cc) map(from:dd) use_device_addr(cc,dd)
+     call copy3_scalar(c_loc(cc), c_loc(dd))
+     !$omp end target data
+     if (abs(cc - 33.0_c_double) > 10.0_c_double * epsilon(cc)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(cc)) call abort()
+
+     !$omp target data map(to:ee) map(from:ff) use_device_addr(ee,ff)
+     call copy3_scalar(c_loc(ee), c_loc(ff))
+     !$omp end target data
+     if (abs(ee - 55.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ee)) call abort()
+
+
+     !$omp target data map(to:gg) map(from:hh) use_device_addr(gg,hh)
+     call copy3_array(c_loc(gg), c_loc(hh), N)
+     !$omp end target data
+     if (any(abs(gg - 77.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(gg))) call abort()
+  end subroutine test_dummy_callee_1
+
+  ! Save device ptr - and recall pointer
+  subroutine test_dummy_call_2()
+     integer, parameter :: N = 1000
+
+     ! scalars
+     real(c_double), target :: aa, bb
+     real(c_double), target, allocatable :: cc, dd
+     real(c_double), pointer :: ee, ff
+
+     ! non-descriptor arrays
+     real(c_double), target :: gg(N), hh(N)
+
+     type(c_ptr) :: c_aptr, c_bptr, c_cptr, c_dptr, c_eptr, c_fptr, c_gptr, c_hptr
+     real(c_double), pointer :: aptr, bptr, cptr, dptr, eptr, fptr
+     real(c_double), pointer :: gptr(:), hptr(:)
+
+     allocate(cc, dd, ee, ff)
+     call test_dummy_callee_2(aa, bb, cc, dd, ee, ff, gg, hh, &
+                               c_aptr, c_bptr, c_cptr, c_dptr, c_eptr, c_fptr, c_gptr, c_hptr, &
+                               aptr, bptr, cptr, dptr, eptr, fptr, gptr, hptr, &
+                               N)
+     deallocate(ee, ff)
+  end subroutine test_dummy_call_2
+
+  subroutine test_dummy_callee_2(aa, bb, cc, dd, ee, ff, gg, hh, &
+                                  c_aptr, c_bptr, c_cptr, c_dptr, c_eptr, c_fptr, c_gptr, c_hptr, &
+                                  aptr, bptr, cptr, dptr, eptr, fptr, gptr, hptr, &
+                                  N)
+     ! scalars
+     real(c_double), target :: aa, bb
+     real(c_double), target, allocatable :: cc, dd
+     real(c_double), pointer :: ee, ff
+
+     ! non-descriptor arrays
+     real(c_double), target :: gg(N), hh(N)
+
+     type(c_ptr) :: c_aptr, c_bptr, c_cptr, c_dptr, c_eptr, c_fptr, c_gptr, c_hptr
+     real(c_double), pointer :: aptr, bptr, cptr, dptr, eptr, fptr
+     real(c_double), pointer :: gptr(:), hptr(:)
+
+     integer, value :: N
+
+     real(c_double) :: dummy
+
+     aa = 111.0_c_double
+     bb = 222.0_c_double
+     cc = 333.0_c_double
+     dd = 444.0_c_double
+     ee = 555.0_c_double
+     ff = 666.0_c_double
+     gg = 777.0_c_double
+     hh = 888.0_c_double
+
+     !$omp target data map(to:aa) map(from:bb)
+     !$omp target data map(alloc:dummy) use_device_addr(aa,bb)
+     c_aptr = c_loc(aa)
+     c_bptr = c_loc(bb)
+     aptr => aa
+     bptr => bb
+     !$omp end target data
+
+     ! check c_loc ptr once
+     call copy3_scalar(c_aptr, c_bptr)
+     !$omp target update from(bb)
+     if (abs(aa - 111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+     ! check c_loc ptr again after target-value modification
+     aa = 1111.0_c_double
+     !$omp target update to(aa)
+     call copy3_scalar(c_aptr, c_bptr)
+     !$omp target update from(bb)
+     if (abs(aa - 1111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+     ! check Fortran pointer after target-value modification
+     aa = 11111.0_c_double
+     !$omp target update to(aa)
+     call copy3_scalar(c_loc(aptr), c_loc(bptr))
+     !$omp target update from(bb)
+     if (abs(aa - 11111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+     !$omp end target data
+
+     if (abs(aa - 11111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+
+     !$omp target data map(to:cc) map(from:dd)
+     !$omp target data map(alloc:dummy) use_device_addr(cc,dd)
+     c_cptr = c_loc(cc)
+     c_dptr = c_loc(dd)
+     cptr => cc
+     dptr => dd
+     !$omp end target data
+
+     ! check c_loc ptr once
+     call copy3_scalar(c_cptr, c_dptr)
+     !$omp target update from(dd)
+     if (abs(cc - 333.0_c_double) > 10.0_c_double * epsilon(cc)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(cc)) call abort()
+
+     ! check c_loc ptr again after target-value modification
+     cc = 3333.0_c_double
+     !$omp target update to(cc)
+     call copy3_scalar(c_cptr, c_dptr)
+     !$omp target update from(dd)
+     if (abs(cc - 3333.0_c_double) > 10.0_c_double * epsilon(cc)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(cc)) call abort()
+
+     ! check Fortran pointer after target-value modification
+     cc = 33333.0_c_double
+     !$omp target update to(cc)
+     call copy3_scalar(c_loc(cptr), c_loc(dptr))
+     !$omp target update from(dd)
+     if (abs(cc - 33333.0_c_double) > 10.0_c_double * epsilon(cc)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(cc)) call abort()
+     !$omp end target data
+
+     if (abs(cc - 33333.0_c_double) > 10.0_c_double * epsilon(dd)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(dd)) call abort()
+
+
+     !$omp target data map(to:ee) map(from:ff)
+     !$omp target data map(alloc:dummy) use_device_addr(ee,ff)
+     c_eptr = c_loc(ee)
+     c_fptr = c_loc(ff)
+     eptr => ee
+     fptr => ff
+     !$omp end target data
+
+     ! check c_loc ptr once
+     call copy3_scalar(c_eptr, c_fptr)
+     !$omp target update from(ff)
+     if (abs(ee - 555.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ee)) call abort()
+
+     ! check c_loc ptr again after target-value modification
+     ee = 5555.0_c_double
+     !$omp target update to(ee)
+     call copy3_scalar(c_eptr, c_fptr)
+     !$omp target update from(ff)
+     if (abs(ee - 5555.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ee)) call abort()
+
+     ! check Fortran pointer after target-value modification
+     ee = 55555.0_c_double
+     !$omp target update to(ee)
+     call copy3_scalar(c_loc(eptr), c_loc(fptr))
+     !$omp target update from(ff)
+     if (abs(ee - 55555.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ff)) call abort()
+     !$omp end target data
+
+     if (abs(ee - 55555.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ee)) call abort()
+
+
+     !$omp target data map(to:gg) map(from:hh)
+     !$omp target data map(alloc:dummy) use_device_addr(gg,hh)
+     c_gptr = c_loc(gg)
+     c_hptr = c_loc(hh)
+     gptr => gg
+     hptr => hh
+     !$omp end target data
+
+     ! check c_loc ptr once
+     call copy3_array(c_gptr, c_hptr, N)
+     !$omp target update from(hh)
+     if (any(abs(gg - 777.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(hh))) call abort()
+
+     ! check c_loc ptr again after target-value modification
+     gg = 7777.0_c_double
+     !$omp target update to(gg)
+     call copy3_array(c_gptr, c_hptr, N)
+     !$omp target update from(hh)
+     if (any(abs(gg - 7777.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(gg))) call abort()
+
+     ! check Fortran pointer after target-value modification
+     gg = 77777.0_c_double
+     !$omp target update to(gg)
+     call copy3_array(c_loc(gptr), c_loc(hptr), N)
+     !$omp target update from(hh)
+     if (any(abs(gg - 77777.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(gg))) call abort()
+     !$omp end target data
+
+     if (any(abs(gg - 77777.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(gg))) call abort()
+  end subroutine test_dummy_callee_2
+end module test_dummies
+
+
+
+! Test local dummy arguments + VALUE (w/o optional)
+module test_dummies_value
+  use iso_c_binding
+  use target_procs
+  implicit none
+  private
+  public :: test_dummy_val_call_1, test_dummy_val_call_2
+contains
+  subroutine test_dummy_val_call_1()
+     ! scalars - with value, neither allocatable nor pointer no dimension permitted
+     real(c_double), target :: aa, bb
+
+     aa = 11.0_c_double
+     bb = 22.0_c_double
+
+     call test_dummy_val_callee_1(aa, bb)
+  end subroutine test_dummy_val_call_1
+
+  subroutine test_dummy_val_callee_1(aa, bb)
+     ! scalars
+     real(c_double), value, target :: aa, bb
+
+     !$omp target data map(to:aa) map(from:bb) use_device_addr(aa,bb)
+     call copy3_scalar(c_loc(aa), c_loc(bb))
+     !$omp end target data
+     if (abs(aa - 11.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+  end subroutine test_dummy_val_callee_1
+
+  ! Save device ptr - and recall pointer
+  subroutine test_dummy_val_call_2()
+     ! scalars - with value, neither allocatable nor pointer no dimension permitted
+     real(c_double), target :: aa, bb
+     type(c_ptr) :: c_aptr, c_bptr
+     real(c_double), pointer :: aptr, bptr
+
+     call test_dummy_val_callee_2(aa, bb, c_aptr, c_bptr, aptr, bptr)
+  end subroutine test_dummy_val_call_2
+
+  subroutine test_dummy_val_callee_2(aa, bb, c_aptr, c_bptr, aptr, bptr)
+     real(c_double), value, target :: aa, bb
+     type(c_ptr), value :: c_aptr, c_bptr
+     real(c_double), pointer :: aptr, bptr
+
+     real(c_double) :: dummy
+
+     aa = 111.0_c_double
+     bb = 222.0_c_double
+
+     !$omp target data map(to:aa) map(from:bb)
+     !$omp target data map(alloc:dummy) use_device_addr(aa,bb)
+     c_aptr = c_loc(aa)
+     c_bptr = c_loc(bb)
+     aptr => aa
+     bptr => bb
+     !$omp end target data
+
+     ! check c_loc ptr once
+     call copy3_scalar(c_aptr, c_bptr)
+     !$omp target update from(bb)
+     if (abs(aa - 111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+     ! check c_loc ptr again after target-value modification
+     aa = 1111.0_c_double
+     !$omp target update to(aa)
+     call copy3_scalar(c_aptr, c_bptr)
+     !$omp target update from(bb)
+     if (abs(aa - 1111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+     ! check Fortran pointer after target-value modification
+     aa = 11111.0_c_double
+     !$omp target update to(aa)
+     call copy3_scalar(c_loc(aptr), c_loc(bptr))
+     !$omp target update from(bb)
+     if (abs(aa - 11111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+     !$omp end target data
+
+     if (abs(aa - 11111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+  end subroutine test_dummy_val_callee_2
+end module test_dummies_value
+
+
+
+! Test local dummy arguments + OPTIONAL
+! Values present and ptr associated to nonzero
+module test_dummies_opt
+  use iso_c_binding
+  use target_procs
+  implicit none
+  private
+  public :: test_dummy_opt_call_1, test_dummy_opt_call_2
+contains
+  subroutine test_dummy_opt_call_1()
+     integer, parameter :: N = 1000
+    
+     ! scalars
+     real(c_double), target :: aa, bb
+     real(c_double), target, allocatable :: cc, dd
+     real(c_double), pointer :: ee, ff
+
+     ! non-descriptor arrays
+     real(c_double), target :: gg(N), hh(N)
+
+     allocate(cc, dd, ee, ff)
+
+     aa = 11.0_c_double
+     bb = 22.0_c_double
+     cc = 33.0_c_double
+     dd = 44.0_c_double
+     ee = 55.0_c_double
+     ff = 66.0_c_double
+     gg = 77.0_c_double
+     hh = 88.0_c_double
+
+     call test_dummy_opt_callee_1(aa, bb, cc, dd, ee, ff, gg, hh, N)
+     deallocate(ee, ff) ! pointers, only
+  end subroutine test_dummy_opt_call_1
+
+  subroutine test_dummy_opt_callee_1(aa, bb, cc, dd, ee, ff, gg, hh, N)
+     ! scalars
+     real(c_double), optional, target :: aa, bb
+     real(c_double), optional, target, allocatable :: cc, dd
+     real(c_double), optional, pointer :: ee, ff
+
+     ! non-descriptor arrays
+     real(c_double), optional, target :: gg(N), hh(N)
+     integer, value :: N
+
+     ! All shall be present - and pointing to non-NULL
+     if (.not.present(aa) .or. .not.present(bb)) call abort()
+     if (.not.present(cc) .or. .not.present(dd)) call abort()
+     if (.not.present(ee) .or. .not.present(ff)) call abort()
+     if (.not.present(gg) .or. .not.present(hh)) call abort()
+
+     if (.not.associated(ee) .or. .not.associated(ff)) call abort()
+
+     !$omp target data map(to:aa) map(from:bb) use_device_addr(aa,bb)
+     if (.not.present(aa) .or. .not.present(bb)) call abort()
+     if (.not.c_associated(c_loc(aa)) .or. .not.c_associated(c_loc(bb))) call abort()
+     call copy3_scalar(c_loc(aa), c_loc(bb))
+     !$omp end target data
+     if (abs(aa - 11.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+     !$omp target data map(to:cc) map(from:dd) use_device_addr(cc,dd)
+     if (.not.present(cc) .or. .not.present(dd)) call abort()
+     if (.not.c_associated(c_loc(cc)) .or. .not.c_associated(c_loc(dd))) call abort()
+     call copy3_scalar(c_loc(cc), c_loc(dd))
+     !$omp end target data
+     if (abs(cc - 33.0_c_double) > 10.0_c_double * epsilon(cc)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(cc)) call abort()
+
+     !$omp target data map(to:ee) map(from:ff) use_device_addr(ee,ff)
+     if (.not.present(ee) .or. .not.present(ff)) call abort()
+     if (.not.associated(ee) .or. .not.associated(ff)) call abort()
+     if (.not.c_associated(c_loc(ee)) .or. .not.c_associated(c_loc(ff))) call abort()
+     call copy3_scalar(c_loc(ee), c_loc(ff))
+     !$omp end target data
+     if (abs(ee - 55.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ee)) call abort()
+
+
+     !$omp target data map(to:gg) map(from:hh) use_device_addr(gg,hh)
+     if (.not.present(gg) .or. .not.present(hh)) call abort()
+     if (.not.c_associated(c_loc(gg)) .or. .not.c_associated(c_loc(hh))) call abort()
+     call copy3_array(c_loc(gg), c_loc(hh), N)
+     !$omp end target data
+     if (any(abs(gg - 77.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(gg))) call abort()
+  end subroutine test_dummy_opt_callee_1
+
+  ! Save device ptr - and recall pointer
+  subroutine test_dummy_opt_call_2()
+     integer, parameter :: N = 1000
+
+     ! scalars
+     real(c_double), target :: aa, bb
+     real(c_double), target, allocatable :: cc, dd
+     real(c_double), pointer :: ee, ff
+
+     ! non-descriptor arrays
+     real(c_double), target :: gg(N), hh(N)
+
+     type(c_ptr) :: c_aptr, c_bptr, c_cptr, c_dptr, c_eptr, c_fptr, c_gptr, c_hptr
+     real(c_double), pointer :: aptr, bptr, cptr, dptr, eptr, fptr
+     real(c_double), pointer :: gptr(:), hptr(:)
+
+     allocate(cc, dd, ee, ff)
+     call test_dummy_opt_callee_2(aa, bb, cc, dd, ee, ff, gg, hh, &
+                                   c_aptr, c_bptr, c_cptr, c_dptr, c_eptr, c_fptr, c_gptr, c_hptr, &
+                                   aptr, bptr, cptr, dptr, eptr, fptr, gptr, hptr, &
+                                   N)
+     deallocate(ee, ff)
+  end subroutine test_dummy_opt_call_2
+
+  subroutine test_dummy_opt_callee_2(aa, bb, cc, dd, ee, ff, gg, hh, &
+                                      c_aptr, c_bptr, c_cptr, c_dptr, c_eptr, c_fptr, c_gptr, c_hptr, &
+                                      aptr, bptr, cptr, dptr, eptr, fptr, gptr, hptr, &
+                                      N)
+     ! scalars
+     real(c_double), optional, target :: aa, bb
+     real(c_double), optional, target, allocatable :: cc, dd
+     real(c_double), optional, pointer :: ee, ff
+
+     ! non-descriptor arrays
+     real(c_double), optional, target :: gg(N), hh(N)
+
+     type(c_ptr) :: c_aptr, c_bptr, c_cptr, c_dptr, c_eptr, c_fptr, c_gptr, c_hptr
+     real(c_double), optional, pointer :: aptr, bptr, cptr, dptr, eptr, fptr
+     real(c_double), optional, pointer :: gptr(:), hptr(:)
+
+     integer, value :: N
+
+     real(c_double) :: dummy
+
+     ! All shall be present - and pointing to non-NULL
+     if (.not.present(aa) .or. .not.present(bb)) call abort()
+     if (.not.present(cc) .or. .not.present(dd)) call abort()
+     if (.not.present(ee) .or. .not.present(ff)) call abort()
+     if (.not.present(gg) .or. .not.present(hh)) call abort()
+
+     if (.not.associated(ee) .or. .not.associated(ff)) call abort()
+
+     aa = 111.0_c_double
+     bb = 222.0_c_double
+     cc = 333.0_c_double
+     dd = 444.0_c_double
+     ee = 555.0_c_double
+     ff = 666.0_c_double
+     gg = 777.0_c_double
+     hh = 888.0_c_double
+
+     !$omp target data map(to:aa) map(from:bb)
+     !$omp target data map(alloc:dummy) use_device_addr(aa,bb)
+     if (.not.present(aa) .or. .not.present(bb)) call abort()
+     if (.not.c_associated(c_loc(aa)) .or. .not.c_associated(c_loc(bb))) call abort()
+     c_aptr = c_loc(aa)
+     c_bptr = c_loc(bb)
+     aptr => aa
+     bptr => bb
+     if (.not.c_associated(c_aptr) .or. .not.c_associated(c_bptr)) call abort()
+     if (.not.associated(aptr) .or. .not.associated(bptr)) call abort()
+     !$omp end target data
+
+     if (.not.present(aa) .or. .not.present(bb)) call abort()
+     if (.not.c_associated(c_loc(aa)) .or. .not.c_associated(c_loc(bb))) call abort()
+     if (.not.c_associated(c_aptr) .or. .not.c_associated(c_bptr)) call abort()
+     if (.not.associated(aptr) .or. .not.associated(bptr)) call abort()
+
+     ! check c_loc ptr once
+     call copy3_scalar(c_aptr, c_bptr)
+     !$omp target update from(bb)
+     if (abs(aa - 111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+     ! check c_loc ptr again after target-value modification
+     aa = 1111.0_c_double
+     !$omp target update to(aa)
+     call copy3_scalar(c_aptr, c_bptr)
+     !$omp target update from(bb)
+     if (abs(aa - 1111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+     ! check Fortran pointer after target-value modification
+     aa = 11111.0_c_double
+     !$omp target update to(aa)
+     call copy3_scalar(c_loc(aptr), c_loc(bptr))
+     !$omp target update from(bb)
+     if (abs(aa - 11111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+     !$omp end target data
+
+     if (abs(aa - 11111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+
+     !$omp target data map(to:cc) map(from:dd)
+     !$omp target data map(alloc:dummy) use_device_addr(cc,dd)
+     if (.not.present(cc) .or. .not.present(dd)) call abort()
+     if (.not.c_associated(c_loc(cc)) .or. .not.c_associated(c_loc(dd))) call abort()
+     c_cptr = c_loc(cc)
+     c_dptr = c_loc(dd)
+     cptr => cc
+     dptr => dd
+     if (.not.c_associated(c_cptr) .or. .not.c_associated(c_dptr)) call abort()
+     if (.not.associated(cptr) .or. .not.associated(dptr)) call abort()
+     !$omp end target data
+     if (.not.present(cc) .or. .not.present(dd)) call abort()
+     if (.not.c_associated(c_loc(cc)) .or. .not.c_associated(c_loc(dd))) call abort()
+     if (.not.c_associated(c_cptr) .or. .not.c_associated(c_dptr)) call abort()
+     if (.not.associated(cptr) .or. .not.associated(dptr)) call abort()
+
+     ! check c_loc ptr once
+     call copy3_scalar(c_cptr, c_dptr)
+     !$omp target update from(dd)
+     if (abs(cc - 333.0_c_double) > 10.0_c_double * epsilon(cc)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(cc)) call abort()
+
+     ! check c_loc ptr again after target-value modification
+     cc = 3333.0_c_double
+     !$omp target update to(cc)
+     call copy3_scalar(c_cptr, c_dptr)
+     !$omp target update from(dd)
+     if (abs(cc - 3333.0_c_double) > 10.0_c_double * epsilon(cc)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(cc)) call abort()
+
+     ! check Fortran pointer after target-value modification
+     cc = 33333.0_c_double
+     !$omp target update to(cc)
+     call copy3_scalar(c_loc(cptr), c_loc(dptr))
+     !$omp target update from(dd)
+     if (abs(cc - 33333.0_c_double) > 10.0_c_double * epsilon(cc)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(cc)) call abort()
+     !$omp end target data
+
+     if (abs(cc - 33333.0_c_double) > 10.0_c_double * epsilon(dd)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(dd)) call abort()
+
+
+     !$omp target data map(to:ee) map(from:ff)
+     !$omp target data map(alloc:dummy) use_device_addr(ee,ff)
+     if (.not.present(ee) .or. .not.present(ff)) call abort()
+     if (.not.associated(ee) .or. .not.associated(ff)) call abort()
+     if (.not.c_associated(c_loc(ee)) .or. .not.c_associated(c_loc(ff))) call abort()
+     c_eptr = c_loc(ee)
+     c_fptr = c_loc(ff)
+     eptr => ee
+     fptr => ff
+     if (.not.c_associated(c_eptr) .or. .not.c_associated(c_fptr)) call abort()
+     if (.not.associated(eptr) .or. .not.associated(fptr)) call abort()
+     !$omp end target data
+     if (.not.present(ee) .or. .not.present(ff)) call abort()
+     if (.not.associated(ee) .or. .not.associated(ff)) call abort()
+     if (.not.c_associated(c_loc(ee)) .or. .not.c_associated(c_loc(ff))) call abort()
+     if (.not.c_associated(c_eptr) .or. .not.c_associated(c_fptr)) call abort()
+     if (.not.associated(eptr) .or. .not.associated(fptr)) call abort()
+
+     ! check c_loc ptr once
+     call copy3_scalar(c_eptr, c_fptr)
+     !$omp target update from(ff)
+     if (abs(ee - 555.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ee)) call abort()
+
+     ! check c_loc ptr again after target-value modification
+     ee = 5555.0_c_double
+     !$omp target update to(ee)
+     call copy3_scalar(c_eptr, c_fptr)
+     !$omp target update from(ff)
+     if (abs(ee - 5555.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ee)) call abort()
+
+     ! check Fortran pointer after target-value modification
+     ee = 55555.0_c_double
+     !$omp target update to(ee)
+     call copy3_scalar(c_loc(eptr), c_loc(fptr))
+     !$omp target update from(ff)
+     if (abs(ee - 55555.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ff)) call abort()
+     !$omp end target data
+
+     if (abs(ee - 55555.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ee)) call abort()
+
+
+     !$omp target data map(to:gg) map(from:hh)
+     !$omp target data map(alloc:dummy) use_device_addr(gg,hh)
+     if (.not.present(gg) .or. .not.present(hh)) call abort()
+     if (.not.c_associated(c_loc(gg)) .or. .not.c_associated(c_loc(hh))) call abort()
+     c_gptr = c_loc(gg)
+     c_hptr = c_loc(hh)
+     gptr => gg
+     hptr => hh
+     if (.not.c_associated(c_gptr) .or. .not.c_associated(c_hptr)) call abort()
+     if (.not.associated(gptr) .or. .not.associated(hptr)) call abort()
+     !$omp end target data
+     if (.not.present(gg) .or. .not.present(hh)) call abort()
+     if (.not.c_associated(c_loc(gg)) .or. .not.c_associated(c_loc(hh))) call abort()
+     if (.not.c_associated(c_gptr) .or. .not.c_associated(c_hptr)) call abort()
+     if (.not.associated(gptr) .or. .not.associated(hptr)) call abort()
+
+     ! check c_loc ptr once
+     call copy3_array(c_gptr, c_hptr, N)
+     !$omp target update from(hh)
+     if (any(abs(gg - 777.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(hh))) call abort()
+
+     ! check c_loc ptr again after target-value modification
+     gg = 7777.0_c_double
+     !$omp target update to(gg)
+     call copy3_array(c_gptr, c_hptr, N)
+     !$omp target update from(hh)
+     if (any(abs(gg - 7777.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(gg))) call abort()
+
+     ! check Fortran pointer after target-value modification
+     gg = 77777.0_c_double
+     !$omp target update to(gg)
+     call copy3_array(c_loc(gptr), c_loc(hptr), N)
+     !$omp target update from(hh)
+     if (any(abs(gg - 77777.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(gg))) call abort()
+     !$omp end target data
+
+     if (any(abs(gg - 77777.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(gg))) call abort()
+  end subroutine test_dummy_opt_callee_2
+end module test_dummies_opt
+
+
+
+! Test local dummy arguments + OPTIONAL + VALUE
+! Values present
+module test_dummies_opt_value
+  use iso_c_binding
+  use target_procs
+  implicit none
+  private
+  public :: test_dummy_opt_val_call_1, test_dummy_opt_val_call_2
+contains
+  subroutine test_dummy_opt_val_call_1()
+     ! scalars - with value, neither allocatable nor pointer no dimension permitted
+     real(c_double), target :: aa, bb
+
+     aa = 11.0_c_double
+     bb = 22.0_c_double
+
+     call test_dummy_opt_val_callee_1(aa, bb)
+  end subroutine test_dummy_opt_val_call_1
+
+  subroutine test_dummy_opt_val_callee_1(aa, bb)
+     ! scalars
+     real(c_double), optional, value, target :: aa, bb
+
+     if (.not.present(aa) .or. .not.present(bb)) call abort()
+
+     !$omp target data map(to:aa) map(from:bb) use_device_addr(aa,bb)
+     if (.not.present(aa) .or. .not.present(bb)) call abort()
+     if (.not.c_associated(c_loc(aa)) .or. .not.c_associated(c_loc(bb))) call abort()
+     call copy3_scalar(c_loc(aa), c_loc(bb))
+     !$omp end target data
+     if (abs(aa - 11.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+  end subroutine test_dummy_opt_val_callee_1
+
+  ! Save device ptr - and recall pointer
+  subroutine test_dummy_opt_val_call_2()
+     ! scalars - with value, neither allocatable nor pointer no dimension permitted
+     real(c_double), target :: aa, bb
+     type(c_ptr) :: c_aptr, c_bptr
+     real(c_double), pointer :: aptr, bptr
+
+     call test_dummy_opt_val_callee_2(aa, bb, c_aptr, c_bptr, aptr, bptr)
+  end subroutine test_dummy_opt_val_call_2
+
+  subroutine test_dummy_opt_val_callee_2(aa, bb, c_aptr, c_bptr, aptr, bptr)
+     real(c_double), optional, value, target :: aa, bb
+     type(c_ptr), optional, value :: c_aptr, c_bptr
+     real(c_double), optional, pointer :: aptr, bptr
+
+     real(c_double) :: dummy
+
+     if (.not.present(aa) .or. .not.present(bb)) call abort()
+     if (.not.present(c_aptr) .or. .not.present(c_bptr)) call abort()
+     if (.not.present(aptr) .or. .not.present(bptr)) call abort()
+
+     aa = 111.0_c_double
+     bb = 222.0_c_double
+
+     !$omp target data map(to:aa) map(from:bb)
+     if (.not.present(aa) .or. .not.present(bb)) call abort()
+     if (.not.present(c_aptr) .or. .not.present(c_bptr)) call abort()
+     if (.not.present(aptr) .or. .not.present(bptr)) call abort()
+
+     !$omp target data map(alloc:dummy) use_device_addr(aa,bb)
+     if (.not.present(aa) .or. .not.present(bb)) call abort()
+     if (.not.present(c_aptr) .or. .not.present(c_bptr)) call abort()
+     if (.not.present(aptr) .or. .not.present(bptr)) call abort()
+
+     c_aptr = c_loc(aa)
+     c_bptr = c_loc(bb)
+     aptr => aa
+     bptr => bb
+     if (.not.c_associated(c_aptr) .or. .not.c_associated(c_bptr)) call abort()
+     if (.not.associated(aptr) .or. .not.associated(bptr)) call abort()
+     !$omp end target data
+
+     ! check c_loc ptr once
+     call copy3_scalar(c_aptr, c_bptr)
+     !$omp target update from(bb)
+     if (abs(aa - 111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+     ! check c_loc ptr again after target-value modification
+     aa = 1111.0_c_double
+     !$omp target update to(aa)
+     call copy3_scalar(c_aptr, c_bptr)
+     !$omp target update from(bb)
+     if (abs(aa - 1111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+     ! check Fortran pointer after target-value modification
+     aa = 11111.0_c_double
+     !$omp target update to(aa)
+     call copy3_scalar(c_loc(aptr), c_loc(bptr))
+     !$omp target update from(bb)
+     if (abs(aa - 11111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+     !$omp end target data
+
+     if (abs(aa - 11111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+  end subroutine test_dummy_opt_val_callee_2
+end module test_dummies_opt_value
+
+
+
+! Test nullptr
+module test_nullptr
+  use iso_c_binding
+  implicit none
+  private
+  public :: test_nullptr_1
+contains
+  subroutine test_nullptr_1()
+     ! scalars
+     real(c_double), pointer :: aa, bb
+     real(c_double), pointer :: ee, ff
+
+     type(c_ptr) :: c_aptr, c_bptr, c_eptr, c_fptr
+     real(c_double), pointer :: aptr, bptr, eptr, fptr
+
+     aa => null()
+     bb => null()
+     ee => null()
+     ff => null()
+
+     if (associated(aa) .or. associated(bb)) call abort()
+     !$omp target data map(to:aa) map(from:bb) use_device_addr(aa,bb)
+     if (c_associated(c_loc(aa)) .or. c_associated(c_loc(bb))) call abort()
+     c_aptr = c_loc(aa)
+     c_bptr = c_loc(bb)
+     aptr => aa
+     bptr => bb
+     if (c_associated(c_aptr) .or. c_associated(c_bptr)) call abort()
+     if (associated(aptr) .or. associated(bptr, bb)) call abort()
+     !$omp end target data
+     if (c_associated(c_aptr) .or. c_associated(c_bptr)) call abort()
+     if (associated(aptr) .or. associated(bptr, bb)) call abort()
+
+     call test_dummy_opt_nullptr_callee_1(ee, ff, c_eptr, c_fptr, eptr, fptr)
+  end subroutine test_nullptr_1
+
+  subroutine test_dummy_opt_nullptr_callee_1(ee, ff, c_eptr, c_fptr, eptr, fptr)
+     ! scalars
+     real(c_double), optional, pointer :: ee, ff
+
+     type(c_ptr), optional :: c_eptr, c_fptr
+     real(c_double), optional, pointer :: eptr, fptr
+
+     if (.not.present(ee) .or. .not.present(ff)) call abort()
+     if (associated(ee) .or. associated(ff)) call abort()
+
+     !$omp target data map(to:ee) map(from:ff) use_device_addr(ee,ff)
+     if (.not.present(ee) .or. .not.present(ff)) call abort()
+     if (associated(ee) .or. associated(ff)) call abort()
+     if (c_associated(c_loc(ee)) .or. c_associated(c_loc(ff))) call abort()
+     c_eptr = c_loc(ee)
+     c_fptr = c_loc(ff)
+     eptr => ee
+     fptr => ff
+     if (c_associated(c_eptr) .or. c_associated(c_fptr)) call abort()
+     if (associated(eptr) .or. associated(fptr)) call abort()
+     !$omp end target data
+
+     if (c_associated(c_eptr) .or. c_associated(c_fptr)) call abort()
+     if (associated(eptr) .or. associated(fptr)) call abort()
+  end subroutine test_dummy_opt_nullptr_callee_1
+end module test_nullptr
+
+
+
+! Test local variables
+module tests
+  use iso_c_binding
+  use target_procs
+  implicit none
+  private
+  public :: test_main_1, test_main_2
+contains
+   ! map + use_device_addr + c_loc
+   subroutine test_main_1()
+     integer, parameter :: N = 1000
+    
+     ! scalars
+     real(c_double), target :: aa, bb
+     real(c_double), target, allocatable :: cc, dd
+     real(c_double), pointer :: ee, ff
+
+     ! non-descriptor arrays
+     real(c_double), target :: gg(N), hh(N)
+
+     allocate(cc, dd, ee, ff)
+
+
+     aa = 11.0_c_double
+     bb = 22.0_c_double
+     cc = 33.0_c_double
+     dd = 44.0_c_double
+     ee = 55.0_c_double
+     ff = 66.0_c_double
+     gg = 77.0_c_double
+     hh = 88.0_c_double
+
+     !$omp target data map(to:aa) map(from:bb) use_device_addr(aa,bb)
+     call copy3_scalar(c_loc(aa), c_loc(bb))
+     !$omp end target data
+     if (abs(aa - 11.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+     !$omp target data map(to:cc) map(from:dd) use_device_addr(cc,dd)
+     call copy3_scalar(c_loc(cc), c_loc(dd))
+     !$omp end target data
+     if (abs(cc - 33.0_c_double) > 10.0_c_double * epsilon(cc)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(cc)) call abort()
+
+     !$omp target data map(to:ee) map(from:ff) use_device_addr(ee,ff)
+     call copy3_scalar(c_loc(ee), c_loc(ff))
+     !$omp end target data
+     if (abs(ee - 55.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ee)) call abort()
+
+
+     !$omp target data map(to:gg) map(from:hh) use_device_addr(gg,hh)
+     call copy3_array(c_loc(gg), c_loc(hh), N)
+     !$omp end target data
+     if (any(abs(gg - 77.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(gg))) call abort()
+
+     deallocate(ee, ff) ! pointers, only
+   end subroutine test_main_1
+
+   ! Save device ptr - and recall pointer
+   subroutine test_main_2
+     integer, parameter :: N = 1000
+    
+     ! scalars
+     real(c_double), target :: aa, bb
+     real(c_double), target, allocatable :: cc, dd
+     real(c_double), pointer :: ee, ff
+
+     ! non-descriptor arrays
+     real(c_double), target :: gg(N), hh(N)
+
+     real(c_double) :: dummy
+     type(c_ptr) :: c_aptr, c_bptr, c_cptr, c_dptr, c_eptr, c_fptr, c_gptr, c_hptr
+     real(c_double), pointer :: aptr, bptr, cptr, dptr, eptr, fptr
+     real(c_double), pointer :: gptr(:), hptr(:)
+
+     allocate(cc, dd, ee, ff)
+
+     aa = 111.0_c_double
+     bb = 222.0_c_double
+     cc = 333.0_c_double
+     dd = 444.0_c_double
+     ee = 555.0_c_double
+     ff = 666.0_c_double
+     gg = 777.0_c_double
+     hh = 888.0_c_double
+
+     !$omp target data map(to:aa) map(from:bb)
+     !$omp target data map(alloc:dummy) use_device_addr(aa,bb)
+     c_aptr = c_loc(aa)
+     c_bptr = c_loc(bb)
+     aptr => aa
+     bptr => bb
+     !$omp end target data
+
+     ! check c_loc ptr once
+     call copy3_scalar(c_aptr, c_bptr)
+     !$omp target update from(bb)
+     if (abs(aa - 111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+     ! check c_loc ptr again after target-value modification
+     aa = 1111.0_c_double
+     !$omp target update to(aa)
+     call copy3_scalar(c_aptr, c_bptr)
+     !$omp target update from(bb)
+     if (abs(aa - 1111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+     ! check Fortran pointer after target-value modification
+     aa = 11111.0_c_double
+     !$omp target update to(aa)
+     call copy3_scalar(c_loc(aptr), c_loc(bptr))
+     !$omp target update from(bb)
+     if (abs(aa - 11111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+     !$omp end target data
+
+     if (abs(aa - 11111.0_c_double) > 10.0_c_double * epsilon(aa)) call abort()
+     if (abs(3.0_c_double * aa - bb) > 10.0_c_double * epsilon(aa)) call abort()
+
+
+     !$omp target data map(to:cc) map(from:dd)
+     !$omp target data map(alloc:dummy) use_device_addr(cc,dd)
+     c_cptr = c_loc(cc)
+     c_dptr = c_loc(dd)
+     cptr => cc
+     dptr => dd
+     !$omp end target data
+
+     ! check c_loc ptr once
+     call copy3_scalar(c_cptr, c_dptr)
+     !$omp target update from(dd)
+     if (abs(cc - 333.0_c_double) > 10.0_c_double * epsilon(cc)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(cc)) call abort()
+
+     ! check c_loc ptr again after target-value modification
+     cc = 3333.0_c_double
+     !$omp target update to(cc)
+     call copy3_scalar(c_cptr, c_dptr)
+     !$omp target update from(dd)
+     if (abs(cc - 3333.0_c_double) > 10.0_c_double * epsilon(cc)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(cc)) call abort()
+
+     ! check Fortran pointer after target-value modification
+     cc = 33333.0_c_double
+     !$omp target update to(cc)
+     call copy3_scalar(c_loc(cptr), c_loc(dptr))
+     !$omp target update from(dd)
+     if (abs(cc - 33333.0_c_double) > 10.0_c_double * epsilon(cc)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(cc)) call abort()
+     !$omp end target data
+
+     if (abs(cc - 33333.0_c_double) > 10.0_c_double * epsilon(dd)) call abort()
+     if (abs(3.0_c_double * cc - dd) > 10.0_c_double * epsilon(dd)) call abort()
+
+
+     !$omp target data map(to:ee) map(from:ff)
+     !$omp target data map(alloc:dummy) use_device_addr(ee,ff)
+     c_eptr = c_loc(ee)
+     c_fptr = c_loc(ff)
+     eptr => ee
+     fptr => ff
+     !$omp end target data
+
+     ! check c_loc ptr once
+     call copy3_scalar(c_eptr, c_fptr)
+     !$omp target update from(ff)
+     if (abs(ee - 555.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ee)) call abort()
+
+     ! check c_loc ptr again after target-value modification
+     ee = 5555.0_c_double
+     !$omp target update to(ee)
+     call copy3_scalar(c_eptr, c_fptr)
+     !$omp target update from(ff)
+     if (abs(ee - 5555.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ee)) call abort()
+
+     ! check Fortran pointer after target-value modification
+     ee = 55555.0_c_double
+     !$omp target update to(ee)
+     call copy3_scalar(c_loc(eptr), c_loc(fptr))
+     !$omp target update from(ff)
+     if (abs(ee - 55555.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ff)) call abort()
+     !$omp end target data
+
+     if (abs(ee - 55555.0_c_double) > 10.0_c_double * epsilon(ee)) call abort()
+     if (abs(3.0_c_double * ee - ff) > 10.0_c_double * epsilon(ee)) call abort()
+
+
+     !$omp target data map(to:gg) map(from:hh)
+     !$omp target data map(alloc:dummy) use_device_addr(gg,hh)
+     c_gptr = c_loc(gg)
+     c_hptr = c_loc(hh)
+     gptr => gg
+     hptr => hh
+     !$omp end target data
+
+     ! check c_loc ptr once
+     call copy3_array(c_gptr, c_hptr, N)
+     !$omp target update from(hh)
+     if (any(abs(gg - 777.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(hh))) call abort()
+
+     ! check c_loc ptr again after target-value modification
+     gg = 7777.0_c_double
+     !$omp target update to(gg)
+     call copy3_array(c_gptr, c_hptr, N)
+     !$omp target update from(hh)
+     if (any(abs(gg - 7777.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(gg))) call abort()
+
+     ! check Fortran pointer after target-value modification
+     gg = 77777.0_c_double
+     !$omp target update to(gg)
+     call copy3_array(c_loc(gptr), c_loc(hptr), N)
+     !$omp target update from(hh)
+     if (any(abs(gg - 77777.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(gg))) call abort()
+     !$omp end target data
+
+     if (any(abs(gg - 77777.0_c_double) > 10.0_c_double * epsilon(gg))) call abort()
+     if (any(abs(3.0_c_double * gg - hh) > 10.0_c_double * epsilon(gg))) call abort()
+
+     deallocate(ee, ff)
+   end subroutine test_main_2
+end module tests
+
+
+program omp_device_addr
+  use tests
+  use test_dummies
+  use test_dummies_value
+  use test_dummies_opt
+  use test_dummies_opt_value
+  use test_nullptr
+  implicit none
+
+  call test_main_1()
+  call test_main_2()
+
+  call test_dummy_call_1()
+  call test_dummy_call_2()
+
+  call test_dummy_val_call_1()
+  call test_dummy_val_call_2()
+
+  call test_dummy_opt_call_1()
+  call test_dummy_opt_call_2()
+
+  call test_dummy_opt_val_call_1()
+  call test_dummy_opt_val_call_2()
+
+  call test_nullptr_1()
+end program omp_device_addr