/[MITgcm]/MITgcm/model/src/solve_for_pressure.F
ViewVC logotype

Annotation of /MITgcm/model/src/solve_for_pressure.F

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


Revision 1.54 - (hide annotations) (download)
Fri May 5 19:00:28 2006 UTC (18 years, 1 month ago) by ce107
Branch: MAIN
Changes since 1.53: +46 -9 lines
Updates to support PCL performance counters, fix real*4 bug for PAPIS
and enhance PAPI counter support (including IPC per timestep output)

1 ce107 1.54 C $Header: /u/gcmpack/MITgcm/model/src/solve_for_pressure.F,v 1.53 2006/02/23 20:55:49 jmc Exp $
2 heimbach 1.21 C $Name: $
3 cnh 1.1
4 edhill 1.39 #include "PACKAGES_CONFIG.h"
5 adcroft 1.5 #include "CPP_OPTIONS.h"
6 cnh 1.1
7 cnh 1.27 CBOP
8     C !ROUTINE: SOLVE_FOR_PRESSURE
9     C !INTERFACE:
10 jmc 1.29 SUBROUTINE SOLVE_FOR_PRESSURE(myTime, myIter, myThid)
11 cnh 1.27
12     C !DESCRIPTION: \bv
13     C *==========================================================*
14     C | SUBROUTINE SOLVE_FOR_PRESSURE
15     C | o Controls inversion of two and/or three-dimensional
16     C | elliptic problems for the pressure field.
17     C *==========================================================*
18     C \ev
19    
20     C !USES:
21 adcroft 1.8 IMPLICIT NONE
22 cnh 1.4 C == Global variables
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "PARAMS.h"
26 adcroft 1.12 #include "GRID.h"
27 jmc 1.17 #include "SURFACE.h"
28 jmc 1.28 #include "FFIELDS.h"
29 jmc 1.48 #include "DYNVARS.h"
30     #include "SOLVE_FOR_PRESSURE.h"
31 adcroft 1.9 #ifdef ALLOW_NONHYDROSTATIC
32 adcroft 1.25 #include "SOLVE_FOR_PRESSURE3D.h"
33 jmc 1.48 #include "NH_VARS.h"
34     #endif
35     #ifdef ALLOW_CD_CODE
36     #include "CD_CODE_VARS.h"
37 adcroft 1.12 #endif
38 adcroft 1.11 #ifdef ALLOW_OBCS
39 adcroft 1.9 #include "OBCS.h"
40 adcroft 1.11 #endif
41 cnh 1.4
42 jmc 1.32 C === Functions ====
43 jmc 1.46 LOGICAL DIFFERENT_MULTIPLE
44     EXTERNAL DIFFERENT_MULTIPLE
45 jmc 1.32
46 cnh 1.27 C !INPUT/OUTPUT PARAMETERS:
47 cnh 1.1 C == Routine arguments ==
48 jmc 1.28 C myTime - Current time in simulation
49     C myIter - Current iteration number in simulation
50     C myThid - Thread number for this instance of SOLVE_FOR_PRESSURE
51     _RL myTime
52     INTEGER myIter
53 jmc 1.29 INTEGER myThid
54 cnh 1.4
55 cnh 1.27 C !LOCAL VARIABLES:
56 adcroft 1.22 C == Local variables ==
57 cnh 1.6 INTEGER i,j,k,bi,bj
58 adcroft 1.9 _RS uf(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
59     _RS vf(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
60 adcroft 1.22 _RL firstResidual,lastResidual
61 jmc 1.36 _RL tmpFac
62 jmc 1.47 _RL sumEmP, tileEmP
63     LOGICAL putPmEinXvector
64 adcroft 1.19 INTEGER numIters
65 adcroft 1.25 CHARACTER*(MAX_LEN_MBUF) msgBuf
66 jmc 1.49 #ifdef ALLOW_NONHYDROSTATIC
67 jmc 1.51 INTEGER ks, kp1
68     _RL maskKp1
69 jmc 1.49 LOGICAL zeroPsNH
70     #endif
71 cnh 1.27 CEOP
72 jmc 1.17
73 ce107 1.52 #ifdef TIME_PER_TIMESTEP_SFP
74 ce107 1.44 CCE107 common block for per timestep timing
75     C !TIMING VARIABLES
76     C == Timing variables ==
77     REAL*8 utnew, utold, stnew, stold, wtnew, wtold
78     COMMON /timevars/ utnew, utold, stnew, stold, wtnew, wtold
79     #endif
80 ce107 1.52 #ifdef USE_PAPI_FLOPS_SFP
81     CCE107 common block for PAPI summary performance
82     #include <fpapi.h>
83 ce107 1.54 INTEGER*8 flpops, instr
84 ce107 1.52 INTEGER check
85 ce107 1.54 REAL*4 real_time, proc_time, mflops, ipc
86     COMMON /papivars/ flpops, instr, real_time, proc_time, mflops, ipc
87     #else
88     #ifdef USE_PCL_FLOPS_SFP
89     CCE107 common block for PCL summary performance
90     #include <pclh.f>
91     INTEGER pcl_counter_list(5), flags, nevents, res, ipcl
92     INTEGER*8 i_result(5), descr
93     REAL*8 fp_result(5)
94     COMMON /pclvars/ i_result, descr, fp_result, pcl_counter_list,
95     $ flags, nevents
96     INTEGER nmaxevents
97     PARAMETER (nmaxevents = 61)
98     CHARACTER*22 pcl_counter_name(0:nmaxevents-1)
99     COMMON /pclnames/ pcl_counter_name
100     #endif
101 ce107 1.52 #endif
102 ce107 1.44
103 jmc 1.49 #ifdef ALLOW_NONHYDROSTATIC
104     c zeroPsNH = .FALSE.
105     zeroPsNH = exactConserv
106     #endif
107    
108 jmc 1.47 C-- Initialise the Vector solution with etaN + deltaT*Global_mean_PmE
109     C instead of simply etaN ; This can speed-up the solver convergence in
110     C the case where |Global_mean_PmE| is large.
111     putPmEinXvector = .FALSE.
112     c putPmEinXvector = useRealFreshWaterFlux
113    
114 jmc 1.17 C-- Save previous solution & Initialise Vector solution and source term :
115 jmc 1.47 sumEmP = 0.
116 jmc 1.17 DO bj=myByLo(myThid),myByHi(myThid)
117     DO bi=myBxLo(myThid),myBxHi(myThid)
118     DO j=1-OLy,sNy+OLy
119     DO i=1-OLx,sNx+OLx
120 edhill 1.40 #ifdef ALLOW_CD_CODE
121 jmc 1.17 etaNm1(i,j,bi,bj) = etaN(i,j,bi,bj)
122 jmc 1.26 #endif
123 jmc 1.18 cg2d_x(i,j,bi,bj) = Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
124 jmc 1.17 cg2d_b(i,j,bi,bj) = 0.
125     ENDDO
126     ENDDO
127 jmc 1.29 IF (useRealFreshWaterFlux) THEN
128 jmc 1.36 tmpFac = freeSurfFac*convertEmP2rUnit
129 mlosch 1.35 IF (exactConserv)
130 jmc 1.36 & tmpFac = freeSurfFac*convertEmP2rUnit*implicDiv2DFlow
131 jmc 1.29 DO j=1,sNy
132     DO i=1,sNx
133     cg2d_b(i,j,bi,bj) =
134     & tmpFac*_rA(i,j,bi,bj)*EmPmR(i,j,bi,bj)/deltaTMom
135     ENDDO
136     ENDDO
137     ENDIF
138 jmc 1.47 IF ( putPmEinXvector ) THEN
139     tileEmP = 0.
140     DO j=1,sNy
141     DO i=1,sNx
142     tileEmP = tileEmP + rA(i,j,bi,bj)*EmPmR(i,j,bi,bj)
143     & *maskH(i,j,bi,bj)
144     ENDDO
145     ENDDO
146     sumEmP = sumEmP + tileEmP
147     ENDIF
148 jmc 1.17 ENDDO
149     ENDDO
150 jmc 1.47 IF ( putPmEinXvector ) THEN
151     _GLOBAL_SUM_R8( sumEmP, myThid )
152     ENDIF
153 adcroft 1.12
154     DO bj=myByLo(myThid),myByHi(myThid)
155     DO bi=myBxLo(myThid),myBxHi(myThid)
156 jmc 1.47 IF ( putPmEinXvector ) THEN
157     tmpFac = 0.
158     IF (globalArea.GT.0.) tmpFac = freeSurfFac*deltaTfreesurf
159     & *convertEmP2rUnit*sumEmP/globalArea
160     DO j=1,sNy
161     DO i=1,sNx
162     cg2d_x(i,j,bi,bj) = cg2d_x(i,j,bi,bj)
163     & - tmpFac*Bo_surf(i,j,bi,bj)
164     ENDDO
165     ENDDO
166     ENDIF
167 adcroft 1.12 DO K=Nr,1,-1
168     DO j=1,sNy+1
169     DO i=1,sNx+1
170     uf(i,j) = _dyG(i,j,bi,bj)
171     & *drF(k)*_hFacW(i,j,k,bi,bj)
172     vf(i,j) = _dxG(i,j,bi,bj)
173     & *drF(k)*_hFacS(i,j,k,bi,bj)
174     ENDDO
175     ENDDO
176     CALL CALC_DIV_GHAT(
177     I bi,bj,1,sNx,1,sNy,K,
178     I uf,vf,
179 jmc 1.17 U cg2d_b,
180 adcroft 1.12 I myThid)
181     ENDDO
182     ENDDO
183     ENDDO
184 cnh 1.4
185 adcroft 1.12 C-- Add source term arising from w=d/dt (p_s + p_nh)
186     DO bj=myByLo(myThid),myByHi(myThid)
187     DO bi=myBxLo(myThid),myBxHi(myThid)
188 adcroft 1.13 #ifdef ALLOW_NONHYDROSTATIC
189 jmc 1.53 IF ( use3Dsolver .AND. zeroPsNH ) THEN
190 jmc 1.49 DO j=1,sNy
191     DO i=1,sNx
192 jmc 1.51 ks = ksurfC(i,j,bi,bj)
193     IF ( ks.LE.Nr ) THEN
194     cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
195 jmc 1.49 & -freeSurfFac*_rA(i,j,bi,bj)/deltaTMom/deltaTfreesurf
196     & * etaH(i,j,bi,bj)
197 jmc 1.51 cg3d_b(i,j,ks,bi,bj) = cg3d_b(i,j,ks,bi,bj)
198 jmc 1.49 & -freeSurfFac*_rA(i,j,bi,bj)/deltaTMom/deltaTfreesurf
199     & * etaH(i,j,bi,bj)
200 jmc 1.51 ENDIF
201 jmc 1.49 ENDDO
202     ENDDO
203 jmc 1.53 ELSEIF ( use3Dsolver ) THEN
204 jmc 1.28 DO j=1,sNy
205     DO i=1,sNx
206 jmc 1.51 ks = ksurfC(i,j,bi,bj)
207     IF ( ks.LE.Nr ) THEN
208     cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
209 adcroft 1.33 & -freeSurfFac*_rA(i,j,bi,bj)/deltaTMom/deltaTfreesurf
210 jmc 1.28 & *( etaN(i,j,bi,bj)
211 jmc 1.51 & +phi_nh(i,j,ks,bi,bj)*horiVertRatio/gravity )
212     cg3d_b(i,j,ks,bi,bj) = cg3d_b(i,j,ks,bi,bj)
213 adcroft 1.33 & -freeSurfFac*_rA(i,j,bi,bj)/deltaTMom/deltaTfreesurf
214 jmc 1.28 & *( etaN(i,j,bi,bj)
215 jmc 1.51 & +phi_nh(i,j,ks,bi,bj)*horiVertRatio/gravity )
216     ENDIF
217 jmc 1.28 ENDDO
218 adcroft 1.12 ENDDO
219 jmc 1.28 ELSEIF ( exactConserv ) THEN
220 adcroft 1.13 #else
221 jmc 1.26 IF ( exactConserv ) THEN
222 edhill 1.39 #endif /* ALLOW_NONHYDROSTATIC */
223 jmc 1.26 DO j=1,sNy
224     DO i=1,sNx
225     cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
226 adcroft 1.33 & -freeSurfFac*_rA(i,j,bi,bj)/deltaTMom/deltaTfreesurf
227 jmc 1.26 & * etaH(i,j,bi,bj)
228     ENDDO
229     ENDDO
230     ELSE
231     DO j=1,sNy
232     DO i=1,sNx
233     cg2d_b(i,j,bi,bj) = cg2d_b(i,j,bi,bj)
234 adcroft 1.33 & -freeSurfFac*_rA(i,j,bi,bj)/deltaTMom/deltaTfreesurf
235 jmc 1.26 & * etaN(i,j,bi,bj)
236     ENDDO
237 adcroft 1.12 ENDDO
238 jmc 1.26 ENDIF
239 adcroft 1.12
240     #ifdef ALLOW_OBCS
241 adcroft 1.14 IF (useOBCS) THEN
242 adcroft 1.12 DO i=1,sNx
243     C Northern boundary
244     IF (OB_Jn(I,bi,bj).NE.0) THEN
245     cg2d_b(I,OB_Jn(I,bi,bj),bi,bj)=0.
246 jmc 1.31 cg2d_x(I,OB_Jn(I,bi,bj),bi,bj)=0.
247 adcroft 1.12 ENDIF
248     C Southern boundary
249     IF (OB_Js(I,bi,bj).NE.0) THEN
250     cg2d_b(I,OB_Js(I,bi,bj),bi,bj)=0.
251 jmc 1.31 cg2d_x(I,OB_Js(I,bi,bj),bi,bj)=0.
252 adcroft 1.12 ENDIF
253     ENDDO
254     DO j=1,sNy
255     C Eastern boundary
256     IF (OB_Ie(J,bi,bj).NE.0) THEN
257     cg2d_b(OB_Ie(J,bi,bj),J,bi,bj)=0.
258 jmc 1.31 cg2d_x(OB_Ie(J,bi,bj),J,bi,bj)=0.
259 adcroft 1.12 ENDIF
260     C Western boundary
261     IF (OB_Iw(J,bi,bj).NE.0) THEN
262     cg2d_b(OB_Iw(J,bi,bj),J,bi,bj)=0.
263 jmc 1.31 cg2d_x(OB_Iw(J,bi,bj),J,bi,bj)=0.
264 adcroft 1.12 ENDIF
265     ENDDO
266     ENDIF
267 jmc 1.49 #endif /* ALLOW_OBCS */
268     C- end bi,bj loops
269 adcroft 1.12 ENDDO
270     ENDDO
271    
272 edhill 1.42 #ifdef ALLOW_DEBUG
273 heimbach 1.38 IF ( debugLevel .GE. debLevB ) THEN
274 adcroft 1.23 CALL DEBUG_STATS_RL(1,cg2d_b,'cg2d_b (SOLVE_FOR_PRESSURE)',
275     & myThid)
276 adcroft 1.24 ENDIF
277 adcroft 1.23 #endif
278 adcroft 1.12
279 cnh 1.1 C-- Find the surface pressure using a two-dimensional conjugate
280     C-- gradient solver.
281 adcroft 1.22 C see CG2D.h for the interface to this routine.
282     firstResidual=0.
283     lastResidual=0.
284 adcroft 1.19 numIters=cg2dMaxIters
285 jmc 1.50 c CALL TIMER_START('CG2D [SOLVE_FOR_PRESSURE]',myThid)
286 cnh 1.1 CALL CG2D(
287 adcroft 1.22 U cg2d_b,
288 cnh 1.6 U cg2d_x,
289 adcroft 1.22 O firstResidual,
290     O lastResidual,
291 adcroft 1.19 U numIters,
292 cnh 1.1 I myThid )
293 adcroft 1.19 _EXCH_XY_R8(cg2d_x, myThid )
294 jmc 1.50 c CALL TIMER_STOP ('CG2D [SOLVE_FOR_PRESSURE]',myThid)
295 adcroft 1.23
296 edhill 1.42 #ifdef ALLOW_DEBUG
297 heimbach 1.38 IF ( debugLevel .GE. debLevB ) THEN
298 adcroft 1.23 CALL DEBUG_STATS_RL(1,cg2d_x,'cg2d_x (SOLVE_FOR_PRESSURE)',
299     & myThid)
300 adcroft 1.24 ENDIF
301 adcroft 1.23 #endif
302 cnh 1.1
303 jmc 1.32 C- dump CG2D output at monitorFreq (to reduce size of STD-OUTPUT files) :
304 jmc 1.46 IF ( DIFFERENT_MULTIPLE(monitorFreq,myTime,deltaTClock)
305 jmc 1.45 & ) THEN
306 heimbach 1.38 IF ( debugLevel .GE. debLevA ) THEN
307     _BEGIN_MASTER( myThid )
308     WRITE(msgBuf,'(A34,1PE24.14)') 'cg2d_init_res =',firstResidual
309     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
310     WRITE(msgBuf,'(A34,I6)') 'cg2d_iters =',numIters
311     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
312     WRITE(msgBuf,'(A34,1PE24.14)') 'cg2d_res =',lastResidual
313     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
314 edhill 1.43 _END_MASTER( myThid )
315 heimbach 1.38 ENDIF
316 jmc 1.32 ENDIF
317 jmc 1.17
318     C-- Transfert the 2D-solution to "etaN" :
319     DO bj=myByLo(myThid),myByHi(myThid)
320     DO bi=myBxLo(myThid),myBxHi(myThid)
321     DO j=1-OLy,sNy+OLy
322     DO i=1-OLx,sNx+OLx
323 jmc 1.18 etaN(i,j,bi,bj) = recip_Bo(i,j,bi,bj)*cg2d_x(i,j,bi,bj)
324 jmc 1.17 ENDDO
325     ENDDO
326     ENDDO
327     ENDDO
328 adcroft 1.10
329 adcroft 1.9 #ifdef ALLOW_NONHYDROSTATIC
330 jmc 1.53 IF ( use3Dsolver ) THEN
331 adcroft 1.9
332     C-- Solve for a three-dimensional pressure term (NH or IGW or both ).
333     C see CG3D.h for the interface to this routine.
334     DO bj=myByLo(myThid),myByHi(myThid)
335     DO bi=myBxLo(myThid),myBxHi(myThid)
336     DO j=1,sNy+1
337     DO i=1,sNx+1
338 jmc 1.18 uf(i,j)=-_recip_dxC(i,j,bi,bj)*
339 adcroft 1.9 & (cg2d_x(i,j,bi,bj)-cg2d_x(i-1,j,bi,bj))
340 jmc 1.18 vf(i,j)=-_recip_dyC(i,j,bi,bj)*
341 adcroft 1.9 & (cg2d_x(i,j,bi,bj)-cg2d_x(i,j-1,bi,bj))
342     ENDDO
343     ENDDO
344    
345 adcroft 1.12 #ifdef ALLOW_OBCS
346 adcroft 1.14 IF (useOBCS) THEN
347 adcroft 1.9 DO i=1,sNx+1
348     C Northern boundary
349     IF (OB_Jn(I,bi,bj).NE.0) THEN
350     vf(I,OB_Jn(I,bi,bj))=0.
351     ENDIF
352     C Southern boundary
353     IF (OB_Js(I,bi,bj).NE.0) THEN
354     vf(I,OB_Js(I,bi,bj)+1)=0.
355     ENDIF
356     ENDDO
357     DO j=1,sNy+1
358     C Eastern boundary
359     IF (OB_Ie(J,bi,bj).NE.0) THEN
360     uf(OB_Ie(J,bi,bj),J)=0.
361     ENDIF
362     C Western boundary
363     IF (OB_Iw(J,bi,bj).NE.0) THEN
364     uf(OB_Iw(J,bi,bj)+1,J)=0.
365     ENDIF
366     ENDDO
367     ENDIF
368 jmc 1.49 #endif /* ALLOW_OBCS */
369 adcroft 1.9
370 jmc 1.51 IF ( usingZCoords ) THEN
371     C- Z coordinate: assume surface @ level k=1
372     tmpFac = freeSurfFac
373     ELSE
374     C- Other than Z coordinate: no assumption on surface level index
375     tmpFac = 0.
376     DO j=1,sNy
377     DO i=1,sNx
378     ks = ksurfC(i,j,bi,bj)
379     IF ( ks.LE.Nr ) THEN
380     cg3d_b(i,j,ks,bi,bj) = cg3d_b(i,j,ks,bi,bj)
381     & +freeSurfFac*etaN(i,j,bi,bj)/deltaTfreesurf
382     & *_rA(i,j,bi,bj)/deltaTmom
383     ENDIF
384     ENDDO
385     ENDDO
386     ENDIF
387 adcroft 1.12 K=1
388 jmc 1.51 kp1 = MIN(k+1,Nr)
389     maskKp1 = 1.
390     IF (k.GE.Nr) maskKp1 = 0.
391 adcroft 1.12 DO j=1,sNy
392     DO i=1,sNx
393 jmc 1.51 cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)
394     & +drF(K)*dyG(i+1,j,bi,bj)*hFacW(i+1,j,k,bi,bj)*uf(i+1,j)
395     & -drF(K)*dyG( i ,j,bi,bj)*hFacW( i ,j,k,bi,bj)*uf( i ,j)
396     & +drF(K)*dxG(i,j+1,bi,bj)*hFacS(i,j+1,k,bi,bj)*vf(i,j+1)
397     & -drF(K)*dxG(i, j ,bi,bj)*hFacS(i, j ,k,bi,bj)*vf(i, j )
398     & +( tmpFac*etaN(i,j,bi,bj)/deltaTfreesurf
399     & -wVel(i,j,kp1,bi,bj)*maskKp1
400 adcroft 1.12 & )*_rA(i,j,bi,bj)/deltaTmom
401     ENDDO
402     ENDDO
403 jmc 1.51 DO K=2,Nr
404     kp1 = MIN(k+1,Nr)
405     maskKp1 = 1.
406     IF (k.GE.Nr) maskKp1 = 0.
407 adcroft 1.9 DO j=1,sNy
408     DO i=1,sNx
409     cg3d_b(i,j,k,bi,bj) = cg3d_b(i,j,k,bi,bj)
410 jmc 1.51 & +drF(K)*dyG(i+1,j,bi,bj)*hFacW(i+1,j,k,bi,bj)*uf(i+1,j)
411     & -drF(K)*dyG( i ,j,bi,bj)*hFacW( i ,j,k,bi,bj)*uf( i ,j)
412     & +drF(K)*dxG(i,j+1,bi,bj)*hFacS(i,j+1,k,bi,bj)*vf(i,j+1)
413     & -drF(K)*dxG(i, j ,bi,bj)*hFacS(i, j ,k,bi,bj)*vf(i, j )
414     & +( wVel(i,j,k ,bi,bj)*maskC(i,j,k-1,bi,bj)
415     & -wVel(i,j,kp1,bi,bj)*maskKp1
416 adcroft 1.12 & )*_rA(i,j,bi,bj)/deltaTmom
417    
418 adcroft 1.9 ENDDO
419     ENDDO
420     ENDDO
421 adcroft 1.12
422     #ifdef ALLOW_OBCS
423 adcroft 1.14 IF (useOBCS) THEN
424 adcroft 1.12 DO K=1,Nr
425     DO i=1,sNx
426     C Northern boundary
427     IF (OB_Jn(I,bi,bj).NE.0) THEN
428     cg3d_b(I,OB_Jn(I,bi,bj),K,bi,bj)=0.
429     ENDIF
430     C Southern boundary
431     IF (OB_Js(I,bi,bj).NE.0) THEN
432     cg3d_b(I,OB_Js(I,bi,bj),K,bi,bj)=0.
433     ENDIF
434     ENDDO
435     DO j=1,sNy
436     C Eastern boundary
437     IF (OB_Ie(J,bi,bj).NE.0) THEN
438     cg3d_b(OB_Ie(J,bi,bj),J,K,bi,bj)=0.
439     ENDIF
440     C Western boundary
441     IF (OB_Iw(J,bi,bj).NE.0) THEN
442     cg3d_b(OB_Iw(J,bi,bj),J,K,bi,bj)=0.
443     ENDIF
444     ENDDO
445     ENDDO
446     ENDIF
447 jmc 1.49 #endif /* ALLOW_OBCS */
448     C- end bi,bj loops
449     ENDDO
450     ENDDO
451 adcroft 1.9
452 adcroft 1.25 firstResidual=0.
453     lastResidual=0.
454 jmc 1.49 numIters=cg3dMaxIters
455 jmc 1.50 CALL TIMER_START('CG3D [SOLVE_FOR_PRESSURE]',myThid)
456 adcroft 1.25 CALL CG3D(
457     U cg3d_b,
458     U phi_nh,
459     O firstResidual,
460     O lastResidual,
461     U numIters,
462     I myThid )
463     _EXCH_XYZ_R8(phi_nh, myThid )
464 jmc 1.50 CALL TIMER_STOP ('CG3D [SOLVE_FOR_PRESSURE]',myThid)
465 adcroft 1.25
466 jmc 1.46 IF ( DIFFERENT_MULTIPLE(monitorFreq,myTime,deltaTClock)
467 jmc 1.45 & ) THEN
468 heimbach 1.38 IF ( debugLevel .GE. debLevA ) THEN
469     _BEGIN_MASTER( myThid )
470     WRITE(msgBuf,'(A34,1PE24.14)') 'cg3d_init_res =',firstResidual
471     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
472     WRITE(msgBuf,'(A34,I6)') 'cg3d_iters =',numIters
473     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
474     WRITE(msgBuf,'(A34,1PE24.14)') 'cg3d_res =',lastResidual
475     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
476 edhill 1.43 _END_MASTER( myThid )
477 heimbach 1.38 ENDIF
478 mlosch 1.37 ENDIF
479 adcroft 1.9
480 jmc 1.49 C-- Update surface pressure (account for NH-p @ surface level) and NH pressure:
481     IF ( zeroPsNH ) THEN
482     DO bj=myByLo(myThid),myByHi(myThid)
483     DO bi=myBxLo(myThid),myBxHi(myThid)
484    
485     IF ( usingZCoords ) THEN
486     C- Z coordinate: assume surface @ level k=1
487     DO k=2,Nr
488     DO j=1-OLy,sNy+OLy
489     DO i=1-OLx,sNx+OLx
490     phi_nh(i,j,k,bi,bj) = phi_nh(i,j,k,bi,bj)
491     & - phi_nh(i,j,1,bi,bj)
492     ENDDO
493     ENDDO
494     ENDDO
495     DO j=1-OLy,sNy+OLy
496     DO i=1-OLx,sNx+OLx
497     etaN(i,j,bi,bj) = recip_Bo(i,j,bi,bj)
498     & *(cg2d_x(i,j,bi,bj) + phi_nh(i,j,1,bi,bj))
499     phi_nh(i,j,1,bi,bj) = 0.
500     ENDDO
501     ENDDO
502     ELSE
503     C- Other than Z coordinate: no assumption on surface level index
504     DO j=1-OLy,sNy+OLy
505     DO i=1-OLx,sNx+OLx
506     ks = ksurfC(i,j,bi,bj)
507     IF ( ks.LE.Nr ) THEN
508     etaN(i,j,bi,bj) = recip_Bo(i,j,bi,bj)
509     & *(cg2d_x(i,j,bi,bj) + phi_nh(i,j,ks,bi,bj))
510     DO k=Nr,1,-1
511     phi_nh(i,j,k,bi,bj) = phi_nh(i,j,k,bi,bj)
512     & - phi_nh(i,j,ks,bi,bj)
513     ENDDO
514     ENDIF
515     ENDDO
516     ENDDO
517     ENDIF
518    
519     ENDDO
520     ENDDO
521 adcroft 1.9 ENDIF
522 jmc 1.49
523     ENDIF
524     #endif /* ALLOW_NONHYDROSTATIC */
525 cnh 1.1
526 ce107 1.52 #ifdef TIME_PER_TIMESTEP_SFP
527 ce107 1.44 CCE107 Time per timestep information
528     _BEGIN_MASTER( myThid )
529     CALL TIMER_GET_TIME( utnew, stnew, wtnew )
530     C Only output timing information after the 1st timestep
531     IF ( wtold .NE. 0.0D0 ) THEN
532     WRITE(msgBuf,'(A34,3F10.6)')
533     $ 'User, system and wallclock time:', utnew - utold,
534     $ stnew - stold, wtnew - wtold
535     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
536     ENDIF
537     utold = utnew
538     stold = stnew
539     wtold = wtnew
540     _END_MASTER( myThid )
541     #endif
542 ce107 1.52 #ifdef USE_PAPI_FLOPS_SFP
543     CCE107 PAPI summary performance
544     _BEGIN_MASTER( myThid )
545 ce107 1.54 #ifdef USE_FLIPS
546     call PAPIF_flips(real_time, proc_time, flpops, mflops, check)
547     #else
548 ce107 1.52 call PAPIF_flops(real_time, proc_time, flpops, mflops, check)
549 ce107 1.54 #endif
550 ce107 1.52 WRITE(msgBuf,'(A34,F10.6)')
551     $ 'Mflop/s during this timestep:', mflops
552     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
553 ce107 1.54 #ifdef PAPI_VERSION
554     call PAPIF_ipc(real_time, proc_time, instr, ipc, check)
555     WRITE(msgBuf,'(A34,F10.6)')
556     $ 'IPC during this timestep:', ipc
557     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
558     #endif
559 ce107 1.52 _END_MASTER( myThid )
560 ce107 1.54 #else
561     #ifdef USE_PCL_FLOPS_SFP
562     CCE107 PCL summary performance
563     _BEGIN_MASTER( myThid )
564     PCLstop(descr, i_result, fp_result, nevents)
565     do ipcl = 1, nevents
566     WRITE(msgBuf,'(A22,A26,F10.6)'),
567     $ pcl_counter_name(pcl_counter_list(ipcl)),
568     $ 'during this timestep:', fp_results(ipcl)
569     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
570     enddo
571     PCLstart(descr, pcl_counter_list, nevents, flags)
572     _END_MASTER( myThid )
573     #endif
574 ce107 1.52 #endif
575 cnh 1.1 RETURN
576     END
577 ce107 1.44
578 ce107 1.52 #ifdef TIME_PER_TIMESTEP_SFP
579 ce107 1.44 CCE107 Initialization of common block for per timestep timing
580     BLOCK DATA settimers
581     C !TIMING VARIABLES
582     C == Timing variables ==
583     REAL*8 utnew, utold, stnew, stold, wtnew, wtold
584     COMMON /timevars/ utnew, utold, stnew, stold, wtnew, wtold
585     DATA utnew, utold, stnew, stold, wtnew, wtold /6*0.0D0/
586     END
587     #endif
588 ce107 1.52 #ifdef USE_PAPI_FLOPS_SFP
589     CCE107 Initialization of common block for PAPI summary performance
590     BLOCK DATA setpapis
591 ce107 1.54 INTEGER*8 flpops, instr
592     REAL real_time, proc_time, mflops, ipc
593     COMMON /papivars/ flpops, instr, real_time, proc_time, mflops, ipc
594     DATA flpops, instr, real_time, proc_time, mflops, ipc /2*0,4*0.E0/
595 ce107 1.52 END
596     #endif

  ViewVC Help
Powered by ViewVC 1.1.22