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

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

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


Revision 1.53 - (show annotations) (download)
Thu Feb 23 20:55:49 2006 UTC (18 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58b_post, checkpoint58d_post, checkpoint58c_post
Changes since 1.52: +4 -4 lines
1rst implementation of  Implicit IGW using the 3-D solver (use3Dsolver=T)
 and based on the reference stratification

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

  ViewVC Help
Powered by ViewVC 1.1.22