/[MITgcm]/MITgcm_contrib/dgoldberg/streamice/adstreamice_cg_solve.F
ViewVC logotype

Contents of /MITgcm_contrib/dgoldberg/streamice/adstreamice_cg_solve.F

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


Revision 1.6 - (show annotations) (download)
Wed Aug 27 19:29:12 2014 UTC (10 years, 10 months ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
Changes since 1.5: +48 -54 lines
updating contrib streamice repo with latest files, and separated out convergence checks; and parameterised maximum iteration counts and interface w shelfice for coupling

1 C $Header: /u/gcmpack/MITgcm/pkg/streamice/adstreamice_cg_solve.F,v 1.4 2013/08/22 22:56:18 jmc Exp $
2 C $Name: $
3
4 #include "STREAMICE_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7
8 CBOP
9 SUBROUTINE ADSTREAMICE_CG_SOLVE(
10 U U_state, ! velocities - need to be recalc ed
11 I cg_Bu, ! adjoint of vel (input)
12 U V_state, ! velocities - need to be recalc ed
13 I cg_Bv, ! adjoint of vel (input)
14 I Bu_state, ! to recalc velocities
15 U cg_Uin, ! adjoint of RHS (output)
16 I Bv_state, ! to recalc velocities
17 U cg_Vin, ! adjoint of RHS (output)
18 I A_uu, ! section of matrix that multiplies u and projects on u
19 U adA_uu, ! adjoint of matrix coeffs (output)
20 I A_uv, ! section of matrix that multiplies v and projects on u
21 U adA_uv, ! adjoint of matrix coeffs (output)
22 I A_vu, ! section of matrix that multiplies u and projects on v
23 U adA_vu, ! adjoint of matrix coeffs (output)
24 I A_vv, ! section of matrix that multiplies v and projects on v
25 U adA_vv, ! adjoint of matrix coeffs (output)
26 I tolerance,
27 I maxiters,
28 I myThid )
29 C *============================================================*
30 C | SUBROUTINE |
31 C | o |
32 C *============================================================*
33
34 C !USES:
35 IMPLICIT NONE
36
37 C === Global variables ===
38 #include "SIZE.h"
39 #include "EEPARAMS.h"
40 #include "PARAMS.h"
41 #include "STREAMICE.h"
42 #include "STREAMICE_CG.h"
43
44 C !INPUT/OUTPUT ARGUMENTS
45 C cg_Uin, cg_Vin - input and output velocities
46 C cg_Bu, cg_Bv - driving stress
47 _RL cg_Uin (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
48 _RL cg_Vin (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
49 _RL cg_Bu (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
50 _RL cg_Bv (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
51 _RL U_state (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
52 _RL V_state (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
53 _RL Bu_state (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
54 _RL Bv_state (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
55 _RL
56 & A_uu (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy,-1:1,-1:1),
57 & A_vu (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy,-1:1,-1:1),
58 & A_uv (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy,-1:1,-1:1),
59 & A_vv (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy,-1:1,-1:1),
60 & adA_uu (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy,-1:1,-1:1),
61 & adA_vu (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy,-1:1,-1:1),
62 & adA_uv (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy,-1:1,-1:1),
63 & adA_vv (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy,-1:1,-1:1)
64 _RL tolerance
65 INTEGER maxiters
66 INTEGER myThid
67
68 C !LOCAL VARIABLES
69 INTEGER i, j, bi, bj, cg_halo, conv_flag, tmpiter
70 INTEGER iter, is, js, ie, je, colx, coly, k
71 _RL Utemp (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
72 _RL Vtemp (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
73 _RL UtempSt (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
74 _RL VtempSt (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
75 _RL dot_p1, dot_p2, alpha_k, beta_k, resid, resid_0
76 _RL dot_p1_tile (nSx,nSy)
77 _RL dot_p2_tile (nSx,nSy)
78 _RL ad_tolerance
79 CHARACTER*(MAX_LEN_MBUF) msgBuf
80 CEOP
81
82 ! iters = streamice_max_cg_iter
83
84 #ifdef ALLOW_STREAMICE
85
86 WRITE(msgBuf,'(A)') 'CALLING MANUAL CG ADJOINT'
87 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
88 & SQUEEZE_RIGHT , 1)
89
90 print *, "GOT HERE mythid=", mythid, tolerance
91
92 conv_flag = 0
93 ad_tolerance = 1.e-14
94
95 DO bj = myByLo(myThid), myByHi(myThid)
96 DO bi = myBxLo(myThid), myBxHi(myThid)
97 DO j=1-OLy,sNy+OLy
98 DO i=1-OLx,sNx+OLx
99 Utemp (i,j,bi,bj) =
100 & cg_Uin (i,j,bi,bj)
101 Vtemp (i,j,bi,bj) =
102 & cg_Vin (i,j,bi,bj)
103 UtempSt (i,j,bi,bj) =
104 & U_state (i,j,bi,bj)
105 VtempSt (i,j,bi,bj) =
106 & V_state (i,j,bi,bj)
107 ENDDO
108 ENDDO
109 ENDDO
110 ENDDO
111
112 print *, "GOT HERE 2 mythid=", mythid, tolerance
113
114 CALL STREAMICE_CG_SOLVE(
115 & U_state,
116 & V_state,
117 & Bu_state,
118 & Bv_state,
119 & A_uu,
120 & A_uv,
121 & A_vu,
122 & A_vv,
123 & tolerance,
124 & tmpiter,
125 & maxiters,
126 & myThid )
127
128 print *, "GOT HERE 3 mythid=", mythid, tolerance
129
130 tmpiter = 0
131
132 _EXCH_XY_RL( cg_Bu, myThid )
133 _EXCH_XY_RL( cg_Bv, myThid )
134
135 CALL STREAMICE_CG_SOLVE(
136 & cg_Uin,
137 & cg_Vin,
138 & cg_Bu,
139 & cg_Bv,
140 & A_uu,
141 & A_uv,
142 & A_vu,
143 & A_vv,
144 & ad_tolerance,
145 & tmpiter,
146 & maxiters,
147 & myThid )
148
149 print *, "GOT HERE 4 mythid=", mythid, tolerance
150
151 _EXCH_XY_RL( cg_Uin, myThid )
152 _EXCH_XY_RL( cg_Vin, myThid )
153 _EXCH_XY_RL( U_state, myThid )
154 _EXCH_XY_RL( V_state, myThid )
155
156 DO bj = myByLo(myThid), myByHi(myThid)
157 DO bi = myBxLo(myThid), myBxHi(myThid)
158 DO j=1,sNy
159 DO i=1,sNx
160 DO colx=-1,1
161 DO coly=-1,1
162
163 if (STREAMICE_umask(i,j,bi,bj).eq.1) then
164 if (STREAMICE_umask(i+colx,j+coly,bi,bj).eq.1) then
165 adA_uu(i,j,bi,bj,colx,coly) =
166 & adA_uu(i,j,bi,bj,colx,coly) -
167 & cg_Uin(i,j,bi,bj) *
168 & U_state(i+colx,j+coly,bi,bj)
169
170 endif
171 if (STREAMICE_vmask(i+colx,j+coly,bi,bj).eq.1) then
172 adA_uv(i,j,bi,bj,colx,coly) =
173 & adA_uv(i,j,bi,bj,colx,coly) -
174 & cg_Uin(i,j,bi,bj) *
175 & V_state(i+colx,j+coly,bi,bj)
176 endif
177 endif
178
179 if (STREAMICE_vmask(i,j,bi,bj).eq.1) then
180 if (STREAMICE_umask(i+colx,j+coly,bi,bj).eq.1) then
181 adA_vu(i,j,bi,bj,colx,coly) =
182 & adA_vu(i,j,bi,bj,colx,coly) -
183 & cg_Vin(i,j,bi,bj) *
184 & U_state(i+colx,j+coly,bi,bj)
185 endif
186 if (STREAMICE_vmask(i+colx,j+coly,bi,bj).eq.1) then
187 adA_vv(i,j,bi,bj,colx,coly) =
188 & adA_vv(i,j,bi,bj,colx,coly) -
189 & cg_Vin(i,j,bi,bj) *
190 & V_state(i+colx,j+coly,bi,bj)
191 endif
192 endif
193
194 enddo
195 enddo
196 enddo
197 enddo
198 enddo
199 enddo
200
201 DO bj = myByLo(myThid), myByHi(myThid)
202 DO bi = myBxLo(myThid), myBxHi(myThid)
203 DO j=1-OLy,sNy+OLy
204 DO i=1-OLx,sNx+OLx
205 if (i.lt.1.or.i.gt.sNx.or.
206 & j.lt.1.or.j.gt.sNy) then
207 cg_Uin (i,j,bi,bj) = 0.0
208 cg_Vin (i,j,bi,bj) = 0.0
209
210 DO colx=-1,1
211 DO coly=-1,1
212 ada_uu(i,j,bi,bj,colx,coly)=0.0
213 ada_uv(i,j,bi,bj,colx,coly)=0.0
214 ada_vu(i,j,bi,bj,colx,coly)=0.0
215 ada_vv(i,j,bi,bj,colx,coly)=0.0
216 enddo
217 enddo
218
219 endif
220 cg_Uin (i,j,bi,bj) =
221 & cg_Uin (i,j,bi,bj) +
222 & Utemp (i,j,bi,bj)
223 cg_Vin (i,j,bi,bj) =
224 & cg_Vin (i,j,bi,bj) +
225 & Vtemp (i,j,bi,bj)
226 cg_bu (i,j,bi,bj) = 0.
227 cg_bv (i,j,bi,bj) = 0.
228 U_state (i,j,bi,bj) =
229 & UtempSt (i,j,bi,bj)
230 V_state (i,j,bi,bj) =
231 & VtempSt (i,j,bi,bj)
232 ENDDO
233 ENDDO
234 ENDDO
235 ENDDO
236
237 WRITE(msgBuf,'(A,I5,A)') 'DONE WITH MANUAL CG ADJOINT:',tmpiter,
238 & 'ITERS'
239 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
240 & SQUEEZE_RIGHT , 1)
241
242 #endif
243 RETURN
244 END
245

  ViewVC Help
Powered by ViewVC 1.1.22