/[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.3 - (hide annotations) (download)
Thu Mar 7 15:23:19 2013 UTC (12 years, 4 months ago) by dgoldberg
Branch: MAIN
Changes since 1.2: +3 -1 lines
bug fixes, GL smoothing, changes for controlling bathym with const surf elev

1 dgoldberg 1.3 C $Header: /u/gcmpack/MITgcm_contrib/dgoldberg/streamice/streamice_cg_wrapper.F,v 1.2 2013/01/09 21:56:18 dgoldberg 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     I myThid )
17    
18     C /============================================================\
19     C | SUBROUTINE |
20     C | o |
21     C |============================================================|
22     C | |
23     C \============================================================/
24     IMPLICIT NONE
25    
26     C === Global variables ===
27     #include "SIZE.h"
28     #include "EEPARAMS.h"
29     #include "PARAMS.h"
30     #include "STREAMICE.h"
31     #include "STREAMICE_CG.h"
32    
33    
34     C !INPUT/OUTPUT ARGUMENTS
35     C cg_Uin, cg_Vin - input and output velocities
36     C cg_Bu, cg_Bv - driving stress
37    
38     INTEGER myThid
39     INTEGER iters
40     _RL tolerance
41    
42     _RL cg_Uin (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
43     _RL cg_Vin (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
44     _RL cg_tauU (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
45     _RL cg_tauV (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
46    
47     #ifdef ALLOW_STREAMICE
48    
49     _RL dot_p1, dot_p2
50     _RL dot_p1_tile (nSx,nSy)
51     _RL dot_p2_tile (nSx,nSy)
52     INTEGER i, j, bi, bj
53    
54    
55    
56     DO bj = myByLo(myThid), myByHi(myThid)
57     DO bi = myBxLo(myThid), myBxHi(myThid)
58     DO j=1,sNy
59     DO i=1,sNx
60    
61     DIAGu_SI (i,j,bi,bj) = 0. _d 0
62     DIAGv_SI (i,j,bi,bj) = 0. _d 0
63     ubd_SI (i,j,bi,bj) = 0. _d 0
64     vbd_SI (i,j,bi,bj) = 0. _d 0
65     ENDDO
66     ENDDO
67     ENDDO
68     ENDDO
69    
70     C DIRICHLET BOUNDARY VALUES ADDED TO RHS
71    
72     CALL STREAMICE_CG_BOUND_VALS( myThid,
73     O ubd_SI,
74     O vbd_SI)
75    
76 dgoldberg 1.3 _EXCH_XY_RL (ubd_SI, myThid)
77     _EXCH_XY_RL (vbd_SI, myThid)
78 dgoldberg 1.2
79     ! CALL WRITE_FLD_XY_RL ( "ubd_SI", "",
80     ! & ubd_SI, 0, myThid )
81    
82     ! CALL WRITE_FLD_XY_RL ( "vbd_SI", "",
83     ! & STREAMICE_vmask, 0, myThid )
84    
85 dgoldberg 1.1 DO bj = myByLo(myThid), myByHi(myThid)
86     DO bi = myBxLo(myThid), myBxHi(myThid)
87     DO j=1-OLy,sNy+OLy
88     DO i=1-OLx,sNx+OLx
89     RHSu_SI (i,j,bi,bj) = cg_tauU (i,j,bi,bj)
90     & - ubd_SI(i,j,bi,bj)
91     RHSv_SI (i,j,bi,bj) = cg_tauV (i,j,bi,bj)
92     & - vbd_SI(i,j,bi,bj)
93     ENDDO
94     ENDDO
95     ENDDO
96     ENDDO
97    
98     _EXCH_XY_RL( RHSu_SI, myThid )
99     _EXCH_XY_RL( RHSv_SI, myThid )
100    
101     C GET DIAGONAL OF MATRIX
102    
103     CALL STREAMICE_CG_ADIAG( myThid,
104     O DIAGu_SI,
105     O DIAGv_SI)
106    
107     _EXCH_XY_RL( DIAGu_SI, myThid )
108     _EXCH_XY_RL( DIAGv_SI, myThid )
109    
110     C ccccc
111    
112 dgoldberg 1.2 DO bj = myByLo(myThid), myByHi(myThid)
113     DO bi = myBxLo(myThid), myBxHi(myThid)
114     DO j=1-OLy,sNy+OLy
115     DO i=1-OLy,sNx+OLy
116     IF (STREAMICE_umask(i,j,bi,bj).ne.1.0)
117     & cg_Uin(i,j,bi,bj)=0.0
118     IF (STREAMICE_vmask(i,j,bi,bj).ne.1.0)
119     & cg_Vin(i,j,bi,bj)=0.0
120    
121     ! print *, "rhs", i,j,RHSu_SI(i,j,bi,bj)
122    
123     ENDDO
124     ENDDO
125     ENDDO
126     ENDDO
127 dgoldberg 1.1
128    
129     #ifdef STREAMICE_CONSTRUCT_MATRIX
130    
131    
132     CALL STREAMICE_CG_MAKE_A(myThid)
133    
134     ! print *, "MATRIX 1"
135     ! do i=1,sNx
136     ! print *, i,
137     ! & streamice_cg_A1(i,1,1,1,-1,0),
138     ! & streamice_cg_A1(i,1,1,1,0,0),
139     ! & streamice_cg_A1(i,1,1,1,1,0),
140     ! & streamice_cg_A1(i,2,1,1,-1,0),
141     ! & streamice_cg_A1(i,2,1,1,0,0),
142     ! & streamice_cg_A1(i,2,1,1,1,0),
143     ! & streamice_cg_A1(i,3,1,1,-1,0),
144     ! & streamice_cg_A1(i,3,1,1,0,0),
145     ! & streamice_cg_A1(i,3,1,1,1,0),
146     ! & visc_streamice(i,1,1,1),visc_streamice(i,2,1,1),
147     ! & visc_streamice(i,3,1,1)
148     ! enddo
149    
150     CALL STREAMICE_CG_SOLVE(
151     & cg_Uin,
152     & cg_Vin,
153     & RHSu_SI,
154     & RHSv_SI,
155     & streamice_cg_A1,
156     & streamice_cg_A2,
157     & streamice_cg_A3,
158     & streamice_cg_A4,
159     & tolerance,
160     & iters,
161     & myThid )
162    
163     _EXCH_XY_RL( RHSu_SI, myThid )
164     _EXCH_XY_RL( RHSv_SI, myThid )
165    
166     ! DO bj = myByLo(myThid), myByHi(myThid)
167     ! DO bi = myBxLo(myThid), myBxHi(myThid)
168     ! DO j=1-OLy,sNy+OLy
169     ! DO i=1-OLx,sNx+OLx
170     ! cg_Uin(i,j,bi,bj) = cg_Uin(i,j,bi,bj) +
171     ! & 0.0 * cg_Uin(i,j,bi,bj)**2
172     ! cg_Vin(i,j,bi,bj) = cg_Vin(i,j,bi,bj) +
173     ! & 0.0 * cg_Vin(i,j,bi,bj)**2
174     ! ENDDO
175     ! ENDDO
176     ! ENDDO
177     ! ENDDO
178    
179    
180    
181     #else
182    
183     CALL STREAMICE_CG_SOLVE_MATFREE(
184     & cg_Uin,
185     & cg_Vin,
186     & RHSu_SI,
187     & RHSv_SI,
188     & tolerance,
189     & iters,
190     & myThid )
191    
192     #endif
193    
194    
195     C ACTUAL CG CALL
196    
197    
198    
199    
200     DO bj = myByLo(myThid), myByHi(myThid)
201     DO bi = myBxLo(myThid), myBxHi(myThid)
202     DO j=1-OLy,sNy+OLy
203     DO i=1-OLy,sNx+OLy
204     IF (STREAMICE_umask(i,j,bi,bj).eq.3.0)
205     & cg_Uin(i,j,bi,bj)=u_bdry_values_SI(i,j,bi,bj)
206     IF (STREAMICE_vmask(i,j,bi,bj).eq.3.0)
207     & cg_Vin(i,j,bi,bj)=v_bdry_values_SI(i,j,bi,bj)
208    
209     ! print *, "rhs", i,j,RHSu_SI(i,j,bi,bj)
210    
211     ENDDO
212     ENDDO
213     ENDDO
214     ENDDO
215    
216     _EXCH_XY_RL( cg_Uin, myThid )
217     _EXCH_XY_RL( cg_Vin, myThid )
218    
219    
220     #endif
221     RETURN
222     END
223    

  ViewVC Help
Powered by ViewVC 1.1.22