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

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

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


Revision 1.3 - (show annotations) (download)
Sat May 16 13:41:19 2009 UTC (15 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61o
Changes since 1.2: +51 -12 lines
- fix GLOBAL_SUM_SINGLECPU when using Exch2; re-use same buffers and
  same gather/scatter S/R as with SingleCpuIO (=> 1 less 2D global RL array).
- remove gather_2d.F (no longer used).

1 C $Header: /u/gcmpack/MITgcm/eesupp/src/global_sum_singlecpu.F,v 1.2 2009/01/09 22:51:12 jmc Exp $
2 C $Name: $
3
4 C-- File global_sum_singlecpu.F: Routines that perform global sum
5 C on a single CPU
6 C Contents
7 C o global_sum_singlecpu_rl
8 C o global_sum_singlecpu_rs <- not yet coded
9
10 #include "PACKAGES_CONFIG.h"
11 #include "CPP_EEOPTIONS.h"
12
13 CBOP
14 C !ROUTINE: GLOBAL_SUM_SINGLECPU_RL
15
16 C !INTERFACE:
17 SUBROUTINE GLOBAL_SUM_SINGLECPU_RL(
18 I phiLocal,
19 O sumPhi,
20 I oLi, oLj, myThid )
21 IMPLICIT NONE
22 C !DESCRIPTION:
23 C *==========================================================*
24 C | SUBROUTINE GLOBAL\_SUM\_SINGLECPU\_RL
25 C | o Handle sum for _RL data.
26 C *==========================================================*
27 C | Global sum of 2d array
28 C | independent of tiling as sum is performed on a single CPU
29 C | sum is performed in REAL*8
30 C *==========================================================*
31
32 C !USES:
33 C == Global data ==
34 #include "SIZE.h"
35 #include "EEPARAMS.h"
36 #include "EESUPPORT.h"
37 #include "GLOBAL_SUM.h"
38 #ifdef ALLOW_EXCH2
39 #include "W2_EXCH2_SIZE.h"
40 #include "W2_EXCH2_TOPOLOGY.h"
41 #endif
42 #include "EEBUFF_SCPU.h"
43
44 C !INPUT/OUTPUT PARAMETERS:
45 C == Routine arguments ==
46 C phiLocal :: local input array without overlap regions.
47 C sumPhi :: Result of sum.
48 C oLi, oLj :: overlap size of input array in I & J direction.
49 C myThid :: My thread id.
50 INTEGER oLi, oLj
51 _RL phiLocal(1-oLi:sNx+oLi,1-oLj:sNy+oLj,nSx,nSy)
52 _RL sumPhi
53 INTEGER myThid
54
55 C !LOCAL VARIABLES:
56 C == Local variables ==
57 C- type declaration of: sumAll, globalBuf :
58 C sumAll needs to have the same length as MPI_DOUBLE_PRECISION
59 LOGICAL useExch2GlobLayOut, zeroBuff
60 INTEGER xSize, ySize
61 INTEGER i, j, ij
62 INTEGER bi, bj
63 Real*8 sumAll
64 #ifdef ALLOW_USE_MPI
65 INTEGER npe
66 INTEGER lbuff, idest, itag
67 INTEGER istatus(MPI_STATUS_SIZE), ierr
68 #endif /* ALLOW_USE_MPI */
69 CEOP
70
71 #ifdef ALLOW_EXCH2
72 zeroBuff = .TRUE.
73 useExch2GlobLayOut = .TRUE.
74 xSize = exch2_global_Nx
75 ySize = exch2_global_Ny
76 #else /* ALLOW_EXCH2 */
77 zeroBuff = .FALSE.
78 useExch2GlobLayOut = .FALSE.
79 xSize = Nx
80 ySize = Ny
81 #endif /* ALLOW_EXCH2 */
82
83 C-- copy (and conversion to real*8) to Shared buffer:
84 DO bj = myByLo(myThid), myByHi(myThid)
85 DO bi = myBxLo(myThid), myBxHi(myThid)
86 DO j=1,sNy
87 DO i=1,sNx
88 sharedLocBuf_r8(i,j,bi,bj) = phiLocal(i,j,bi,bj)
89 ENDDO
90 ENDDO
91 ENDDO
92 ENDDO
93
94 C- note(jmc): do not see why we need this Barrier here + the one at the end ;
95 C however a) both are present in the standard version of global_sum ;
96 C b) with OpenMP on hugo, does not work if both are commented out
97 CALL BAR2( myThid )
98
99 C-- Gather local arrays
100 CALL GATHER_2D_R8(
101 O xy_buffer_r8,
102 I sharedLocBuf_r8,
103 I xSize, ySize,
104 I useExch2GlobLayOut, zeroBuff, myThid )
105
106 C-- Master thread does the communications and the global sum
107 C-- Master thread cannot start until everyone is ready:
108 CALL BAR2( myThid )
109 _BEGIN_MASTER( myThid )
110
111 #ifdef ALLOW_USE_MPI
112 idest = 0
113 itag = 0
114
115 IF ( mpiMyId.EQ.0 ) THEN
116 #endif
117
118 C-- Process 0 sums the global array
119 sumAll = 0. _d 0
120 DO ij=1,xSize*ySize
121 sumAll = sumAll + xy_buffer_r8(ij)
122 ENDDO
123
124 #ifdef ALLOW_USE_MPI
125 C-- Process 0 sends result to all other processes
126 lbuff = 1
127 DO npe = 1, numberOfProcs-1
128 CALL MPI_SEND (sumAll, 1, MPI_DOUBLE_PRECISION,
129 & npe, itag, MPI_COMM_MODEL, ierr)
130 ENDDO
131
132 ELSE
133
134 C-- All proceses except 0 receive result from process 0
135 CALL MPI_RECV (sumAll, 1, MPI_DOUBLE_PRECISION,
136 & idest, itag, MPI_COMM_MODEL, istatus, ierr)
137
138 ENDIF
139 #endif /* not ALLOW_USE_MPI */
140
141 C-- Write solution to shared buffer (all threads can see it)
142 shareBufGSR8(1,1) = sumAll
143
144 _END_MASTER( myThid )
145 C-- Everyone wait for Master thread to be ready
146 CALL BAR2( myThid )
147
148 C-- set result for every threads
149 sumPhi = shareBufGSR8(1,1)
150
151 C- note(jmc): do not see why we need this Barrier here (see comment @ the top)
152 CALL BAR2( myThid )
153
154 RETURN
155 END

  ViewVC Help
Powered by ViewVC 1.1.22