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

Annotation of /MITgcm_contrib/heimbach/OpenAD/code_shallow_openad2/cg2d.F

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


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

1 utke 1.2 C $Header: /u/gcmpack/MITgcm_contrib/heimbach/OpenAD/code_shallow_openad2/cg2d.F,v 1.1 2006/08/01 19:26:59 utke Exp $
2 utke 1.1 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 "GRID.h"
48     #include "CG2D.h"
49     #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 - Block index in X and Y.
72     C bj
73     C eta_qrN - Used in computing search directions
74     C eta_qrNM1 suffix N and NM1 denote current and
75     C cgBeta previous iterations respectively.
76     C alpha
77     C sumRHS - Sum of right-hand-side. Sometimes this is a
78     C useful debuggin/trouble shooting diagnostic.
79     C For neumann problems sumRHS needs to be ~0.
80     C or they converge at a non-zero residual.
81     C err - Measure of residual of Ax - b, usually the norm.
82     C I, J, N - Loop counters ( N counts CG iterations )
83     INTEGER actualIts
84     _RL actualResidual
85     INTEGER bi, bj
86     INTEGER I, J, it2d
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     CEOP
96    
97    
98     CcnhDebugStarts
99     C CHARACTER*(MAX_LEN_FNAM) suff
100     CcnhDebugEnds
101    
102    
103     C-- Initialise inverter
104     eta_qrNM1 = 1. _d 0
105    
106     CcnhDebugStarts
107     C _EXCH_XY_R8( cg2d_b, myThid )
108     C CALL PLOT_FIELD_XYRL( cg2d_b, 'CG2D.0 CG2D_B' , 1, myThid )
109     C suff = 'unnormalised'
110     C CALL WRITE_FLD_XY_RL ( 'cg2d_b.',suff, cg2d_b, 1, myThid)
111     C STOP
112     CcnhDebugEnds
113    
114     C-- Normalise RHS
115     rhsMax = 0. _d 0
116     DO bj=myByLo(myThid),myByHi(myThid)
117     DO bi=myBxLo(myThid),myBxHi(myThid)
118     DO J=1,sNy
119     DO I=1,sNx
120     cg2d_b(I,J,bi,bj) = cg2d_b(I,J,bi,bj)*cg2dNorm
121     rhsMax = MAX(ABS(cg2d_b(I,J,bi,bj)),rhsMax)
122     ENDDO
123     ENDDO
124     ENDDO
125     ENDDO
126    
127     IF (cg2dNormaliseRHS) THEN
128     C- Normalise RHS :
129     #ifdef LETS_MAKE_JAM
130     C _GLOBAL_MAX_R8( rhsMax, myThid )
131     rhsMax=1.
132     #else
133     _GLOBAL_MAX_R8( rhsMax, myThid )
134     Catm rhsMax=1.
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     cg2d_s(I,J,bi,bj) = 0.
170     cg2d_r(I,J,bi,bj) = cg2d_b(I,J,bi,bj) -
171     & (aW2d(I ,J ,bi,bj)*cg2d_x(I-1,J ,bi,bj)
172     & +aW2d(I+1,J ,bi,bj)*cg2d_x(I+1,J ,bi,bj)
173     & +aS2d(I ,J ,bi,bj)*cg2d_x(I ,J-1,bi,bj)
174     & +aS2d(I ,J+1,bi,bj)*cg2d_x(I ,J+1,bi,bj)
175     & -aW2d(I ,J ,bi,bj)*cg2d_x(I ,J ,bi,bj)
176     & -aW2d(I+1,J ,bi,bj)*cg2d_x(I ,J ,bi,bj)
177     & -aS2d(I ,J ,bi,bj)*cg2d_x(I ,J ,bi,bj)
178     & -aS2d(I ,J+1,bi,bj)*cg2d_x(I ,J ,bi,bj)
179     & -freeSurfFac*_rA(i,j,bi,bj)*recip_Bo(i,j,bi,bj)*
180     & cg2d_x(I ,J ,bi,bj)/deltaTMom/deltaTfreesurf*cg2dNorm
181     & )
182     errTile = errTile +
183     & cg2d_r(I,J,bi,bj)*cg2d_r(I,J,bi,bj)
184     sumRHStile = sumRHStile +
185     & cg2d_b(I,J,bi,bj)
186     ENDDO
187     ENDDO
188     sumRHS = sumRHS + sumRHStile
189     err = err + errTile
190     ENDDO
191     ENDDO
192     C _EXCH_XY_R8( cg2d_r, myThid )
193     #ifdef LETS_MAKE_JAM
194     CALL EXCH_XY_O1_R8_JAM( cg2d_r )
195     #else
196     CALL EXCH_XY_RL( cg2d_r, myThid )
197     #endif
198     C _EXCH_XY_R8( cg2d_s, myThid )
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 = ',
214     & sumRHS,rhsMax
215     _END_MASTER( myThid )
216     ENDIF
217     C _BARRIER
218     c _BEGIN_MASTER( myThid )
219     c WRITE(standardmessageunit,'(A,I6,1PE30.14)')
220     c & ' CG2D iters, err = ',
221     c & actualIts, actualResidual
222     c _END_MASTER( myThid )
223     firstResidual=actualResidual
224    
225     IF ( err .ge. cg2dTolerance ) then
226    
227     C >>>>>>>>>>>>>>> BEGIN SOLVER <<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
228     it2d=1
229    
230     DO while ((it2d .le. numIters .and. err .ge. cg2dTolerance))
231    
232     CcnhDebugStarts
233     C WRITE(*,*) ' CG2D: Iteration ',it2d-1,' residual = ',
234     C & actualResidual
235     CcnhDebugEnds
236     C-- Solve preconditioning equation and update
237     C-- conjugate direction vector "s".
238     eta_qrN = 0. _d 0
239     DO bj=myByLo(myThid),myByHi(myThid)
240     DO bi=myBxLo(myThid),myBxHi(myThid)
241     eta_qrNtile = 0. _d 0
242     DO J=1,sNy
243     DO I=1,sNx
244     cg2d_q(I,J,bi,bj) =
245     & pC(I ,J ,bi,bj)*cg2d_r(I ,J ,bi,bj)
246     & +pW(I ,J ,bi,bj)*cg2d_r(I-1,J ,bi,bj)
247     & +pW(I+1,J ,bi,bj)*cg2d_r(I+1,J ,bi,bj)
248     & +pS(I ,J ,bi,bj)*cg2d_r(I ,J-1,bi,bj)
249     & +pS(I ,J+1,bi,bj)*cg2d_r(I ,J+1,bi,bj)
250     CcnhDebugStarts
251     C cg2d_q(I,J,bi,bj) = cg2d_r(I ,J ,bi,bj)
252     CcnhDebugEnds
253     eta_qrNtile = eta_qrNtile
254     & +cg2d_q(I,J,bi,bj)*cg2d_r(I,J,bi,bj)
255     ENDDO
256     ENDDO
257     eta_qrN = eta_qrN + eta_qrNtile
258     ENDDO
259     ENDDO
260    
261     _GLOBAL_SUM_R8(eta_qrN, myThid)
262     CcnhDebugStarts
263     C WRITE(*,*) ' CG2D: Iteration ',it2d-1,' eta_qrN = ',eta_qrN
264     CcnhDebugEnds
265     cgBeta = eta_qrN/eta_qrNM1
266     CcnhDebugStarts
267     C WRITE(*,*) ' CG2D: Iteration ',it2d-1,' beta = ',cgBeta
268     CcnhDebugEnds
269     eta_qrNM1 = eta_qrN
270    
271     DO bj=myByLo(myThid),myByHi(myThid)
272     DO bi=myBxLo(myThid),myBxHi(myThid)
273     DO J=1,sNy
274     DO I=1,sNx
275     cg2d_s(I,J,bi,bj) = cg2d_q(I,J,bi,bj)
276     & + cgBeta*cg2d_s(I,J,bi,bj)
277     ENDDO
278     ENDDO
279     ENDDO
280     ENDDO
281    
282     C-- Do exchanges that require messages i.e. between
283     C-- processes.
284     C _EXCH_XY_R8( cg2d_s, myThid )
285     #ifdef LETS_MAKE_JAM
286     CALL EXCH_XY_O1_R8_JAM( cg2d_s )
287     #else
288     CALL EXCH_XY_RL( cg2d_s, myThid )
289     #endif
290    
291     C== Evaluate laplace operator on conjugate gradient vector
292     C== q = A.s
293     alpha = 0. _d 0
294     DO bj=myByLo(myThid),myByHi(myThid)
295     DO bi=myBxLo(myThid),myBxHi(myThid)
296     alphaTile = 0. _d 0
297     DO J=1,sNy
298     DO I=1,sNx
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     & -aW2d(I ,J ,bi,bj)*cg2d_s(I ,J ,bi,bj)
305     & -aW2d(I+1,J ,bi,bj)*cg2d_s(I ,J ,bi,bj)
306     & -aS2d(I ,J ,bi,bj)*cg2d_s(I ,J ,bi,bj)
307     & -aS2d(I ,J+1,bi,bj)*cg2d_s(I ,J ,bi,bj)
308     & -freeSurfFac*_rA(i,j,bi,bj)*recip_Bo(i,j,bi,bj)*
309     & cg2d_s(I ,J ,bi,bj)/deltaTMom/deltaTfreesurf*cg2dNorm
310     alphaTile = alphaTile+cg2d_s(I,J,bi,bj)*cg2d_q(I,J,bi,bj)
311     ENDDO
312     ENDDO
313     alpha = alpha + alphaTile
314     ENDDO
315     ENDDO
316     _GLOBAL_SUM_R8(alpha,myThid)
317     CcnhDebugStarts
318     C WRITE(*,*) ' CG2D: Iteration ',it2d-1,' SUM(s*q)= ',alpha
319     CcnhDebugEnds
320     alpha = eta_qrN/alpha
321     CcnhDebugStarts
322     C WRITE(*,*) ' CG2D: Iteration ',it2d-1,' alpha= ',alpha
323     CcnhDebugEnds
324    
325     C== Update solution and residual vectors
326     C Now compute "interior" points.
327     err = 0. _d 0
328     DO bj=myByLo(myThid),myByHi(myThid)
329     DO bi=myBxLo(myThid),myBxHi(myThid)
330     errTile = 0. _d 0
331     DO J=1,sNy
332     DO I=1,sNx
333     cg2d_x(I,J,bi,bj)=cg2d_x(I,J,bi,bj)+alpha*cg2d_s(I,J,bi,bj)
334     cg2d_r(I,J,bi,bj)=cg2d_r(I,J,bi,bj)-alpha*cg2d_q(I,J,bi,bj)
335     errTile = errTile+cg2d_r(I,J,bi,bj)*cg2d_r(I,J,bi,bj)
336     ENDDO
337     ENDDO
338     err = err + errTile
339     ENDDO
340     ENDDO
341    
342     _GLOBAL_SUM_R8( err , myThid )
343     err = SQRT(err)
344     actualIts = it2d
345     actualResidual = err
346     C _EXCH_XY_R8(cg2d_r, myThid )
347     #ifdef LETS_MAKE_JAM
348     CALL EXCH_XY_O1_R8_JAM( cg2d_r )
349     #else
350     CALL EXCH_XY_RL( cg2d_r, myThid )
351     #endif
352     it2d=it2d+1
353    
354     end do
355     end if
356    
357     IF (cg2dNormaliseRHS) THEN
358     C-- Un-normalise the answer
359     DO bj=myByLo(myThid),myByHi(myThid)
360     DO bi=myBxLo(myThid),myBxHi(myThid)
361     DO J=1,sNy
362     DO I=1,sNx
363     cg2d_x(I ,J ,bi,bj) = cg2d_x(I ,J ,bi,bj)/rhsNorm
364     ENDDO
365     ENDDO
366     ENDDO
367     ENDDO
368     ENDIF
369    
370     C The following exchange was moved up to solve_for_pressure
371     C for compatibility with TAMC.
372     C _EXCH_XY_R8(cg2d_x, myThid )
373     c _BEGIN_MASTER( myThid )
374     c WRITE(*,'(A,I6,1PE30.14)') ' CG2D iters, err = ',
375     c & actualIts, actualResidual
376     c _END_MASTER( myThid )
377    
378     C-- Return parameters to caller
379     lastResidual=actualResidual
380     numIters=actualIts
381    
382     CcnhDebugStarts
383     C CALL PLOT_FIELD_XYRL( cg2d_x, 'CALC_MOM_RHS CG2D_X' , 1, myThid )
384     C err = 0. _d 0
385     C DO bj=myByLo(myThid),myByHi(myThid)
386     C DO bi=myBxLo(myThid),myBxHi(myThid)
387     C DO J=1,sNy
388     C DO I=1,sNx
389     C cg2d_r(I,J,bi,bj) = cg2d_b(I,J,bi,bj) -
390     C & (aW2d(I ,J ,bi,bj)*cg2d_x(I-1,J ,bi,bj)
391     C & +aW2d(I+1,J ,bi,bj)*cg2d_x(I+1,J ,bi,bj)
392     C & +aS2d(I ,J ,bi,bj)*cg2d_x(I ,J-1,bi,bj)
393     C & +aS2d(I ,J+1,bi,bj)*cg2d_x(I ,J+1,bi,bj)
394     C & -aW2d(I ,J ,bi,bj)*cg2d_x(I ,J ,bi,bj)
395     C & -aW2d(I+1,J ,bi,bj)*cg2d_x(I ,J ,bi,bj)
396     C & -aS2d(I ,J ,bi,bj)*cg2d_x(I ,J ,bi,bj)
397     C & -aS2d(I ,J+1,bi,bj)*cg2d_x(I ,J ,bi,bj))
398     C err = err +
399     C & cg2d_r(I,J,bi,bj)*cg2d_r(I,J,bi,bj)
400     C ENDDO
401     C ENDDO
402     C ENDDO
403     C ENDDO
404     C _GLOBAL_SUM_R8( err , myThid )
405     C write(*,*) 'cg2d: Ax - b = ',SQRT(err)
406     CcnhDebugEnds
407    
408     RETURN
409     END

  ViewVC Help
Powered by ViewVC 1.1.22