/[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.3 - (show annotations) (download)
Thu Apr 23 20:56:54 1998 UTC (26 years, 1 month ago) by cnh
Branch: MAIN
CVS Tags: checkpoint11, checkpoint10, checkpoint13, checkpoint15, checkpoint14, redigm, checkpoint5, checkpoint4, checkpoint7, checkpoint6, checkpoint1, checkpoint3, checkpoint2, checkpoint9, checkpoint8, kloop1, kloop2, checkpoint12, branch-point-rdot
Branch point for: checkpoint7-4degree-ref, branch-rdot
Changes since 1.2: +1 -3 lines
Further changes to convert from $Id to $Header

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

  ViewVC Help
Powered by ViewVC 1.1.22