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

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

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


Revision 1.1 - (hide annotations) (download)
Tue Jan 8 23:53:47 2008 UTC (16 years, 5 months ago) by jahn
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59m, checkpoint59o, checkpoint59n, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a
global sum of a 2d array, performed on a single CPU

1 jahn 1.1 C $Header$
2     C $Name$
3    
4     C-- File global_sum_singlecpu.F: Routines that perform global sum
5     C on a single CPU
6     #include "CPP_EEOPTIONS.h"
7    
8     CBOP
9     C !ROUTINE: GLOBAL_SUM_SINGLECPU_RL
10    
11     C !INTERFACE:
12     SUBROUTINE GLOBAL_SUM_SINGLECPU_RL(
13     I phiLocal,
14     O sumPhi,
15     I myThid )
16     IMPLICIT NONE
17     C !DESCRIPTION:
18     C *==========================================================*
19     C | SUBROUTINE GLOBAL\_SUM\_SINGLECPU\_RL
20     C | o Handle sum for _RL data.
21     C *==========================================================*
22     C | Global sum of 2d array
23     C | independent of tiling as sum is performed on a single CPU
24     C | sum is performed in REAL*8
25     C *==========================================================*
26    
27     C !USES:
28     C == Global data ==
29     #include "SIZE.h"
30     #include "EEPARAMS.h"
31     #include "EESUPPORT.h"
32     #include "GLOBAL_SUM.h"
33    
34     C !INPUT/OUTPUT PARAMETERS:
35     C == Routine arguments ==
36     C phiLocal :: local input array without overlap regions.
37     C sumPhi :: Result of sum.
38     C myThid :: My thread id.
39     _RL phiLocal(1:sNx,1:sNy,nSx,nSy)
40     _RL sumPhi
41     INTEGER myThid
42    
43     C !LOCAL VARIABLES:
44     C == Local variables ==
45     C- type declaration of: sumAll, globalBuf :
46     C sumAll needs to have the same length as MPI_DOUBLE_PRECISION
47     INTEGER I,J
48     Real*8 globalBuf(Nx,Ny)
49     Real*8 sumAll
50     #ifdef ALLOW_USE_MPI
51     INTEGER npe
52     INTEGER lbuff, idest, itag
53     INTEGER istatus(MPI_STATUS_SIZE), ierr
54     #endif /* ALLOW_USE_MPI */
55     CEOP
56    
57     C- note(jmc): do not see why we need this Barrier here + the one at the end ;
58     C however a) both are present in the standard version of global_sum ;
59     C b) with OpenMP on hugo, does not work if both are commented out
60     CALL BAR2( myThid )
61    
62     C-- Gather local arrays
63     CALL GATHER_2D( globalBuf, phiLocal, myThid )
64    
65     C-- Master thread does the communications and the global sum
66     C-- Master thread cannot start until everyone is ready:
67     CALL BAR2( myThid )
68     _BEGIN_MASTER( myThid )
69    
70     #ifdef ALLOW_USE_MPI
71     idest = 0
72     itag = 0
73    
74     IF ( mpiMyId.EQ.0 ) THEN
75     #endif
76    
77     C-- Process 0 sums the global array
78     sumAll = 0.d0
79     DO J=1,Ny
80     DO I=1,Nx
81     sumAll = sumAll + globalBuf(I,J)
82     ENDDO
83     ENDDO
84    
85     #ifdef ALLOW_USE_MPI
86     C-- Process 0 sends result to all other processes
87     lbuff = 1
88     DO npe = 1, numberOfProcs-1
89     CALL MPI_SEND (sumAll, 1, MPI_DOUBLE_PRECISION,
90     & npe, itag, MPI_COMM_MODEL, ierr)
91     ENDDO
92    
93     ELSE
94    
95     C-- All proceses except 0 receive result from process 0
96     CALL MPI_RECV (sumAll, 1, MPI_DOUBLE_PRECISION,
97     & idest, itag, MPI_COMM_MODEL, istatus, ierr)
98    
99     ENDIF
100     #endif /* not ALLOW_USE_MPI */
101    
102     C-- Write solution to shared buffer (all threads can see it)
103     shareBufGSR8(1,1) = sumAll
104    
105     _END_MASTER( myThid )
106     C-- Everyone wait for Master thread to be ready
107     CALL BAR2( myThid )
108    
109     C-- set result for every threads
110     sumPhi = shareBufGSR8(1,1)
111    
112     C- note(jmc): do not see why we need this Barrier here (see comment @ the top)
113     CALL BAR2( myThid )
114    
115     RETURN
116     END

  ViewVC Help
Powered by ViewVC 1.1.22