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

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

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


Revision 1.4 - (show annotations) (download)
Thu Jul 22 22:52:59 2004 UTC (19 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint55c_post, checkpoint54e_post, checkpoint55d_pre, checkpoint55j_post, checkpoint56b_post, checkpoint55h_post, checkpoint55b_post, checkpoint54d_post, checkpoint56c_post, checkpoint55, checkpoint57a_post, checkpoint54f_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, checkpoint55e_post, checkpoint55a_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.3: +9 -7 lines
update debuging write.

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_solve4temp.F,v 1.3 2004/05/07 21:33:34 jmc Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: THSICE_SOLVE4TEMP
8 C !INTERFACE:
9 SUBROUTINE THSICE_SOLVE4TEMP(
10 I useBlkFlx, flxExcSw, Tf, hi, hs,
11 U flxSW, Tsf, qicen,
12 O Tice, sHeating, flxCnB,
13 O dTsf, flxAtm, evpAtm,
14 I i,j,bi,bj, myThid)
15 C !DESCRIPTION: \bv
16 C *==========================================================*
17 C | S/R THSICE_SOLVE4TEMP
18 C *==========================================================*
19 C | Solve (implicitly) for sea-ice and surface temperature
20 C *==========================================================*
21 C \ev
22
23 C !USES:
24 IMPLICIT NONE
25
26 C == Global variables ===
27 #include "THSICE_SIZE.h"
28 #include "THSICE_PARAMS.h"
29
30 C !INPUT/OUTPUT PARAMETERS:
31 C == Routine Arguments ==
32 C useBlkFlx :: use surf. fluxes from bulk-forcing external S/R
33 C flxExcSw :: surf. heat flux (+=down) except SW, function of surf. temp Ts:
34 C 0: Flx(Ts=0) ; 1: Flx(Ts=Ts^n) ; 2: d.Flx/dTs(Ts=Ts^n)
35 C Tf :: freezing temperature (oC) of local sea-water
36 C hi :: ice height
37 C hs :: snow height
38 C flxSW :: net Short-Wave flux (+=down) [W/m2]: input= at surface
39 C :: output= at the sea-ice base to the ocean
40 C Tsf :: surface (ice or snow) temperature
41 C qicen :: ice enthalpy (J m-3)
42 C Tice :: internal ice temperatures
43 C sHeating :: surf heating left to melt snow or ice (= Atmos-conduction)
44 C flxCnB :: heat flux conducted through the ice to bottom surface
45 C dTsf :: surf. temp adjusment: Ts^n+1 - Ts^n
46 C flxAtm :: net flux of energy from the atmosphere [W/m2] (+=down)
47 C without snow precip. (energy=0 for liquid water at 0.oC)
48 C evpAtm :: evaporation to the atmosphere (kg/m2/s) (>0 if evaporate)
49 C i,j,bi,bj :: indices of current grid point
50 C myThid :: Thread no. that called this routine.
51 LOGICAL useBlkFlx
52 _RL flxExcSw(0:2)
53 _RL Tf
54 _RL hi
55 _RL hs
56
57 _RL flxSW
58 _RL Tsf
59 _RL qicen(nlyr)
60
61 _RL Tice (nlyr)
62 _RL sHeating
63 _RL flxCnB
64 _RL dTsf
65 _RL flxAtm
66 _RL evpAtm
67 INTEGER i,j, bi,bj
68 INTEGER myThid
69 CEOP
70
71 #ifdef ALLOW_THSICE
72
73 C ADAPTED FROM:
74 C LANL CICE.v2.0.2
75 C-----------------------------------------------------------------------
76 C.. thermodynamics (vertical physics) based on M. Winton 3-layer model
77 C.. See Bitz, C. M. and W. H. Lipscomb, 1999: "An energy-conserving
78 C.. thermodynamic sea ice model for climate study." J. Geophys.
79 C.. Res., 104, 15669 - 15677.
80 C.. Winton, M., 1999: "A reformulated three-layer sea ice model."
81 C.. Submitted to J. Atmos. Ocean. Technol.
82 C.. authors Elizabeth C. Hunke and William Lipscomb
83 C.. Fluid Dynamics Group, Los Alamos National Laboratory
84 C-----------------------------------------------------------------------
85 Cc****subroutine thermo_winton(n,fice,fsnow,dqice,dTsfc)
86 C.. Compute temperature change using Winton model with 2 ice layers, of
87 C.. which only the top layer has a variable heat capacity.
88
89 C == Local Variables ==
90 INTEGER k
91
92 _RL frsnow ! fractional snow cover
93
94 _RL fswpen ! SW penetrating beneath surface (W m-2)
95 _RL fswdn ! SW absorbed at surface (W m-2)
96 _RL fswint ! SW absorbed in ice (W m-2)
97 _RL fswocn ! SW passed through ice to ocean (W m-2)
98
99 _RL flxExceptSw ! net surface heat flux, except short-wave (W/m2)
100 C evap :: evaporation over snow/ice [kg/m2/s] (>0 if evaporate)
101 C dEvdT :: derivative of evap. with respect to Tsf [kg/m2/s/K]
102 _RL evap, dEvdT
103 _RL flx0 ! net surf heat flux, from Atmos. to sea-ice (W m-2)
104 _RL fct ! heat conducted to top surface
105
106 _RL df0dT ! deriv of flx0 wrt Tsf (W m-2 deg-1)
107
108 _RL k12, k32 ! thermal conductivity terms
109 _RL a10, b10 ! coefficients in quadratic eqn for T1
110 _RL a1, b1, c1 ! coefficients in quadratic eqn for T1
111 c _RL Tsf_start ! old value of Tsf
112
113 _RL dt ! timestep
114
115 INTEGER iceornot
116 LOGICAL dBug
117
118 1010 FORMAT(A,I3,3F8.3)
119 1020 FORMAT(A,1P4E11.3)
120
121 dt = thSIce_deltaT
122 dBug = .FALSE.
123 c dBug = ( bi.EQ.3 .AND. i.EQ.15 .AND. j.EQ.11 )
124 c dBug = ( bi.EQ.6 .AND. i.EQ.18 .AND. j.EQ.10 )
125 IF (dBug) WRITE(6,'(A,2I4,2I2)') 'ThSI_SOLVE4T: i,j=',i,j,bi,bj
126
127 if ( hi.lt.himin ) then
128 C If hi < himin, melt the ice.
129 STOP 'THSICE_SOLVE4TEMP: should not enter if hi<himin'
130 endif
131
132 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
133
134 C fractional snow cover
135 frsnow = 0. _d 0
136 if (hs .gt. 0. _d 0) frsnow = 1. _d 0
137
138 C Compute SW flux absorbed at surface and penetrating to layer 1.
139 fswpen = flxSW * (1. _d 0 - frsnow) * i0
140 fswocn = fswpen * exp(-ksolar*hi)
141 fswint = fswpen - fswocn
142
143 fswdn = flxSW - fswpen
144
145 C Compute conductivity terms at layer interfaces.
146
147 k12 = 4. _d 0*kice*ksnow / (ksnow*hi + 4. _d 0*kice*hs)
148 k32 = 2. _d 0*kice / hi
149
150 C compute ice temperatures
151 a1 = cpice
152 b1 = qicen(1) + (cpwater-cpice )*Tmlt1 - Lfresh
153 c1 = Lfresh * Tmlt1
154 Tice(1) = 0.5 _d 0 *(-b1 - sqrt(b1*b1-4. _d 0*a1*c1))/a1
155 Tice(2) = (Lfresh-qicen(2)) / cpice
156
157 if (Tice(1).gt.0. _d 0 .or. Tice(2).gt.0. _d 0) then
158 write (6,*) 'BBerr Tice(1) > 0 = ',Tice(1)
159 write (6,*) 'BBerr Tice(2) > 0 = ',Tice(2)
160 endif
161 IF (dBug) WRITE(6,1010) 'ThSI_SOLVE4T: k, Ts, Tice=',0,Tsf,Tice
162
163 C Compute coefficients used in quadratic formula.
164
165 a10 = rhoi*cpice *hi/(2. _d 0*dt) +
166 & k32 * (4. _d 0*dt*k32 + rhoi*cpice *hi)
167 & / (6. _d 0*dt*k32 + rhoi*cpice *hi)
168 b10 = -hi*
169 & (rhoi*cpice*Tice(1)+rhoi*Lfresh*Tmlt1/Tice(1))
170 & /(2. _d 0*dt)
171 & - k32 * (4. _d 0*dt*k32*Tf+rhoi*cpice *hi*Tice(2))
172 & / (6. _d 0*dt*k32 + rhoi*cpice *hi) - fswint
173 c1 = rhoi*Lfresh*hi*Tmlt1 / (2. _d 0*dt)
174
175 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
176 C Compute new surface and internal temperatures; iterate until
177 C Tsfc converges.
178
179 C ----- begin iteration -----
180 do 100 k = 1,nitMaxTsf
181
182 C Save temperatures at start of iteration.
183 c Tsf_start = Tsf
184
185 IF ( useBlkFlx ) THEN
186 C Compute top surface flux.
187 if (hs.gt.3. _d -1) then
188 iceornot=2
189 else
190 iceornot=1
191 endif
192 CALL THSICE_GET_BULKF(
193 I iceornot, Tsf,
194 O flxExceptSw, df0dT, evap, dEvdT,
195 I i,j,bi,bj,myThid )
196 flx0 = fswdn + flxExceptSw
197 ELSE
198 flx0 = fswdn + flxExcSw(1)
199 df0dT = flxExcSw(2)
200 ENDIF
201 IF ( dBug ) WRITE(6,1020) 'ThSI_SOLVE4T: flx0,df0dT,k12,D=',
202 & flx0,df0dT,k12,k12-df0dT
203
204 C Compute new top layer and surface temperatures.
205 C If Tsfc is computed to be > 0 C, fix Tsfc = 0 and recompute T1
206 C with different coefficients.
207
208 a1 = a10 - k12*df0dT / (k12-df0dT)
209 b1 = b10 - k12*(flx0-df0dT*Tsf) / (k12-df0dT)
210 Tice(1) = -(b1 + sqrt(b1*b1-4. _d 0*a1*c1))/(2. _d 0*a1)
211 dTsf = (flx0 + k12*(Tice(1)-Tsf)) / (k12-df0dT)
212 Tsf = Tsf + dTsf
213 if (Tsf .gt. 0. _d 0) then
214 IF(dBug) WRITE(6,1010) 'ThSI_SOLVE4T: k,ts,t1,dTs=',
215 & k,Tsf,Tice(1),dTsf
216 a1 = a10 + k12
217 b1 = b10 ! note b1 = b10 - k12*Tf0
218 Tice(1) = (-b1 - sqrt(b1*b1-4. _d 0*a1*c1))/(2. _d 0*a1)
219 Tsf = 0. _d 0
220 IF ( useBlkFlx ) THEN
221 if (hs.gt.3. _d -1) then
222 iceornot=2
223 else
224 iceornot=1
225 endif
226 CALL THSICE_GET_BULKF(
227 I iceornot, Tsf,
228 O flxExceptSw, df0dT, evap, dEvdT,
229 I i,j,bi,bj,myThid )
230 flx0 = fswdn + flxExceptSw
231 dTsf = 0. _d 0
232 ELSE
233 flx0 = fswdn + flxExcSw(0)
234 dTsf = 1000.
235 df0dT = 0.
236 ENDIF
237 Tsf = 0. _d 0
238 endif
239
240 C Check for convergence. If no convergence, then repeat.
241 C
242 C Convergence test: Make sure Tsfc has converged, within prescribed error.
243 C (Energy conservation is guaranteed within machine roundoff, even
244 C if Tsfc has not converged.)
245 C If no convergence, then repeat.
246
247 IF ( dBug ) WRITE(6,1010) 'ThSI_SOLVE4T: k,ts,t1,dTs=',
248 & k,Tsf,Tice(1),dTsf
249 IF ( useBlkFlx ) THEN
250 if (abs(dTsf).lt.Terrmax) then
251 goto 150
252 elseif (k.eq.nitMaxTsf) then
253 write (6,*) 'BB: thermw conv err ',i,j,bi,bj,dTsf
254 write (6,*) 'BB: thermw conv err, iceheight ', hi
255 write (6,*) 'BB: thermw conv err: Tsf, flx0', Tsf,flx0
256 if (Tsf.lt.-70. _d 0) stop !QQQQ fails
257 endif
258 ELSE
259 goto 150
260 ENDIF
261
262 100 continue ! surface temperature iteration
263 150 continue
264 C ------ end iteration ------------
265
266 c if (Tsf.lt.-70. _d 0) then
267 cQQ print*,'QQQQQ Tsf =',Tsf
268 cQQ stop !QQQQ fails
269 c endif
270
271 C Compute new bottom layer temperature.
272
273 Tice(2) = (2. _d 0*dt*k32*(Tice(1)+2. _d 0*Tf)
274 & + rhoi*cpice *hi*Tice(2))
275 & /(6. _d 0*dt*k32 + rhoi*cpice *hi)
276 IF (dBug) WRITE(6,1010) 'ThSI_SOLVE4T: k, Ts, Tice=',k,Tsf,Tice
277
278
279 C Compute final flux values at surfaces.
280
281 fct = k12*(Tsf-Tice(1))
282 flxCnB = 4. _d 0*kice *(Tice(2)-Tf)/hi
283 flx0 = flx0 + df0dT*dTsf
284 IF ( useBlkFlx ) THEN
285 evpAtm = evap
286 C-- needs to update also Evap (Tsf changes) since Latent heat has been updated
287 evpAtm = evap + dEvdT*dTsf
288 C- energy flux to Atmos: use net short-wave flux at surf. and
289 C use latent heat = Lvap (energy=0 for liq. water at 0.oC)
290 flxAtm = flxSW + flxExceptSw + df0dT*dTsf
291 & + evpAtm*Lfresh
292 ELSE
293 flxAtm = 0.
294 evpAtm = 0.
295 ENDIF
296 sHeating = flx0 - fct
297
298 C- SW flux at sea-ice base left to the ocean
299 flxSW = fswocn
300
301 IF (dBug) WRITE(6,1020) 'ThSI_SOLVE4T: flx0,fct,Dif,flxCnB=',
302 & flx0,fct,flx0-fct,flxCnB
303
304 C Compute new enthalpy for each layer.
305
306 qicen(1) = -cpwater*Tmlt1 + cpice *(Tmlt1-Tice(1)) +
307 & Lfresh*(1. _d 0-Tmlt1/Tice(1))
308 qicen(2) = -cpice *Tice(2) + Lfresh
309
310 C Make sure internal ice temperatures do not exceed Tmlt.
311 C (This should not happen for reasonable values of i0.)
312
313 if (Tice(1) .ge. Tmlt1) then
314 write (6,'(A,2I4,2I3,1P2E14.6)')
315 & 'BBerr - Bug: IceT(1) > Tmlt',i,j,bi,bj,Tice(1),Tmlt1
316 endif
317 if (Tice(2) .ge. 0. _d 0) then
318 write (6,'(A,2I4,2I3,1P2E14.6)')
319 & 'BBerr - Bug: IceT(2) > 0',i,j,bi,bj,Tice(2)
320 endif
321
322 #endif /* ALLOW_THSICE */
323
324 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
325
326 RETURN
327 END

  ViewVC Help
Powered by ViewVC 1.1.22