ROMS
Loading...
Searching...
No Matches
mp_routines.F
Go to the documentation of this file.
1#include "cppdefs.h"
2!
3!git $Id$
4!================================================== Hernan G. Arango ===
5! Copyright (c) 2002-2025 The ROMS Group !
6! Licensed under a MIT/X style license !
7! See License_ROMS.md !
8!=======================================================================
9! !
10! This package contains multi-processing routines used during !
11! parallel applications: !
12! !
13! my_getarg Returns the argument from command-line. !
14! my_getpid Returns process ID of the calling process. !
15! my_numthreads Returns number of threads that would !
16! execute in parallel regions. !
17! my_threadnum Returns which thread number is working !
18! in a parallel region. !
19! my_wtime Returns an elapsed wall time in seconds since !
20! an arbitrary time in the past. !
21! !
22!=======================================================================
23
24#ifdef DISTRIBUTE
25!
26!-----------------------------------------------------------------------
27 SUBROUTINE my_getarg (Iarg, Carg)
28!-----------------------------------------------------------------------
29!
30 USE mod_kinds
31# if defined NAGFOR
32 USE f90_unix_env
33# endif
34!
35 implicit none
36!
37! Imported variable declarations.
38!
39 integer, intent(in) :: Iarg
40 character (len=*), intent(inout) :: Carg
41!
42! Local variable declarations.
43!
44 integer :: Lstr, ierror
45!
46! Get argument value from command-line.
47!
48# ifdef CRAY
49 CALL pxfgetarg (iarg, carg, lstr, ierror)
50# else
51 CALL getarg (iarg, carg)
52# endif
53!
54 RETURN
55 END SUBROUTINE my_getarg
56#endif
57!
58!-----------------------------------------------------------------------
59 FUNCTION my_getpid ()
60!-----------------------------------------------------------------------
61!
62 USE mod_kinds
63#if defined NAGFOR
64 USE f90_unix_env
65#endif
66!
67 implicit none
68!
69#ifndef NAGFOR
70 integer :: getpid
71#endif
72 integer :: my_getpid
73!
74! Get ID of the calling process.
75!
76#if defined CRAYX1
77 my_getpid=0
78#elif defined CYGWIN
79 my_getpid=0
80#else
81 my_getpid=getpid()
82#endif
83!
84 RETURN
85 END FUNCTION my_getpid
86!
87!-----------------------------------------------------------------------
88 FUNCTION my_numthreads ()
89!-----------------------------------------------------------------------
90!
91 USE mod_kinds
92!
93 implicit none
94!
95 integer :: my_numthreads
96!
97! Get the number of Persistent Execution Threads (PET) that would
98! execute in parallel regions.
99!
100#ifdef DISTRIBUTE
102#elif defined _OPENMP
103 integer :: omp_get_max_threads
104!! integer :: omp_get_num_threads
105
106 my_numthreads=omp_get_max_threads()
107!! my_numthreads=omp_get_num_threads()
108#elif defined SGI
109 integer :: mp_numthreads
110
111 my_numthreads=mp_numthreads()
112#else
114#endif
115!
116 RETURN
117 END FUNCTION my_numthreads
118!
119!-----------------------------------------------------------------------
120 FUNCTION my_threadnum ()
121!-----------------------------------------------------------------------
122!
123 USE mod_kinds
124!
125 implicit none
126!
127 integer :: my_threadnum
128!
129! Get the Persistent Execution Thread (PET) number is working that is
130! is working in a parallel region.
131!
132#if defined _OPENMP
133 integer :: omp_get_thread_num
134
135 my_threadnum=omp_get_thread_num()
136#elif defined SGI
137 integer :: mp_my_threadnum
138
139 my_threadnum=mp_my_threadnum()
140#else
142#endif
143!
144 RETURN
145 END FUNCTION my_threadnum
146!
147!-----------------------------------------------------------------------
148 FUNCTION my_wtime (wtime)
149!-----------------------------------------------------------------------
150!
151 USE mod_kinds
152!
153 implicit none
154!
155 real(r8) :: wtime(2)
156 real(r8) :: my_wtime
157#ifdef _OPENMP
158 real(r8) :: omp_get_wtime
159#endif
160#ifdef CRAYX1
161 integer :: count, count_rate, count_max
162#endif
163!
164! Get the elapsed wall time (seconds) since an arbitrary time in the
165! past.
166!
167#if defined _OPENMP
168 my_wtime=omp_get_wtime()
169#elif defined CRAYX1
170 CALL system_clock (count, count_rate, count_max)
171 my_wtime=real(count,r8)/real(count_rate,r8)
172#else
173 CALL cpu_time (wtime(1))
174 my_wtime=wtime(1)
175#endif
176!
177 RETURN
178 END FUNCTION my_wtime
real(r8) function my_wtime(wtime)
subroutine my_getarg(iarg, carg)
Definition mp_routines.F:28
integer function my_threadnum()
integer function my_getpid()
Definition mp_routines.F:60
integer function my_numthreads()
Definition mp_routines.F:89
integer, parameter r8
Definition mod_kinds.F:28