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

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

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


Revision 1.43 - (hide annotations) (download)
Wed Jul 20 22:33:02 2005 UTC (18 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57m_post, checkpoint57s_post, checkpoint58b_post, checkpoint57y_post, checkpoint57r_post, checkpoint58, checkpoint58f_post, checkpoint57n_post, checkpoint58d_post, checkpoint58a_post, checkpoint57z_post, checkpoint58m_post, checkpoint57t_post, checkpoint57v_post, checkpoint57y_pre, checkpoint58o_post, checkpoint58p_post, checkpoint58e_post, checkpoint58n_post, checkpoint57p_post, checkpint57u_post, checkpoint57q_post, checkpoint58k_post, checkpoint58l_post, checkpoint58g_post, checkpoint58h_post, checkpoint58j_post, checkpoint57o_post, checkpoint57w_post, checkpoint58i_post, checkpoint57x_post, checkpoint58c_post
Changes since 1.42: +18 -33 lines
use "globalArea" (no need to re-compute it)

1 jmc 1.43 C $Header: /u/gcmpack/MITgcm/model/src/ini_cg2d.F,v 1.42 2003/10/09 04:19:18 edhill Exp $
2 jmc 1.30 C $Name: $
3 cnh 1.1
4 edhill 1.42 #include "PACKAGES_CONFIG.h"
5 adcroft 1.13 #include "CPP_OPTIONS.h"
6 cnh 1.1
7 cnh 1.37 CBOP
8     C !ROUTINE: INI_CG2D
9     C !INTERFACE:
10 cnh 1.1 SUBROUTINE INI_CG2D( myThid )
11 cnh 1.37
12     C !DESCRIPTION: \bv
13     C *==========================================================*
14     C | SUBROUTINE INI_CG2D
15     C | o Initialise 2d conjugate gradient solver operators.
16     C *==========================================================*
17     C | These arrays are purely a function of the basin geom.
18     C | We set then here once and them use then repeatedly.
19     C *==========================================================*
20     C \ev
21    
22     C !USES:
23 adcroft 1.23 IMPLICIT NONE
24 cnh 1.1 C === Global variables ===
25     #include "SIZE.h"
26     #include "EEPARAMS.h"
27     #include "PARAMS.h"
28     #include "GRID.h"
29 jmc 1.31 #include "SURFACE.h"
30 adcroft 1.34 #include "CG2D.h"
31 adcroft 1.26 #ifdef ALLOW_OBCS
32 adcroft 1.22 #include "OBCS.h"
33 adcroft 1.26 #endif
34 cnh 1.1
35 cnh 1.37 C !INPUT/OUTPUT PARAMETERS:
36 cnh 1.1 C === Routine arguments ===
37     C myThid - Thread no. that called this routine.
38     INTEGER myThid
39    
40 cnh 1.37 C !LOCAL VARIABLES:
41 cnh 1.1 C === Local variables ===
42     C xG, yG - Global coordinate location.
43     C zG
44     C iG, jG - Global coordinate index
45     C bi,bj - Loop counters
46     C faceArea - Temporary used to hold cell face areas.
47     C I,J,K
48 adcroft 1.34 C myNorm - Work variable used in calculating normalisation factor
49     C sumArea - Work variable used to compute the total Domain Area
50 cnh 1.1 CHARACTER*(MAX_LEN_MBUF) msgBuf
51     INTEGER bi, bj
52     INTEGER I, J, K
53 cnh 1.7 _RL faceArea
54 cnh 1.15 _RS myNorm
55 cnh 1.4 _RL aC, aCw, aCs
56 cnh 1.37 CEOP
57 jmc 1.38
58     C-- Initialize arrays in common blocs (CG2D.h) ; not really necessary
59     C but safer when EXCH do not fill all the overlap regions.
60     DO bj=myByLo(myThid),myByHi(myThid)
61     DO bi=myBxLo(myThid),myBxHi(myThid)
62     DO J=1-OLy,sNy+OLy
63     DO I=1-OLx,sNx+OLx
64     aW2d(I,J,bi,bj) = 0. _d 0
65     aS2d(I,J,bi,bj) = 0. _d 0
66     pW(I,J,bi,bj) = 0. _d 0
67     pS(I,J,bi,bj) = 0. _d 0
68     pC(I,J,bi,bj) = 0. _d 0
69     cg2d_q(I,J,bi,bj) = 0. _d 0
70     ENDDO
71     ENDDO
72     DO J=1-1,sNy+1
73     DO I=1-1,sNx+1
74     cg2d_r(I,J,bi,bj) = 0. _d 0
75     cg2d_s(I,J,bi,bj) = 0. _d 0
76     ENDDO
77     ENDDO
78     ENDDO
79     ENDDO
80 jmc 1.31
81 cnh 1.1 C-- Initialise laplace operator
82     C aW2d: integral in Z Ax/dX
83     C aS2d: integral in Z Ay/dY
84     myNorm = 0. _d 0
85     DO bj=myByLo(myThid),myByHi(myThid)
86     DO bi=myBxLo(myThid),myBxHi(myThid)
87     DO J=1,sNy
88     DO I=1,sNx
89     aW2d(I,J,bi,bj) = 0. _d 0
90     aS2d(I,J,bi,bj) = 0. _d 0
91     ENDDO
92     ENDDO
93 cnh 1.17 DO K=1,Nr
94 cnh 1.1 DO J=1,sNy
95     DO I=1,sNx
96 cnh 1.20 faceArea = _dyG(I,J,bi,bj)*drF(K)
97     & *_hFacW(I,J,K,bi,bj)
98 cnh 1.1 aW2d(I,J,bi,bj) = aW2d(I,J,bi,bj) +
99 jmc 1.32 & implicSurfPress*implicDiv2DFlow
100     & *faceArea*recip_dxC(I,J,bi,bj)
101 cnh 1.20 faceArea = _dxG(I,J,bi,bj)*drF(K)
102     & *_hFacS(I,J,K,bi,bj)
103 cnh 1.1 aS2d(I,J,bi,bj) = aS2d(I,J,bi,bj) +
104 jmc 1.32 & implicSurfPress*implicDiv2DFlow
105     & *faceArea*recip_dyC(I,J,bi,bj)
106 cnh 1.1 ENDDO
107     ENDDO
108     ENDDO
109 adcroft 1.26 #ifdef ALLOW_OBCS
110 adcroft 1.28 IF (useOBCS) THEN
111 adcroft 1.22 DO I=1,sNx
112     IF (OB_Jn(I,bi,bj).NE.0) aS2d(I,OB_Jn(I,bi,bj),bi,bj)=0.
113     IF (OB_Jn(I,bi,bj).NE.0) aS2d(I,OB_Jn(I,bi,bj)+1,bi,bj)=0.
114     IF (OB_Js(I,bi,bj).NE.0) aS2d(I,OB_Js(I,bi,bj)+1,bi,bj)=0.
115     IF (OB_Js(I,bi,bj).NE.0) aS2d(I,OB_Js(I,bi,bj),bi,bj)=0.
116     ENDDO
117     DO J=1,sNy
118     IF (OB_Ie(J,bi,bj).NE.0) aW2d(OB_Ie(J,bi,bj),J,bi,bj)=0.
119     IF (OB_Ie(J,bi,bj).NE.0) aW2d(OB_Ie(J,bi,bj)+1,J,bi,bj)=0.
120     IF (OB_Iw(J,bi,bj).NE.0) aW2d(OB_Iw(J,bi,bj)+1,J,bi,bj)=0.
121     IF (OB_Iw(J,bi,bj).NE.0) aW2d(OB_Iw(J,bi,bj),J,bi,bj)=0.
122     ENDDO
123     ENDIF
124 adcroft 1.26 #endif
125 cnh 1.1 DO J=1,sNy
126     DO I=1,sNx
127     myNorm = MAX(ABS(aW2d(I,J,bi,bj)),myNorm)
128     myNorm = MAX(ABS(aS2d(I,J,bi,bj)),myNorm)
129     ENDDO
130     ENDDO
131     ENDDO
132     ENDDO
133 adcroft 1.25 _GLOBAL_MAX_R4( myNorm, myThid )
134     IF ( myNorm .NE. 0. _d 0 ) THEN
135     myNorm = 1. _d 0/myNorm
136 cnh 1.1 ELSE
137     myNorm = 1. _d 0
138     ENDIF
139 cnh 1.5 cg2dNorm = myNorm
140 cnh 1.1 DO bj=myByLo(myThid),myByHi(myThid)
141     DO bi=myBxLo(myThid),myBxHi(myThid)
142     DO J=1,sNy
143     DO I=1,sNx
144     aW2d(I,J,bi,bj) = aW2d(I,J,bi,bj)*myNorm
145     aS2d(I,J,bi,bj) = aS2d(I,J,bi,bj)*myNorm
146     ENDDO
147     ENDDO
148     ENDDO
149     ENDDO
150    
151     C-- Update overlap regions
152     CcnhDebugStarts
153 cnh 1.14 C CALL PLOT_FIELD_XYRS( aW2d, 'AW2D INI_CG2D.1' , 1, myThid )
154     C CALL PLOT_FIELD_XYRS( aS2d, 'AS2D INI_CG2D.1' , 1, myThid )
155 cnh 1.1 CcnhDebugEnds
156 adcroft 1.34 c _EXCH_XY_R4(aW2d, myThid)
157     c _EXCH_XY_R4(aS2d, myThid)
158     CALL EXCH_UV_XY_RS(aW2d,aS2d,.FALSE.,myThid)
159 cnh 1.1 CcnhDebugStarts
160 adcroft 1.24 C CALL PLOT_FIELD_XYRS( aW2d, 'AW2D INI_CG2D.2' , 1, myThid )
161     C CALL PLOT_FIELD_XYRS( aS2d, 'AS2D INI_CG2D.2' , 1, myThid )
162 cnh 1.1 CcnhDebugEnds
163    
164 adcroft 1.34 C-- Define the solver tolerance in the appropriate Unit :
165 jmc 1.43 cg2dNormaliseRHS = cg2dTargetResWunit.LE.0.
166 adcroft 1.34 IF (cg2dNormaliseRHS) THEN
167     C- when using a normalisation of RHS, tolerance has no unit => no conversion
168     cg2dTolerance = cg2dTargetResidual
169     ELSE
170     C- convert Target-Residual (in W unit) to cg2d-solver residual unit [m^2/s^2]
171     cg2dTolerance = cg2dNorm * cg2dTargetResWunit
172 jmc 1.43 & * globalArea / deltaTmom
173 adcroft 1.34 ENDIF
174 jmc 1.43
175     CcnhDebugStarts
176     _BEGIN_MASTER( myThid )
177     WRITE(msgBuf,'(2A,1PE23.16)') 'INI_CG2D: ',
178     & 'CG2D normalisation factor = ', cg2dNorm
179     CALL PRINT_MESSAGE( msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
180     IF (.NOT.cg2dNormaliseRHS) THEN
181     WRITE(msgBuf,'(2A,1PE22.15,A,1PE16.10,A)') 'INI_CG2D: ',
182     & 'cg2dTolerance =', cg2dTolerance, ' (Area=',globalArea,')'
183     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
184     ENDIF
185     WRITE(msgBuf,*) ' '
186     CALL PRINT_MESSAGE( msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
187     _END_MASTER( myThid )
188     CcnhDebugEnds
189 adcroft 1.34
190 cnh 1.1 C-- Initialise preconditioner
191 cnh 1.4 C Note. 20th May 1998
192     C I made a weird discovery! In the model paper we argue
193     C for the form of the preconditioner used here ( see
194     C A Finite-volume, Incompressible Navier-Stokes Model
195     C ...., Marshall et. al ). The algebra gives a simple
196     C 0.5 factor for the averaging of ac and aCw to get a
197     C symmettric pre-conditioner. By using a factor of 0.51
198     C i.e. scaling the off-diagonal terms in the
199     C preconditioner down slightly I managed to get the
200     C number of iterations for convergence in a test case to
201     C drop form 192 -> 134! Need to investigate this further!
202     C For now I have introduced a parameter cg2dpcOffDFac which
203     C defaults to 0.51 but can be set at runtime.
204 cnh 1.1 DO bj=myByLo(myThid),myByHi(myThid)
205     DO bi=myBxLo(myThid),myBxHi(myThid)
206     DO J=1,sNy
207     DO I=1,sNx
208     pC(I,J,bi,bj) = 1. _d 0
209 cnh 1.4 aC = -(
210     & aW2d(I,J,bi,bj) + aW2d(I+1,J ,bi,bj)
211 adcroft 1.24 & +aS2d(I,J,bi,bj) + aS2d(I ,J+1,bi,bj)
212 jmc 1.32 & +freeSurfFac*myNorm*recip_Bo(I,J,bi,bj)*
213 adcroft 1.39 & rA(I,J,bi,bj)/deltaTMom/deltaTfreesurf
214 cnh 1.4 & )
215     aCs = -(
216     & aW2d(I,J-1,bi,bj) + aW2d(I+1,J-1,bi,bj)
217     & +aS2d(I,J-1,bi,bj) + aS2d(I ,J ,bi,bj)
218 jmc 1.32 & +freeSurfFac*myNorm*recip_Bo(I,J-1,bi,bj)*
219 adcroft 1.39 & rA(I,J-1,bi,bj)/deltaTMom/deltaTfreesurf
220 cnh 1.4 & )
221     aCw = -(
222     & aW2d(I-1,J,bi,bj) + aW2d(I ,J ,bi,bj)
223     & +aS2d(I-1,J,bi,bj) + aS2d(I-1,J+1,bi,bj)
224 jmc 1.32 & +freeSurfFac*myNorm*recip_Bo(I-1,J,bi,bj)*
225 adcroft 1.39 & rA(I-1,J,bi,bj)/deltaTMom/deltaTfreesurf
226 cnh 1.4 & )
227     IF ( aC .EQ. 0. ) THEN
228 adcroft 1.27 pC(I,J,bi,bj) = 1. _d 0
229 cnh 1.4 ELSE
230     pC(I,J,bi,bj) = 1. _d 0 / aC
231     ENDIF
232     IF ( aC + aCw .EQ. 0. ) THEN
233     pW(I,J,bi,bj) = 0.
234     ELSE
235     pW(I,J,bi,bj) =
236     & -aW2d(I ,J ,bi,bj)/((cg2dpcOffDFac *(aCw+aC))**2 )
237     ENDIF
238     IF ( aC + aCs .EQ. 0. ) THEN
239     pS(I,J,bi,bj) = 0.
240     ELSE
241     pS(I,J,bi,bj) =
242     & -aS2d(I ,J ,bi,bj)/((cg2dpcOffDFac *(aCs+aC))**2 )
243     ENDIF
244 cnh 1.6 C pC(I,J,bi,bj) = 1.
245     C pW(I,J,bi,bj) = 0.
246     C pS(I,J,bi,bj) = 0.
247 cnh 1.1 ENDDO
248     ENDDO
249     ENDDO
250     ENDDO
251     C-- Update overlap regions
252     _EXCH_XY_R4(pC, myThid)
253 adcroft 1.34 c _EXCH_XY_R4(pW, myThid)
254     c _EXCH_XY_R4(pS, myThid)
255     CALL EXCH_UV_XY_RS(pW,pS,.FALSE.,myThid)
256 cnh 1.18 CcnhDebugStarts
257 adcroft 1.24 C CALL PLOT_FIELD_XYRS( pC, 'pC INI_CG2D.2' , 1, myThid )
258     C CALL PLOT_FIELD_XYRS( pW, 'pW INI_CG2D.2' , 1, myThid )
259     C CALL PLOT_FIELD_XYRS( pS, 'pS INI_CG2D.2' , 1, myThid )
260 cnh 1.18 CcnhDebugEnds
261 cnh 1.1
262     RETURN
263     END

  ViewVC Help
Powered by ViewVC 1.1.22