1!  OpenACC Runtime Library Definitions.
2
3!  Copyright (C) 2014-2021 Free Software Foundation, Inc.
4
5!  Contributed by Tobias Burnus <burnus@net-b.de>
6!              and Mentor Embedded.
7
8!  This file is part of the GNU Offloading and Multi Processing Library
9!  (libgomp).
10
11!  Libgomp is free software; you can redistribute it and/or modify it
12!  under the terms of the GNU General Public License as published by
13!  the Free Software Foundation; either version 3, or (at your option)
14!  any later version.
15
16!  Libgomp is distributed in the hope that it will be useful, but WITHOUT ANY
17!  WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
18!  FOR A PARTICULAR PURPOSE.  See the GNU General Public License for
19!  more details.
20
21!  Under Section 7 of GPL version 3, you are granted additional
22!  permissions described in the GCC Runtime Library Exception, version
23!  3.1, as published by the Free Software Foundation.
24
25!  You should have received a copy of the GNU General Public License and
26!  a copy of the GCC Runtime Library Exception along with this program;
27!  see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
28!  <http://www.gnu.org/licenses/>.
29
30! Keep in sync with config/accel/openacc.f90 and openacc_lib.h.
31
32module openacc_kinds
33  use iso_fortran_env, only: int32
34  implicit none
35
36  public
37  private :: int32
38
39  ! When adding items, also update 'public' setting in 'module openacc' below.
40
41  integer, parameter :: acc_device_kind = int32
42
43  ! Keep in sync with include/gomp-constants.h.
44  integer (acc_device_kind), parameter :: acc_device_current = -1
45  integer (acc_device_kind), parameter :: acc_device_none = 0
46  integer (acc_device_kind), parameter :: acc_device_default = 1
47  integer (acc_device_kind), parameter :: acc_device_host = 2
48  ! integer (acc_device_kind), parameter :: acc_device_host_nonshm = 3 removed.
49  integer (acc_device_kind), parameter :: acc_device_not_host = 4
50  integer (acc_device_kind), parameter :: acc_device_nvidia = 5
51  integer (acc_device_kind), parameter :: acc_device_radeon = 8
52
53  integer, parameter :: acc_device_property_kind = int32
54  ! OpenACC 2.6/2.7/3.0 used acc_device_property; in a spec update the
55  ! missing '_kind' was added for consistency.  For backward compatibility, keep:
56  integer, parameter :: acc_device_property = acc_device_property_kind
57
58  ! Keep in sync with 'libgomp/libgomp-plugin.h:goacc_property'.
59  integer (acc_device_property_kind), parameter :: acc_property_memory = 1
60  integer (acc_device_property_kind), parameter :: acc_property_free_memory = 2
61  integer (acc_device_property_kind), parameter :: acc_property_name = int(Z'10001')
62  integer (acc_device_property_kind), parameter :: acc_property_vendor = int(Z'10002')
63  integer (acc_device_property_kind), parameter :: acc_property_driver = int(Z'10003')
64
65  integer, parameter :: acc_handle_kind = int32
66
67  ! Keep in sync with include/gomp-constants.h.
68  integer (acc_handle_kind), parameter :: acc_async_noval = -1
69  integer (acc_handle_kind), parameter :: acc_async_sync = -2
70end module openacc_kinds
71
72module openacc_internal
73  use openacc_kinds
74  implicit none
75
76  interface
77    function acc_get_num_devices_h (devicetype)
78      import
79      integer acc_get_num_devices_h
80      integer (acc_device_kind) devicetype
81    end function
82
83    subroutine acc_set_device_type_h (devicetype)
84      import
85      integer (acc_device_kind) devicetype
86    end subroutine
87
88    function acc_get_device_type_h ()
89      import
90      integer (acc_device_kind) acc_get_device_type_h
91    end function
92
93    subroutine acc_set_device_num_h (devicenum, devicetype)
94      import
95      integer devicenum
96      integer (acc_device_kind) devicetype
97    end subroutine
98
99    function acc_get_device_num_h (devicetype)
100      import
101      integer acc_get_device_num_h
102      integer (acc_device_kind) devicetype
103    end function
104
105    function acc_get_property_h (devicenum, devicetype, property)
106      use iso_c_binding, only: c_size_t
107      import
108      implicit none (type, external)
109      integer (c_size_t) :: acc_get_property_h
110      integer, value :: devicenum
111      integer (acc_device_kind), value :: devicetype
112      integer (acc_device_property_kind), value :: property
113    end function
114
115    subroutine acc_get_property_string_h (devicenum, devicetype, property, string)
116      import
117      implicit none (type, external)
118      integer, value :: devicenum
119      integer (acc_device_kind), value :: devicetype
120      integer (acc_device_property_kind), value :: property
121      character (*) :: string
122    end subroutine
123
124    function acc_async_test_h (arg)
125      logical acc_async_test_h
126      integer arg
127    end function
128
129    function acc_async_test_all_h ()
130      logical acc_async_test_all_h
131    end function
132
133    subroutine acc_wait_h (arg)
134      integer arg
135    end subroutine
136
137    subroutine acc_wait_async_h (arg, async)
138      integer arg, async
139    end subroutine
140
141    subroutine acc_wait_all_h ()
142    end subroutine
143
144    subroutine acc_wait_all_async_h (async)
145      integer async
146    end subroutine
147
148    subroutine acc_init_h (devicetype)
149      import
150      integer (acc_device_kind) devicetype
151    end subroutine
152
153    subroutine acc_shutdown_h (devicetype)
154      import
155      integer (acc_device_kind) devicetype
156    end subroutine
157
158    function acc_on_device_h (devicetype)
159      import
160      integer (acc_device_kind) devicetype
161      logical acc_on_device_h
162    end function
163
164    subroutine acc_copyin_32_h (a, len)
165      use iso_c_binding, only: c_int32_t
166      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
167      type (*), dimension (*) :: a
168      integer (c_int32_t) len
169    end subroutine
170
171    subroutine acc_copyin_64_h (a, len)
172      use iso_c_binding, only: c_int64_t
173      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
174      type (*), dimension (*) :: a
175      integer (c_int64_t) len
176    end subroutine
177
178    subroutine acc_copyin_array_h (a)
179      type (*), dimension (..), contiguous :: a
180    end subroutine
181
182    subroutine acc_present_or_copyin_32_h (a, len)
183      use iso_c_binding, only: c_int32_t
184      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
185      type (*), dimension (*) :: a
186      integer (c_int32_t) len
187    end subroutine
188
189    subroutine acc_present_or_copyin_64_h (a, len)
190      use iso_c_binding, only: c_int64_t
191      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
192      type (*), dimension (*) :: a
193      integer (c_int64_t) len
194    end subroutine
195
196    subroutine acc_present_or_copyin_array_h (a)
197      type (*), dimension (..), contiguous :: a
198    end subroutine
199
200    subroutine acc_create_32_h (a, len)
201      use iso_c_binding, only: c_int32_t
202      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
203      type (*), dimension (*) :: a
204      integer (c_int32_t) len
205    end subroutine
206
207    subroutine acc_create_64_h (a, len)
208      use iso_c_binding, only: c_int64_t
209      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
210      type (*), dimension (*) :: a
211      integer (c_int64_t) len
212    end subroutine
213
214    subroutine acc_create_array_h (a)
215      type (*), dimension (..), contiguous :: a
216    end subroutine
217
218    subroutine acc_present_or_create_32_h (a, len)
219      use iso_c_binding, only: c_int32_t
220      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
221      type (*), dimension (*) :: a
222      integer (c_int32_t) len
223    end subroutine
224
225    subroutine acc_present_or_create_64_h (a, len)
226      use iso_c_binding, only: c_int64_t
227      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
228      type (*), dimension (*) :: a
229      integer (c_int64_t) len
230    end subroutine
231
232    subroutine acc_present_or_create_array_h (a)
233      type (*), dimension (..), contiguous :: a
234    end subroutine
235
236    subroutine acc_copyout_32_h (a, len)
237      use iso_c_binding, only: c_int32_t
238      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
239      type (*), dimension (*) :: a
240      integer (c_int32_t) len
241    end subroutine
242
243    subroutine acc_copyout_64_h (a, len)
244      use iso_c_binding, only: c_int64_t
245      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
246      type (*), dimension (*) :: a
247      integer (c_int64_t) len
248    end subroutine
249
250    subroutine acc_copyout_array_h (a)
251      type (*), dimension (..), contiguous :: a
252    end subroutine
253
254    subroutine acc_copyout_finalize_32_h (a, len)
255      use iso_c_binding, only: c_int32_t
256      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
257      type (*), dimension (*) :: a
258      integer (c_int32_t) len
259    end subroutine
260
261    subroutine acc_copyout_finalize_64_h (a, len)
262      use iso_c_binding, only: c_int64_t
263      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
264      type (*), dimension (*) :: a
265      integer (c_int64_t) len
266    end subroutine
267
268    subroutine acc_copyout_finalize_array_h (a)
269      type (*), dimension (..), contiguous :: a
270    end subroutine
271
272    subroutine acc_delete_32_h (a, len)
273      use iso_c_binding, only: c_int32_t
274      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
275      type (*), dimension (*) :: a
276      integer (c_int32_t) len
277    end subroutine
278
279    subroutine acc_delete_64_h (a, len)
280      use iso_c_binding, only: c_int64_t
281      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
282      type (*), dimension (*) :: a
283      integer (c_int64_t) len
284    end subroutine
285
286    subroutine acc_delete_array_h (a)
287      type (*), dimension (..), contiguous :: a
288    end subroutine
289
290    subroutine acc_delete_finalize_32_h (a, len)
291      use iso_c_binding, only: c_int32_t
292      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
293      type (*), dimension (*) :: a
294      integer (c_int32_t) len
295    end subroutine
296
297    subroutine acc_delete_finalize_64_h (a, len)
298      use iso_c_binding, only: c_int64_t
299      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
300      type (*), dimension (*) :: a
301      integer (c_int64_t) len
302    end subroutine
303
304    subroutine acc_delete_finalize_array_h (a)
305      type (*), dimension (..), contiguous :: a
306    end subroutine
307
308    subroutine acc_update_device_32_h (a, len)
309      use iso_c_binding, only: c_int32_t
310      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
311      type (*), dimension (*) :: a
312      integer (c_int32_t) len
313    end subroutine
314
315    subroutine acc_update_device_64_h (a, len)
316      use iso_c_binding, only: c_int64_t
317      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
318      type (*), dimension (*) :: a
319      integer (c_int64_t) len
320    end subroutine
321
322    subroutine acc_update_device_array_h (a)
323      type (*), dimension (..), contiguous :: a
324    end subroutine
325
326    subroutine acc_update_self_32_h (a, len)
327      use iso_c_binding, only: c_int32_t
328      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
329      type (*), dimension (*) :: a
330      integer (c_int32_t) len
331    end subroutine
332
333    subroutine acc_update_self_64_h (a, len)
334      use iso_c_binding, only: c_int64_t
335      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
336      type (*), dimension (*) :: a
337      integer (c_int64_t) len
338    end subroutine
339
340    subroutine acc_update_self_array_h (a)
341      type (*), dimension (..), contiguous :: a
342    end subroutine
343
344    function acc_is_present_32_h (a, len)
345      use iso_c_binding, only: c_int32_t
346      logical acc_is_present_32_h
347      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
348      type (*), dimension (*) :: a
349      integer (c_int32_t) len
350    end function
351
352    function acc_is_present_64_h (a, len)
353      use iso_c_binding, only: c_int64_t
354      logical acc_is_present_64_h
355      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
356      type (*), dimension (*) :: a
357      integer (c_int64_t) len
358    end function
359
360    function acc_is_present_array_h (a)
361      logical acc_is_present_array_h
362      type (*), dimension (..), contiguous :: a
363    end function
364
365    subroutine acc_copyin_async_32_h (a, len, async)
366      use iso_c_binding, only: c_int32_t
367      use openacc_kinds, only: acc_handle_kind
368      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
369      type (*), dimension (*) :: a
370      integer (c_int32_t) len
371      integer (acc_handle_kind) async
372    end subroutine
373
374    subroutine acc_copyin_async_64_h (a, len, async)
375      use iso_c_binding, only: c_int64_t
376      use openacc_kinds, only: acc_handle_kind
377      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
378      type (*), dimension (*) :: a
379      integer (c_int64_t) len
380      integer (acc_handle_kind) async
381    end subroutine
382
383    subroutine acc_copyin_async_array_h (a, async)
384      use openacc_kinds, only: acc_handle_kind
385      type (*), dimension (..), contiguous :: a
386      integer (acc_handle_kind) async
387    end subroutine
388
389    subroutine acc_create_async_32_h (a, len, async)
390      use iso_c_binding, only: c_int32_t
391      use openacc_kinds, only: acc_handle_kind
392      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
393      type (*), dimension (*) :: a
394      integer (c_int32_t) len
395      integer (acc_handle_kind) async
396    end subroutine
397
398    subroutine acc_create_async_64_h (a, len, async)
399      use iso_c_binding, only: c_int64_t
400      use openacc_kinds, only: acc_handle_kind
401      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
402      type (*), dimension (*) :: a
403      integer (c_int64_t) len
404      integer (acc_handle_kind) async
405    end subroutine
406
407    subroutine acc_create_async_array_h (a, async)
408      use openacc_kinds, only: acc_handle_kind
409      type (*), dimension (..), contiguous :: a
410      integer (acc_handle_kind) async
411    end subroutine
412
413    subroutine acc_copyout_async_32_h (a, len, async)
414      use iso_c_binding, only: c_int32_t
415      use openacc_kinds, only: acc_handle_kind
416      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
417      type (*), dimension (*) :: a
418      integer (c_int32_t) len
419      integer (acc_handle_kind) async
420    end subroutine
421
422    subroutine acc_copyout_async_64_h (a, len, async)
423      use iso_c_binding, only: c_int64_t
424      use openacc_kinds, only: acc_handle_kind
425      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
426      type (*), dimension (*) :: a
427      integer (c_int64_t) len
428      integer (acc_handle_kind) async
429    end subroutine
430
431    subroutine acc_copyout_async_array_h (a, async)
432      use openacc_kinds, only: acc_handle_kind
433      type (*), dimension (..), contiguous :: a
434      integer (acc_handle_kind) async
435    end subroutine
436
437    subroutine acc_delete_async_32_h (a, len, async)
438      use iso_c_binding, only: c_int32_t
439      use openacc_kinds, only: acc_handle_kind
440      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
441      type (*), dimension (*) :: a
442      integer (c_int32_t) len
443      integer (acc_handle_kind) async
444    end subroutine
445
446    subroutine acc_delete_async_64_h (a, len, async)
447      use iso_c_binding, only: c_int64_t
448      use openacc_kinds, only: acc_handle_kind
449      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
450      type (*), dimension (*) :: a
451      integer (c_int64_t) len
452      integer (acc_handle_kind) async
453    end subroutine
454
455    subroutine acc_delete_async_array_h (a, async)
456      use openacc_kinds, only: acc_handle_kind
457      type (*), dimension (..), contiguous :: a
458      integer (acc_handle_kind) async
459    end subroutine
460
461    subroutine acc_update_device_async_32_h (a, len, async)
462      use iso_c_binding, only: c_int32_t
463      use openacc_kinds, only: acc_handle_kind
464      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
465      type (*), dimension (*) :: a
466      integer (c_int32_t) len
467      integer (acc_handle_kind) async
468    end subroutine
469
470    subroutine acc_update_device_async_64_h (a, len, async)
471      use iso_c_binding, only: c_int64_t
472      use openacc_kinds, only: acc_handle_kind
473      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
474      type (*), dimension (*) :: a
475      integer (c_int64_t) len
476      integer (acc_handle_kind) async
477    end subroutine
478
479    subroutine acc_update_device_async_array_h (a, async)
480      use openacc_kinds, only: acc_handle_kind
481      type (*), dimension (..), contiguous :: a
482      integer (acc_handle_kind) async
483    end subroutine
484
485    subroutine acc_update_self_async_32_h (a, len, async)
486      use iso_c_binding, only: c_int32_t
487      use openacc_kinds, only: acc_handle_kind
488      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
489      type (*), dimension (*) :: a
490      integer (c_int32_t) len
491      integer (acc_handle_kind) async
492    end subroutine
493
494    subroutine acc_update_self_async_64_h (a, len, async)
495      use iso_c_binding, only: c_int64_t
496      use openacc_kinds, only: acc_handle_kind
497      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
498      type (*), dimension (*) :: a
499      integer (c_int64_t) len
500      integer (acc_handle_kind) async
501    end subroutine
502
503    subroutine acc_update_self_async_array_h (a, async)
504      use openacc_kinds, only: acc_handle_kind
505      type (*), dimension (..), contiguous :: a
506      integer (acc_handle_kind) async
507    end subroutine
508  end interface
509
510  interface
511    function acc_get_num_devices_l (devicetype) &
512        bind (C, name = "acc_get_num_devices")
513      use iso_c_binding, only: c_int
514      integer (c_int) :: acc_get_num_devices_l
515      integer (c_int), value :: devicetype
516    end function
517
518    subroutine acc_set_device_type_l (devicetype) &
519        bind (C, name = "acc_set_device_type")
520      use iso_c_binding, only: c_int
521      integer (c_int), value :: devicetype
522    end subroutine
523
524    function acc_get_device_type_l () &
525        bind (C, name = "acc_get_device_type")
526      use iso_c_binding, only: c_int
527      integer (c_int) :: acc_get_device_type_l
528    end function
529
530    subroutine acc_set_device_num_l (devicenum, devicetype) &
531        bind (C, name = "acc_set_device_num")
532      use iso_c_binding, only: c_int
533      integer (c_int), value :: devicenum, devicetype
534    end subroutine
535
536    function acc_get_device_num_l (devicetype) &
537        bind (C, name = "acc_get_device_num")
538      use iso_c_binding, only: c_int
539      integer (c_int) :: acc_get_device_num_l
540      integer (c_int), value :: devicetype
541    end function
542
543    function acc_get_property_l (devicenum, devicetype, property) &
544        bind (C, name = "acc_get_property")
545      use iso_c_binding, only: c_int, c_size_t
546      implicit none (type, external)
547      integer (c_size_t) :: acc_get_property_l
548      integer (c_int), value :: devicenum
549      integer (c_int), value :: devicetype
550      integer (c_int), value :: property
551    end function
552
553    function acc_get_property_string_l (devicenum, devicetype, property) &
554        bind (C, name = "acc_get_property_string")
555      use iso_c_binding, only: c_int, c_ptr
556      implicit none (type, external)
557      type (c_ptr) :: acc_get_property_string_l
558      integer (c_int), value :: devicenum
559      integer (c_int), value :: devicetype
560      integer (c_int), value :: property
561    end function
562
563    function acc_async_test_l (a) &
564        bind (C, name = "acc_async_test")
565      use iso_c_binding, only: c_int
566      integer (c_int) :: acc_async_test_l
567      integer (c_int), value :: a
568    end function
569
570    function acc_async_test_all_l () &
571        bind (C, name = "acc_async_test_all")
572      use iso_c_binding, only: c_int
573      integer (c_int) :: acc_async_test_all_l
574    end function
575
576    subroutine acc_wait_l (a) &
577        bind (C, name = "acc_wait")
578      use iso_c_binding, only: c_int
579      integer (c_int), value :: a
580    end subroutine
581
582    subroutine acc_wait_async_l (arg, async) &
583        bind (C, name = "acc_wait_async")
584      use iso_c_binding, only: c_int
585      integer (c_int), value :: arg, async
586    end subroutine
587
588    subroutine acc_wait_all_l () &
589        bind (C, name = "acc_wait_all")
590      use iso_c_binding, only: c_int
591    end subroutine
592
593    subroutine acc_wait_all_async_l (async) &
594        bind (C, name = "acc_wait_all_async")
595      use iso_c_binding, only: c_int
596      integer (c_int), value :: async
597    end subroutine
598
599    subroutine acc_init_l (devicetype) &
600        bind (C, name = "acc_init")
601      use iso_c_binding, only: c_int
602      integer (c_int), value :: devicetype
603    end subroutine
604
605    subroutine acc_shutdown_l (devicetype) &
606        bind (C, name = "acc_shutdown")
607      use iso_c_binding, only: c_int
608      integer (c_int), value :: devicetype
609    end subroutine
610
611    function acc_on_device_l (devicetype) &
612        bind (C, name = "acc_on_device")
613      use iso_c_binding, only: c_int
614      integer (c_int) :: acc_on_device_l
615      integer (c_int), value :: devicetype
616    end function
617
618    subroutine acc_copyin_l (a, len) &
619        bind (C, name = "acc_copyin")
620      use iso_c_binding, only: c_size_t
621      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
622      type (*), dimension (*) :: a
623      integer (c_size_t), value :: len
624    end subroutine
625
626    subroutine acc_present_or_copyin_l (a, len) &
627        bind (C, name = "acc_present_or_copyin")
628      use iso_c_binding, only: c_size_t
629      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
630      type (*), dimension (*) :: a
631      integer (c_size_t), value :: len
632    end subroutine
633
634    subroutine acc_create_l (a, len) &
635        bind (C, name = "acc_create")
636      use iso_c_binding, only: c_size_t
637      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
638      type (*), dimension (*) :: a
639      integer (c_size_t), value :: len
640    end subroutine
641
642    subroutine acc_present_or_create_l (a, len) &
643        bind (C, name = "acc_present_or_create")
644      use iso_c_binding, only: c_size_t
645      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
646      type (*), dimension (*) :: a
647      integer (c_size_t), value :: len
648    end subroutine
649
650    subroutine acc_copyout_l (a, len) &
651        bind (C, name = "acc_copyout")
652      use iso_c_binding, only: c_size_t
653      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
654      type (*), dimension (*) :: a
655      integer (c_size_t), value :: len
656    end subroutine
657
658    subroutine acc_copyout_finalize_l (a, len) &
659        bind (C, name = "acc_copyout_finalize")
660      use iso_c_binding, only: c_size_t
661      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
662      type (*), dimension (*) :: a
663      integer (c_size_t), value :: len
664    end subroutine
665
666    subroutine acc_delete_l (a, len) &
667        bind (C, name = "acc_delete")
668      use iso_c_binding, only: c_size_t
669      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
670      type (*), dimension (*) :: a
671      integer (c_size_t), value :: len
672    end subroutine
673
674    subroutine acc_delete_finalize_l (a, len) &
675        bind (C, name = "acc_delete_finalize")
676      use iso_c_binding, only: c_size_t
677      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
678      type (*), dimension (*) :: a
679      integer (c_size_t), value :: len
680    end subroutine
681
682    subroutine acc_update_device_l (a, len) &
683        bind (C, name = "acc_update_device")
684      use iso_c_binding, only: c_size_t
685      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
686      type (*), dimension (*) :: a
687      integer (c_size_t), value :: len
688    end subroutine
689
690    subroutine acc_update_self_l (a, len) &
691        bind (C, name = "acc_update_self")
692      use iso_c_binding, only: c_size_t
693      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
694      type (*), dimension (*) :: a
695      integer (c_size_t), value :: len
696    end subroutine
697
698    function acc_is_present_l (a, len) &
699        bind (C, name = "acc_is_present")
700      use iso_c_binding, only: c_int32_t, c_size_t
701      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
702      integer (c_int32_t) :: acc_is_present_l
703      type (*), dimension (*) :: a
704      integer (c_size_t), value :: len
705    end function
706
707    subroutine acc_copyin_async_l (a, len, async) &
708        bind (C, name = "acc_copyin_async")
709      use iso_c_binding, only: c_size_t, c_int
710      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
711      type (*), dimension (*) :: a
712      integer (c_size_t), value :: len
713      integer (c_int), value :: async
714    end subroutine
715
716    subroutine acc_create_async_l (a, len, async) &
717        bind (C, name = "acc_create_async")
718      use iso_c_binding, only: c_size_t, c_int
719      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
720      type (*), dimension (*) :: a
721      integer (c_size_t), value :: len
722      integer (c_int), value :: async
723    end subroutine
724
725    subroutine acc_copyout_async_l (a, len, async) &
726        bind (C, name = "acc_copyout_async")
727      use iso_c_binding, only: c_size_t, c_int
728      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
729      type (*), dimension (*) :: a
730      integer (c_size_t), value :: len
731      integer (c_int), value :: async
732    end subroutine
733
734    subroutine acc_delete_async_l (a, len, async) &
735        bind (C, name = "acc_delete_async")
736      use iso_c_binding, only: c_size_t, c_int
737      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
738      type (*), dimension (*) :: a
739      integer (c_size_t), value :: len
740      integer (c_int), value :: async
741    end subroutine
742
743    subroutine acc_update_device_async_l (a, len, async) &
744        bind (C, name = "acc_update_device_async")
745      use iso_c_binding, only: c_size_t, c_int
746      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
747      type (*), dimension (*) :: a
748      integer (c_size_t), value :: len
749      integer (c_int), value :: async
750    end subroutine
751
752    subroutine acc_update_self_async_l (a, len, async) &
753        bind (C, name = "acc_update_self_async")
754      use iso_c_binding, only: c_size_t, c_int
755      !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
756      type (*), dimension (*) :: a
757      integer (c_size_t), value :: len
758      integer (c_int), value :: async
759    end subroutine
760  end interface
761end module openacc_internal
762
763module openacc
764  use openacc_kinds
765  use openacc_internal
766  implicit none
767
768  private
769
770  ! From openacc_kinds
771  public :: acc_device_kind
772  public :: acc_device_none, acc_device_default, acc_device_host
773  public :: acc_device_not_host, acc_device_nvidia, acc_device_radeon
774
775  public :: acc_device_property_kind, acc_device_property
776  public :: acc_property_memory, acc_property_free_memory
777  public :: acc_property_name, acc_property_vendor, acc_property_driver
778
779  public :: acc_handle_kind
780  public :: acc_async_noval, acc_async_sync
781
782  public :: openacc_version
783
784  public :: acc_get_num_devices, acc_set_device_type, acc_get_device_type
785  public :: acc_set_device_num, acc_get_device_num
786  public :: acc_get_property, acc_get_property_string
787  public :: acc_async_test, acc_async_test_all
788  public :: acc_wait, acc_async_wait, acc_wait_async
789  public :: acc_wait_all, acc_async_wait_all, acc_wait_all_async
790  public :: acc_init, acc_shutdown, acc_on_device
791  public :: acc_copyin, acc_present_or_copyin, acc_pcopyin, acc_create
792  public :: acc_present_or_create, acc_pcreate, acc_copyout, acc_delete
793  public :: acc_update_device, acc_update_self, acc_is_present
794  public :: acc_copyin_async, acc_create_async, acc_copyout_async
795  public :: acc_delete_async, acc_update_device_async, acc_update_self_async
796  public :: acc_copyout_finalize, acc_delete_finalize
797
798  integer, parameter :: openacc_version = 201711
799
800  interface acc_get_num_devices
801    procedure :: acc_get_num_devices_h
802  end interface
803
804  interface acc_set_device_type
805    procedure :: acc_set_device_type_h
806  end interface
807
808  interface acc_get_device_type
809    procedure :: acc_get_device_type_h
810  end interface
811
812  interface acc_set_device_num
813    procedure :: acc_set_device_num_h
814  end interface
815
816  interface acc_get_device_num
817    procedure :: acc_get_device_num_h
818  end interface
819
820  interface acc_get_property
821    procedure :: acc_get_property_h
822  end interface
823
824  interface acc_get_property_string
825    procedure :: acc_get_property_string_h
826  end interface
827
828  interface acc_async_test
829    procedure :: acc_async_test_h
830  end interface
831
832  interface acc_async_test_all
833    procedure :: acc_async_test_all_h
834  end interface
835
836  interface acc_wait
837    procedure :: acc_wait_h
838  end interface
839
840  ! acc_async_wait is an OpenACC 1.0 compatibility name for acc_wait.
841  interface acc_async_wait
842    procedure :: acc_wait_h
843  end interface
844
845  interface acc_wait_async
846    procedure :: acc_wait_async_h
847  end interface
848
849  interface acc_wait_all
850    procedure :: acc_wait_all_h
851  end interface
852
853  ! acc_async_wait_all is an OpenACC 1.0 compatibility name for acc_wait_all.
854  interface acc_async_wait_all
855    procedure :: acc_wait_all_h
856  end interface
857
858  interface acc_wait_all_async
859    procedure :: acc_wait_all_async_h
860  end interface
861
862  interface acc_init
863    procedure :: acc_init_h
864  end interface
865
866  interface acc_shutdown
867    procedure :: acc_shutdown_h
868  end interface
869
870  interface acc_on_device
871    procedure :: acc_on_device_h
872  end interface
873
874  ! acc_malloc: Only available in C/C++
875  ! acc_free: Only available in C/C++
876
877  ! As vendor extension, the following code supports both 32bit and 64bit
878  ! arguments for "size"; the OpenACC standard only permits default-kind
879  ! integers, which are of kind 4 (i.e. 32 bits).
880  ! Additionally, the two-argument version also takes arrays as argument.
881  ! and the one argument version also scalars. Note that the code assumes
882  ! that the arrays are contiguous.
883
884  interface acc_copyin
885    procedure :: acc_copyin_32_h
886    procedure :: acc_copyin_64_h
887    procedure :: acc_copyin_array_h
888  end interface
889
890  interface acc_present_or_copyin
891    procedure :: acc_present_or_copyin_32_h
892    procedure :: acc_present_or_copyin_64_h
893    procedure :: acc_present_or_copyin_array_h
894  end interface
895
896  interface acc_pcopyin
897    procedure :: acc_present_or_copyin_32_h
898    procedure :: acc_present_or_copyin_64_h
899    procedure :: acc_present_or_copyin_array_h
900  end interface
901
902  interface acc_create
903    procedure :: acc_create_32_h
904    procedure :: acc_create_64_h
905    procedure :: acc_create_array_h
906  end interface
907
908  interface acc_present_or_create
909    procedure :: acc_present_or_create_32_h
910    procedure :: acc_present_or_create_64_h
911    procedure :: acc_present_or_create_array_h
912  end interface
913
914  interface acc_pcreate
915    procedure :: acc_present_or_create_32_h
916    procedure :: acc_present_or_create_64_h
917    procedure :: acc_present_or_create_array_h
918  end interface
919
920  interface acc_copyout
921    procedure :: acc_copyout_32_h
922    procedure :: acc_copyout_64_h
923    procedure :: acc_copyout_array_h
924  end interface
925
926  interface acc_copyout_finalize
927    procedure :: acc_copyout_finalize_32_h
928    procedure :: acc_copyout_finalize_64_h
929    procedure :: acc_copyout_finalize_array_h
930  end interface
931
932  interface acc_delete
933    procedure :: acc_delete_32_h
934    procedure :: acc_delete_64_h
935    procedure :: acc_delete_array_h
936  end interface
937
938  interface acc_delete_finalize
939    procedure :: acc_delete_finalize_32_h
940    procedure :: acc_delete_finalize_64_h
941    procedure :: acc_delete_finalize_array_h
942  end interface
943
944  interface acc_update_device
945    procedure :: acc_update_device_32_h
946    procedure :: acc_update_device_64_h
947    procedure :: acc_update_device_array_h
948  end interface
949
950  interface acc_update_self
951    procedure :: acc_update_self_32_h
952    procedure :: acc_update_self_64_h
953    procedure :: acc_update_self_array_h
954  end interface
955
956  ! acc_map_data: Only available in C/C++
957  ! acc_unmap_data: Only available in C/C++
958  ! acc_deviceptr: Only available in C/C++
959  ! acc_hostptr: Only available in C/C++
960
961  interface acc_is_present
962    procedure :: acc_is_present_32_h
963    procedure :: acc_is_present_64_h
964    procedure :: acc_is_present_array_h
965  end interface
966
967  ! acc_memcpy_to_device: Only available in C/C++
968  ! acc_memcpy_from_device: Only available in C/C++
969
970  interface acc_copyin_async
971    procedure :: acc_copyin_async_32_h
972    procedure :: acc_copyin_async_64_h
973    procedure :: acc_copyin_async_array_h
974  end interface
975
976  interface acc_create_async
977    procedure :: acc_create_async_32_h
978    procedure :: acc_create_async_64_h
979    procedure :: acc_create_async_array_h
980  end interface
981
982  interface acc_copyout_async
983    procedure :: acc_copyout_async_32_h
984    procedure :: acc_copyout_async_64_h
985    procedure :: acc_copyout_async_array_h
986  end interface
987
988  interface acc_delete_async
989    procedure :: acc_delete_async_32_h
990    procedure :: acc_delete_async_64_h
991    procedure :: acc_delete_async_array_h
992  end interface
993
994  interface acc_update_device_async
995    procedure :: acc_update_device_async_32_h
996    procedure :: acc_update_device_async_64_h
997    procedure :: acc_update_device_async_array_h
998  end interface
999
1000  interface acc_update_self_async
1001    procedure :: acc_update_self_async_32_h
1002    procedure :: acc_update_self_async_64_h
1003    procedure :: acc_update_self_async_array_h
1004  end interface
1005
1006end module openacc
1007
1008function acc_get_num_devices_h (devicetype)
1009  use openacc_internal, only: acc_get_num_devices_l
1010  use openacc_kinds
1011  integer acc_get_num_devices_h
1012  integer (acc_device_kind) devicetype
1013  acc_get_num_devices_h = acc_get_num_devices_l (devicetype)
1014end function
1015
1016subroutine acc_set_device_type_h (devicetype)
1017  use openacc_internal, only: acc_set_device_type_l
1018  use openacc_kinds
1019  integer (acc_device_kind) devicetype
1020  call acc_set_device_type_l (devicetype)
1021end subroutine
1022
1023function acc_get_device_type_h ()
1024  use openacc_internal, only: acc_get_device_type_l
1025  use openacc_kinds
1026  integer (acc_device_kind) acc_get_device_type_h
1027  acc_get_device_type_h = acc_get_device_type_l ()
1028end function
1029
1030subroutine acc_set_device_num_h (devicenum, devicetype)
1031  use openacc_internal, only: acc_set_device_num_l
1032  use openacc_kinds
1033  integer devicenum
1034  integer (acc_device_kind) devicetype
1035  call acc_set_device_num_l (devicenum, devicetype)
1036end subroutine
1037
1038function acc_get_device_num_h (devicetype)
1039  use openacc_internal, only: acc_get_device_num_l
1040  use openacc_kinds
1041  integer acc_get_device_num_h
1042  integer (acc_device_kind) devicetype
1043  acc_get_device_num_h = acc_get_device_num_l (devicetype)
1044end function
1045
1046function acc_get_property_h (devicenum, devicetype, property)
1047  use iso_c_binding, only: c_size_t
1048  use openacc_internal, only: acc_get_property_l
1049  use openacc_kinds
1050  implicit none (type, external)
1051  integer (c_size_t) :: acc_get_property_h
1052  integer, value :: devicenum
1053  integer (acc_device_kind), value :: devicetype
1054  integer (acc_device_property_kind), value :: property
1055  acc_get_property_h = acc_get_property_l (devicenum, devicetype, property)
1056end function
1057
1058subroutine acc_get_property_string_h (devicenum, devicetype, property, string)
1059  use iso_c_binding, only: c_char, c_size_t, c_ptr, c_f_pointer, c_associated
1060  use openacc_internal, only: acc_get_property_string_l
1061  use openacc_kinds
1062  implicit none (type, external)
1063  integer, value :: devicenum
1064  integer (acc_device_kind), value :: devicetype
1065  integer (acc_device_property_kind), value :: property
1066  character (*) :: string
1067
1068  type (c_ptr) :: cptr
1069  integer(c_size_t) :: clen, slen, i
1070  character (kind=c_char, len=1), pointer, contiguous :: sptr (:)
1071
1072  interface
1073     function strlen (s) bind (C, name = "strlen")
1074       use iso_c_binding, only: c_ptr, c_size_t
1075       type (c_ptr), intent(in), value :: s
1076       integer (c_size_t) :: strlen
1077     end function strlen
1078  end interface
1079
1080  cptr = acc_get_property_string_l (devicenum, devicetype, property)
1081  string = ""
1082  if (.not. c_associated (cptr)) then
1083     return
1084  end if
1085
1086  clen = strlen (cptr)
1087  call c_f_pointer (cptr, sptr, [clen])
1088
1089  slen = min (clen, len (string, kind=c_size_t))
1090  do i = 1, slen
1091    string (i:i) = sptr (i)
1092  end do
1093end subroutine
1094
1095function acc_async_test_h (arg)
1096  use openacc_internal, only: acc_async_test_l
1097  logical acc_async_test_h
1098  integer arg
1099  acc_async_test_h = acc_async_test_l (arg) /= 0
1100end function
1101
1102function acc_async_test_all_h ()
1103  use openacc_internal, only: acc_async_test_all_l
1104  logical acc_async_test_all_h
1105  acc_async_test_all_h = acc_async_test_all_l () /= 0
1106end function
1107
1108subroutine acc_wait_h (arg)
1109  use openacc_internal, only: acc_wait_l
1110  integer arg
1111  call acc_wait_l (arg)
1112end subroutine
1113
1114subroutine acc_wait_async_h (arg, async)
1115  use openacc_internal, only: acc_wait_async_l
1116  integer arg, async
1117  call acc_wait_async_l (arg, async)
1118end subroutine
1119
1120subroutine acc_wait_all_h ()
1121  use openacc_internal, only: acc_wait_all_l
1122  call acc_wait_all_l ()
1123end subroutine
1124
1125subroutine acc_wait_all_async_h (async)
1126  use openacc_internal, only: acc_wait_all_async_l
1127  integer async
1128  call acc_wait_all_async_l (async)
1129end subroutine
1130
1131subroutine acc_init_h (devicetype)
1132  use openacc_internal, only: acc_init_l
1133  use openacc_kinds
1134  integer (acc_device_kind) devicetype
1135  call acc_init_l (devicetype)
1136end subroutine
1137
1138subroutine acc_shutdown_h (devicetype)
1139  use openacc_internal, only: acc_shutdown_l
1140  use openacc_kinds
1141  integer (acc_device_kind) devicetype
1142  call acc_shutdown_l (devicetype)
1143end subroutine
1144
1145function acc_on_device_h (devicetype)
1146  use openacc_internal, only: acc_on_device_l
1147  use openacc_kinds
1148  integer (acc_device_kind) devicetype
1149  logical acc_on_device_h
1150  acc_on_device_h = acc_on_device_l (devicetype) /= 0
1151end function
1152
1153subroutine acc_copyin_32_h (a, len)
1154  use iso_c_binding, only: c_int32_t, c_size_t
1155  use openacc_internal, only: acc_copyin_l
1156  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1157  type (*), dimension (*) :: a
1158  integer (c_int32_t) len
1159  call acc_copyin_l (a, int (len, kind = c_size_t))
1160end subroutine
1161
1162subroutine acc_copyin_64_h (a, len)
1163  use iso_c_binding, only: c_int64_t, c_size_t
1164  use openacc_internal, only: acc_copyin_l
1165  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1166  type (*), dimension (*) :: a
1167  integer (c_int64_t) len
1168  call acc_copyin_l (a, int (len, kind = c_size_t))
1169end subroutine
1170
1171subroutine acc_copyin_array_h (a)
1172  use openacc_internal, only: acc_copyin_l
1173  type (*), dimension (..), contiguous :: a
1174  call acc_copyin_l (a, sizeof (a))
1175end subroutine
1176
1177subroutine acc_present_or_copyin_32_h (a, len)
1178  use iso_c_binding, only: c_int32_t, c_size_t
1179  use openacc_internal, only: acc_present_or_copyin_l
1180  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1181  type (*), dimension (*) :: a
1182  integer (c_int32_t) len
1183  call acc_present_or_copyin_l (a, int (len, kind = c_size_t))
1184end subroutine
1185
1186subroutine acc_present_or_copyin_64_h (a, len)
1187  use iso_c_binding, only: c_int64_t, c_size_t
1188  use openacc_internal, only: acc_present_or_copyin_l
1189  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1190  type (*), dimension (*) :: a
1191  integer (c_int64_t) len
1192  call acc_present_or_copyin_l (a, int (len, kind = c_size_t))
1193end subroutine
1194
1195subroutine acc_present_or_copyin_array_h (a)
1196  use openacc_internal, only: acc_present_or_copyin_l
1197  type (*), dimension (..), contiguous :: a
1198  call acc_present_or_copyin_l (a, sizeof (a))
1199end subroutine
1200
1201subroutine acc_create_32_h (a, len)
1202  use iso_c_binding, only: c_int32_t, c_size_t
1203  use openacc_internal, only: acc_create_l
1204  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1205  type (*), dimension (*) :: a
1206  integer (c_int32_t) len
1207  call acc_create_l (a, int (len, kind = c_size_t))
1208end subroutine
1209
1210subroutine acc_create_64_h (a, len)
1211  use iso_c_binding, only: c_int64_t, c_size_t
1212  use openacc_internal, only: acc_create_l
1213  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1214  type (*), dimension (*) :: a
1215  integer (c_int64_t) len
1216  call acc_create_l (a, int (len, kind = c_size_t))
1217end subroutine
1218
1219subroutine acc_create_array_h (a)
1220  use openacc_internal, only: acc_create_l
1221  type (*), dimension (..), contiguous :: a
1222  call acc_create_l (a, sizeof (a))
1223end subroutine
1224
1225subroutine acc_present_or_create_32_h (a, len)
1226  use iso_c_binding, only: c_int32_t, c_size_t
1227  use openacc_internal, only: acc_present_or_create_l
1228  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1229  type (*), dimension (*) :: a
1230  integer (c_int32_t) len
1231  call acc_present_or_create_l (a, int (len, kind = c_size_t))
1232end subroutine
1233
1234subroutine acc_present_or_create_64_h (a, len)
1235  use iso_c_binding, only: c_int64_t, c_size_t
1236  use openacc_internal, only: acc_present_or_create_l
1237  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1238  type (*), dimension (*) :: a
1239  integer (c_int64_t) len
1240  call acc_present_or_create_l (a, int (len, kind = c_size_t))
1241end subroutine
1242
1243subroutine acc_present_or_create_array_h (a)
1244  use openacc_internal, only: acc_present_or_create_l
1245  type (*), dimension (..), contiguous :: a
1246  call acc_present_or_create_l (a, sizeof (a))
1247end subroutine
1248
1249subroutine acc_copyout_32_h (a, len)
1250  use iso_c_binding, only: c_int32_t, c_size_t
1251  use openacc_internal, only: acc_copyout_l
1252  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1253  type (*), dimension (*) :: a
1254  integer (c_int32_t) len
1255  call acc_copyout_l (a, int (len, kind = c_size_t))
1256end subroutine
1257
1258subroutine acc_copyout_64_h (a, len)
1259  use iso_c_binding, only: c_int64_t, c_size_t
1260  use openacc_internal, only: acc_copyout_l
1261  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1262  type (*), dimension (*) :: a
1263  integer (c_int64_t) len
1264  call acc_copyout_l (a, int (len, kind = c_size_t))
1265end subroutine
1266
1267subroutine acc_copyout_array_h (a)
1268  use openacc_internal, only: acc_copyout_l
1269  type (*), dimension (..), contiguous :: a
1270  call acc_copyout_l (a, sizeof (a))
1271end subroutine
1272
1273subroutine acc_copyout_finalize_32_h (a, len)
1274  use iso_c_binding, only: c_int32_t, c_size_t
1275  use openacc_internal, only: acc_copyout_finalize_l
1276  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1277  type (*), dimension (*) :: a
1278  integer (c_int32_t) len
1279  call acc_copyout_finalize_l (a, int (len, kind = c_size_t))
1280end subroutine
1281
1282subroutine acc_copyout_finalize_64_h (a, len)
1283  use iso_c_binding, only: c_int64_t, c_size_t
1284  use openacc_internal, only: acc_copyout_finalize_l
1285  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1286  type (*), dimension (*) :: a
1287  integer (c_int64_t) len
1288  call acc_copyout_finalize_l (a, int (len, kind = c_size_t))
1289end subroutine
1290
1291subroutine acc_copyout_finalize_array_h (a)
1292  use openacc_internal, only: acc_copyout_finalize_l
1293  type (*), dimension (..), contiguous :: a
1294  call acc_copyout_finalize_l (a, sizeof (a))
1295end subroutine
1296
1297subroutine acc_delete_32_h (a, len)
1298  use iso_c_binding, only: c_int32_t, c_size_t
1299  use openacc_internal, only: acc_delete_l
1300  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1301  type (*), dimension (*) :: a
1302  integer (c_int32_t) len
1303  call acc_delete_l (a, int (len, kind = c_size_t))
1304end subroutine
1305
1306subroutine acc_delete_64_h (a, len)
1307  use iso_c_binding, only: c_int64_t, c_size_t
1308  use openacc_internal, only: acc_delete_l
1309  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1310  type (*), dimension (*) :: a
1311  integer (c_int64_t) len
1312  call acc_delete_l (a, int (len, kind = c_size_t))
1313end subroutine
1314
1315subroutine acc_delete_array_h (a)
1316  use openacc_internal, only: acc_delete_l
1317  type (*), dimension (..), contiguous :: a
1318  call acc_delete_l (a, sizeof (a))
1319end subroutine
1320
1321subroutine acc_delete_finalize_32_h (a, len)
1322  use iso_c_binding, only: c_int32_t, c_size_t
1323  use openacc_internal, only: acc_delete_finalize_l
1324  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1325  type (*), dimension (*) :: a
1326  integer (c_int32_t) len
1327  call acc_delete_finalize_l (a, int (len, kind = c_size_t))
1328end subroutine
1329
1330subroutine acc_delete_finalize_64_h (a, len)
1331  use iso_c_binding, only: c_int64_t, c_size_t
1332  use openacc_internal, only: acc_delete_finalize_l
1333  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1334  type (*), dimension (*) :: a
1335  integer (c_int64_t) len
1336  call acc_delete_finalize_l (a, int (len, kind = c_size_t))
1337end subroutine
1338
1339subroutine acc_delete_finalize_array_h (a)
1340  use openacc_internal, only: acc_delete_finalize_l
1341  type (*), dimension (..), contiguous :: a
1342  call acc_delete_finalize_l (a, sizeof (a))
1343end subroutine
1344
1345subroutine acc_update_device_32_h (a, len)
1346  use iso_c_binding, only: c_int32_t, c_size_t
1347  use openacc_internal, only: acc_update_device_l
1348  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1349  type (*), dimension (*) :: a
1350  integer (c_int32_t) len
1351  call acc_update_device_l (a, int (len, kind = c_size_t))
1352end subroutine
1353
1354subroutine acc_update_device_64_h (a, len)
1355  use iso_c_binding, only: c_int64_t, c_size_t
1356  use openacc_internal, only: acc_update_device_l
1357  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1358  type (*), dimension (*) :: a
1359  integer (c_int64_t) len
1360  call acc_update_device_l (a, int (len, kind = c_size_t))
1361end subroutine
1362
1363subroutine acc_update_device_array_h (a)
1364  use openacc_internal, only: acc_update_device_l
1365  type (*), dimension (..), contiguous :: a
1366  call acc_update_device_l (a, sizeof (a))
1367end subroutine
1368
1369subroutine acc_update_self_32_h (a, len)
1370  use iso_c_binding, only: c_int32_t, c_size_t
1371  use openacc_internal, only: acc_update_self_l
1372  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1373  type (*), dimension (*) :: a
1374  integer (c_int32_t) len
1375  call acc_update_self_l (a, int (len, kind = c_size_t))
1376end subroutine
1377
1378subroutine acc_update_self_64_h (a, len)
1379  use iso_c_binding, only: c_int64_t, c_size_t
1380  use openacc_internal, only: acc_update_self_l
1381  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1382  type (*), dimension (*) :: a
1383  integer (c_int64_t) len
1384  call acc_update_self_l (a, int (len, kind = c_size_t))
1385end subroutine
1386
1387subroutine acc_update_self_array_h (a)
1388  use openacc_internal, only: acc_update_self_l
1389  type (*), dimension (..), contiguous :: a
1390  call acc_update_self_l (a, sizeof (a))
1391end subroutine
1392
1393function acc_is_present_32_h (a, len)
1394  use iso_c_binding, only: c_int32_t, c_size_t
1395  use openacc_internal, only: acc_is_present_l
1396  logical acc_is_present_32_h
1397  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1398  type (*), dimension (*) :: a
1399  integer (c_int32_t) len
1400  acc_is_present_32_h = acc_is_present_l (a, int (len, kind = c_size_t)) /= 0
1401end function
1402
1403function acc_is_present_64_h (a, len)
1404  use iso_c_binding, only: c_int64_t, c_size_t
1405  use openacc_internal, only: acc_is_present_l
1406  logical acc_is_present_64_h
1407  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1408  type (*), dimension (*) :: a
1409  integer (c_int64_t) len
1410  acc_is_present_64_h = acc_is_present_l (a, int (len, kind = c_size_t)) /= 0
1411end function
1412
1413function acc_is_present_array_h (a)
1414  use openacc_internal, only: acc_is_present_l
1415  logical acc_is_present_array_h
1416  type (*), dimension (..), contiguous :: a
1417  acc_is_present_array_h = acc_is_present_l (a, sizeof (a)) /= 0
1418end function
1419
1420subroutine acc_copyin_async_32_h (a, len, async)
1421  use iso_c_binding, only: c_int32_t, c_size_t, c_int
1422  use openacc_internal, only: acc_copyin_async_l
1423  use openacc_kinds, only: acc_handle_kind
1424  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1425  type (*), dimension (*) :: a
1426  integer (c_int32_t) len
1427  integer (acc_handle_kind) async
1428  call acc_copyin_async_l (a, int (len, kind = c_size_t), int (async, kind = c_int))
1429end subroutine
1430
1431subroutine acc_copyin_async_64_h (a, len, async)
1432  use iso_c_binding, only: c_int64_t, c_size_t, c_int
1433  use openacc_internal, only: acc_copyin_async_l
1434  use openacc_kinds, only: acc_handle_kind
1435  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1436  type (*), dimension (*) :: a
1437  integer (c_int64_t) len
1438  integer (acc_handle_kind) async
1439  call acc_copyin_async_l (a, int (len, kind = c_size_t), int (async, kind = c_int))
1440end subroutine
1441
1442subroutine acc_copyin_async_array_h (a, async)
1443  use iso_c_binding, only: c_int
1444  use openacc_internal, only: acc_copyin_async_l
1445  use openacc_kinds, only: acc_handle_kind
1446  type (*), dimension (..), contiguous :: a
1447  integer (acc_handle_kind) async
1448  call acc_copyin_async_l (a, sizeof (a), int (async, kind = c_int))
1449end subroutine
1450
1451subroutine acc_create_async_32_h (a, len, async)
1452  use iso_c_binding, only: c_int32_t, c_size_t, c_int
1453  use openacc_internal, only: acc_create_async_l
1454  use openacc_kinds, only: acc_handle_kind
1455  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1456  type (*), dimension (*) :: a
1457  integer (c_int32_t) len
1458  integer (acc_handle_kind) async
1459  call acc_create_async_l (a, int (len, kind = c_size_t), int (async, kind = c_int))
1460end subroutine
1461
1462subroutine acc_create_async_64_h (a, len, async)
1463  use iso_c_binding, only: c_int64_t, c_size_t, c_int
1464  use openacc_internal, only: acc_create_async_l
1465  use openacc_kinds, only: acc_handle_kind
1466  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1467  type (*), dimension (*) :: a
1468  integer (c_int64_t) len
1469  integer (acc_handle_kind) async
1470  call acc_create_async_l (a, int (len, kind = c_size_t), int (async, kind = c_int))
1471end subroutine
1472
1473subroutine acc_create_async_array_h (a, async)
1474  use iso_c_binding, only: c_int
1475  use openacc_internal, only: acc_create_async_l
1476  use openacc_kinds, only: acc_handle_kind
1477  type (*), dimension (..), contiguous :: a
1478  integer (acc_handle_kind) async
1479  call acc_create_async_l (a, sizeof (a), int (async, kind = c_int))
1480end subroutine
1481
1482subroutine acc_copyout_async_32_h (a, len, async)
1483  use iso_c_binding, only: c_int32_t, c_size_t, c_int
1484  use openacc_internal, only: acc_copyout_async_l
1485  use openacc_kinds, only: acc_handle_kind
1486  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1487  type (*), dimension (*) :: a
1488  integer (c_int32_t) len
1489  integer (acc_handle_kind) async
1490  call acc_copyout_async_l (a, int (len, kind = c_size_t), int (async, kind = c_int))
1491end subroutine
1492
1493subroutine acc_copyout_async_64_h (a, len, async)
1494  use iso_c_binding, only: c_int64_t, c_size_t, c_int
1495  use openacc_internal, only: acc_copyout_async_l
1496  use openacc_kinds, only: acc_handle_kind
1497  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1498  type (*), dimension (*) :: a
1499  integer (c_int64_t) len
1500  integer (acc_handle_kind) async
1501  call acc_copyout_async_l (a, int (len, kind = c_size_t), int (async, kind = c_int))
1502end subroutine
1503
1504subroutine acc_copyout_async_array_h (a, async)
1505  use iso_c_binding, only: c_int
1506  use openacc_internal, only: acc_copyout_async_l
1507  use openacc_kinds, only: acc_handle_kind
1508  type (*), dimension (..), contiguous :: a
1509  integer (acc_handle_kind) async
1510  call acc_copyout_async_l (a, sizeof (a), int (async, kind = c_int))
1511end subroutine
1512
1513subroutine acc_delete_async_32_h (a, len, async)
1514  use iso_c_binding, only: c_int32_t, c_size_t, c_int
1515  use openacc_internal, only: acc_delete_async_l
1516  use openacc_kinds, only: acc_handle_kind
1517  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1518  type (*), dimension (*) :: a
1519  integer (c_int32_t) len
1520  integer (acc_handle_kind) async
1521  call acc_delete_async_l (a, int (len, kind = c_size_t), int (async, kind = c_int))
1522end subroutine
1523
1524subroutine acc_delete_async_64_h (a, len, async)
1525  use iso_c_binding, only: c_int64_t, c_size_t, c_int
1526  use openacc_internal, only: acc_delete_async_l
1527  use openacc_kinds, only: acc_handle_kind
1528  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1529  type (*), dimension (*) :: a
1530  integer (c_int64_t) len
1531  integer (acc_handle_kind) async
1532  call acc_delete_async_l (a, int (len, kind = c_size_t), int (async, kind = c_int))
1533end subroutine
1534
1535subroutine acc_delete_async_array_h (a, async)
1536  use iso_c_binding, only: c_int
1537  use openacc_internal, only: acc_delete_async_l
1538  use openacc_kinds, only: acc_handle_kind
1539  type (*), dimension (..), contiguous :: a
1540  integer (acc_handle_kind) async
1541  call acc_delete_async_l (a, sizeof (a), int (async, kind = c_int))
1542end subroutine
1543
1544subroutine acc_update_device_async_32_h (a, len, async)
1545  use iso_c_binding, only: c_int32_t, c_size_t, c_int
1546  use openacc_internal, only: acc_update_device_async_l
1547  use openacc_kinds, only: acc_handle_kind
1548  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1549  type (*), dimension (*) :: a
1550  integer (c_int32_t) len
1551  integer (acc_handle_kind) async
1552  call acc_update_device_async_l (a, int (len, kind = c_size_t), int (async, kind = c_int))
1553end subroutine
1554
1555subroutine acc_update_device_async_64_h (a, len, async)
1556  use iso_c_binding, only: c_int64_t, c_size_t, c_int
1557  use openacc_internal, only: acc_update_device_async_l
1558  use openacc_kinds, only: acc_handle_kind
1559  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1560  type (*), dimension (*) :: a
1561  integer (c_int64_t) len
1562  integer (acc_handle_kind) async
1563  call acc_update_device_async_l (a, int (len, kind = c_size_t), int (async, kind = c_int))
1564end subroutine
1565
1566subroutine acc_update_device_async_array_h (a, async)
1567  use iso_c_binding, only: c_int
1568  use openacc_internal, only: acc_update_device_async_l
1569  use openacc_kinds, only: acc_handle_kind
1570  type (*), dimension (..), contiguous :: a
1571  integer (acc_handle_kind) async
1572  call acc_update_device_async_l (a, sizeof (a), int (async, kind = c_int))
1573end subroutine
1574
1575subroutine acc_update_self_async_32_h (a, len, async)
1576  use iso_c_binding, only: c_int32_t, c_size_t, c_int
1577  use openacc_internal, only: acc_update_self_async_l
1578  use openacc_kinds, only: acc_handle_kind
1579  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1580  type (*), dimension (*) :: a
1581  integer (c_int32_t) len
1582  integer (acc_handle_kind) async
1583  call acc_update_self_async_l (a, int (len, kind = c_size_t), int (async, kind = c_int))
1584end subroutine
1585
1586subroutine acc_update_self_async_64_h (a, len, async)
1587  use iso_c_binding, only: c_int64_t, c_size_t, c_int
1588  use openacc_internal, only: acc_update_self_async_l
1589  use openacc_kinds, only: acc_handle_kind
1590  !GCC$ ATTRIBUTES NO_ARG_CHECK :: a
1591  type (*), dimension (*) :: a
1592  integer (c_int64_t) len
1593  integer (acc_handle_kind) async
1594  call acc_update_self_async_l (a, int (len, kind = c_size_t), int (async, kind = c_int))
1595end subroutine
1596
1597subroutine acc_update_self_async_array_h (a, async)
1598  use iso_c_binding, only: c_int
1599  use openacc_internal, only: acc_update_self_async_l
1600  use openacc_kinds, only: acc_handle_kind
1601  type (*), dimension (..), contiguous :: a
1602  integer (acc_handle_kind) async
1603  call acc_update_self_async_l (a, sizeof (a), int (async, kind = c_int))
1604end subroutine
1605