/[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.6 - (show annotations) (download)
Fri Feb 10 00:24:12 2006 UTC (18 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58a_post
Changes since 1.5: +44 -45 lines
get rid of "goto" statement

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_solve4temp.F,v 1.5 2004/12/17 03:44:52 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/kg)
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, iterMax
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 IF ( useBlkFlx ) THEN
181 iterMax = nitMaxTsf
182 ELSE
183 iterMax = 1
184 ENDIF
185 dTsf = Terrmax
186
187 C ----- begin iteration -----
188 DO k = 1,iterMax
189 IF ( ABS(dTsf).GE.Terrmax ) THEN
190
191 C Save temperatures at start of iteration.
192 c Tsf_start = Tsf
193
194 IF ( useBlkFlx ) THEN
195 C Compute top surface flux.
196 IF (hs.GT.3. _d -1) THEN
197 iceornot=2
198 ELSE
199 iceornot=1
200 ENDIF
201 CALL THSICE_GET_BULKF(
202 I iceornot, Tsf,
203 O flxExceptSw, df0dT, evap, dEvdT,
204 I i,j,bi,bj,myThid )
205 flx0 = fswdn + flxExceptSw
206 ELSE
207 flx0 = fswdn + flxExcSw(1)
208 df0dT = flxExcSw(2)
209 ENDIF
210 IF ( dBug ) WRITE(6,1020) 'ThSI_SOLVE4T: flx0,df0dT,k12,D=',
211 & flx0,df0dT,k12,k12-df0dT
212
213 C Compute new top layer and surface temperatures.
214 C If Tsfc is computed to be > 0 C, fix Tsfc = 0 and recompute T1
215 C with different coefficients.
216
217 a1 = a10 - k12*df0dT / (k12-df0dT)
218 b1 = b10 - k12*(flx0-df0dT*Tsf) / (k12-df0dT)
219 Tice(1) = -(b1 + SQRT(b1*b1-4. _d 0*a1*c1))/(2. _d 0*a1)
220 dTsf = (flx0 + k12*(Tice(1)-Tsf)) / (k12-df0dT)
221 Tsf = Tsf + dTsf
222 IF (Tsf .GT. 0. _d 0) THEN
223 IF(dBug) WRITE(6,1010) 'ThSI_SOLVE4T: k,ts,t1,dTs=',
224 & k,Tsf,Tice(1),dTsf
225 a1 = a10 + k12
226 b1 = b10 ! note b1 = b10 - k12*Tf0
227 Tice(1) = (-b1 - SQRT(b1*b1-4. _d 0*a1*c1))/(2. _d 0*a1)
228 Tsf = 0. _d 0
229 IF ( useBlkFlx ) THEN
230 IF (hs.GT.3. _d -1) THEN
231 iceornot=2
232 ELSE
233 iceornot=1
234 ENDIF
235 CALL THSICE_GET_BULKF(
236 I iceornot, Tsf,
237 O flxExceptSw, df0dT, evap, dEvdT,
238 I i,j,bi,bj,myThid )
239 flx0 = fswdn + flxExceptSw
240 dTsf = 0. _d 0
241 ELSE
242 flx0 = fswdn + flxExcSw(0)
243 dTsf = 1000.
244 df0dT = 0.
245 ENDIF
246 ENDIF
247
248 C Check for convergence. If no convergence, then repeat.
249 C
250 C Convergence test: Make sure Tsfc has converged, within prescribed error.
251 C (Energy conservation is guaranteed within machine roundoff, even
252 C if Tsfc has not converged.)
253 C If no convergence, then repeat.
254
255 IF ( dBug ) WRITE(6,1010) 'ThSI_SOLVE4T: k,ts,t1,dTs=',
256 & k,Tsf,Tice(1),dTsf
257 IF ( useBlkFlx .AND. k.EQ.nitMaxTsf
258 & .AND. ABS(dTsf).GE.Terrmax ) THEN
259 WRITE (6,*) 'BB: thermw conv err ',i,j,bi,bj,dTsf
260 WRITE (6,*) 'BB: thermw conv err, iceheight ', hi
261 WRITE (6,*) 'BB: thermw conv err: Tsf, flx0', Tsf,flx0
262 IF (Tsf.LT.-70. _d 0) STOP
263 ENDIF
264
265 100 continue ! surface temperature iteration
266 ENDIF
267 ENDDO
268 150 continue
269 C ------ end iteration ------------
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