summaryrefslogtreecommitdiff
path: root/libgomp/openacc.f90
diff options
context:
space:
mode:
Diffstat (limited to 'libgomp/openacc.f90')
-rw-r--r--libgomp/openacc.f90281
1 files changed, 128 insertions, 153 deletions
diff --git a/libgomp/openacc.f90 b/libgomp/openacc.f90
index db39421bf07..467fb612c54 100644
--- a/libgomp/openacc.f90
+++ b/libgomp/openacc.f90
@@ -31,11 +31,10 @@
module openacc_kinds
use iso_fortran_env, only: int32
- use iso_c_binding, only: c_size_t
implicit none
public
- private :: int32, c_size_t
+ private :: int32
! When adding items, also update 'public' setting in 'module openacc' below.
@@ -51,14 +50,17 @@ module openacc_kinds
integer (acc_device_kind), parameter :: acc_device_nvidia = 5
integer (acc_device_kind), parameter :: acc_device_radeon = 8
- integer, parameter :: acc_device_property = c_size_t
+ integer, parameter :: acc_device_property_kind = int32
+ ! OpenACC 2.6/2.7/3.0 used acc_device_property; in a spec update the
+ ! missing '_kind' was added for consistency. For backward compatibility, keep:
+ integer, parameter :: acc_device_property = acc_device_property_kind
! Keep in sync with 'libgomp/libgomp-plugin.h:goacc_property'.
- integer (acc_device_property), parameter :: acc_property_memory = 1
- integer (acc_device_property), parameter :: acc_property_free_memory = 2
- integer (acc_device_property), parameter :: acc_property_name = int(Z'10001')
- integer (acc_device_property), parameter :: acc_property_vendor = int(Z'10002')
- integer (acc_device_property), parameter :: acc_property_driver = int(Z'10003')
+ integer (acc_device_property_kind), parameter :: acc_property_memory = 1
+ integer (acc_device_property_kind), parameter :: acc_property_free_memory = 2
+ integer (acc_device_property_kind), parameter :: acc_property_name = int(Z'10001')
+ integer (acc_device_property_kind), parameter :: acc_property_vendor = int(Z'10002')
+ integer (acc_device_property_kind), parameter :: acc_property_driver = int(Z'10003')
integer, parameter :: acc_handle_kind = int32
@@ -72,15 +74,15 @@ module openacc_internal
implicit none
interface
- function acc_get_num_devices_h (d)
+ function acc_get_num_devices_h (devicetype)
import
integer acc_get_num_devices_h
- integer (acc_device_kind) d
+ integer (acc_device_kind) devicetype
end function
- subroutine acc_set_device_type_h (d)
+ subroutine acc_set_device_type_h (devicetype)
import
- integer (acc_device_kind) d
+ integer (acc_device_kind) devicetype
end subroutine
function acc_get_device_type_h ()
@@ -88,73 +90,74 @@ module openacc_internal
integer (acc_device_kind) acc_get_device_type_h
end function
- subroutine acc_set_device_num_h (n, d)
+ subroutine acc_set_device_num_h (devicenum, devicetype)
import
- integer n
- integer (acc_device_kind) d
+ integer devicenum
+ integer (acc_device_kind) devicetype
end subroutine
- function acc_get_device_num_h (d)
+ function acc_get_device_num_h (devicetype)
import
integer acc_get_device_num_h
- integer (acc_device_kind) d
+ integer (acc_device_kind) devicetype
end function
- function acc_get_property_h (n, d, p)
+ function acc_get_property_h (devicenum, devicetype, property)
+ use iso_c_binding, only: c_size_t
import
implicit none (type, external)
- integer (acc_device_property) :: acc_get_property_h
- integer, value :: n
- integer (acc_device_kind), value :: d
- integer (acc_device_property), value :: p
+ integer (c_size_t) :: acc_get_property_h
+ integer, value :: devicenum
+ integer (acc_device_kind), value :: devicetype
+ integer (acc_device_property_kind), value :: property
end function
- subroutine acc_get_property_string_h (n, d, p, s)
+ subroutine acc_get_property_string_h (devicenum, devicetype, property, string)
import
implicit none (type, external)
- integer, value :: n
- integer (acc_device_kind), value :: d
- integer (acc_device_property), value :: p
- character (*) :: s
+ integer, value :: devicenum
+ integer (acc_device_kind), value :: devicetype
+ integer (acc_device_property_kind), value :: property
+ character (*) :: string
end subroutine
- function acc_async_test_h (a)
+ function acc_async_test_h (arg)
logical acc_async_test_h
- integer a
+ integer arg
end function
function acc_async_test_all_h ()
logical acc_async_test_all_h
end function
- subroutine acc_wait_h (a)
- integer a
+ subroutine acc_wait_h (arg)
+ integer arg
end subroutine
- subroutine acc_wait_async_h (a1, a2)
- integer a1, a2
+ subroutine acc_wait_async_h (arg, async)
+ integer arg, async
end subroutine
subroutine acc_wait_all_h ()
end subroutine
- subroutine acc_wait_all_async_h (a)
- integer a
+ subroutine acc_wait_all_async_h (async)
+ integer async
end subroutine
- subroutine acc_init_h (d)
+ subroutine acc_init_h (devicetype)
import
- integer (acc_device_kind) d
+ integer (acc_device_kind) devicetype
end subroutine
- subroutine acc_shutdown_h (d)
+ subroutine acc_shutdown_h (devicetype)
import
- integer (acc_device_kind) d
+ integer (acc_device_kind) devicetype
end subroutine
- function acc_on_device_h (d)
+ function acc_on_device_h (devicetype)
import
- integer (acc_device_kind) d
+ integer (acc_device_kind) devicetype
logical acc_on_device_h
end function
@@ -505,17 +508,17 @@ module openacc_internal
end interface
interface
- function acc_get_num_devices_l (d) &
+ function acc_get_num_devices_l (devicetype) &
bind (C, name = "acc_get_num_devices")
use iso_c_binding, only: c_int
integer (c_int) :: acc_get_num_devices_l
- integer (c_int), value :: d
+ integer (c_int), value :: devicetype
end function
- subroutine acc_set_device_type_l (d) &
+ subroutine acc_set_device_type_l (devicetype) &
bind (C, name = "acc_set_device_type")
use iso_c_binding, only: c_int
- integer (c_int), value :: d
+ integer (c_int), value :: devicetype
end subroutine
function acc_get_device_type_l () &
@@ -524,37 +527,37 @@ module openacc_internal
integer (c_int) :: acc_get_device_type_l
end function
- subroutine acc_set_device_num_l (n, d) &
+ subroutine acc_set_device_num_l (devicenum, devicetype) &
bind (C, name = "acc_set_device_num")
use iso_c_binding, only: c_int
- integer (c_int), value :: n, d
+ integer (c_int), value :: devicenum, devicetype
end subroutine
- function acc_get_device_num_l (d) &
+ function acc_get_device_num_l (devicetype) &
bind (C, name = "acc_get_device_num")
use iso_c_binding, only: c_int
integer (c_int) :: acc_get_device_num_l
- integer (c_int), value :: d
+ integer (c_int), value :: devicetype
end function
- function acc_get_property_l (n, d, p) &
+ function acc_get_property_l (devicenum, devicetype, property) &
bind (C, name = "acc_get_property")
use iso_c_binding, only: c_int, c_size_t
implicit none (type, external)
integer (c_size_t) :: acc_get_property_l
- integer (c_int), value :: n
- integer (c_int), value :: d
- integer (c_int), value :: p
+ integer (c_int), value :: devicenum
+ integer (c_int), value :: devicetype
+ integer (c_int), value :: property
end function
- function acc_get_property_string_l (n, d, p) &
+ function acc_get_property_string_l (devicenum, devicetype, property) &
bind (C, name = "acc_get_property_string")
use iso_c_binding, only: c_int, c_ptr
implicit none (type, external)
type (c_ptr) :: acc_get_property_string_l
- integer (c_int), value :: n
- integer (c_int), value :: d
- integer (c_int), value :: p
+ integer (c_int), value :: devicenum
+ integer (c_int), value :: devicetype
+ integer (c_int), value :: property
end function
function acc_async_test_l (a) &
@@ -576,10 +579,10 @@ module openacc_internal
integer (c_int), value :: a
end subroutine
- subroutine acc_wait_async_l (a1, a2) &
+ subroutine acc_wait_async_l (arg, async) &
bind (C, name = "acc_wait_async")
use iso_c_binding, only: c_int
- integer (c_int), value :: a1, a2
+ integer (c_int), value :: arg, async
end subroutine
subroutine acc_wait_all_l () &
@@ -587,29 +590,29 @@ module openacc_internal
use iso_c_binding, only: c_int
end subroutine
- subroutine acc_wait_all_async_l (a) &
+ subroutine acc_wait_all_async_l (async) &
bind (C, name = "acc_wait_all_async")
use iso_c_binding, only: c_int
- integer (c_int), value :: a
+ integer (c_int), value :: async
end subroutine
- subroutine acc_init_l (d) &
+ subroutine acc_init_l (devicetype) &
bind (C, name = "acc_init")
use iso_c_binding, only: c_int
- integer (c_int), value :: d
+ integer (c_int), value :: devicetype
end subroutine
- subroutine acc_shutdown_l (d) &
+ subroutine acc_shutdown_l (devicetype) &
bind (C, name = "acc_shutdown")
use iso_c_binding, only: c_int
- integer (c_int), value :: d
+ integer (c_int), value :: devicetype
end subroutine
- function acc_on_device_l (d) &
+ function acc_on_device_l (devicetype) &
bind (C, name = "acc_on_device")
use iso_c_binding, only: c_int
integer (c_int) :: acc_on_device_l
- integer (c_int), value :: d
+ integer (c_int), value :: devicetype
end function
subroutine acc_copyin_l (a, len) &
@@ -769,7 +772,7 @@ module openacc
public :: acc_device_none, acc_device_default, acc_device_host
public :: acc_device_not_host, acc_device_nvidia, acc_device_radeon
- public :: acc_device_property
+ public :: acc_device_property_kind, acc_device_property
public :: acc_property_memory, acc_property_free_memory
public :: acc_property_name, acc_property_vendor, acc_property_driver
@@ -1002,19 +1005,19 @@ module openacc
end module openacc
-function acc_get_num_devices_h (d)
+function acc_get_num_devices_h (devicetype)
use openacc_internal, only: acc_get_num_devices_l
use openacc_kinds
integer acc_get_num_devices_h
- integer (acc_device_kind) d
- acc_get_num_devices_h = acc_get_num_devices_l (d)
+ integer (acc_device_kind) devicetype
+ acc_get_num_devices_h = acc_get_num_devices_l (devicetype)
end function
-subroutine acc_set_device_type_h (d)
+subroutine acc_set_device_type_h (devicetype)
use openacc_internal, only: acc_set_device_type_l
use openacc_kinds
- integer (acc_device_kind) d
- call acc_set_device_type_l (d)
+ integer (acc_device_kind) devicetype
+ call acc_set_device_type_l (devicetype)
end subroutine
function acc_get_device_type_h ()
@@ -1024,54 +1027,47 @@ function acc_get_device_type_h ()
acc_get_device_type_h = acc_get_device_type_l ()
end function
-subroutine acc_set_device_num_h (n, d)
+subroutine acc_set_device_num_h (devicenum, devicetype)
use openacc_internal, only: acc_set_device_num_l
use openacc_kinds
- integer n
- integer (acc_device_kind) d
- call acc_set_device_num_l (n, d)
+ integer devicenum
+ integer (acc_device_kind) devicetype
+ call acc_set_device_num_l (devicenum, devicetype)
end subroutine
-function acc_get_device_num_h (d)
+function acc_get_device_num_h (devicetype)
use openacc_internal, only: acc_get_device_num_l
use openacc_kinds
integer acc_get_device_num_h
- integer (acc_device_kind) d
- acc_get_device_num_h = acc_get_device_num_l (d)
+ integer (acc_device_kind) devicetype
+ acc_get_device_num_h = acc_get_device_num_l (devicetype)
end function
-function acc_get_property_h (n, d, p)
- use iso_c_binding, only: c_int, c_size_t
+function acc_get_property_h (devicenum, devicetype, property)
+ use iso_c_binding, only: c_size_t
use openacc_internal, only: acc_get_property_l
use openacc_kinds
implicit none (type, external)
- integer (acc_device_property) :: acc_get_property_h
- integer, value :: n
- integer (acc_device_kind), value :: d
- integer (acc_device_property), value :: p
-
- integer (c_int) :: pint
-
- pint = int (p, c_int)
- acc_get_property_h = acc_get_property_l (n, d, pint)
+ integer (c_size_t) :: acc_get_property_h
+ integer, value :: devicenum
+ integer (acc_device_kind), value :: devicetype
+ integer (acc_device_property_kind), value :: property
+ acc_get_property_h = acc_get_property_l (devicenum, devicetype, property)
end function
-subroutine acc_get_property_string_h (n, d, p, s)
- use iso_c_binding, only: c_char, c_int, c_ptr, c_f_pointer, c_associated
+subroutine acc_get_property_string_h (devicenum, devicetype, property, string)
+ use iso_c_binding, only: c_char, c_size_t, c_ptr, c_f_pointer, c_associated
use openacc_internal, only: acc_get_property_string_l
use openacc_kinds
implicit none (type, external)
- integer, value :: n
- integer (acc_device_kind), value :: d
- integer (acc_device_property), value :: p
- character (*) :: s
+ integer, value :: devicenum
+ integer (acc_device_kind), value :: devicetype
+ integer (acc_device_property_kind), value :: property
+ character (*) :: string
- integer (c_int) :: pint
type (c_ptr) :: cptr
- integer :: clen
+ integer(c_size_t) :: clen, slen, i
character (kind=c_char, len=1), pointer, contiguous :: sptr (:)
- integer :: slen
- integer :: i
interface
function strlen (s) bind (C, name = "strlen")
@@ -1081,53 +1077,44 @@ subroutine acc_get_property_string_h (n, d, p, s)
end function strlen
end interface
- pint = int (p, c_int)
- cptr = acc_get_property_string_l (n, d, pint)
- s = ""
+ cptr = acc_get_property_string_l (devicenum, devicetype, property)
+ string = ""
if (.not. c_associated (cptr)) then
return
end if
- clen = int (strlen (cptr))
+ clen = strlen (cptr)
call c_f_pointer (cptr, sptr, [clen])
- slen = min (clen, len (s))
+ slen = min (clen, len (string, kind=c_size_t))
do i = 1, slen
- s (i:i) = sptr (i)
+ string (i:i) = sptr (i)
end do
end subroutine
-function acc_async_test_h (a)
+function acc_async_test_h (arg)
use openacc_internal, only: acc_async_test_l
logical acc_async_test_h
- integer a
- if (acc_async_test_l (a) .eq. 1) then
- acc_async_test_h = .TRUE.
- else
- acc_async_test_h = .FALSE.
- end if
+ integer arg
+ acc_async_test_h = acc_async_test_l (arg) /= 0
end function
function acc_async_test_all_h ()
use openacc_internal, only: acc_async_test_all_l
logical acc_async_test_all_h
- if (acc_async_test_all_l () .eq. 1) then
- acc_async_test_all_h = .TRUE.
- else
- acc_async_test_all_h = .FALSE.
- end if
+ acc_async_test_all_h = acc_async_test_all_l () /= 0
end function
-subroutine acc_wait_h (a)
+subroutine acc_wait_h (arg)
use openacc_internal, only: acc_wait_l
- integer a
- call acc_wait_l (a)
+ integer arg
+ call acc_wait_l (arg)
end subroutine
-subroutine acc_wait_async_h (a1, a2)
+subroutine acc_wait_async_h (arg, async)
use openacc_internal, only: acc_wait_async_l
- integer a1, a2
- call acc_wait_async_l (a1, a2)
+ integer arg, async
+ call acc_wait_async_l (arg, async)
end subroutine
subroutine acc_wait_all_h ()
@@ -1135,36 +1122,32 @@ subroutine acc_wait_all_h ()
call acc_wait_all_l ()
end subroutine
-subroutine acc_wait_all_async_h (a)
+subroutine acc_wait_all_async_h (async)
use openacc_internal, only: acc_wait_all_async_l
- integer a
- call acc_wait_all_async_l (a)
+ integer async
+ call acc_wait_all_async_l (async)
end subroutine
-subroutine acc_init_h (d)
+subroutine acc_init_h (devicetype)
use openacc_internal, only: acc_init_l
use openacc_kinds
- integer (acc_device_kind) d
- call acc_init_l (d)
+ integer (acc_device_kind) devicetype
+ call acc_init_l (devicetype)
end subroutine
-subroutine acc_shutdown_h (d)
+subroutine acc_shutdown_h (devicetype)
use openacc_internal, only: acc_shutdown_l
use openacc_kinds
- integer (acc_device_kind) d
- call acc_shutdown_l (d)
+ integer (acc_device_kind) devicetype
+ call acc_shutdown_l (devicetype)
end subroutine
-function acc_on_device_h (d)
+function acc_on_device_h (devicetype)
use openacc_internal, only: acc_on_device_l
use openacc_kinds
- integer (acc_device_kind) d
+ integer (acc_device_kind) devicetype
logical acc_on_device_h
- if (acc_on_device_l (d) .eq. 1) then
- acc_on_device_h = .TRUE.
- else
- acc_on_device_h = .FALSE.
- end if
+ acc_on_device_h = acc_on_device_l (devicetype) /= 0
end function
subroutine acc_copyin_32_h (a, len)
@@ -1414,11 +1397,7 @@ function acc_is_present_32_h (a, len)
!GCC$ ATTRIBUTES NO_ARG_CHECK :: a
type (*), dimension (*) :: a
integer (c_int32_t) len
- if (acc_is_present_l (a, int (len, kind = c_size_t)) .eq. 1) then
- acc_is_present_32_h = .TRUE.
- else
- acc_is_present_32_h = .FALSE.
- end if
+ acc_is_present_32_h = acc_is_present_l (a, int (len, kind = c_size_t)) /= 0
end function
function acc_is_present_64_h (a, len)
@@ -1428,18 +1407,14 @@ function acc_is_present_64_h (a, len)
!GCC$ ATTRIBUTES NO_ARG_CHECK :: a
type (*), dimension (*) :: a
integer (c_int64_t) len
- if (acc_is_present_l (a, int (len, kind = c_size_t)) .eq. 1) then
- acc_is_present_64_h = .TRUE.
- else
- acc_is_present_64_h = .FALSE.
- end if
+ acc_is_present_64_h = acc_is_present_l (a, int (len, kind = c_size_t)) /= 0
end function
function acc_is_present_array_h (a)
use openacc_internal, only: acc_is_present_l
logical acc_is_present_array_h
type (*), dimension (..), contiguous :: a
- acc_is_present_array_h = acc_is_present_l (a, sizeof (a)) == 1
+ acc_is_present_array_h = acc_is_present_l (a, sizeof (a)) /= 0
end function
subroutine acc_copyin_async_32_h (a, len, async)