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