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

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

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


Revision 1.53 - (show annotations) (download)
Sat Jul 11 22:00:40 2009 UTC (14 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62c, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62w, checkpoint62y, checkpoint62x, checkpoint62, checkpoint62b, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.52: +16 -30 lines
use simple EXCH (overlap 1 and no Corner Exch): this reduces number of
 EXCH calls by 2 if using exch2).

1 C $Header: /u/gcmpack/MITgcm/model/src/cg2d.F,v 1.52 2009/05/16 13:42:15 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5 #ifdef TARGET_NEC_SX
6 C set a sensible default for the outer loop unrolling parameter that can
7 C be overriden in the Makefile with the DEFINES macro or in CPP_OPTIONS.h
8 #ifndef CG2D_OUTERLOOPITERS
9 # define CG2D_OUTERLOOPITERS 10
10 #endif
11 #endif /* TARGET_NEC_SX */
12
13 CBOP
14 C !ROUTINE: CG2D
15 C !INTERFACE:
16 SUBROUTINE CG2D(
17 I cg2d_b,
18 U cg2d_x,
19 O firstResidual,
20 O lastResidual,
21 U numIters,
22 I myThid )
23 C !DESCRIPTION: \bv
24 C *==========================================================*
25 C | SUBROUTINE CG2D
26 C | o Two-dimensional grid problem conjugate-gradient
27 C | inverter (with preconditioner).
28 C *==========================================================*
29 C | Con. grad is an iterative procedure for solving Ax = b.
30 C | It requires the A be symmetric.
31 C | This implementation assumes A is a five-diagonal
32 C | matrix of the form that arises in the discrete
33 C | representation of the del^2 operator in a
34 C | two-dimensional space.
35 C | Notes:
36 C | ======
37 C | This implementation can support shared-memory
38 C | multi-threaded execution. In order to do this COMMON
39 C | blocks are used for many of the arrays - even ones that
40 C | are only used for intermedaite results. This design is
41 C | OK if you want to all the threads to collaborate on
42 C | solving the same problem. On the other hand if you want
43 C | the threads to solve several different problems
44 C | concurrently this implementation will not work.
45 C *==========================================================*
46 C \ev
47
48 C !USES:
49 IMPLICIT NONE
50 C === Global data ===
51 #include "SIZE.h"
52 #include "EEPARAMS.h"
53 #include "PARAMS.h"
54 #include "CG2D.h"
55 c#include "GRID.h"
56 c#include "SURFACE.h"
57
58 C !INPUT/OUTPUT PARAMETERS:
59 C === Routine arguments ===
60 C cg2d_b :: The source term or "right hand side"
61 C cg2d_x :: The solution
62 C firstResidual :: the initial residual before any iterations
63 C lastResidual :: the actual residual reached
64 C numIters :: Entry: the maximum number of iterations allowed
65 C Exit: the actual number of iterations used
66 C myThid :: Thread on which I am working.
67 _RL cg2d_b(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
68 _RL cg2d_x(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
69 _RL firstResidual
70 _RL lastResidual
71 INTEGER numIters
72 INTEGER myThid
73
74 C !LOCAL VARIABLES:
75 C === Local variables ====
76 C actualIts :: Number of iterations taken
77 C actualResidual :: residual
78 C bi, bj :: Block index in X and Y.
79 C eta_qrN :: Used in computing search directions
80 C eta_qrNM1 suffix N and NM1 denote current and
81 C cgBeta previous iterations respectively.
82 C alpha
83 C sumRHS :: Sum of right-hand-side. Sometimes this is a
84 C useful debuggin/trouble shooting diagnostic.
85 C For neumann problems sumRHS needs to be ~0.
86 C or they converge at a non-zero residual.
87 C err :: Measure of residual of Ax - b, usually the norm.
88 C I, J, it2d :: Loop counters ( it2d counts CG iterations )
89 INTEGER actualIts
90 _RL actualResidual
91 INTEGER bi, bj
92 INTEGER I, J, it2d
93 c INTEGER ks
94 _RL err, errTile(nSx,nSy)
95 _RL eta_qrN,eta_qrNtile(nSx,nSy)
96 _RL eta_qrNM1
97 _RL cgBeta
98 _RL alpha, alphaTile(nSx,nSy)
99 _RL sumRHS, sumRHStile(nSx,nSy)
100 _RL rhsMax
101 _RL rhsNorm
102 #ifdef CG2D_SINGLECPU_SUM
103 _RL localBuf(1:sNx,1:sNy,nSx,nSy)
104 #endif
105 CHARACTER*(MAX_LEN_MBUF) msgBuf
106 CEOP
107
108
109 CcnhDebugStarts
110 C CHARACTER*(MAX_LEN_FNAM) suff
111 CcnhDebugEnds
112
113
114 C-- Initialise inverter
115 eta_qrNM1 = 1. _d 0
116
117 CcnhDebugStarts
118 C _EXCH_XY_RL( cg2d_b, myThid )
119 C CALL PLOT_FIELD_XYRL( cg2d_b, 'CG2D.0 CG2D_B' , 1, myThid )
120 C suff = 'unnormalised'
121 C CALL WRITE_FLD_XY_RL ( 'cg2d_b.',suff, cg2d_b, 1, myThid)
122 C STOP
123 CcnhDebugEnds
124
125 C-- Normalise RHS
126 rhsMax = 0. _d 0
127 DO bj=myByLo(myThid),myByHi(myThid)
128 DO bi=myBxLo(myThid),myBxHi(myThid)
129 DO J=1,sNy
130 DO I=1,sNx
131 cg2d_b(I,J,bi,bj) = cg2d_b(I,J,bi,bj)*cg2dNorm
132 rhsMax = MAX(ABS(cg2d_b(I,J,bi,bj)),rhsMax)
133 ENDDO
134 ENDDO
135 ENDDO
136 ENDDO
137
138 IF (cg2dNormaliseRHS) THEN
139 C- Normalise RHS :
140 #ifdef LETS_MAKE_JAM
141 C _GLOBAL_MAX_RL( rhsMax, myThid )
142 rhsMax=1.
143 #else
144 _GLOBAL_MAX_RL( rhsMax, myThid )
145 #endif
146 rhsNorm = 1. _d 0
147 IF ( rhsMax .NE. 0. ) rhsNorm = 1. _d 0 / rhsMax
148 DO bj=myByLo(myThid),myByHi(myThid)
149 DO bi=myBxLo(myThid),myBxHi(myThid)
150 DO J=1,sNy
151 DO I=1,sNx
152 cg2d_b(I,J,bi,bj) = cg2d_b(I,J,bi,bj)*rhsNorm
153 cg2d_x(I,J,bi,bj) = cg2d_x(I,J,bi,bj)*rhsNorm
154 ENDDO
155 ENDDO
156 ENDDO
157 ENDDO
158 C- end Normalise RHS
159 ENDIF
160
161 C-- Update overlaps
162 c CALL EXCH_XY_RL( cg2d_b, myThid )
163 CALL EXCH_XY_RL( cg2d_x, myThid )
164 CcnhDebugStarts
165 C CALL PLOT_FIELD_XYRL( cg2d_b, 'CG2D.1 CG2D_B' , 1, myThid )
166 C suff = 'normalised'
167 C CALL WRITE_FLD_XY_RL ( 'cg2d_b.',suff, cg2d_b, 1, myThid)
168 CcnhDebugEnds
169
170 C-- Initial residual calculation
171 DO bj=myByLo(myThid),myByHi(myThid)
172 DO bi=myBxLo(myThid),myBxHi(myThid)
173 DO J=1-1,sNy+1
174 DO I=1-1,sNx+1
175 cg2d_s(I,J,bi,bj) = 0.
176 ENDDO
177 ENDDO
178 sumRHStile(bi,bj) = 0. _d 0
179 errTile(bi,bj) = 0. _d 0
180 #ifdef TARGET_NEC_SX
181 !CDIR OUTERUNROLL=CG2D_OUTERLOOPITERS
182 #endif /* TARGET_NEC_SX */
183 DO J=1,sNy
184 DO I=1,sNx
185 c ks = ksurfC(I,J,bi,bj)
186 cg2d_r(I,J,bi,bj) = cg2d_b(I,J,bi,bj) -
187 & (aW2d(I ,J ,bi,bj)*cg2d_x(I-1,J ,bi,bj)
188 & +aW2d(I+1,J ,bi,bj)*cg2d_x(I+1,J ,bi,bj)
189 & +aS2d(I ,J ,bi,bj)*cg2d_x(I ,J-1,bi,bj)
190 & +aS2d(I ,J+1,bi,bj)*cg2d_x(I ,J+1,bi,bj)
191 & +aC2d(I ,J ,bi,bj)*cg2d_x(I ,J ,bi,bj)
192 & )
193 c & -aW2d(I ,J ,bi,bj)*cg2d_x(I ,J ,bi,bj)
194 c & -aW2d(I+1,J ,bi,bj)*cg2d_x(I ,J ,bi,bj)
195 c & -aS2d(I ,J ,bi,bj)*cg2d_x(I ,J ,bi,bj)
196 c & -aS2d(I ,J+1,bi,bj)*cg2d_x(I ,J ,bi,bj)
197 c & -freeSurfFac*_rA(i,j,bi,bj)*deepFac2F(ks)*recip_Bo(i,j,bi,bj)
198 c & *cg2d_x(I ,J ,bi,bj)
199 c & /deltaTMom/deltaTfreesurf*cg2dNorm
200 c & )
201 #ifdef CG2D_SINGLECPU_SUM
202 localBuf(I,J,bi,bj) = cg2d_r(I,J,bi,bj)*cg2d_r(I,J,bi,bj)
203 #else
204 errTile(bi,bj) = errTile(bi,bj)
205 & + cg2d_r(I,J,bi,bj)*cg2d_r(I,J,bi,bj)
206 sumRHStile(bi,bj) = sumRHStile(bi,bj) + cg2d_b(I,J,bi,bj)
207 #endif
208 ENDDO
209 ENDDO
210 ENDDO
211 ENDDO
212 CALL EXCH_S3D_RL( cg2d_r, 1, myThid )
213 #ifdef CG2D_SINGLECPU_SUM
214 CALL GLOBAL_SUM_SINGLECPU_RL(localBuf, err, 0, 0, myThid)
215 CALL GLOBAL_SUM_SINGLECPU_RL(cg2d_b, sumRHS, OLx, OLy, myThid)
216 #else
217 CALL GLOBAL_SUM_TILE_RL( errTile, err, myThid )
218 CALL GLOBAL_SUM_TILE_RL( sumRHStile, sumRHS, myThid )
219 #endif
220 err = SQRT(err)
221 actualIts = 0
222 actualResidual = err
223
224 IF ( debugLevel .GE. debLevZero ) THEN
225 _BEGIN_MASTER( myThid )
226 WRITE(standardmessageunit,'(A,1P2E22.14)')
227 & ' cg2d: Sum(rhs),rhsMax = ', sumRHS,rhsMax
228 _END_MASTER( myThid )
229 ENDIF
230 C _BARRIER
231 c _BEGIN_MASTER( myThid )
232 c WRITE(standardmessageunit,'(A,I6,1PE30.14)')
233 c & ' CG2D iters, err = ',
234 c & actualIts, actualResidual
235 c _END_MASTER( myThid )
236 firstResidual=actualResidual
237
238 IF ( err .LT. cg2dTolerance ) GOTO 11
239
240 C >>>>>>>>>>>>>>> BEGIN SOLVER <<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
241 DO 10 it2d=1, numIters
242
243 CcnhDebugStarts
244 C WRITE(*,*) ' CG2D: Iteration ',it2d-1,' residual = ',
245 C & actualResidual
246 CcnhDebugEnds
247 C-- Solve preconditioning equation and update
248 C-- conjugate direction vector "s".
249 DO bj=myByLo(myThid),myByHi(myThid)
250 DO bi=myBxLo(myThid),myBxHi(myThid)
251 eta_qrNtile(bi,bj) = 0. _d 0
252 #ifdef TARGET_NEC_SX
253 !CDIR OUTERUNROLL=CG2D_OUTERLOOPITERS
254 #endif /* TARGET_NEC_SX */
255 DO J=1,sNy
256 DO I=1,sNx
257 cg2d_q(I,J,bi,bj) =
258 & pC(I ,J ,bi,bj)*cg2d_r(I ,J ,bi,bj)
259 & +pW(I ,J ,bi,bj)*cg2d_r(I-1,J ,bi,bj)
260 & +pW(I+1,J ,bi,bj)*cg2d_r(I+1,J ,bi,bj)
261 & +pS(I ,J ,bi,bj)*cg2d_r(I ,J-1,bi,bj)
262 & +pS(I ,J+1,bi,bj)*cg2d_r(I ,J+1,bi,bj)
263 CcnhDebugStarts
264 C cg2d_q(I,J,bi,bj) = cg2d_r(I ,J ,bi,bj)
265 CcnhDebugEnds
266 #ifdef CG2D_SINGLECPU_SUM
267 localBuf(I,J,bi,bj) =
268 & cg2d_q(I,J,bi,bj)*cg2d_r(I,J,bi,bj)
269 #else
270 eta_qrNtile(bi,bj) = eta_qrNtile(bi,bj)
271 & +cg2d_q(I,J,bi,bj)*cg2d_r(I,J,bi,bj)
272 #endif
273 ENDDO
274 ENDDO
275 ENDDO
276 ENDDO
277
278 #ifdef CG2D_SINGLECPU_SUM
279 CALL GLOBAL_SUM_SINGLECPU_RL( localBuf,eta_qrN,0,0,myThid )
280 #else
281 CALL GLOBAL_SUM_TILE_RL( eta_qrNtile,eta_qrN,myThid )
282 #endif
283 CcnhDebugStarts
284 C WRITE(*,*) ' CG2D: Iteration ',it2d-1,' eta_qrN = ',eta_qrN
285 CcnhDebugEnds
286 cgBeta = eta_qrN/eta_qrNM1
287 CcnhDebugStarts
288 C WRITE(*,*) ' CG2D: Iteration ',it2d-1,' beta = ',cgBeta
289 CcnhDebugEnds
290 eta_qrNM1 = eta_qrN
291
292 DO bj=myByLo(myThid),myByHi(myThid)
293 DO bi=myBxLo(myThid),myBxHi(myThid)
294 DO J=1,sNy
295 DO I=1,sNx
296 cg2d_s(I,J,bi,bj) = cg2d_q(I,J,bi,bj)
297 & + cgBeta*cg2d_s(I,J,bi,bj)
298 ENDDO
299 ENDDO
300 ENDDO
301 ENDDO
302
303 C-- Do exchanges that require messages i.e. between
304 C-- processes.
305 CALL EXCH_S3D_RL( cg2d_s, 1, myThid )
306
307 C== Evaluate laplace operator on conjugate gradient vector
308 C== q = A.s
309 DO bj=myByLo(myThid),myByHi(myThid)
310 DO bi=myBxLo(myThid),myBxHi(myThid)
311 alphaTile(bi,bj) = 0. _d 0
312 #ifdef TARGET_NEC_SX
313 !CDIR OUTERUNROLL=CG2D_OUTERLOOPITERS
314 #endif /* TARGET_NEC_SX */
315 DO J=1,sNy
316 DO I=1,sNx
317 c ks = ksurfC(I,J,bi,bj)
318 cg2d_q(I,J,bi,bj) =
319 & aW2d(I ,J ,bi,bj)*cg2d_s(I-1,J ,bi,bj)
320 & +aW2d(I+1,J ,bi,bj)*cg2d_s(I+1,J ,bi,bj)
321 & +aS2d(I ,J ,bi,bj)*cg2d_s(I ,J-1,bi,bj)
322 & +aS2d(I ,J+1,bi,bj)*cg2d_s(I ,J+1,bi,bj)
323 & +aC2d(I ,J ,bi,bj)*cg2d_s(I ,J ,bi,bj)
324 c & -aW2d(I ,J ,bi,bj)*cg2d_s(I ,J ,bi,bj)
325 c & -aW2d(I+1,J ,bi,bj)*cg2d_s(I ,J ,bi,bj)
326 c & -aS2d(I ,J ,bi,bj)*cg2d_s(I ,J ,bi,bj)
327 c & -aS2d(I ,J+1,bi,bj)*cg2d_s(I ,J ,bi,bj)
328 c & -freeSurfFac*_rA(i,j,bi,bj)*deepFac2F(ks)*recip_Bo(i,j,bi,bj)
329 c & *cg2d_s(I ,J ,bi,bj)
330 c & /deltaTMom/deltaTfreesurf*cg2dNorm
331 #ifdef CG2D_SINGLECPU_SUM
332 localBuf(I,J,bi,bj) = cg2d_s(I,J,bi,bj)*cg2d_q(I,J,bi,bj)
333 #else
334 alphaTile(bi,bj) = alphaTile(bi,bj)
335 & + cg2d_s(I,J,bi,bj)*cg2d_q(I,J,bi,bj)
336 #endif
337 ENDDO
338 ENDDO
339 ENDDO
340 ENDDO
341 #ifdef CG2D_SINGLECPU_SUM
342 CALL GLOBAL_SUM_SINGLECPU_RL(localBuf, alpha, 0, 0, myThid)
343 #else
344 CALL GLOBAL_SUM_TILE_RL( alphaTile, alpha, myThid )
345 #endif
346 CcnhDebugStarts
347 C WRITE(*,*) ' CG2D: Iteration ',it2d-1,' SUM(s*q)= ',alpha
348 CcnhDebugEnds
349 alpha = eta_qrN/alpha
350 CcnhDebugStarts
351 C WRITE(*,*) ' CG2D: Iteration ',it2d-1,' alpha= ',alpha
352 CcnhDebugEnds
353
354 C== Update solution and residual vectors
355 C Now compute "interior" points.
356 DO bj=myByLo(myThid),myByHi(myThid)
357 DO bi=myBxLo(myThid),myBxHi(myThid)
358 errTile(bi,bj) = 0. _d 0
359 DO J=1,sNy
360 DO I=1,sNx
361 cg2d_x(I,J,bi,bj)=cg2d_x(I,J,bi,bj)+alpha*cg2d_s(I,J,bi,bj)
362 cg2d_r(I,J,bi,bj)=cg2d_r(I,J,bi,bj)-alpha*cg2d_q(I,J,bi,bj)
363 #ifdef CG2D_SINGLECPU_SUM
364 localBuf(I,J,bi,bj) = cg2d_r(I,J,bi,bj)*cg2d_r(I,J,bi,bj)
365 #else
366 errTile(bi,bj) = errTile(bi,bj)
367 & + cg2d_r(I,J,bi,bj)*cg2d_r(I,J,bi,bj)
368 #endif
369 ENDDO
370 ENDDO
371 ENDDO
372 ENDDO
373
374 #ifdef CG2D_SINGLECPU_SUM
375 CALL GLOBAL_SUM_SINGLECPU_RL(localBuf, err, 0, 0, myThid)
376 #else
377 CALL GLOBAL_SUM_TILE_RL( errTile, err, myThid )
378 #endif
379 err = SQRT(err)
380 actualIts = it2d
381 actualResidual = err
382 IF ( debugLevel.GT.debLevB ) THEN
383 c IF ( DIFFERENT_MULTIPLE(monitorFreq,myTime,deltaTClock)
384 c & ) THEN
385 _BEGIN_MASTER( myThid )
386 WRITE(msgBuf,'(A,I6,A,1PE21.14)')
387 & ' cg2d: iter=', actualIts, ' ; resid.= ', actualResidual
388 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
389 _END_MASTER( myThid )
390 c ENDIF
391 ENDIF
392 IF ( err .LT. cg2dTolerance ) GOTO 11
393
394 CALL EXCH_S3D_RL( cg2d_r, 1, myThid )
395
396 10 CONTINUE
397 11 CONTINUE
398
399 IF (cg2dNormaliseRHS) THEN
400 C-- Un-normalise the answer
401 DO bj=myByLo(myThid),myByHi(myThid)
402 DO bi=myBxLo(myThid),myBxHi(myThid)
403 DO J=1,sNy
404 DO I=1,sNx
405 cg2d_x(I ,J ,bi,bj) = cg2d_x(I ,J ,bi,bj)/rhsNorm
406 ENDDO
407 ENDDO
408 ENDDO
409 ENDDO
410 ENDIF
411
412 C The following exchange was moved up to solve_for_pressure
413 C for compatibility with TAMC.
414 C _EXCH_XY_RL(cg2d_x, myThid )
415 c _BEGIN_MASTER( myThid )
416 c WRITE(*,'(A,I6,1PE30.14)') ' CG2D iters, err = ',
417 c & actualIts, actualResidual
418 c _END_MASTER( myThid )
419
420 C-- Return parameters to caller
421 lastResidual=actualResidual
422 numIters=actualIts
423
424 CcnhDebugStarts
425 C CALL PLOT_FIELD_XYRL( cg2d_x, 'CALC_MOM_RHS CG2D_X' , 1, myThid )
426 C err = 0. _d 0
427 C DO bj=myByLo(myThid),myByHi(myThid)
428 C DO bi=myBxLo(myThid),myBxHi(myThid)
429 C DO J=1,sNy
430 C DO I=1,sNx
431 C cg2d_r(I,J,bi,bj) = cg2d_b(I,J,bi,bj) -
432 C & (aW2d(I ,J ,bi,bj)*cg2d_x(I-1,J ,bi,bj)
433 C & +aW2d(I+1,J ,bi,bj)*cg2d_x(I+1,J ,bi,bj)
434 C & +aS2d(I ,J ,bi,bj)*cg2d_x(I ,J-1,bi,bj)
435 C & +aS2d(I ,J+1,bi,bj)*cg2d_x(I ,J+1,bi,bj)
436 C & -aW2d(I ,J ,bi,bj)*cg2d_x(I ,J ,bi,bj)
437 C & -aW2d(I+1,J ,bi,bj)*cg2d_x(I ,J ,bi,bj)
438 C & -aS2d(I ,J ,bi,bj)*cg2d_x(I ,J ,bi,bj)
439 C & -aS2d(I ,J+1,bi,bj)*cg2d_x(I ,J ,bi,bj))
440 C err = err +
441 C & cg2d_r(I,J,bi,bj)*cg2d_r(I,J,bi,bj)
442 C ENDDO
443 C ENDDO
444 C ENDDO
445 C ENDDO
446 C _GLOBAL_SUM_RL( err , myThid )
447 C write(*,*) 'cg2d: Ax - b = ',SQRT(err)
448 CcnhDebugEnds
449
450 RETURN
451 END

  ViewVC Help
Powered by ViewVC 1.1.22