/[MITgcm]/MITgcm/eesupp/src/global_max.F
ViewVC logotype

Contents of /MITgcm/eesupp/src/global_max.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.6 - (show annotations) (download)
Tue May 18 17:35:23 1999 UTC (25 years, 1 month ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint28, checkpoint29, checkpoint22, checkpoint23, checkpoint24, checkpoint25, checkpoint27, branch-atmos-merge-freeze, branch-atmos-merge-start, checkpoint26, branch-atmos-merge-shapiro, checkpoint33, checkpoint32, checkpoint31, checkpoint30, checkpoint34, branch-atmos-merge-zonalfilt, branch-atmos-merge-phase5, branch-atmos-merge-phase4, branch-atmos-merge-phase7, branch-atmos-merge-phase6, branch-atmos-merge-phase1, branch-atmos-merge-phase3, branch-atmos-merge-phase2
Branch point for: branch-atmos-merge
Changes since 1.5: +23 -11 lines
Changed number of arguments to GLOBAL_SUM and GLOBAL_MAX to two.
Instigated by Ralf.

1 C $Header: /u/gcmpack/models/MITgcmUV/eesupp/src/global_max.F,v 1.4 1998/10/28 03:11:35 cnh Exp $
2
3 C-- File global_max.F: Routines that perform global max reduction on an array
4 C of thread values.
5 C Contents
6 C o global_max_r4
7 C o global_max_r8
8 #include "CPP_EEOPTIONS.h"
9
10 CStartOfInterface
11 SUBROUTINE GLOBAL_MAX_R4(
12 U maxPhi,
13 I myThid )
14 C /==========================================================\
15 C | SUBROUTINE GLOBAL_MAX_R4 |
16 C | o Handle max for real*4 data. |
17 C |==========================================================|
18 C | Perform max on array of one value per thread and then |
19 C | max result of all the processes. |
20 C | Notes |
21 C | ===== |
22 C | Within a process only one thread does the max, each |
23 C | thread is assumed to have already maxed its local data. |
24 C | The same thread also does the inter-process max for |
25 C | example with MPI and then writes the result into a shared|
26 C | location. All threads wait until the max is avaiailable. |
27 C \==========================================================/
28 IMPLICIT NONE
29
30 C == Global data ==
31 #include "SIZE.h"
32 #include "EEPARAMS.h"
33 #include "EESUPPORT.h"
34
35 C == Routine arguments ==
36 C maxPhi - Result of max.
37 C myThid - My thread id.
38 Real*4 maxPhi
39 INTEGER myThid
40 CEndOfInterface
41
42 C == Local variables ==
43 C phi - Array to be maxed.
44 C I - Loop counters
45 C mpiRC - MPI return code
46 Real*4 phi(lShare4,MAX_NO_THREADS)
47 INTEGER I
48 Real*4 tmp
49 #ifdef ALLOW_USE_MPI
50 INTEGER mpiRC
51 #endif /* ALLOW_USE_MPI */
52
53 C-- write local max into array
54 phi(1,myThid) = maxPhi
55
56 C-- Can not start until everyone is ready
57 _BARRIER
58
59 C-- Max within the process first
60 _BEGIN_MASTER( myThid )
61 tmp = phi(1,1)
62 DO I=2,nThreads
63 tmp = MAX(tmp,phi(1,I))
64 ENDDO
65 maxPhi = tmp
66 #ifdef ALLOW_USE_MPI
67 #ifndef ALWAYS_USE_MPI
68 IF ( usingMPI ) THEN
69 #endif
70 CALL MPI_Allreduce(tmp,maxPhi,1,MPI_REAL,MPI_MAX,
71 & MPI_COMM_WORLD,mpiRC)
72 #ifndef ALWAYS_USE_MPI
73 ENDIF
74 #endif
75 #endif /* ALLOW_USE_MPI */
76 phi(1,1) = maxPhi
77 _END_MASTER( myThid )
78 C--
79 _BARRIER
80
81 C-- set result for every process
82 maxPhi = phi(1,1)
83
84 RETURN
85 END
86
87
88 CStartOfInterface
89 SUBROUTINE GLOBAL_MAX_R8(
90 O maxPhi,
91 I myThid )
92 C /==========================================================\
93 C | SUBROUTINE GLOBAL_MAX_R8 |
94 C | o Handle max for real*8 data. |
95 C |==========================================================|
96 C | Perform max on array of one value per thread and then |
97 C | max result of all the processes. |
98 C | Notes |
99 C | ===== |
100 C | Within a process only one thread does the max, each |
101 C | thread is assumed to have already maxed its local data. |
102 C | The same thread also does the inter-process max for |
103 C | example with MPI and then writes the result into a shared|
104 C | location. All threads wait until the max is avaiailable. |
105 C \==========================================================/
106 IMPLICIT NONE
107
108 C === Global data ===
109 #include "SIZE.h"
110 #include "EEPARAMS.h"
111 #include "EESUPPORT.h"
112
113 C === Routine arguments ===
114 C maxPhi - Result of max.
115 C myThid - My thread id.
116 Real*8 maxPhi
117 INTEGER myThid
118 CEndOfInterface
119
120 C === Local variables ===
121 C phi - Array to be maxed.
122 C I - Loop counters
123 C mpiRC - MPI return code
124 Real*8 phi(lShare8,MAX_NO_THREADS)
125 INTEGER I
126 Real*8 tmp
127 #ifdef ALLOW_USE_MPI
128 INTEGER mpiRC
129 #endif /* ALLOW_USE_MPI */
130
131 C-- write local max into array
132 phi(1,myThid) = maxPhi
133
134 C-- Can not start until everyone is ready
135 _BARRIER
136
137 C-- Max within the process first
138 _BEGIN_MASTER( myThid )
139 tmp = phi(1,1)
140 DO I=2,nThreads
141 tmp = MAX(tmp,phi(1,I))
142 ENDDO
143 maxPhi = tmp
144 #ifdef ALLOW_USE_MPI
145 #ifndef ALWAYS_USE_MPI
146 IF ( usingMPI ) THEN
147 #endif
148 CALL MPI_Allreduce(tmp,maxPhi,1,MPI_DOUBLE_PRECISION,MPI_MAX,
149 & MPI_COMM_WORLD,mpiRC)
150 #ifndef ALWAYS_USE_MPI
151 ENDIF
152 #endif
153 #endif /* ALLOW_USE_MPI */
154 C-- Write solution to place where all threads can see it
155 phi(1,1) = maxPhi
156 _END_MASTER( myThid )
157
158 C-- Do not leave until we are sure that the max is done
159 _BARRIER
160
161 C-- set result for every process
162 maxPhi = phi(1,1)
163
164 RETURN
165 END

  ViewVC Help
Powered by ViewVC 1.1.22