/[MITgcm]/MITgcm_contrib/heimbach/OpenAD/code_shallow_openad3/cg2d.F
ViewVC logotype

Contents of /MITgcm_contrib/heimbach/OpenAD/code_shallow_openad3/cg2d.F

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


Revision 1.3 - (show annotations) (download)
Thu Dec 19 16:10:21 2013 UTC (11 years, 7 months ago) by utke
Branch: MAIN
CVS Tags: HEAD
Changes since 1.2: +1 -1 lines
FILE REMOVED
stale

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

  ViewVC Help
Powered by ViewVC 1.1.22