/[MITgcm]/MITgcm/pkg/thsice/thsice_step_fwd.F
ViewVC logotype

Contents of /MITgcm/pkg/thsice/thsice_step_fwd.F

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


Revision 1.42 - (show annotations) (download)
Mon Jun 10 20:05:15 2013 UTC (11 years, 3 months ago) by jmc
Branch: MAIN
Changes since 1.41: +6 -11 lines
fix filling of snow-precip diagnostic (SIsnwPrc) (bug introduced when
 removing snowPrc from common bloc, on May 2nd, cvs revision 1.40)

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_step_fwd.F,v 1.41 2013/06/04 22:52:58 jmc Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5 #ifdef ALLOW_ATM2D
6 # include "ctrparam.h"
7 #endif
8
9 CBOP
10 C !ROUTINE: THSICE_STEP_FWD
11 C !INTERFACE:
12 SUBROUTINE THSICE_STEP_FWD(
13 I bi, bj, iMin, iMax, jMin, jMax,
14 I prcAtm, snowPrc, qPrcRnO,
15 I myTime, myIter, myThid )
16 C !DESCRIPTION: \bv
17 C *==========================================================*
18 C | S/R THSICE_STEP_FWD
19 C | o Step Forward Therm-SeaIce model.
20 C *==========================================================*
21 C \ev
22
23 C !USES:
24 IMPLICIT NONE
25
26 C === Global variables ===
27 #include "SIZE.h"
28 #include "EEPARAMS.h"
29 #include "PARAMS.h"
30 #include "FFIELDS.h"
31 #ifdef ALLOW_ATM2D
32 # include "ATMSIZE.h"
33 # include "ATM2D_VARS.h"
34 #endif
35 #include "THSICE_SIZE.h"
36 #include "THSICE_PARAMS.h"
37 #include "THSICE_VARS.h"
38 #include "THSICE_TAVE.h"
39 #ifdef ALLOW_AUTODIFF_TAMC
40 # include "tamc.h"
41 # include "tamc_keys.h"
42 #endif
43
44 INTEGER siLo, siHi, sjLo, sjHi
45 PARAMETER ( siLo = 1-OLx , siHi = sNx+OLx )
46 PARAMETER ( sjLo = 1-OLy , sjHi = sNy+OLy )
47
48 C !INPUT/OUTPUT PARAMETERS:
49 C === Routine arguments ===
50 C- input:
51 C bi,bj :: tile indices
52 C iMin,iMax :: computation domain: 1rst index range
53 C jMin,jMax :: computation domain: 2nd index range
54 C prcAtm :: total precip from the atmosphere [kg/m2/s]
55 C snowPrc :: snow precipitation [kg/m2/s]
56 C qPrcRnO :: Energy content of Precip+RunOff (+=down) [W/m2]
57 C myTime :: current Time of simulation [s]
58 C myIter :: current Iteration number in simulation
59 C myThid :: my Thread Id number
60 C-- Use fluxes hold in commom blocks
61 C- input:
62 C icFlxSW :: net short-wave heat flux (+=down) below sea-ice, into ocean
63 C icFlxAtm :: net Atmospheric surf. heat flux over sea-ice [W/m2], (+=down)
64 C icFrwAtm :: evaporation over sea-ice to the atmosphere [kg/m2/s] (+=up)
65 C- output
66 C icFlxAtm :: net Atmospheric surf. heat flux over ice+ocean [W/m2], (+=down)
67 C icFrwAtm :: net fresh-water flux (E-P) from the atmosphere [kg/m2/s] (+=up)
68 INTEGER bi,bj
69 INTEGER iMin, iMax
70 INTEGER jMin, jMax
71 _RL prcAtm (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72 _RL snowPrc(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73 _RL qPrcRnO(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74 _RL myTime
75 INTEGER myIter
76 INTEGER myThid
77 CEOP
78
79 #ifdef ALLOW_THSICE
80 C !LOCAL VARIABLES:
81 C === Local variables ===
82 C iceFrac :: fraction of grid area covered in ice
83 C flx2oc :: net heat flux from the ice to the ocean (+=down) [W/m2]
84 C frw2oc :: fresh-water flux from the ice to the ocean (+=down)
85 C fsalt :: mass salt flux to the ocean (+=down)
86 C frzSeaWat :: seawater freezing rate (expressed as mass flux) [kg/m^2/s]
87 C frzmltMxL :: ocean mixed-layer freezing/melting potential [W/m2]
88 C tFrzOce :: sea-water freezing temperature [oC] (function of S)
89 C isIceFree :: true for ice-free grid-cell that remains ice-free
90 C ageFac :: snow aging factor [1]
91 C snowFac :: snowing refreshing-age factor [units of 1/snowPr]
92 LOGICAL isIceFree(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
93 _RL iceFrac (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
94 _RL flx2oc (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
95 _RL frw2oc (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
96 _RL fsalt (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
97 _RL frzSeaWat(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
98 _RL tFrzOce (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
99 _RL frzmltMxL(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
100 _RL ageFac
101 _RL snowFac
102 _RL cphm
103 _RL opFrac, icFrac
104 INTEGER i,j
105 LOGICAL dBugFlag
106
107 C- define grid-point location where to print debugging values
108 #include "THSICE_DEBUG.h"
109
110 1010 FORMAT(A,1P4E14.6)
111
112 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
113
114 #ifdef ALLOW_AUTODIFF_TAMC
115 act1 = bi - myBxLo(myThid)
116 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
117 act2 = bj - myByLo(myThid)
118 max2 = myByHi(myThid) - myByLo(myThid) + 1
119 act3 = myThid - 1
120 max3 = nTx*nTy
121 act4 = ikey_dynamics - 1
122 ticekey = (act1 + 1) + act2*max1
123 & + act3*max1*max2
124 & + act4*max1*max2*max3
125 #endif /* ALLOW_AUTODIFF_TAMC */
126
127 C- Initialise
128 dBugFlag = debugLevel.GE.debLevC
129 DO j = 1-OLy, sNy+OLy
130 DO i = 1-OLx, sNx+OLx
131 isIceFree(i,j) = .FALSE.
132 #ifdef ALLOW_ATM2D
133 sFluxFromIce(i,j) = 0. _d 0
134 #else
135 saltFlux(i,j,bi,bj) = 0. _d 0
136 #endif
137 frzSeaWat(i,j) = 0. _d 0
138 #ifdef ALLOW_AUTODIFF_TAMC
139 iceFrac(i,j) = 0.
140 C- set these arrays everywhere: overlap are not set and not used,
141 C but some arrays are stored and storage includes overlap.
142 flx2oc(i,j) = 0. _d 0
143 frw2oc(i,j) = 0. _d 0
144 fsalt (i,j) = 0. _d 0
145 c tFrzOce (i,j) = 0. _d 0
146 c frzmltMxL(i,j) = 0. _d 0
147 #endif
148 ENDDO
149 ENDDO
150
151 ageFac = 1. _d 0 - thSIce_deltaT/snowAgTime
152 snowFac = thSIce_deltaT/(rhos*hNewSnowAge)
153
154 #ifdef ALLOW_AUTODIFF_TAMC
155 CADJ STORE iceMask(:,:,bi,bj) = comlev1_bibj,key=ticekey,byte=isbyte
156 CADJ STORE iceheight(:,:,bi,bj) = comlev1_bibj,key=ticekey,byte=isbyte
157 CADJ STORE icfrwatm(:,:,bi,bj) = comlev1_bibj,key=ticekey,byte=isbyte
158 CADJ STORE qice1(:,:,bi,bj) = comlev1_bibj,key=ticekey,byte=isbyte
159 CADJ STORE qice2(:,:,bi,bj) = comlev1_bibj,key=ticekey,byte=isbyte
160 CADJ STORE snowheight(:,:,bi,bj) = comlev1_bibj,key=ticekey,byte=isbyte
161 #endif
162 DO j = jMin, jMax
163 DO i = iMin, iMax
164 IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN
165 C-- Snow aging :
166 snowAge(i,j,bi,bj) = thSIce_deltaT
167 & + snowAge(i,j,bi,bj)*ageFac
168 IF ( snowPrc(i,j).GT.0. _d 0 )
169 & snowAge(i,j,bi,bj) = snowAge(i,j,bi,bj)
170 & * EXP( - snowFac*snowPrc(i,j) )
171 C-------
172 C note: Any flux of mass (here fresh water) that enter or leave the system
173 C with a non zero energy HAS TO be counted: add snow precip.
174 icFlxAtm(i,j,bi,bj) = icFlxAtm(i,j,bi,bj)
175 & - Lfresh*snowPrc(i,j)
176 & + qPrcRnO(i,j)
177 C--
178 ENDIF
179 ENDDO
180 ENDDO
181
182 #ifdef ALLOW_DIAGNOSTICS
183 IF ( useDiagnostics ) THEN
184 CALL DIAGNOSTICS_FILL(iceMask,'SI_FrcFx',0,1,1,bi,bj,myThid)
185 CALL DIAGNOSTICS_FRACT_FILL( snowPrc,
186 I iceMask(1-OLx,1-OLy,bi,bj), oneRL, 1,
187 I 'SIsnwPrc', 0,1,2,bi,bj,myThid )
188 CALL DIAGNOSTICS_FRACT_FILL( siceAlb, iceMask, oneRL, 1,
189 I 'SIalbedo', 0,1,1,bi,bj,myThid )
190 ENDIF
191 #endif /* ALLOW_DIAGNOSTICS */
192 DO j = jMin, jMax
193 DO i = iMin, iMax
194 siceAlb(i,j,bi,bj) = iceMask(i,j,bi,bj)*siceAlb(i,j,bi,bj)
195 ENDDO
196 ENDDO
197
198 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
199 C part.2 : ice-covered fraction ;
200 C change in ice/snow thickness and ice-fraction
201 C note: can only reduce the ice-fraction but not increase it.
202 C-------
203 DO j = jMin, jMax
204 DO i = iMin, iMax
205
206 tFrzOce(i,j) = -mu_Tf*sOceMxL(i,j,bi,bj)
207 cphm = cpwater*rhosw*hOceMxL(i,j,bi,bj)
208 frzmltMxL(i,j) = ( tFrzOce(i,j)-tOceMxL(i,j,bi,bj) )
209 & * cphm/ocean_deltaT
210 iceFrac(i,j) = iceMask(i,j,bi,bj)
211 flx2oc(i,j) = icFlxSW(i,j,bi,bj) + qPrcRnO(i,j)
212 C-------
213 #ifdef ALLOW_DBUG_THSICE
214 IF ( dBug(i,j,bi,bj) ) THEN
215 IF (frzmltMxL(i,j).GT.0. .OR. iceFrac(i,j).GT.0.) THEN
216 WRITE(6,'(A,2I4,2I2)') 'ThSI_FWD: i,j=',i,j,bi,bj
217 WRITE(6,1010) 'ThSI_FWD:-1- iceMask, hIc, hSn, Tsf =',
218 & iceFrac(i,j), iceHeight(i,j,bi,bj),
219 & snowHeight(i,j,bi,bj), Tsrf(i,j,bi,bj)
220 WRITE(6,1010) 'ThSI_FWD: ocTs,tFrzOce,frzmltMxL,Qnet=',
221 & tOceMxL(i,j,bi,bj), tFrzOce(i,j),
222 & frzmltMxL(i,j), Qnet(i,j,bi,bj)
223 ENDIF
224 IF (iceFrac(i,j).GT.0.)
225 & WRITE(6,1010) 'ThSI_FWD: icFrac,flxAtm,evpAtm,flxSnw=',
226 & iceFrac(i,j), icFlxAtm(i,j,bi,bj),
227 & icFrwAtm(i,j,bi,bj),-Lfresh*snowPrc(i,j)
228 ENDIF
229 #endif
230 ENDDO
231 ENDDO
232
233 #ifdef ALLOW_AUTODIFF_TAMC
234 CADJ STORE iceMask(:,:,bi,bj) = comlev1_bibj,key=ticekey,byte=isbyte
235 #endif
236
237 CALL THSICE_CALC_THICKN(
238 I bi, bj,
239 I iMin,iMax, jMin,jMax, dBugFlag,
240 I iceMask(siLo,sjLo,bi,bj), tFrzOce,
241 I tOceMxL(siLo,sjLo,bi,bj), v2ocMxL(siLo,sjLo,bi,bj),
242 I snowPrc(siLo,sjLo), prcAtm,
243 I sHeating(siLo,sjLo,bi,bj), flxCndBt(siLo,sjLo,bi,bj),
244 U iceFrac, iceHeight(siLo,sjLo,bi,bj),
245 U snowHeight(siLo,sjLo,bi,bj), Tsrf(siLo,sjLo,bi,bj),
246 U Qice1(siLo,sjLo,bi,bj), Qice2(siLo,sjLo,bi,bj),
247 U icFrwAtm(siLo,sjLo,bi,bj), frzmltMxL, flx2oc,
248 O frw2oc, fsalt, frzSeaWat,
249 I myTime, myIter, myThid )
250
251 #ifdef ALLOW_AUTODIFF_TAMC
252 CADJ STORE iceMask(:,:,bi,bj) = comlev1_bibj,key=ticekey,byte=isbyte
253 CADJ STORE fsalt(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
254 CADJ STORE flx2oc(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
255 CADJ STORE frw2oc(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
256 #endif
257 C-- Net fluxes :
258 DO j = jMin, jMax
259 DO i = iMin, iMax
260 c#ifdef ALLOW_AUTODIFF_TAMC
261 c ikey_1 = i
262 c & + sNx*(j-1)
263 c & + sNx*sNy*act1
264 c & + sNx*sNy*max1*act2
265 c & + sNx*sNy*max1*max2*act3
266 c & + sNx*sNy*max1*max2*max3*act4
267 c#endif /* ALLOW_AUTODIFF_TAMC */
268 c#ifdef ALLOW_AUTODIFF_TAMC
269 cCADJ STORE icemask(i,j,bi,bj) = comlev1_thsice_1, key=ikey_1
270 c#endif
271 IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN
272 C- weighted average net fluxes:
273 c#ifdef ALLOW_AUTODIFF_TAMC
274 cCADJ STORE fsalt(i,j) = comlev1_thsice_1, key=ikey_1
275 cCADJ STORE flx2oc(i,j) = comlev1_thsice_1, key=ikey_1
276 cCADJ STORE frw2oc(i,j) = comlev1_thsice_1, key=ikey_1
277 cCADJ STORE icemask(i,j,bi,bj) = comlev1_thsice_1, key=ikey_1
278 c#endif
279 icFrac = iceMask(i,j,bi,bj)
280 opFrac= 1. _d 0-icFrac
281 #ifdef ALLOW_ATM2D
282 pass_qnet(i,j) = pass_qnet(i,j) - icFrac*flx2oc(i,j)
283 pass_evap(i,j) = pass_evap(i,j) - icFrac*frw2oc(i,j)/rhofw
284 sFluxFromIce(i,j) = -icFrac*fsalt(i,j)
285 #else
286 icFlxAtm(i,j,bi,bj) = icFrac*icFlxAtm(i,j,bi,bj)
287 & - opFrac*Qnet(i,j,bi,bj)
288 icFrwAtm(i,j,bi,bj) = icFrac*icFrwAtm(i,j,bi,bj)
289 & + opFrac*EmPmR(i,j,bi,bj)
290 Qnet(i,j,bi,bj) = -icFrac*flx2oc(i,j) + opFrac*Qnet(i,j,bi,bj)
291 EmPmR(i,j,bi,bj)= -icFrac*frw2oc(i,j)
292 & + opFrac*EmPmR(i,j,bi,bj)
293 saltFlux(i,j,bi,bj) = -icFrac*fsalt(i,j)
294 #endif
295 C- All seawater freezing (no reduction by surf. melting) from CALC_THICKN
296 c frzSeaWat(i,j) = icFrac*frzSeaWat(i,j)
297 C- Net seawater freezing (underestimated if there is surf. melting or rain)
298 frzSeaWat(i,j) = MAX( -icFrac*frw2oc(i,j), 0. _d 0 )
299
300 #ifdef ALLOW_DBUG_THSICE
301 IF (dBug(i,j,bi,bj)) WRITE(6,1010)
302 & 'ThSI_FWD:-3- iceFrac, hIc, hSn, Qnet =',
303 & iceFrac(i,j), iceHeight(i,j,bi,bj),
304 & snowHeight(i,j,bi,bj), Qnet(i,j,bi,bj)
305 #endif
306
307 ELSEIF (hOceMxL(i,j,bi,bj).GT.0. _d 0) THEN
308 icFlxAtm(i,j,bi,bj) = -Qnet(i,j,bi,bj)
309 icFrwAtm(i,j,bi,bj) = EmPmR(i,j,bi,bj)
310 ELSE
311 icFlxAtm(i,j,bi,bj) = 0. _d 0
312 icFrwAtm(i,j,bi,bj) = 0. _d 0
313 ENDIF
314 ENDDO
315 ENDDO
316
317 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
318 C part.3 : freezing of sea-water
319 C over ice-free fraction and what is left from ice-covered fraction
320 C-------
321 DO j = 1-OLy, sNy+OLy
322 DO i = 1-OLx, sNx+OLx
323 flx2oc(i,j) = 0. _d 0
324 frw2oc(i,j) = 0. _d 0
325 fsalt (i,j) = 0. _d 0
326 ENDDO
327 ENDDO
328 CALL THSICE_EXTEND(
329 I bi, bj,
330 I iMin,iMax, jMin,jMax, dBugFlag,
331 I frzmltMxL, tFrzOce,
332 I tOceMxL(siLo,sjLo,bi,bj),
333 U iceFrac, iceHeight(siLo,sjLo,bi,bj),
334 U snowHeight(siLo,sjLo,bi,bj), Tsrf(siLo,sjLo,bi,bj),
335 U Tice1(siLo,sjLo,bi,bj), Tice2(siLo,sjLo,bi,bj),
336 U Qice1(siLo,sjLo,bi,bj), Qice2(siLo,sjLo,bi,bj),
337 O flx2oc, frw2oc, fsalt,
338 I myTime, myIter, myThid )
339
340 #ifdef ALLOW_AUTODIFF_TAMC
341 CADJ STORE snowHeight(:,:,bi,bj) =
342 CADJ & comlev1_bibj,key=ticekey,byte=isbyte
343 #endif
344 DO j = jMin, jMax
345 DO i = iMin, iMax
346 C-- Net fluxes : (only non-zero contribution where frzmltMxL > 0 )
347 #ifdef ALLOW_ATM2D
348 pass_qnet(i,j) = pass_qnet(i,j) - flx2oc(i,j)
349 pass_evap(i,j) = pass_evap(i,j) - frw2oc(i,j)/rhofw
350 sFluxFromIce(i,j)= sFluxFromIce(i,j) - fsalt(i,j)
351 #else
352 Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj) - flx2oc(i,j)
353 EmPmR(i,j,bi,bj)= EmPmR(i,j,bi,bj)- frw2oc(i,j)
354 saltFlux(i,j,bi,bj)=saltFlux(i,j,bi,bj) - fsalt(i,j)
355 #endif
356 frzSeaWat(i,j) = frzSeaWat(i,j) + MAX(-frw2oc(i,j), 0. _d 0 )
357
358 #ifdef ALLOW_DBUG_THSICE
359 IF (dBug(i,j,bi,bj)) WRITE(6,1010)
360 & 'ThSI_FWD:-4- iceFrac, hIc, hSn, Qnet =',
361 & iceFrac(i,j), iceHeight(i,j,bi,bj),
362 & snowHeight(i,j,bi,bj), Qnet(i,j,bi,bj)
363 #endif
364
365 IF ( hOceMxL(i,j,bi,bj).GT.0. _d 0 )
366 & isIceFree(i,j) = iceMask(i,j,bi,bj).LE.0. _d 0
367 & .AND. iceFrac(i,j) .LE.0. _d 0
368 IF ( iceFrac(i,j) .GT. 0. _d 0 ) THEN
369 iceMask(i,j,bi,bj)=iceFrac(i,j)
370 IF ( snowHeight(i,j,bi,bj).EQ.0. _d 0 )
371 & snowAge(i,j,bi,bj) = 0. _d 0
372 ELSE
373 iceMask(i,j,bi,bj) = 0. _d 0
374 iceHeight(i,j,bi,bj)= 0. _d 0
375 snowHeight(i,j,bi,bj)=0. _d 0
376 snowAge(i,j,bi,bj) = 0. _d 0
377 Tsrf(i,j,bi,bj) = tOceMxL(i,j,bi,bj)
378 Tice1(i,j,bi,bj) = 0. _d 0
379 Tice2(i,j,bi,bj) = 0. _d 0
380 Qice1(i,j,bi,bj) = Lfresh
381 Qice2(i,j,bi,bj) = Lfresh
382 ENDIF
383 ENDDO
384 ENDDO
385
386 #ifdef ALLOW_SALT_PLUME
387 IF ( useSALT_PLUME ) THEN
388 CALL THSICE_SALT_PLUME(
389 I sOceMxL(1-OLx,1-OLy,bi,bj),
390 I frzSeaWat,
391 I iMin,iMax, jMin,jMax, bi, bj,
392 I myTime, myIter, myThid )
393 ENDIF
394 #endif /* ALLOW_SALT_PLUME */
395
396 # ifdef ALLOW_AUTODIFF_TAMC
397 CADJ STORE snowHeight(:,:,bi,bj) =
398 CADJ & comlev1_bibj,key=ticekey,byte=isbyte
399 # endif
400 #ifdef OLD_THSICE_CALL_SEQUENCE
401 IF ( .TRUE. ) THEN
402 #else /* OLD_THSICE_CALL_SEQUENCE */
403 IF ( thSIceAdvScheme.LE.0 ) THEN
404 C- note: 1) regarding sIceLoad in ocean-dynamics, in case thSIceAdvScheme > 0,
405 C compute sIceLoad in THSICE_DO_ADVECT after seaice advection is done.
406 C 2) regarding sIceLoad in seaice-dynamics, probably better not to update
407 C sIceLoad here, to keep the balance between sIceLoad and adjusted Eta.
408 C 3) not sure in the case of no advection (thSIceAdvScheme=0) but using
409 C seaice dynamics (unlikely senario anyway).
410 #endif /* OLD_THSICE_CALL_SEQUENCE */
411 C-- Compute Sea-Ice Loading (= mass of sea-ice + snow / area unit)
412 DO j = jMin, jMax
413 DO i = iMin, iMax
414 sIceLoad(i,j,bi,bj) = ( snowHeight(i,j,bi,bj)*rhos
415 & + iceHeight(i,j,bi,bj)*rhoi
416 & )*iceMask(i,j,bi,bj)
417 #ifdef ALLOW_ATM2D
418 pass_sIceLoad(i,j)=sIceLoad(i,j,bi,bj)
419 #endif
420 ENDDO
421 ENDDO
422 ENDIF
423
424 #ifdef OLD_THSICE_CALL_SEQUENCE
425 IF ( thSIceAdvScheme.GT.0 ) THEN
426 C-- note: those fluxes should to be added directly to Qnet, EmPmR & saltFlux
427 DO j = jMin, jMax
428 DO i = iMin, iMax
429 IF ( hOceMxL(i,j,bi,bj).GT.0. _d 0 ) THEN
430 Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj) - oceQnet(i,j,bi,bj)
431 EmPmR(i,j,bi,bj)= EmPmR(i,j,bi,bj)- oceFWfx(i,j,bi,bj)
432 saltFlux(i,j,bi,bj)=saltFlux(i,j,bi,bj) - oceSflx(i,j,bi,bj)
433 ENDIF
434 ENDDO
435 ENDDO
436 ENDIF
437 #endif /* OLD_THSICE_CALL_SEQUENCE */
438
439 #ifdef ALLOW_BULK_FORCE
440 IF ( useBulkForce ) THEN
441 CALL BULKF_FLUX_ADJUST(
442 I bi, bj, iMin, iMax, jMin, jMax,
443 I isIceFree, myTime, myIter, myThid )
444 ENDIF
445 #endif /* ALLOW_BULK_FORCE */
446
447 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
448 #endif /* ALLOW_THSICE */
449
450 RETURN
451 END

  ViewVC Help
Powered by ViewVC 1.1.22