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

Annotation of /MITgcm_contrib/dgoldberg/streamice/streamice_cg_wrapper.F

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


Revision 1.4 - (hide annotations) (download)
Wed Aug 27 19:29:13 2014 UTC (10 years, 10 months ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
Changes since 1.3: +83 -3 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 dgoldberg 1.4 C $Header: /u/gcmpack/MITgcm/pkg/streamice/streamice_cg_wrapper.F,v 1.3 2014/01/06 14:54:25 mlosch Exp $
2 dgoldberg 1.1 C $Name: $
3    
4     #include "STREAMICE_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7    
8     CBOP
9     SUBROUTINE STREAMICE_CG_WRAPPER(
10     U cg_Uin,
11     U cg_Vin,
12     I cg_tauU,
13     I cg_tauV,
14     I tolerance,
15     O iters,
16 dgoldberg 1.4 I maxIter,
17 dgoldberg 1.1 I myThid )
18    
19     C /============================================================\
20     C | SUBROUTINE |
21     C | o |
22     C |============================================================|
23     C | |
24     C \============================================================/
25     IMPLICIT NONE
26    
27     C === Global variables ===
28     #include "SIZE.h"
29     #include "EEPARAMS.h"
30     #include "PARAMS.h"
31     #include "STREAMICE.h"
32     #include "STREAMICE_CG.h"
33    
34    
35     C !INPUT/OUTPUT ARGUMENTS
36     C cg_Uin, cg_Vin - input and output velocities
37     C cg_Bu, cg_Bv - driving stress
38    
39     INTEGER myThid
40     INTEGER iters
41 dgoldberg 1.4 INTEGER maxIter
42 dgoldberg 1.1 _RL tolerance
43    
44     _RL cg_Uin (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
45     _RL cg_Vin (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
46     _RL cg_tauU (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
47     _RL cg_tauV (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
48    
49     #ifdef ALLOW_STREAMICE
50    
51     _RL dot_p1, dot_p2
52     _RL dot_p1_tile (nSx,nSy)
53     _RL dot_p2_tile (nSx,nSy)
54     INTEGER i, j, bi, bj
55    
56    
57    
58     DO bj = myByLo(myThid), myByHi(myThid)
59     DO bi = myBxLo(myThid), myBxHi(myThid)
60     DO j=1,sNy
61     DO i=1,sNx
62    
63     DIAGu_SI (i,j,bi,bj) = 0. _d 0
64     DIAGv_SI (i,j,bi,bj) = 0. _d 0
65     ubd_SI (i,j,bi,bj) = 0. _d 0
66     vbd_SI (i,j,bi,bj) = 0. _d 0
67     ENDDO
68     ENDDO
69     ENDDO
70     ENDDO
71    
72     C DIRICHLET BOUNDARY VALUES ADDED TO RHS
73    
74     CALL STREAMICE_CG_BOUND_VALS( myThid,
75     O ubd_SI,
76     O vbd_SI)
77    
78 dgoldberg 1.4 _EXCH_XY_RL(ubd_SI, myThid)
79     _EXCH_XY_RL(vbd_SI, myThid)
80 dgoldberg 1.2
81     ! CALL WRITE_FLD_XY_RL ( "ubd_SI", "",
82     ! & ubd_SI, 0, myThid )
83    
84     ! CALL WRITE_FLD_XY_RL ( "vbd_SI", "",
85     ! & STREAMICE_vmask, 0, myThid )
86    
87 dgoldberg 1.1 DO bj = myByLo(myThid), myByHi(myThid)
88     DO bi = myBxLo(myThid), myBxHi(myThid)
89     DO j=1-OLy,sNy+OLy
90     DO i=1-OLx,sNx+OLx
91     RHSu_SI (i,j,bi,bj) = cg_tauU (i,j,bi,bj)
92     & - ubd_SI(i,j,bi,bj)
93     RHSv_SI (i,j,bi,bj) = cg_tauV (i,j,bi,bj)
94     & - vbd_SI(i,j,bi,bj)
95     ENDDO
96     ENDDO
97     ENDDO
98     ENDDO
99    
100     _EXCH_XY_RL( RHSu_SI, myThid )
101     _EXCH_XY_RL( RHSv_SI, myThid )
102    
103     C GET DIAGONAL OF MATRIX
104    
105     CALL STREAMICE_CG_ADIAG( myThid,
106     O DIAGu_SI,
107     O DIAGv_SI)
108    
109     _EXCH_XY_RL( DIAGu_SI, myThid )
110     _EXCH_XY_RL( DIAGv_SI, myThid )
111    
112     C ccccc
113    
114 dgoldberg 1.2 DO bj = myByLo(myThid), myByHi(myThid)
115     DO bi = myBxLo(myThid), myBxHi(myThid)
116     DO j=1-OLy,sNy+OLy
117     DO i=1-OLy,sNx+OLy
118     IF (STREAMICE_umask(i,j,bi,bj).ne.1.0)
119     & cg_Uin(i,j,bi,bj)=0.0
120     IF (STREAMICE_vmask(i,j,bi,bj).ne.1.0)
121     & cg_Vin(i,j,bi,bj)=0.0
122    
123     ! print *, "rhs", i,j,RHSu_SI(i,j,bi,bj)
124    
125     ENDDO
126     ENDDO
127     ENDDO
128     ENDDO
129 dgoldberg 1.1
130    
131     #ifdef STREAMICE_CONSTRUCT_MATRIX
132    
133    
134     CALL STREAMICE_CG_MAKE_A(myThid)
135    
136 dgoldberg 1.4 ! call write_fld_xy_rl ("streamicb_cg_A1_m1_m1","",
137     ! & streamice_cg_A1(:,:,1,1,-1,-1),0,myThid)
138     c call write_fld_xy_rl ("streamicb_cg_A1_m1_0","",
139     c & streamice_cg_A1(:,:,1,1,-1,0),0,myThid)
140     c call write_fld_xy_rl ("streamicb_cg_A1_m1_p1","",
141     c & streamice_cg_A1(:,:,1,1,-1,1),0,myThid)
142     c call write_fld_xy_rl ("streamicb_cg_A1_0_m1","",
143     c & streamice_cg_A1(:,:,1,1,0,-1),0,myThid)
144     c call write_fld_xy_rl ("streamicb_cg_A1_0_0","",
145     c & streamice_cg_A1(:,:,1,1,0,0),0,myThid)
146     c call write_fld_xy_rl ("streamicb_cg_A1_0_p1","",
147     c & streamice_cg_A1(:,:,1,1,0,1),0,myThid)
148     c call write_fld_xy_rl ("streamicb_cg_A1_p1_m1","",
149     c & streamice_cg_A1(:,:,1,1,1,-1),0,myThid)
150     c call write_fld_xy_rl ("streamicb_cg_A1_p1_0","",
151     c & streamice_cg_A1(:,:,1,1,1,0),0,myThid)
152     c call write_fld_xy_rl ("streamicb_cg_A1_p1_p1","",
153     c & streamice_cg_A1(:,:,1,1,1,1),0,myThid)
154     c
155     c call write_fld_xy_rl ("streamicb_cg_A2_m1_m1","",
156     c & streamice_cg_A2(:,:,1,1,-1,-1),0,myThid)
157     c call write_fld_xy_rl ("streamicb_cg_A2_m1_0","",
158     c & streamice_cg_A2(:,:,1,1,-1,0),0,myThid)
159     c call write_fld_xy_rl ("streamicb_cg_A2_m1_p1","",
160     c & streamice_cg_A2(:,:,1,1,-1,1),0,myThid)
161     c call write_fld_xy_rl ("streamicb_cg_A2_0_m1","",
162     c & streamice_cg_A2(:,:,1,1,0,-1),0,myThid)
163     c call write_fld_xy_rl ("streamicb_cg_A2_0_0","",
164     c & streamice_cg_A2(:,:,1,1,0,0),0,myThid)
165     c call write_fld_xy_rl ("streamicb_cg_A2_0_p1","",
166     c & streamice_cg_A2(:,:,1,1,0,1),0,myThid)
167     c call write_fld_xy_rl ("streamicb_cg_A2_p1_m1","",
168     c & streamice_cg_A2(:,:,1,1,1,-1),0,myThid)
169     c call write_fld_xy_rl ("streamicb_cg_A2_p1_0","",
170     c & streamice_cg_A2(:,:,1,1,1,0),0,myThid)
171     c call write_fld_xy_rl ("streamicb_cg_A2_p1_p1","",
172     c & streamice_cg_A2(:,:,1,1,1,1),0,myThid)
173     c
174     c call write_fld_xy_rl ("streamicb_cg_A3_m1_m1","",
175     c & streamice_cg_A3(:,:,1,1,-1,-1),0,myThid)
176     c call write_fld_xy_rl ("streamicb_cg_A3_m1_0","",
177     c & streamice_cg_A3(:,:,1,1,-1,0),0,myThid)
178     c call write_fld_xy_rl ("streamicb_cg_A3_m1_p1","",
179     c & streamice_cg_A3(:,:,1,1,-1,1),0,myThid)
180     c call write_fld_xy_rl ("streamicb_cg_A3_0_m1","",
181     c & streamice_cg_A3(:,:,1,1,0,-1),0,myThid)
182     c call write_fld_xy_rl ("streamicb_cg_A3_0_0","",
183     c & streamice_cg_A3(:,:,1,1,0,0),0,myThid)
184     c call write_fld_xy_rl ("streamicb_cg_A3_0_p1","",
185     c & streamice_cg_A3(:,:,1,1,0,1),0,myThid)
186     c call write_fld_xy_rl ("streamicb_cg_A3_p1_m1","",
187     c & streamice_cg_A3(:,:,1,1,1,-1),0,myThid)
188     c call write_fld_xy_rl ("streamicb_cg_A3_p1_0","",
189     c & streamice_cg_A3(:,:,1,1,1,0),0,myThid)
190     c call write_fld_xy_rl ("streamicb_cg_A3_p1_p1","",
191     c & streamice_cg_A3(:,:,1,1,1,1),0,myThid)
192     c
193     c call write_fld_xy_rl ("streamicb_cg_A4_m1_m1","",
194     c & streamice_cg_A4(:,:,1,1,-1,-1),0,myThid)
195     c call write_fld_xy_rl ("streamicb_cg_A4_m1_0","",
196     c & streamice_cg_A4(:,:,1,1,-1,0),0,myThid)
197     c call write_fld_xy_rl ("streamicb_cg_A4_m1_p1","",
198     c & streamice_cg_A4(:,:,1,1,-1,1),0,myThid)
199     c call write_fld_xy_rl ("streamicb_cg_A4_0_m1","",
200     c & streamice_cg_A4(:,:,1,1,0,-1),0,myThid)
201     c call write_fld_xy_rl ("streamicb_cg_A4_0_0","",
202     c & streamice_cg_A4(:,:,1,1,0,0),0,myThid)
203     c call write_fld_xy_rl ("streamicb_cg_A4_0_p1","",
204     c & streamice_cg_A4(:,:,1,1,0,1),0,myThid)
205     c call write_fld_xy_rl ("streamicb_cg_A4_p1_m1","",
206     c & streamice_cg_A4(:,:,1,1,1,-1),0,myThid)
207     c call write_fld_xy_rl ("streamicb_cg_A4_p1_0","",
208     c & streamice_cg_A4(:,:,1,1,1,0),0,myThid)
209     c call write_fld_xy_rl ("streamicb_cg_A4_p1_p1","",
210     c & streamice_cg_A4(:,:,1,1,1,1),0,myThid)
211     c
212    
213 dgoldberg 1.1 ! print *, "MATRIX 1"
214     ! do i=1,sNx
215     ! print *, i,
216     ! & streamice_cg_A1(i,1,1,1,-1,0),
217     ! & streamice_cg_A1(i,1,1,1,0,0),
218     ! & streamice_cg_A1(i,1,1,1,1,0),
219     ! & streamice_cg_A1(i,2,1,1,-1,0),
220     ! & streamice_cg_A1(i,2,1,1,0,0),
221     ! & streamice_cg_A1(i,2,1,1,1,0),
222     ! & streamice_cg_A1(i,3,1,1,-1,0),
223     ! & streamice_cg_A1(i,3,1,1,0,0),
224     ! & streamice_cg_A1(i,3,1,1,1,0),
225     ! & visc_streamice(i,1,1,1),visc_streamice(i,2,1,1),
226     ! & visc_streamice(i,3,1,1)
227     ! enddo
228    
229     CALL STREAMICE_CG_SOLVE(
230     & cg_Uin,
231     & cg_Vin,
232     & RHSu_SI,
233     & RHSv_SI,
234     & streamice_cg_A1,
235     & streamice_cg_A2,
236     & streamice_cg_A3,
237     & streamice_cg_A4,
238     & tolerance,
239     & iters,
240 dgoldberg 1.4 & maxIter,
241 dgoldberg 1.1 & myThid )
242    
243     _EXCH_XY_RL( RHSu_SI, myThid )
244     _EXCH_XY_RL( RHSv_SI, myThid )
245    
246     ! DO bj = myByLo(myThid), myByHi(myThid)
247     ! DO bi = myBxLo(myThid), myBxHi(myThid)
248     ! DO j=1-OLy,sNy+OLy
249     ! DO i=1-OLx,sNx+OLx
250     ! cg_Uin(i,j,bi,bj) = cg_Uin(i,j,bi,bj) +
251     ! & 0.0 * cg_Uin(i,j,bi,bj)**2
252     ! cg_Vin(i,j,bi,bj) = cg_Vin(i,j,bi,bj) +
253     ! & 0.0 * cg_Vin(i,j,bi,bj)**2
254     ! ENDDO
255     ! ENDDO
256     ! ENDDO
257     ! ENDDO
258    
259    
260    
261     #else
262    
263     CALL STREAMICE_CG_SOLVE_MATFREE(
264     & cg_Uin,
265     & cg_Vin,
266     & RHSu_SI,
267     & RHSv_SI,
268     & tolerance,
269     & iters,
270     & myThid )
271    
272     #endif
273    
274    
275     C ACTUAL CG CALL
276    
277    
278    
279    
280     DO bj = myByLo(myThid), myByHi(myThid)
281     DO bi = myBxLo(myThid), myBxHi(myThid)
282     DO j=1-OLy,sNy+OLy
283     DO i=1-OLy,sNx+OLy
284     IF (STREAMICE_umask(i,j,bi,bj).eq.3.0)
285     & cg_Uin(i,j,bi,bj)=u_bdry_values_SI(i,j,bi,bj)
286     IF (STREAMICE_vmask(i,j,bi,bj).eq.3.0)
287     & cg_Vin(i,j,bi,bj)=v_bdry_values_SI(i,j,bi,bj)
288    
289     ! print *, "rhs", i,j,RHSu_SI(i,j,bi,bj)
290    
291     ENDDO
292     ENDDO
293     ENDDO
294     ENDDO
295    
296     _EXCH_XY_RL( cg_Uin, myThid )
297     _EXCH_XY_RL( cg_Vin, myThid )
298    
299    
300     #endif
301     RETURN
302     END
303    

  ViewVC Help
Powered by ViewVC 1.1.22