xref: /netbsd-src/external/gpl3/gcc/dist/libgomp/omp_lib.f90.in (revision bdc22b2e01993381dcefeff2bc9b56ca75a4235c)
1!  Copyright (C) 2005-2016 Free Software Foundation, Inc.
2!  Contributed by Jakub Jelinek <jakub@redhat.com>.
3
4!  This file is part of the GNU Offloading and Multi Processing Library
5!  (libgomp).
6
7!  Libgomp is free software; you can redistribute it and/or modify it
8!  under the terms of the GNU General Public License as published by
9!  the Free Software Foundation; either version 3, or (at your option)
10!  any later version.
11
12!  Libgomp is distributed in the hope that it will be useful, but WITHOUT ANY
13!  WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
14!  FOR A PARTICULAR PURPOSE.  See the GNU General Public License for
15!  more details.
16
17!  Under Section 7 of GPL version 3, you are granted additional
18!  permissions described in the GCC Runtime Library Exception, version
19!  3.1, as published by the Free Software Foundation.
20
21!  You should have received a copy of the GNU General Public License and
22!  a copy of the GCC Runtime Library Exception along with this program;
23!  see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
24!  <http://www.gnu.org/licenses/>.
25
26      module omp_lib_kinds
27        implicit none
28        integer, parameter :: omp_lock_kind = @OMP_LOCK_KIND@
29        integer, parameter :: omp_nest_lock_kind = @OMP_NEST_LOCK_KIND@
30        integer, parameter :: omp_sched_kind = 4
31        integer, parameter :: omp_proc_bind_kind = 4
32        integer, parameter :: omp_lock_hint_kind = 4
33        integer (omp_sched_kind), parameter :: omp_sched_static = 1
34        integer (omp_sched_kind), parameter :: omp_sched_dynamic = 2
35        integer (omp_sched_kind), parameter :: omp_sched_guided = 3
36        integer (omp_sched_kind), parameter :: omp_sched_auto = 4
37        integer (omp_proc_bind_kind), &
38                 parameter :: omp_proc_bind_false = 0
39        integer (omp_proc_bind_kind), &
40                 parameter :: omp_proc_bind_true = 1
41        integer (omp_proc_bind_kind), &
42                 parameter :: omp_proc_bind_master = 2
43        integer (omp_proc_bind_kind), &
44                 parameter :: omp_proc_bind_close = 3
45        integer (omp_proc_bind_kind), &
46                 parameter :: omp_proc_bind_spread = 4
47        integer (omp_lock_hint_kind), &
48                 parameter :: omp_lock_hint_none = 0
49        integer (omp_lock_hint_kind), &
50                 parameter :: omp_lock_hint_uncontended = 1
51        integer (omp_lock_hint_kind), &
52                 parameter :: omp_lock_hint_contended = 2
53        integer (omp_lock_hint_kind), &
54                 parameter :: omp_lock_hint_nonspeculative = 4
55        integer (omp_lock_hint_kind), &
56                 parameter :: omp_lock_hint_speculative = 8
57      end module
58
59      module omp_lib
60        use omp_lib_kinds
61        implicit none
62        integer, parameter :: openmp_version = 201307
63
64        interface
65          subroutine omp_init_lock (svar)
66            use omp_lib_kinds
67            integer (omp_lock_kind), intent (out) :: svar
68          end subroutine omp_init_lock
69        end interface
70
71        interface
72          subroutine omp_init_lock_with_hint (svar, hint)
73            use omp_lib_kinds
74            integer (omp_lock_kind), intent (out) :: svar
75            integer (omp_lock_hint_kind), intent (in) :: hint
76          end subroutine omp_init_lock_with_hint
77        end interface
78
79        interface
80          subroutine omp_init_nest_lock (nvar)
81            use omp_lib_kinds
82            integer (omp_nest_lock_kind), intent (out) :: nvar
83          end subroutine omp_init_nest_lock
84        end interface
85
86        interface
87          subroutine omp_init_nest_lock_with_hint (nvar, hint)
88            use omp_lib_kinds
89            integer (omp_nest_lock_kind), intent (out) :: nvar
90            integer (omp_lock_hint_kind), intent (in) :: hint
91          end subroutine omp_init_nest_lock_with_hint
92        end interface
93
94        interface
95          subroutine omp_destroy_lock (svar)
96            use omp_lib_kinds
97            integer (omp_lock_kind), intent (inout) :: svar
98          end subroutine omp_destroy_lock
99        end interface
100
101        interface
102          subroutine omp_destroy_nest_lock (nvar)
103            use omp_lib_kinds
104            integer (omp_nest_lock_kind), intent (inout) :: nvar
105          end subroutine omp_destroy_nest_lock
106        end interface
107
108        interface
109          subroutine omp_set_lock (svar)
110            use omp_lib_kinds
111            integer (omp_lock_kind), intent (inout) :: svar
112          end subroutine omp_set_lock
113        end interface
114
115        interface
116          subroutine omp_set_nest_lock (nvar)
117            use omp_lib_kinds
118            integer (omp_nest_lock_kind), intent (inout) :: nvar
119          end subroutine omp_set_nest_lock
120        end interface
121
122        interface
123          subroutine omp_unset_lock (svar)
124            use omp_lib_kinds
125            integer (omp_lock_kind), intent (inout) :: svar
126          end subroutine omp_unset_lock
127        end interface
128
129        interface
130          subroutine omp_unset_nest_lock (nvar)
131            use omp_lib_kinds
132            integer (omp_nest_lock_kind), intent (inout) :: nvar
133          end subroutine omp_unset_nest_lock
134        end interface
135
136        interface omp_set_dynamic
137          subroutine omp_set_dynamic (dynamic_threads)
138            logical (4), intent (in) :: dynamic_threads
139          end subroutine omp_set_dynamic
140          subroutine omp_set_dynamic_8 (dynamic_threads)
141            logical (8), intent (in) :: dynamic_threads
142          end subroutine omp_set_dynamic_8
143        end interface
144
145        interface omp_set_nested
146          subroutine omp_set_nested (nested)
147            logical (4), intent (in) :: nested
148          end subroutine omp_set_nested
149          subroutine omp_set_nested_8 (nested)
150            logical (8), intent (in) :: nested
151          end subroutine omp_set_nested_8
152        end interface
153
154        interface omp_set_num_threads
155          subroutine omp_set_num_threads (num_threads)
156            integer (4), intent (in) :: num_threads
157          end subroutine omp_set_num_threads
158          subroutine omp_set_num_threads_8 (num_threads)
159            integer (8), intent (in) :: num_threads
160          end subroutine omp_set_num_threads_8
161        end interface
162
163        interface
164          function omp_get_dynamic ()
165            logical (4) :: omp_get_dynamic
166          end function omp_get_dynamic
167        end interface
168
169        interface
170          function omp_get_nested ()
171            logical (4) :: omp_get_nested
172          end function omp_get_nested
173        end interface
174
175        interface
176          function omp_in_parallel ()
177            logical (4) :: omp_in_parallel
178          end function omp_in_parallel
179        end interface
180
181        interface
182          function omp_test_lock (svar)
183            use omp_lib_kinds
184            logical (4) :: omp_test_lock
185            integer (omp_lock_kind), intent (inout) :: svar
186          end function omp_test_lock
187        end interface
188
189        interface
190          function omp_get_max_threads ()
191            integer (4) :: omp_get_max_threads
192          end function omp_get_max_threads
193        end interface
194
195        interface
196          function omp_get_num_procs ()
197            integer (4) :: omp_get_num_procs
198          end function omp_get_num_procs
199        end interface
200
201        interface
202          function omp_get_num_threads ()
203            integer (4) :: omp_get_num_threads
204          end function omp_get_num_threads
205        end interface
206
207        interface
208          function omp_get_thread_num ()
209            integer (4) :: omp_get_thread_num
210          end function omp_get_thread_num
211        end interface
212
213        interface
214          function omp_test_nest_lock (nvar)
215            use omp_lib_kinds
216            integer (4) :: omp_test_nest_lock
217            integer (omp_nest_lock_kind), intent (inout) :: nvar
218          end function omp_test_nest_lock
219        end interface
220
221        interface
222          function omp_get_wtick ()
223            double precision :: omp_get_wtick
224          end function omp_get_wtick
225        end interface
226
227        interface
228          function omp_get_wtime ()
229            double precision :: omp_get_wtime
230          end function omp_get_wtime
231        end interface
232
233        interface omp_set_schedule
234          subroutine omp_set_schedule (kind, chunk_size)
235            use omp_lib_kinds
236            integer (omp_sched_kind), intent (in) :: kind
237            integer (4), intent (in) :: chunk_size
238          end subroutine omp_set_schedule
239          subroutine omp_set_schedule_8 (kind, chunk_size)
240            use omp_lib_kinds
241            integer (omp_sched_kind), intent (in) :: kind
242            integer (8), intent (in) :: chunk_size
243          end subroutine omp_set_schedule_8
244         end interface
245
246        interface omp_get_schedule
247          subroutine omp_get_schedule (kind, chunk_size)
248            use omp_lib_kinds
249            integer (omp_sched_kind), intent (out) :: kind
250            integer (4), intent (out) :: chunk_size
251          end subroutine omp_get_schedule
252          subroutine omp_get_schedule_8 (kind, chunk_size)
253            use omp_lib_kinds
254            integer (omp_sched_kind), intent (out) :: kind
255            integer (8), intent (out) :: chunk_size
256          end subroutine omp_get_schedule_8
257         end interface
258
259        interface
260          function omp_get_thread_limit ()
261            integer (4) :: omp_get_thread_limit
262          end function omp_get_thread_limit
263        end interface
264
265        interface omp_set_max_active_levels
266          subroutine omp_set_max_active_levels (max_levels)
267            integer (4), intent (in) :: max_levels
268          end subroutine omp_set_max_active_levels
269          subroutine omp_set_max_active_levels_8 (max_levels)
270            integer (8), intent (in) :: max_levels
271          end subroutine omp_set_max_active_levels_8
272        end interface
273
274        interface
275          function omp_get_max_active_levels ()
276            integer (4) :: omp_get_max_active_levels
277          end function omp_get_max_active_levels
278        end interface
279
280        interface
281          function omp_get_level ()
282            integer (4) :: omp_get_level
283          end function omp_get_level
284        end interface
285
286        interface omp_get_ancestor_thread_num
287          function omp_get_ancestor_thread_num (level)
288            integer (4), intent (in) :: level
289            integer (4) :: omp_get_ancestor_thread_num
290          end function omp_get_ancestor_thread_num
291          function omp_get_ancestor_thread_num_8 (level)
292            integer (8), intent (in) :: level
293            integer (4) :: omp_get_ancestor_thread_num_8
294          end function omp_get_ancestor_thread_num_8
295        end interface
296
297        interface omp_get_team_size
298          function omp_get_team_size (level)
299            integer (4), intent (in) :: level
300            integer (4) :: omp_get_team_size
301          end function omp_get_team_size
302          function omp_get_team_size_8 (level)
303            integer (8), intent (in) :: level
304            integer (4) :: omp_get_team_size_8
305          end function omp_get_team_size_8
306        end interface
307
308        interface
309          function omp_get_active_level ()
310            integer (4) :: omp_get_active_level
311          end function omp_get_active_level
312        end interface
313
314        interface
315          function omp_in_final ()
316            logical (4) :: omp_in_final
317          end function omp_in_final
318        end interface
319
320        interface
321          function omp_get_cancellation ()
322            logical (4) :: omp_get_cancellation
323          end function omp_get_cancellation
324        end interface
325
326        interface
327          function omp_get_proc_bind ()
328            use omp_lib_kinds
329            integer (omp_proc_bind_kind) :: omp_get_proc_bind
330          end function omp_get_proc_bind
331        end interface
332
333        interface
334          function omp_get_num_places ()
335            integer (4) :: omp_get_num_places
336          end function omp_get_num_places
337        end interface
338
339        interface omp_get_place_num_procs
340          function omp_get_place_num_procs (place_num)
341            integer (4), intent(in) :: place_num
342            integer (4) :: omp_get_place_num_procs
343          end function omp_get_place_num_procs
344
345          function omp_get_place_num_procs_8 (place_num)
346            integer (8), intent(in) :: place_num
347            integer (4) :: omp_get_place_num_procs_8
348          end function omp_get_place_num_procs_8
349        end interface
350
351        interface omp_get_place_proc_ids
352          subroutine omp_get_place_proc_ids (place_num, ids)
353            integer (4), intent(in) :: place_num
354            integer (4), intent(out) :: ids(*)
355          end subroutine omp_get_place_proc_ids
356
357          subroutine omp_get_place_proc_ids_8 (place_num, ids)
358            integer (8), intent(in) :: place_num
359            integer (8), intent(out) :: ids(*)
360          end subroutine omp_get_place_proc_ids_8
361        end interface
362
363        interface
364          function omp_get_place_num ()
365            integer (4) :: omp_get_place_num
366          end function omp_get_place_num
367        end interface
368
369        interface
370          function omp_get_partition_num_places ()
371            integer (4) :: omp_get_partition_num_places
372          end function omp_get_partition_num_places
373        end interface
374
375        interface omp_get_partition_place_nums
376          subroutine omp_get_partition_place_nums (place_nums)
377            integer (4), intent(out) :: place_nums(*)
378          end subroutine omp_get_partition_place_nums
379
380          subroutine omp_get_partition_place_nums_8 (place_nums)
381            integer (8), intent(out) :: place_nums(*)
382          end subroutine omp_get_partition_place_nums_8
383        end interface
384
385        interface omp_set_default_device
386          subroutine omp_set_default_device (device_num)
387            integer (4), intent (in) :: device_num
388          end subroutine omp_set_default_device
389          subroutine omp_set_default_device_8 (device_num)
390            integer (8), intent (in) :: device_num
391          end subroutine omp_set_default_device_8
392        end interface
393
394        interface
395          function omp_get_default_device ()
396            integer (4) :: omp_get_default_device
397          end function omp_get_default_device
398        end interface
399
400        interface
401          function omp_get_num_devices ()
402            integer (4) :: omp_get_num_devices
403          end function omp_get_num_devices
404        end interface
405
406        interface
407          function omp_get_num_teams ()
408            integer (4) :: omp_get_num_teams
409          end function omp_get_num_teams
410        end interface
411
412        interface
413          function omp_get_team_num ()
414            integer (4) :: omp_get_team_num
415          end function omp_get_team_num
416        end interface
417
418        interface
419          function omp_is_initial_device ()
420            logical (4) :: omp_is_initial_device
421          end function omp_is_initial_device
422        end interface
423
424        interface
425          function omp_get_initial_device ()
426            integer (4) :: omp_get_initial_device
427          end function omp_get_initial_device
428        end interface
429
430        interface
431          function omp_get_max_task_priority ()
432            integer (4) :: omp_get_max_task_priority
433          end function omp_get_max_task_priority
434        end interface
435
436      end module omp_lib
437