/[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.5 - (show annotations) (download)
Fri Dec 17 03:44:52 2004 UTC (19 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint57o_post, checkpoint57m_post, checkpoint57s_post, checkpoint57k_post, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint57i_post, checkpoint57y_post, checkpoint57e_post, checkpoint57g_pre, checkpoint57y_pre, checkpoint57f_pre, checkpoint57v_post, checkpoint57r_post, checkpoint58, eckpoint57e_pre, checkpoint57h_done, checkpoint57x_post, checkpoint57n_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint57f_post, checkpoint57q_post, checkpoint57z_post, checkpoint57c_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint57h_post
Changes since 1.4: +2 -1 lines
include header file EEPARAMS.h

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

  ViewVC Help
Powered by ViewVC 1.1.22