/[MITgcm]/MITgcm/pkg/streamice/streamice_adv_front.F
ViewVC logotype

Contents of /MITgcm/pkg/streamice/streamice_adv_front.F

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


Revision 1.2 - (show annotations) (download)
Wed Mar 26 17:40:11 2014 UTC (10 years, 1 month ago) by dgoldberg
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64w, checkpoint64v, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65
Changes since 1.1: +16 -4 lines
streamice pickup; impose calving boundary beyond init. front

1 C $Header: /u/gcmpack/MITgcm/pkg/streamice/streamice_adv_front.F,v 1.1 2013/06/12 21:30:21 dgoldberg 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 STREAMICE_ADV_FRONT (
10 & myThid,
11 & time_step,
12 & hflux_x_si,
13 & hflux_y_si )
14
15 C /============================================================\
16 C | SUBROUTINE |
17 C | o |
18 C |============================================================|
19 C | |
20 C \============================================================/
21 IMPLICIT NONE
22
23 C === Global variables ===
24 #include "SIZE.h"
25 #include "GRID.h"
26 #include "EEPARAMS.h"
27 #include "PARAMS.h"
28 #include "STREAMICE.h"
29 #include "STREAMICE_ADV.h"
30 #ifdef ALLOW_AUTODIFF_TAMC
31 # include "tamc.h"
32 #endif
33
34 INTEGER myThid
35 _RL time_step
36 _RL hflux_x_SI (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
37 _RL hflux_y_SI (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
38
39 #ifdef ALLOW_STREAMICE
40
41 INTEGER i, j, bi, bj, k, iter_count, iter_rpt
42 INTEGER Gi, Gj
43 INTEGER new_partial(4)
44 INTEGER ikey_front, ikey_1
45 _RL iter_flag
46 _RL n_flux_1, n_flux_2
47 _RL href, rho, partial_vol, tot_flux, hpot
48 CHARACTER*(MAX_LEN_MBUF) msgBuf
49 _RL hflux_x_SI2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
50 _RL hflux_y_SI2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
51
52
53 rho = streamice_density
54 cph iter_count = 0
55 iter_flag = 1. _d 0
56 iter_rpt = 0
57
58 DO bj=myByLo(myThid),myByHi(myThid)
59 DO bi=myBxLo(myThid),myBxHi(myThid)
60 DO j=1-OLy,sNy+OLy
61 DO i=1-OLx,sNx+OLx
62 hflux_x_SI2(i,j,bi,bj) = 0. _d 0
63 hflux_y_SI2(i,j,bi,bj) = 0. _d 0
64 ENDDO
65 ENDDO
66 ENDDO
67 ENDDO
68
69
70 DO iter_count = 0, 3
71
72 #ifdef ALLOW_AUTODIFF_TAMC
73 ikey_front = (ikey_dynamics-1)*4 + iter_count + 1
74 CADJ STORE area_shelf_streamice
75 CADJ & = comlev1_stream_front, key = ikey_front
76 CADJ STORE h_streamice
77 CADJ & = comlev1_stream_front, key = ikey_front
78 CADJ STORE hflux_x_si
79 CADJ & = comlev1_stream_front, key = ikey_front
80 CADJ STORE hflux_x_si2
81 CADJ & = comlev1_stream_front, key = ikey_front
82 CADJ STORE hflux_y_si
83 CADJ & = comlev1_stream_front, key = ikey_front
84 CADJ STORE hflux_y_si2
85 CADJ & = comlev1_stream_front, key = ikey_front
86 CADJ STORE streamice_hmask
87 CADJ & = comlev1_stream_front, key = ikey_front
88 CADJ STORE iter_flag
89 CADJ & = comlev1_stream_front, key = ikey_front
90 #endif
91
92 IF ( iter_flag .GT. 0. ) THEN
93
94 iter_flag = 0. _d 0
95
96 IF (iter_count .gt. 0) then
97 DO bj=myByLo(myThid),myByHi(myThid)
98 DO bi=myBxLo(myThid),myBxHi(myThid)
99 DO j=1-OLy,sNy+OLy
100 DO i=1-OLx,sNx+OLx
101 hflux_x_SI(i,j,bi,bj)=hflux_x_SI2(i,j,bi,bj)
102 hflux_y_SI(i,j,bi,bj)=hflux_y_SI2(i,j,bi,bj)
103 hflux_x_SI2(i,j,bi,bj) = 0. _d 0
104 hflux_y_SI2(i,j,bi,bj) = 0. _d 0
105 ENDDO
106 ENDDO
107 ENDDO
108 ENDDO
109 ENDIF
110
111 ! iter_count = iter_count + 1
112 iter_rpt = iter_rpt + 1
113
114 DO bj=myByLo(myThid),myByHi(myThid)
115 DO bi=myBxLo(myThid),myBxHi(myThid)
116
117 DO j=1-1,sNy+1
118 Gj = (myYGlobalLo-1)+(bj-1)*sNy+j
119 IF ((Gj .ge. 1) .and. (Gj .le. Ny)) THEN
120 DO i=1-1,sNx+1
121 Gi = (myXGlobalLo-1)+(bi-1)*sNx+i
122
123 #ifdef ALLOW_AUTODIFF_TAMC
124 act1 = bi - myBxLo(myThid)
125 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
126 act2 = bj - myByLo(myThid)
127 max2 = myByHi(myThid) - myByLo(myThid) + 1
128 act3 = myThid - 1
129 max3 = nTx*nTy
130 act4 = ikey_front - 1
131 ikey_1 = i + 1
132 & + (sNx+2)*(j)
133 & + (sNx+2)*(sNy+2)*act1
134 & + (sNx+2)*(sNy+2)*max1*act2
135 & + (sNx+2)*(sNy+2)*max1*max2*act3
136 & + (sNx+2)*(sNy+2)*max1*max2*max3*act4
137 CADJ STORE area_shelf_streamice(i,j,bi,bj)
138 CADJ & = comlev1_stream_ij, key = ikey_1
139 CADJ STORE h_streamice(i,j,bi,bj)
140 CADJ & = comlev1_stream_ij, key = ikey_1
141 CADJ STORE hflux_x_si(i,j,bi,bj)
142 CADJ & = comlev1_stream_ij, key = ikey_1
143 CADJ STORE hflux_y_si(i,j,bi,bj)
144 CADJ & = comlev1_stream_ij, key = ikey_1
145 CADJ STORE streamice_hmask(i,j,bi,bj)
146 CADJ & = comlev1_stream_ij, key = ikey_1
147 #endif
148
149 IF (.not. STREAMICE_calve_to_mask .OR.
150 & STREAMICE_calve_mask (i,j,bi,bj) .eq. 1.0) THEN
151
152 IF ((Gi .ge. 1) .and. (Gi .le. Nx) .and.
153 & (STREAMICE_Hmask(i,j,bi,bj).eq.0.0 .or.
154 & STREAMICE_Hmask(i,j,bi,bj).eq.2.0)) THEN
155 n_flux_1 = 0. _d 0
156 href = 0. _d 0
157 tot_flux = 0. _d 0
158
159 #ifdef ALLOW_AUTODIFF_TAMC
160 CADJ STORE hflux_x_SI(i,j,bi,bj)
161 CADJ & = comlev1_stream_ij, key = ikey_1
162 #endif
163 IF (hflux_x_SI(i,j,bi,bj).gt. 0. _d 0) THEN
164 n_flux_1 = n_flux_1 + 1. _d 0
165 href = href + H_streamice(i-1,j,bi,bj)
166 tot_flux = tot_flux + hflux_x_SI(i,j,bi,bj) *
167 & dxG(i,j,bi,bj) * time_step
168 hflux_x_SI(i,j,bi,bj) = 0. _d 0
169 ENDIF
170
171 #ifdef ALLOW_AUTODIFF_TAMC
172 CADJ STORE hflux_x_SI(i,j,bi,bj)
173 CADJ & = comlev1_stream_ij, key = ikey_1
174 #endif
175 IF (hflux_x_SI(i+1,j,bi,bj).lt. 0. _d 0) THEN
176 n_flux_1 = n_flux_1 + 1. _d 0
177 href = href + H_streamice(i+1,j,bi,bj)
178 tot_flux = tot_flux - hflux_x_SI(i+1,j,bi,bj) *
179 & dxG(i+1,j,bi,bj) * time_step
180 hflux_x_SI(i+1,j,bi,bj) = 0. _d 0
181 ENDIF
182
183 #ifdef ALLOW_AUTODIFF_TAMC
184 CADJ STORE hflux_y_SI(i,j,bi,bj)
185 CADJ & = comlev1_stream_ij, key = ikey_1
186 #endif
187 IF (hflux_y_SI(i,j,bi,bj).gt. 0. _d 0) THEN
188 n_flux_1 = n_flux_1 + 1. _d 0
189 href = href + H_streamice(i,j-1,bi,bj)
190 tot_flux = tot_flux + hflux_y_SI(i,j,bi,bj) *
191 & dyG(i,j,bi,bj) * time_step
192 hflux_y_SI(i,j,bi,bj) = 0. _d 0
193 ENDIF
194
195 #ifdef ALLOW_AUTODIFF_TAMC
196 CADJ STORE hflux_y_SI(i,j,bi,bj)
197 CADJ & = comlev1_stream_ij, key = ikey_1
198 #endif
199 IF (hflux_y_SI(i,j+1,bi,bj).lt. 0. _d 0) THEN
200 n_flux_1 = n_flux_1 + 1. _d 0
201 href = href + H_streamice(i,j+1,bi,bj)
202 tot_flux = tot_flux - hflux_y_SI(i,j+1,bi,bj) *
203 & dyG(i,j+1,bi,bj) * time_step
204 hflux_y_SI(i,j+1,bi,bj) = 0. _d 0
205 ENDIF
206
207 IF (n_flux_1 .gt. 0.) THEN
208
209 href = href / n_flux_1
210 partial_vol = H_streamice (i,j,bi,bj) *
211 & area_shelf_streamice (i,j,bi,bj) + tot_flux
212 hpot = partial_vol * recip_rA(i,j,bi,bj)
213
214 IF (hpot .eq. href) THEN ! cell is exactly covered, no overflow
215 STREAMICE_hmask (i,j,bi,bj) = 1.0
216 H_streamice (i,j,bi,bj) = href
217 area_shelf_streamice(i,j,bi,bj) =
218 & rA(i,j,bi,bj)
219 ELSEIF (hpot .lt. href) THEN ! cell still unfilled
220
221
222
223 STREAMICE_hmask (i,j,bi,bj) = 2.0
224 area_shelf_streamice (i,j,bi,bj) = partial_vol / href
225 H_streamice (i,j,bi,bj) = href
226 ELSE ! cell is filled - do overflow
227
228
229
230 STREAMICE_hmask (i,j,bi,bj) = 1.0
231 area_shelf_streamice(i,j,bi,bj) =
232 & rA(i,j,bi,bj)
233
234 PRINT *, "GOT HERE OVERFLOW ", i,j,
235 & area_shelf_streamice(i,j,bi,bj)
236 partial_vol = partial_vol - href * rA(i,j,bi,bj)
237
238 iter_flag = 1. _d 0
239
240 n_flux_2 = 0. _d 0 ;
241 DO k=1,4
242 new_partial (:) = 0
243 ENDDO
244
245 DO k=1,2
246 IF ( (STREAMICE_ufacemask(i-1+k,j,bi,bj).eq.2.0) .or.
247 & (STREAMICE_calve_to_mask .and.
248 & STREAMICE_calve_mask(i+2*k-3,j,bi,bj).ne.1.0)
249 & ) THEN ! at a permanent calving boundary - no advance allowed
250 n_flux_2 = n_flux_2 + 1. _d 0
251 ELSEIF (STREAMICE_hmask(i+2*k-3,j,bi,bj).eq.0 _d 0) THEN ! adjacent cell is completely ice free
252 n_flux_2 = n_flux_2 + 1. _d 0
253 new_partial (k) = 1
254 ENDIF
255 ENDDO
256 DO k=1,2
257 IF ( (STREAMICE_vfacemask (i,j-1+k,bi,bj).eq.2.0) .or.
258 & (STREAMICE_calve_to_mask .and.
259 & STREAMICE_calve_mask(i,j+2*k-3,bi,bj).ne.1.0)
260 & ) THEN ! at a permanent calving boundary - no advance allowed
261 n_flux_2 = n_flux_2 + 1. _d 0
262 ELSEIF (STREAMICE_hmask(i,j+2*k-3,bi,bj).eq.0 _d 0) THEN
263 n_flux_2 = n_flux_2 + 1. _d 0
264 new_partial (k+2) = 1
265 ENDIF
266 ENDDO
267
268 IF (n_flux_2 .eq. 0.) THEN ! there is nowhere to put the extra ice!
269 H_streamice(i,j,bi,bj) = href + partial_vol *
270 & recip_rA(i,j,bi,bj)
271 ELSE
272 H_streamice(i,j,bi,bj) = href
273
274 DO k=1,2
275 IF (new_partial(k) .eq. 1) THEN
276 hflux_x_SI2(i-1+k,j,bi,bj) =
277 & partial_vol/time_step/n_flux_2/
278 & dxG(i-1+k,j,bi,bj)
279 ENDIF
280 ENDDO
281
282 DO k=1,2
283 IF (new_partial(k+2) .eq. 1) THEN
284 hflux_y_SI2(i,j-1+k,bi,bj) =
285 & partial_vol/time_step/n_flux_2/
286 & dxG(i,j-1+k,bi,bj)
287 ENDIF
288 ENDDO
289
290 ENDIF
291 ENDIF
292 ENDIF
293
294 ENDIF
295 ENDIF
296 ENDDO
297 ENDIF
298 ENDDO
299 c
300 ENDDO
301 ENDDO
302 c
303 ENDIF
304 ENDDO
305
306 IF (iter_rpt.gt.1) THEN
307 WRITE(msgBuf,'(A,I5,A)') 'FRONT ADVANCE: ',iter_rpt,
308 & ' ITERATIONS'
309 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
310 & SQUEEZE_RIGHT , 1)
311 ENDIF
312
313
314
315 #endif
316 RETURN
317 END

  ViewVC Help
Powered by ViewVC 1.1.22