/[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.17 - (show annotations) (download)
Thu May 25 18:03:25 2006 UTC (17 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint58q_post, checkpoint58j_post, checkpoint58f_post, checkpoint58i_post, checkpoint58g_post, checkpoint58o_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58m_post
Changes since 1.16: +151 -248 lines
- put i,j loops inside S/R: THSICE_ALBEDO, THSICE_SOLVE4TEMP, THSICE_EXTEND
   and THSICE_CALC_THICKN
- split thsice_step_fwd.F in 2 S/R: thsice_step_temp.F & thsice_step_fwd.F

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_step_fwd.F,v 1.16 2006/04/09 17:35:30 heimbach Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: THSICE_STEP_FWD
8 C !INTERFACE:
9 SUBROUTINE THSICE_STEP_FWD(
10 I bi, bj, iMin, iMax, jMin, jMax,
11 I prcAtm,
12 I myTime, myIter, myThid )
13 C !DESCRIPTION: \bv
14 C *==========================================================*
15 C | S/R THSICE_STEP_FWD
16 C | o Step Forward Therm-SeaIce model.
17 C *==========================================================*
18 C \ev
19
20 C !USES:
21 IMPLICIT NONE
22
23 C === Global variables ===
24 #include "SIZE.h"
25 #include "EEPARAMS.h"
26 #include "PARAMS.h"
27 #include "FFIELDS.h"
28 #include "THSICE_SIZE.h"
29 #include "THSICE_PARAMS.h"
30 #include "THSICE_VARS.h"
31 #include "THSICE_TAVE.h"
32 INTEGER siLo, siHi, sjLo, sjHi
33 PARAMETER ( siLo = 1-OLx , siHi = sNx+OLx )
34 PARAMETER ( sjLo = 1-OLy , sjHi = sNy+OLy )
35
36 C !INPUT/OUTPUT PARAMETERS:
37 C === Routine arguments ===
38 C- input:
39 C bi,bj :: tile indices
40 C iMin,iMax :: computation domain: 1rst index range
41 C jMin,jMax :: computation domain: 2nd index range
42 C prcAtm :: total precip from the atmosphere [kg/m2/s]
43 C myTime :: current Time of simulation [s]
44 C myIter :: current Iteration number in simulation
45 C myThid :: my Thread Id number
46 C-- Use fluxes hold in commom blocks
47 C- input:
48 C icFlxSW :: net short-wave heat flux (+=down) below sea-ice, into ocean
49 C icFlxAtm :: net Atmospheric surf. heat flux over sea-ice [W/m2], (+=down)
50 C icFrwAtm :: evaporation over sea-ice to the atmosphere [kg/m2/s] (+=up)
51 C- output
52 C icFlxAtm :: net Atmospheric surf. heat flux over ice+ocean [W/m2], (+=down)
53 C icFrwAtm :: net fresh-water flux (E-P) from the atmosphere [m/s] (+=up)
54 INTEGER bi,bj
55 INTEGER iMin, iMax
56 INTEGER jMin, jMax
57 _RL prcAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
58 _RL myTime
59 INTEGER myIter
60 INTEGER myThid
61 CEOP
62
63 #ifdef ALLOW_THSICE
64 C !LOCAL VARIABLES:
65 C === Local variables ===
66 C iceFrac :: fraction of grid area covered in ice
67 C flx2oc :: net heat flux from the ice to the ocean (+=down) [W/m2]
68 C frw2oc :: fresh-water flux from the ice to the ocean
69 C fsalt :: mass salt flux to the ocean
70 C frzmltMxL :: ocean mixed-layer freezing/melting potential [W/m2]
71 C tFrzOce :: sea-water freezing temperature [oC] (function of S)
72 C isIceFree :: true for ice-free grid-cell that remains ice-free
73 C ageFac :: snow aging factor [1]
74 C snowFac :: snowing refreshing-age factor [units of 1/snowPr]
75 LOGICAL isIceFree(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76 _RL iceFrac (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77 _RL flx2oc (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78 _RL frw2oc (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79 _RL fsalt (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80 _RL tFrzOce (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81 _RL frzmltMxL(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82 _RL ageFac
83 _RL snowFac
84 _RL cphm
85 _RL opFrac, icFrac
86 #ifdef ALLOW_DIAGNOSTICS
87 _RL tmpFac
88 #endif
89 INTEGER i,j
90 LOGICAL dBugFlag
91
92 C- define grid-point location where to print debugging values
93 #include "THSICE_DEBUG.h"
94
95 1010 FORMAT(A,1P4E14.6)
96
97 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
98
99 C- Initialise
100 dBugFlag = debugLevel.GE.debLevB
101 DO j = 1-OLy, sNy+OLy
102 DO i = 1-OLx, sNx+OLx
103 isIceFree(i,j) = .FALSE.
104 saltFlux(i,j,bi,bj) = 0. _d 0
105 #ifdef ALLOW_AUTODIFF_TAMC
106 iceFrac(i,j) = 0.
107 #endif
108 ENDDO
109 ENDDO
110
111 ageFac = 1. _d 0 - thSIce_deltaT/snowAgTime
112 snowFac = thSIce_deltaT/(rhos*hNewSnowAge)
113 DO j = jMin, jMax
114 DO i = iMin, iMax
115 IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN
116 C-- Snow aging :
117 snowAge(i,j,bi,bj) = thSIce_deltaT
118 & + snowAge(i,j,bi,bj)*ageFac
119 IF ( snowPrc(i,j,bi,bj).GT.0. _d 0 )
120 & snowAge(i,j,bi,bj) = snowAge(i,j,bi,bj)
121 & * EXP( - snowFac*snowPrc(i,j,bi,bj) )
122 c & * EXP( -(thSIce_deltaT*snowPrc(i,j,bi,bj)/rhos)
123 c & /hNewSnowAge )
124 C-------
125 C note: Any flux of mass (here fresh water) that enter or leave the system
126 C with a non zero energy HAS TO be counted: add snow precip.
127 icFlxAtm(i,j,bi,bj) = icFlxAtm(i,j,bi,bj)
128 & - Lfresh*snowPrc(i,j,bi,bj)
129 C--
130 ENDIF
131 ENDDO
132 ENDDO
133
134 #ifdef ALLOW_DIAGNOSTICS
135 IF ( useDiagnostics ) THEN
136 tmpFac = 1. _d 0
137 CALL DIAGNOSTICS_FRACT_FILL(
138 I snowPrc, iceMask,tmpFac,1,'SIsnwPrc',
139 I 0,1,1,bi,bj,myThid)
140 CALL DIAGNOSTICS_FRACT_FILL(
141 I siceAlb, iceMask,tmpFac,1,'SIalbedo',
142 I 0,1,1,bi,bj,myThid)
143 ENDIF
144 #endif /* ALLOW_DIAGNOSTICS */
145 DO j = jMin, jMax
146 DO i = iMin, iMax
147 siceAlb(i,j,bi,bj) = iceMask(i,j,bi,bj)*siceAlb(i,j,bi,bj)
148 ENDDO
149 ENDDO
150
151 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
152 C part.2 : ice-covered fraction ;
153 C change in ice/snow thickness and ice-fraction
154 C note: can only reduce the ice-fraction but not increase it.
155 C-------
156 DO j = jMin, jMax
157 DO i = iMin, iMax
158
159 tFrzOce(i,j) = -mu_Tf*sOceMxL(i,j,bi,bj)
160 cphm = cpwater*rhosw*hOceMxL(i,j,bi,bj)
161 frzmltMxL(i,j) = ( tFrzOce(i,j)-tOceMxL(i,j,bi,bj) )
162 & * cphm/ocean_deltaT
163 iceFrac(i,j) = iceMask(i,j,bi,bj)
164 flx2oc(i,j) = icFlxSW(i,j,bi,bj)
165 C-------
166 #ifdef ALLOW_DBUG_THSICE
167 IF ( dBug(i,j,bi,bj) ) THEN
168 IF (frzmltMxL(i,j).GT.0. .OR. iceFrac(i,j).GT.0.) THEN
169 WRITE(6,'(A,2I4,2I2)') 'ThSI_FWD: i,j=',i,j,bi,bj
170 WRITE(6,1010) 'ThSI_FWD:-1- iceMask, hIc, hSn, Tsf =',
171 & iceFrac(i,j), iceHeight(i,j,bi,bj),
172 & snowHeight(i,j,bi,bj), Tsrf(i,j,bi,bj)
173 WRITE(6,1010) 'ThSI_FWD: ocTs,tFrzOce,frzmltMxL,Qnet=',
174 & tOceMxL(i,j,bi,bj), tFrzOce(i,j),
175 & frzmltMxL(i,j), Qnet(i,j,bi,bj)
176 ENDIF
177 IF (iceFrac(i,j).GT.0.)
178 & WRITE(6,1010) 'ThSI_FWD: icFrac,flxAtm,evpAtm,flxSnw=',
179 & iceFrac(i,j), icFlxAtm(i,j,bi,bj),
180 & icFrwAtm(i,j,bi,bj),-Lfresh*snowPrc(i,j,bi,bj)
181 ENDIF
182 #endif
183 ENDDO
184 ENDDO
185
186 CALL THSICE_CALC_THICKN(
187 I bi, bj, siLo, siHi, sjLo, sjHi,
188 I iMin,iMax, jMin,jMax, dBugFlag,
189 I iceMask(siLo,sjLo,bi,bj), tFrzOce,
190 I tOceMxL(siLo,sjLo,bi,bj), v2ocMxL(siLo,sjLo,bi,bj),
191 I snowPrc(siLo,sjLo,bi,bj), prcAtm,
192 I sHeating(siLo,sjLo,bi,bj), flxCndBt(siLo,sjLo,bi,bj),
193 U iceFrac, iceHeight(siLo,sjLo,bi,bj),
194 U snowHeight(siLo,sjLo,bi,bj), Tsrf(siLo,sjLo,bi,bj),
195 U Qice1(siLo,sjLo,bi,bj), Qice2(siLo,sjLo,bi,bj),
196 U icFrwAtm(siLo,sjLo,bi,bj), frzmltMxL, flx2oc,
197 O frw2oc, fsalt,
198 I myTime, myIter, myThid )
199
200 C-- Net fluxes :
201 DO j = jMin, jMax
202 DO i = iMin, iMax
203 IF (iceMask(i,j,bi,bj).GT.0. _d 0) THEN
204 C- weighted average net fluxes:
205 icFrac = iceMask(i,j,bi,bj)
206 opFrac= 1. _d 0-icFrac
207 icFlxAtm(i,j,bi,bj) = icFrac*icFlxAtm(i,j,bi,bj)
208 & - opFrac*Qnet(i,j,bi,bj)
209 icFrwAtm(i,j,bi,bj) = icFrac*icFrwAtm(i,j,bi,bj)
210 & + opFrac*rhofw*EmPmR(i,j,bi,bj)
211 Qnet(i,j,bi,bj) = -icFrac*flx2oc(i,j) + opFrac*Qnet(i,j,bi,bj)
212 EmPmR(i,j,bi,bj)= -icFrac*frw2oc(i,j)/rhofw
213 & + opFrac*EmPmR(i,j,bi,bj)
214 saltFlux(i,j,bi,bj) = -icFrac*fsalt(i,j)
215
216 #ifdef ALLOW_DBUG_THSICE
217 IF (dBug(i,j,bi,bj)) WRITE(6,1010)
218 & 'ThSI_FWD:-3- iceFrac, hIc, hSn, Qnet =',
219 & iceFrac(i,j), iceHeight(i,j,bi,bj),
220 & snowHeight(i,j,bi,bj), Qnet(i,j,bi,bj)
221 #endif
222
223 ELSEIF (hOceMxL(i,j,bi,bj).gt.0. _d 0) THEN
224 icFlxAtm(i,j,bi,bj) = -Qnet(i,j,bi,bj)
225 icFrwAtm(i,j,bi,bj) = rhofw*EmPmR(i,j,bi,bj)
226 ELSE
227 icFlxAtm(i,j,bi,bj) = 0. _d 0
228 icFrwAtm(i,j,bi,bj) = 0. _d 0
229 ENDIF
230 ENDDO
231 ENDDO
232
233 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
234 C part.3 : freezing of sea-water
235 C over ice-free fraction and what is left from ice-covered fraction
236 C-------
237 CALL THSICE_EXTEND(
238 I bi, bj, siLo, siHi, sjLo, sjHi,
239 I iMin,iMax, jMin,jMax, dBugFlag,
240 I frzmltMxL, tFrzOce,
241 I tOceMxL(siLo,sjLo,bi,bj),
242 U iceFrac, iceHeight(siLo,sjLo,bi,bj),
243 U snowHeight(siLo,sjLo,bi,bj), Tsrf(siLo,sjLo,bi,bj),
244 U Tice1(siLo,sjLo,bi,bj), Tice2(siLo,sjLo,bi,bj),
245 U Qice1(siLo,sjLo,bi,bj), Qice2(siLo,sjLo,bi,bj),
246 O flx2oc, frw2oc, fsalt,
247 I myTime, myIter, myThid )
248
249 DO j = jMin, jMax
250 DO i = iMin, iMax
251 IF (frzmltMxL(i,j).GT.0. _d 0) THEN
252 C-- Net fluxes :
253 Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj) - flx2oc(i,j)
254 EmPmR(i,j,bi,bj)= EmPmR(i,j,bi,bj)- frw2oc(i,j)/rhofw
255 saltFlux(i,j,bi,bj)=saltFlux(i,j,bi,bj) - fsalt(i,j)
256
257 #ifdef ALLOW_DBUG_THSICE
258 IF (dBug(i,j,bi,bj)) WRITE(6,1010)
259 & 'ThSI_FWD:-4- iceFrac, hIc, hSn, Qnet =',
260 & iceFrac(i,j), iceHeight(i,j,bi,bj),
261 & snowHeight(i,j,bi,bj), Qnet(i,j,bi,bj)
262 #endif
263 ENDIF
264
265 IF ( hOceMxL(i,j,bi,bj).GT.0. _d 0 )
266 & isIceFree(i,j) = iceMask(i,j,bi,bj).LE.0. _d 0
267 & .AND. iceFrac(i,j) .LE.0. _d 0
268 IF ( iceFrac(i,j) .GT. 0. _d 0 ) THEN
269 iceMask(i,j,bi,bj)=iceFrac(i,j)
270 IF ( snowHeight(i,j,bi,bj).EQ.0. _d 0 )
271 & snowAge(i,j,bi,bj) = 0. _d 0
272 ELSE
273 iceMask(i,j,bi,bj) = 0. _d 0
274 iceHeight(i,j,bi,bj)= 0. _d 0
275 snowHeight(i,j,bi,bj)=0. _d 0
276 snowAge(i,j,bi,bj) = 0. _d 0
277 Tsrf(i,j,bi,bj) = tOceMxL(i,j,bi,bj)
278 Tice1(i,j,bi,bj) = 0. _d 0
279 Tice2(i,j,bi,bj) = 0. _d 0
280 Qice1(i,j,bi,bj) = 0. _d 0
281 Qice2(i,j,bi,bj) = 0. _d 0
282 ENDIF
283
284 #ifdef ATMOSPHERIC_LOADING
285 C-- Compute Sea-Ice Loading (= mass of sea-ice + snow / area unit)
286 sIceLoad(i,j,bi,bj) = ( snowHeight(i,j,bi,bj)*rhos
287 & + iceHeight(i,j,bi,bj)*rhoi
288 & )*iceMask(i,j,bi,bj)
289 #endif
290
291 ENDDO
292 ENDDO
293
294 #ifdef ALLOW_BULK_FORCE
295 IF ( useBulkForce ) THEN
296 CALL BULKF_FLUX_ADJUST(
297 I bi, bj, iMin, iMax, jMin, jMax,
298 I isIceFree, myTime, myIter, myThid )
299 ENDIF
300 #endif /* ALLOW_BULK_FORCE */
301
302 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
303 #endif /* ALLOW_THSICE */
304
305 RETURN
306 END

  ViewVC Help
Powered by ViewVC 1.1.22