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

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

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


Revision 1.37 - (hide annotations) (download)
Thu Aug 22 02:10:48 2013 UTC (10 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64o, checkpoint64n, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.36: +3 -3 lines
remove unnecessary included headers

1 jmc 1.37 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_solve4temp.F,v 1.36 2013/06/04 22:52:58 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "THSICE_OPTIONS.h"
5 heimbach 1.30 #ifdef ALLOW_AUTODIFF_TAMC
6     # ifdef ALLOW_EXF
7     # include "EXF_OPTIONS.h"
8     # endif
9     #endif
10 jmc 1.1
11     CBOP
12     C !ROUTINE: THSICE_SOLVE4TEMP
13     C !INTERFACE:
14     SUBROUTINE THSICE_SOLVE4TEMP(
15 heimbach 1.24 I bi, bj,
16 jmc 1.17 I iMin,iMax, jMin,jMax, dBugFlag,
17 mlosch 1.9 I useBulkForce, useEXF,
18 heimbach 1.31 I icMask, hIce, hSnow1, tFrz, flxExSW,
19     U flxSW, tSrf1, qIc1, qIc2,
20     O tIc1, tIc2, dTsrf1,
21 jmc 1.8 O sHeat, flxCnB, flxAtm, evpAtm,
22     I myTime, myIter, myThid )
23 jmc 1.1 C !DESCRIPTION: \bv
24     C *==========================================================*
25     C | S/R THSICE_SOLVE4TEMP
26     C *==========================================================*
27     C | Solve (implicitly) for sea-ice and surface temperature
28     C *==========================================================*
29     C \ev
30    
31 jmc 1.8 C ADAPTED FROM:
32     C LANL CICE.v2.0.2
33     C-----------------------------------------------------------------------
34     C.. thermodynamics (vertical physics) based on M. Winton 3-layer model
35 jmc 1.19 C.. See Bitz, C. M. and W. H. Lipscomb, 1999: An energy-conserving
36     C.. thermodynamic sea ice model for climate study.
37     C.. J. Geophys. Res., 104, 15669 - 15677.
38 jmc 1.8 C.. Winton, M., 1999: "A reformulated three-layer sea ice model."
39     C.. Submitted to J. Atmos. Ocean. Technol.
40     C.. authors Elizabeth C. Hunke and William Lipscomb
41     C.. Fluid Dynamics Group, Los Alamos National Laboratory
42     C-----------------------------------------------------------------------
43     Cc****subroutine thermo_winton(n,fice,fsnow,dqice,dTsfc)
44     C.. Compute temperature change using Winton model with 2 ice layers, of
45     C.. which only the top layer has a variable heat capacity.
46    
47 jmc 1.1 C !USES:
48     IMPLICIT NONE
49    
50     C == Global variables ===
51 jmc 1.5 #include "EEPARAMS.h"
52 jmc 1.21 #include "SIZE.h"
53 jmc 1.1 #include "THSICE_PARAMS.h"
54 heimbach 1.14 #ifdef ALLOW_AUTODIFF_TAMC
55     # include "tamc.h"
56     # include "tamc_keys.h"
57 jmc 1.37 #include "THSICE_SIZE.h"
58     c#include "THSICE_VARS.h"
59 heimbach 1.30 # ifdef ALLOW_EXF
60     # include "EXF_FIELDS.h"
61 heimbach 1.31 # include "EXF_PARAM.h"
62 jmc 1.32 # include "EXF_CONSTANTS.h"
63 heimbach 1.30 # endif
64 heimbach 1.14 #endif
65 jmc 1.1
66     C !INPUT/OUTPUT PARAMETERS:
67     C == Routine Arguments ==
68 jmc 1.8 C bi,bj :: tile indices
69     C iMin,iMax :: computation domain: 1rst index range
70     C jMin,jMax :: computation domain: 2nd index range
71     C dBugFlag :: allow to print debugging stuff (e.g. on 1 grid point).
72 mlosch 1.9 C useBulkForce:: use surf. fluxes from bulk-forcing external S/R
73     C useEXF :: use surf. fluxes from exf external S/R
74 jmc 1.8 C--- Input:
75 jmc 1.32 C icMask :: sea-ice fractional mask [0-1]
76 jmc 1.21 C hIce :: ice height [m]
77 jmc 1.32 C hSnow1 :: snow height [m]
78 jmc 1.21 C tFrz :: sea-water freezing temperature [oC] (function of S)
79     C flxExSW :: surf. heat flux (+=down) except SW, function of surf. temp Ts:
80 jmc 1.8 C 0: Flx(Ts=0) ; 1: Flx(Ts=Ts^n) ; 2: d.Flx/dTs(Ts=Ts^n)
81     C--- Modified (input&output):
82 jmc 1.21 C flxSW :: net Short-Wave flux (+=down) [W/m2]: input= at surface
83     C :: output= below sea-ice, into the ocean
84 jmc 1.32 C tSrf1 :: surface (ice or snow) temperature
85 jmc 1.21 C qIc1 :: ice enthalpy (J/kg), 1rst level
86     C qIc2 :: ice enthalpy (J/kg), 2nd level
87 jmc 1.8 C--- Output
88 jmc 1.21 C tIc1 :: temperature of ice layer 1 [oC]
89     C tIc2 :: temperature of ice layer 2 [oC]
90 jmc 1.32 C dTsrf1 :: surf. temp adjusment: Ts^n+1 - Ts^n
91 jmc 1.21 C sHeat :: surf heating flux left to melt snow or ice (= Atmos-conduction)
92     C flxCnB :: heat flux conducted through the ice to bottom surface
93     C flxAtm :: net flux of energy from the atmosphere [W/m2] (+=down)
94 jmc 1.8 C without snow precip. (energy=0 for liquid water at 0.oC)
95 jmc 1.21 C evpAtm :: evaporation to the atmosphere [kg/m2/s] (>0 if evaporate)
96 jmc 1.8 C--- Input:
97     C myTime :: current Time of simulation [s]
98     C myIter :: current Iteration number in simulation
99     C myThid :: my Thread Id number
100     INTEGER bi,bj
101     INTEGER iMin, iMax
102     INTEGER jMin, jMax
103     LOGICAL dBugFlag
104 mlosch 1.9 LOGICAL useBulkForce
105     LOGICAL useEXF
106 heimbach 1.31 _RL icMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
107 heimbach 1.24 _RL hIce (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
108 jmc 1.32 _RL hSnow1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
109 heimbach 1.24 _RL tFrz (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
110     _RL flxSW (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
111 jmc 1.32 _RL tSrf1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
112 heimbach 1.24 _RL qIc1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
113     _RL qIc2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
114     _RL tIc1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
115     _RL tIc2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
116     _RL sHeat (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
117     _RL flxCnB (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
118     _RL flxAtm (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
119     _RL evpAtm (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120 heimbach 1.31 _RL flxExSW(iMin:iMax,jMin:jMax,0:2)
121 jmc 1.32 _RL dTsrf1 (iMin:iMax,jMin:jMax)
122 heimbach 1.33 _RL myTime
123 jmc 1.8 INTEGER myIter
124     INTEGER myThid
125     CEOP
126    
127     #ifdef ALLOW_THSICE
128     C !LOCAL VARIABLES:
129 jmc 1.1 C == Local Variables ==
130 jmc 1.21 C useBlkFlx :: use some bulk-formulae to compute fluxes over sea-ice
131     C :: (otherwise, fluxes are passed as argument from AIM)
132     C iterate4Tsf :: to stop to iterate when all icy grid pts Tsf did converged
133     C iceFlag :: True= do iterate for Surf.Temp ; False= do nothing
134 jmc 1.18 C frsnow :: fractional snow cover
135     C fswpen :: SW penetrating beneath surface (W m-2)
136     C fswdn :: SW absorbed at surface (W m-2)
137     C fswint :: SW absorbed in ice (W m-2)
138     C fswocn :: SW passed through ice to ocean (W m-2)
139 heimbach 1.31 C Tsf :: surface (ice or snow) temperature (local copy of tSrf1)
140 jmc 1.20 C flx0exSW :: net surface heat flux over melting snow/ice, except short-wave.
141     C flxTexSW :: net surface heat flux, except short-wave (W/m2)
142 jmc 1.21 C dFlxdT :: deriv of flxNet wrt Tsf (W m-2 deg-1)
143 heimbach 1.30 C evap00 :: evaporation over melting snow/ice [kg/m2/s] (>0 if evaporate)
144 jmc 1.36 C renamed to evap00 because TAF confuses symbol with EXF evap0
145 jmc 1.20 C evapT :: evaporation over snow/ice [kg/m2/s] (>0 if evaporate)
146 jmc 1.18 C dEvdT :: derivative of evap. with respect to Tsf [kg/m2/s/K]
147 jmc 1.20 C flxNet :: net surf heat flux (+=down), from Atmos. to sea-ice (W m-2)
148 jmc 1.21 C netSW :: net Short-Wave flux at surface (+=down) [W/m2]
149 jmc 1.18 C fct :: heat conducted to top surface
150     C k12, k32 :: thermal conductivity terms
151 jmc 1.21 C a10,b10,c10 :: coefficients in quadratic eqn for T1
152 jmc 1.18 C a1, b1, c1 :: coefficients in quadratic eqn for T1
153     C dt :: timestep
154 jmc 1.21 LOGICAL useBlkFlx
155     LOGICAL iterate4Tsf
156 jmc 1.27 INTEGER i, j, k, iterMax
157     INTEGER ii, jj, icount, stdUnit
158     CHARACTER*(MAX_LEN_MBUF) msgBuf
159 jmc 1.18 _RL frsnow
160     _RL fswpen
161     _RL fswdn
162     _RL fswint
163     _RL fswocn
164 heimbach 1.31 _RL iceFlag (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
165 jmc 1.21 _RL Tsf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
166     _RL flx0exSW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
167     _RL flxTexSW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
168     _RL dFlxdT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
169 jmc 1.36 _RL evap00 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
170 jmc 1.21 _RL evapT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
171     _RL dEvdT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
172 jmc 1.20 _RL flxNet
173 jmc 1.18 _RL fct
174 jmc 1.21 _RL k12 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
175     _RL k32
176     _RL a10 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
177     _RL b10 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
178     _RL c10 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
179 jmc 1.18 _RL a1, b1, c1
180     _RL dt
181 jmc 1.17 _RL recip_dhSnowLin
182 jmc 1.21 #ifdef ALLOW_DBUG_THSICE
183     _RL netSW
184     #endif
185 jmc 1.1
186 jmc 1.21 C- Define grid-point location where to print debugging values
187 jmc 1.8 #include "THSICE_DEBUG.h"
188 jmc 1.1
189 jmc 1.7 1010 FORMAT(A,I3,3F11.6)
190     1020 FORMAT(A,1P4E14.6)
191 jmc 1.1
192 heimbach 1.24 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|
193 jmc 1.8
194 heimbach 1.14 #ifdef ALLOW_AUTODIFF_TAMC
195 jmc 1.26 act1 = bi - myBxLo(myThid)
196     max1 = myBxHi(myThid) - myBxLo(myThid) + 1
197     act2 = bj - myByLo(myThid)
198     max2 = myByHi(myThid) - myByLo(myThid) + 1
199     act3 = myThid - 1
200     max3 = nTx*nTy
201     act4 = ikey_dynamics - 1
202 gforget 1.29 ticekey = (act1 + 1) + act2*max1
203 heimbach 1.23 & + act3*max1*max2
204     & + act4*max1*max2*max3
205 heimbach 1.14 #endif /* ALLOW_AUTODIFF_TAMC */
206    
207 heimbach 1.24 #ifdef ALLOW_AUTODIFF_TAMC
208 gforget 1.29 CADJ STORE flxsw(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
209 heimbach 1.25 DO j = 1-OLy, sNy+OLy
210     DO i = 1-OLx, sNx+OLx
211 jmc 1.27 tIc1(i,j) = 0. _d 0
212     tIc2(i,j) = 0. _d 0
213 jmc 1.36 C- set these arrays everywhere: overlap are not set and not used,
214     C but some arrays are stored and storage includes overlap.
215     flx0exSW(i,j) = 0. _d 0
216     flxTexSW(i,j) = 0. _d 0
217     dFlxdT (i,j) = 0. _d 0
218     evap00 (i,j) = 0. _d 0
219     evapT (i,j) = 0. _d 0
220     dEvdT (i,j) = 0. _d 0
221     iceFlag (i,j) = 0. _d 0
222     Tsf (i,j) = 0. _d 0
223 jmc 1.27 ENDDO
224     ENDDO
225 heimbach 1.24 #endif
226    
227 jmc 1.27 stdUnit = standardMessageUnit
228 mlosch 1.9 useBlkFlx = useEXF .OR. useBulkForce
229 jmc 1.21 dt = thSIce_dtTemp
230 jmc 1.17 IF ( dhSnowLin.GT.0. _d 0 ) THEN
231     recip_dhSnowLin = 1. _d 0 / dhSnowLin
232     ELSE
233     recip_dhSnowLin = 0. _d 0
234     ENDIF
235 mlosch 1.9
236 jmc 1.21 iterate4Tsf = .FALSE.
237 mlosch 1.22 icount = 0
238 jmc 1.27
239 jmc 1.8 DO j = jMin, jMax
240     DO i = iMin, iMax
241 heimbach 1.14 #ifdef ALLOW_AUTODIFF_TAMC
242 heimbach 1.31 ikey_1 = i
243     & + sNx*(j-1)
244     & + sNx*sNy*act1
245     & + sNx*sNy*max1*act2
246     & + sNx*sNy*max1*max2*act3
247     & + sNx*sNy*max1*max2*max3*act4
248     C--
249     CADJ STORE hSnow1(i,j) = comlev1_thsice_1, key=ikey_1
250 jmc 1.21 cCADJ STORE flxsw(i,j) = comlev1_thsice_1, key=ikey_1
251     cCADJ STORE qic1(i,j) = comlev1_thsice_1, key=ikey_1
252     cCADJ STORE qic2(i,j) = comlev1_thsice_1, key=ikey_1
253 heimbach 1.14 #endif
254 heimbach 1.31 IF ( icMask(i,j).GT.0. _d 0) THEN
255 jmc 1.21 iterate4Tsf = .TRUE.
256 heimbach 1.31 iceFlag(i,j) = 1. _d 0
257 jmc 1.8 #ifdef ALLOW_DBUG_THSICE
258 jmc 1.27 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,'(A,2I4,2I2)')
259 jmc 1.8 & 'ThSI_SOLVE4T: i,j=',i,j,bi,bj
260     #endif
261 jmc 1.21 IF ( hIce(i,j).LT.hIceMin ) THEN
262 mlosch 1.22 C if hi < hIceMin, melt the ice.
263     C keep the position of this problem but do the stop later
264     ii = i
265     jj = j
266     icount = icount + 1
267 heimbach 1.15 ENDIF
268 jmc 1.1
269 jmc 1.21 C-- Fractional snow cover:
270     C assume a linear distribution of snow thickness, with dhSnowLin slope,
271     C from hs-dhSnowLin to hs+dhSnowLin if full ice & snow cover.
272     C frsnow = fraction of snow over the ice-covered part of the grid cell
273 heimbach 1.31 IF ( hSnow1(i,j) .GT. icMask(i,j)*dhSnowLin ) THEN
274 jmc 1.21 frsnow = 1. _d 0
275     ELSE
276 heimbach 1.31 frsnow = hSnow1(i,j)*recip_dhSnowLin/icMask(i,j)
277 jmc 1.21 IF ( frsnow.GT.0. _d 0 ) frsnow = SQRT(frsnow)
278     ENDIF
279 jmc 1.1
280 jmc 1.21 C-- Compute SW flux absorbed at surface and penetrating to layer 1.
281     fswpen = flxSW(i,j) * (1. _d 0 - frsnow) * i0swFrac
282     fswocn = fswpen * exp(-ksolar*hIce(i,j))
283     fswint = fswpen - fswocn
284     fswdn = flxSW(i,j) - fswpen
285    
286     C Initialise Atmospheric surf. heat flux with net SW flux at the surface
287     flxAtm(i,j) = flxSW(i,j)
288     C SW flux at sea-ice base left to the ocean
289     flxSW(i,j) = fswocn
290     C Initialise surface Heating with SW contribution
291     sHeat(i,j) = fswdn
292    
293     C-- Compute conductivity terms at layer interfaces.
294     k12(i,j) = 4. _d 0*kIce*kSnow
295 heimbach 1.31 & / (kSnow*hIce(i,j) + 4. _d 0*kIce*hSnow1(i,j))
296 jmc 1.21 k32 = 2. _d 0*kIce / hIce(i,j)
297    
298     C-- Compute ice temperatures
299     a1 = cpIce
300     b1 = qIc1(i,j) + (cpWater-cpIce )*Tmlt1 - Lfresh
301     c1 = Lfresh * Tmlt1
302     tIc1(i,j) = 0.5 _d 0 *(-b1 - SQRT(b1*b1-4. _d 0*a1*c1))/a1
303     tIc2(i,j) = (Lfresh-qIc2(i,j)) / cpIce
304    
305 mlosch 1.22 #ifdef ALLOW_DBUG_THSICE
306 jmc 1.21 IF (tIc1(i,j).GT.0. _d 0 ) THEN
307 jmc 1.27 WRITE(stdUnit,'(A,I12,1PE14.6)')
308 jmc 1.21 & ' BBerr: Tice(1) > 0 ; it=', myIter, qIc1(i,j)
309 jmc 1.27 WRITE(stdUnit,'(A,4I5,2F11.4)')
310 jmc 1.21 & ' BBerr: i,j,bi,bj,Tice = ',i,j,bi,bj,tIc1(i,j),tIc2(i,j)
311     ENDIF
312     IF ( tIc2(i,j).GT.0. _d 0) THEN
313 jmc 1.27 WRITE(stdUnit,'(A,I12,1PE14.6)')
314 jmc 1.21 & ' BBerr: Tice(2) > 0 ; it=', myIter, qIc2(i,j)
315 jmc 1.27 WRITE(stdUnit,'(A,4I5,2F11.4)')
316 jmc 1.21 & ' BBerr: i,j,bi,bj,Tice = ',i,j,bi,bj,tIc1(i,j),tIc2(i,j)
317     ENDIF
318 jmc 1.27 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,1010)
319 heimbach 1.31 & 'ThSI_SOLVE4T: k, Ts, Tice=',0,tSrf1(i,j),tIc1(i,j),tIc2(i,j)
320 jmc 1.8 #endif
321 jmc 1.1
322 jmc 1.21 C-- Compute coefficients used in quadratic formula.
323 jmc 1.1
324 jmc 1.21 a10(i,j) = rhoi*cpIce *hIce(i,j)/(2. _d 0*dt) +
325     & k32*( 4. _d 0*dt*k32 + rhoi*cpIce *hIce(i,j) )
326     & / ( 6. _d 0*dt*k32 + rhoi*cpIce *hIce(i,j) )
327     b10(i,j) = -hIce(i,j)*
328     & ( rhoi*cpIce*tIc1(i,j) + rhoi*Lfresh*Tmlt1/tIc1(i,j) )
329     & /(2. _d 0*dt)
330     & - k32*( 4. _d 0*dt*k32*tFrz(i,j)
331     & +rhoi*cpIce*hIce(i,j)*tIc2(i,j) )
332     & / ( 6. _d 0*dt*k32 + rhoi*cpIce *hIce(i,j) )
333     & - fswint
334     c10(i,j) = rhoi*Lfresh*hIce(i,j)*Tmlt1 / (2. _d 0*dt)
335    
336     ELSE
337 heimbach 1.31 iceFlag(i,j) = 0. _d 0
338 jmc 1.21 ENDIF
339     ENDDO
340     ENDDO
341 heimbach 1.31 #ifndef ALLOW_AUTODIFF
342 mlosch 1.22 IF ( icount .gt. 0 ) THEN
343 jmc 1.27 WRITE(stdUnit,'(A,I5,A)')
344 mlosch 1.22 & 'THSICE_SOLVE4TEMP: there are ',icount,
345     & ' case(s) where hIce<hIceMin;'
346 jmc 1.27 WRITE(stdUnit,'(A,I3,A1,I3,A)')
347 mlosch 1.22 & 'THSICE_SOLVE4TEMP: the last one was at (',ii,',',jj,
348 jmc 1.26 & ') with hIce = ', hIce(ii,jj)
349 jmc 1.27 WRITE( msgBuf, '(A)')
350     & 'THSICE_SOLVE4TEMP: should not enter if hIce<hIceMin'
351     CALL PRINT_ERROR( msgBuf , myThid )
352     STOP 'ABNORMAL END: S/R THSICE_SOLVE4TEMP'
353 mlosch 1.22 ENDIF
354 heimbach 1.31 #endif /* ALLOW_AUTODIFF */
355 jmc 1.1
356 heimbach 1.24 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|
357    
358     #ifdef ALLOW_AUTODIFF_TAMC
359 gforget 1.29 CADJ STORE devdt(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
360     CADJ STORE tsf(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
361 heimbach 1.31 CADJ STORE hsnow1(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
362     CADJ STORE sh(:,:,:,:) = comlev1_bibj,key=ticekey,byte=isbyte
363 heimbach 1.24 #endif
364    
365 jmc 1.21 C-- Get surface fluxes over melting surface
366 heimbach 1.31 #ifndef ALLOW_AUTODIFF
367 jmc 1.21 IF ( useBlkFlx .AND. iterate4Tsf ) THEN
368     #endif
369     DO j = jMin, jMax
370     DO i = iMin, iMax
371     Tsf(i,j) = 0.
372     ENDDO
373     ENDDO
374 heimbach 1.31 #ifndef ALLOW_AUTODIFF
375 jmc 1.21 IF ( useEXF ) THEN
376 heimbach 1.31 #endif
377 heimbach 1.35 k = 1
378     CALL THSICE_GET_EXF( bi, bj, k,
379 jmc 1.21 I iMin, iMax, jMin, jMax,
380 heimbach 1.31 I iceFlag, hSnow1, Tsf,
381 heimbach 1.30 O flx0exSW, dFlxdT, evap00, dEvdT,
382 jmc 1.21 I myTime, myIter, myThid )
383 jmc 1.32 #ifndef ALLOW_AUTODIFF
384 jmc 1.21 C- could add this "ifdef" to hide THSICE_GET_BULKF from TAF
385     ELSEIF ( useBulkForce ) THEN
386 heimbach 1.24 CALL THSICE_GET_BULKF( bi, bj,
387 jmc 1.21 I iMin, iMax, jMin, jMax,
388 heimbach 1.31 I iceFlag, hSnow1, Tsf,
389 heimbach 1.30 O flx0exSW, dFlxdT, evap00, dEvdT,
390 jmc 1.21 I myTime, myIter, myThid )
391 heimbach 1.31 C--- end if: IF ( useEXF ) THEN
392 jmc 1.21 ENDIF
393 heimbach 1.31 C--- end if: IF ( useBlkFlx .AND. iterate4Tsf ) THEN
394 jmc 1.21 ENDIF
395 heimbach 1.31 #endif
396 jmc 1.20
397 heimbach 1.24 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|
398 jmc 1.21 C--- Compute new surface and internal temperatures; iterate until
399     C Tsfc converges.
400     DO j = jMin, jMax
401     DO i = iMin, iMax
402 heimbach 1.31 Tsf(i,j) = tSrf1(i,j)
403     dTsrf1(i,j) = Terrmax
404 jmc 1.21 ENDDO
405     ENDDO
406 jmc 1.6 IF ( useBlkFlx ) THEN
407     iterMax = nitMaxTsf
408     ELSE
409     iterMax = 1
410     ENDIF
411    
412 heimbach 1.24 #ifdef ALLOW_AUTODIFF_TAMC
413 gforget 1.29 CADJ STORE devdt(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
414     CADJ STORE dflxdt(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
415     CADJ STORE flx0exsw(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
416     CADJ STORE flxtexsw(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
417 jmc 1.36 CADJ STORE evap00(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
418     CADJ STORE evapt(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
419 heimbach 1.24 #endif
420    
421 jmc 1.1 C ----- begin iteration -----
422 jmc 1.6 DO k = 1,iterMax
423 heimbach 1.31 #ifndef ALLOW_AUTODIFF
424 jmc 1.21 IF ( iterate4Tsf ) THEN
425     iterate4Tsf = .FALSE.
426 heimbach 1.31 C
427     IF ( useBlkFlx ) THEN
428     #else
429     kkey = (ticekey-1)*MaxTsf + k
430     CADJ STORE iceflag = comlev1_thsice_s4t, key=kkey, byte=isbyte
431 heimbach 1.35 CADJ STORE hSnow1 = comlev1_thsice_s4t, key=kkey, byte=isbyte
432     CADJ STORE tsf = comlev1_thsice_s4t, key=kkey, byte=isbyte
433     CADJ STORE dEvdT = comlev1_thsice_s4t, key=kkey, byte=isbyte
434 heimbach 1.31 #endif /* ALLOW_AUTODIFF */
435    
436 jmc 1.21 C-- Compute top surface flux.
437 heimbach 1.31 #ifndef ALLOW_AUTODIFF
438 jmc 1.20 IF ( useEXF ) THEN
439 heimbach 1.31 #endif
440 heimbach 1.35 CALL THSICE_GET_EXF( bi, bj, k+1,
441 jmc 1.21 I iMin, iMax, jMin, jMax,
442 heimbach 1.31 I iceFlag, hSnow1, Tsf,
443 jmc 1.21 O flxTexSW, dFlxdT, evapT, dEvdT,
444     I myTime, myIter, myThid )
445     C- could add this "ifdef" to hide THSICE_GET_BULKF from TAF
446 jmc 1.32 #ifndef ALLOW_AUTODIFF
447 jmc 1.20 ELSEIF ( useBulkForce ) THEN
448 heimbach 1.24 CALL THSICE_GET_BULKF( bi, bj,
449 jmc 1.21 I iMin, iMax, jMin, jMax,
450 heimbach 1.31 I iceFlag, hSnow1, Tsf,
451 jmc 1.21 O flxTexSW, dFlxdT, evapT, dEvdT,
452     I myTime, myIter, myThid )
453 heimbach 1.31 C--- end if: IF ( useEXF ) THEN
454 mlosch 1.9 ENDIF
455 jmc 1.21 ELSE
456     DO j = jMin, jMax
457     DO i = iMin, iMax
458 heimbach 1.31 IF ( iceFlag(i,j).GT.0. _d 0 ) THEN
459 jmc 1.21 flxTexSW(i,j) = flxExSW(i,j,1)
460     dFlxdT(i,j) = flxExSW(i,j,2)
461     ENDIF
462     ENDDO
463     ENDDO
464 heimbach 1.31 C--- end if: IF ( useBlkFlx ) THEN
465 jmc 1.21 ENDIF
466 heimbach 1.31 #endif /* ALLOW_AUTODIFF */
467 jmc 1.21
468 heimbach 1.23 #ifdef ALLOW_AUTODIFF_TAMC
469 gforget 1.29 CADJ STORE devdt(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
470     CADJ STORE dflxdt(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
471     CADJ STORE flxtexsw(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
472     CADJ STORE iceflag(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
473     CADJ STORE tsf(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
474 heimbach 1.23 #endif
475    
476 jmc 1.21 C-- Compute new top layer and surface temperatures.
477     C If Tsfc is computed to be > 0 C, fix Tsfc = 0 and recompute T1
478     C with different coefficients.
479     DO j = jMin, jMax
480     DO i = iMin, iMax
481 heimbach 1.31 IF ( iceFlag(i,j).GT.0. _d 0 ) THEN
482 jmc 1.21 flxNet = sHeat(i,j) + flxTexSW(i,j)
483 jmc 1.8 #ifdef ALLOW_DBUG_THSICE
484 jmc 1.27 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,1020)
485 jmc 1.21 & 'ThSI_SOLVE4T: flxNet,dFlxdT,k12,D=',
486     & flxNet, dFlxdT(i,j), k12(i,j), k12(i,j)-dFlxdT(i,j)
487 jmc 1.8 #endif
488 jmc 1.1
489 jmc 1.21 a1 = a10(i,j) - k12(i,j)*dFlxdT(i,j) / (k12(i,j)-dFlxdT(i,j))
490     b1 = b10(i,j) - k12(i,j)*(flxNet-dFlxdT(i,j)*Tsf(i,j))
491     & /(k12(i,j)-dFlxdT(i,j))
492     c1 = c10(i,j)
493     tIc1(i,j) = -(b1 + SQRT(b1*b1-4. _d 0*a1*c1))/(2. _d 0*a1)
494 heimbach 1.31 dTsrf1(i,j) = (flxNet + k12(i,j)*(tIc1(i,j)-Tsf(i,j)))
495 jmc 1.21 & /(k12(i,j)-dFlxdT(i,j))
496 heimbach 1.31 Tsf(i,j) = Tsf(i,j) + dTsrf1(i,j)
497     C
498 jmc 1.21 IF ( Tsf(i,j) .GT. 0. _d 0 ) THEN
499 jmc 1.8 #ifdef ALLOW_DBUG_THSICE
500 jmc 1.27 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,1010)
501 heimbach 1.31 & 'ThSI_SOLVE4T: k,ts,t1,dTs=',k,Tsf(i,j),tIc1(i,j),dTsrf1(i,j)
502 jmc 1.8 #endif
503 jmc 1.21 a1 = a10(i,j) + k12(i,j)
504 jmc 1.18 C note: b1 = b10 - k12*Tf0
505 jmc 1.21 b1 = b10(i,j)
506     tIc1(i,j) = (-b1 - SQRT(b1*b1-4. _d 0*a1*c1))/(2. _d 0*a1)
507     Tsf(i,j) = 0. _d 0
508 heimbach 1.31 #ifndef ALLOW_AUTODIFF
509 jmc 1.1 IF ( useBlkFlx ) THEN
510 heimbach 1.31 #endif /* ALLOW_AUTODIFF */
511 jmc 1.21 flxTexSW(i,j) = flx0exSW(i,j)
512 heimbach 1.30 evapT(i,j) = evap00(i,j)
513 heimbach 1.31 dTsrf1(i,j) = 0. _d 0
514     #ifndef ALLOW_AUTODIFF
515 jmc 1.1 ELSE
516 jmc 1.21 flxTexSW(i,j) = flxExSW(i,j,0)
517 heimbach 1.31 dTsrf1(i,j) = 1000.
518 jmc 1.21 dFlxdT(i,j) = 0.
519 jmc 1.1 ENDIF
520 heimbach 1.31 #endif /* ALLOW_AUTODIFF */
521 jmc 1.21 ENDIF
522 jmc 1.1
523 jmc 1.21 C-- Check for convergence. If no convergence, then repeat.
524 heimbach 1.31 IF (ABS(dTsrf1(i,j)).GE.Terrmax) THEN
525     iceFlag(i,j) = 1. _d 0
526     ELSE
527     iceFlag(i,j) = 0. _d 0
528 jmc 1.32 ENDIF
529 heimbach 1.31 iterate4Tsf = iterate4Tsf .OR. (iceFlag(i,j).GT.0. _d 0)
530 jmc 1.21
531     C Convergence test: Make sure Tsfc has converged, within prescribed error.
532     C (Energy conservation is guaranteed within machine roundoff, even
533     C if Tsfc has not converged.)
534     C If no convergence, then repeat.
535 jmc 1.1
536 jmc 1.8 #ifdef ALLOW_DBUG_THSICE
537 jmc 1.27 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,1010)
538 heimbach 1.31 & 'ThSI_SOLVE4T: k,ts,t1,dTs=', k,Tsf(i,j),tIc1(i,j),dTsrf1(i,j)
539 jmc 1.32 IF ( useBlkFlx .AND. k.EQ.nitMaxTsf .AND.
540 heimbach 1.31 & (iceFlag(i,j).GT.0. _d 0) ) THEN
541 jmc 1.27 WRITE(stdUnit,'(A,4I4,I12,F15.9)')
542 jmc 1.21 & ' BB: not converge: i,j,it,hi=',i,j,bi,bj,myIter,hIce(i,j)
543 jmc 1.27 WRITE(stdUnit,*)
544 heimbach 1.31 & 'BB: not converge: Tsf, dTsf=', Tsf(i,j), dTsrf1(i,j)
545 jmc 1.27 WRITE(stdUnit,*)
546     & 'BB: not converge: flxNet,dFlxT=', flxNet, dFlxdT(i,j)
547     IF ( Tsf(i,j).LT.-70. _d 0 ) THEN
548     WRITE( msgBuf, '(A,2I4,2I3,I10,F12.3)')
549     & 'THSICE_SOLVE4TEMP: Too low Tsf in', i, j, bi, bj,
550     & myIter, Tsf(i,j)
551     CALL PRINT_ERROR( msgBuf , myThid )
552     STOP 'ABNORMAL END: S/R THSICE_SOLVE4TEMP'
553     ENDIF
554 jmc 1.21 ENDIF
555 jmc 1.32 #endif /* ALLOW_DBUG_THSICE */
556 jmc 1.21
557 jmc 1.1 ENDIF
558 jmc 1.21 ENDDO
559     ENDDO
560 heimbach 1.31 #ifndef ALLOW_AUTODIFF
561     C--- end if: IF ( iterate4Tsf ) THEN
562 jmc 1.6 ENDIF
563 heimbach 1.31 #endif /* ALLOW_AUTODIFF */
564     C--- end loop DO k = 1,iterMax
565 jmc 1.6 ENDDO
566 jmc 1.1 C ------ end iteration ------------
567    
568 heimbach 1.24 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|
569 jmc 1.21
570     DO j = jMin, jMax
571     DO i = iMin, iMax
572 heimbach 1.31 IF ( icMask(i,j).GT.0. _d 0 ) THEN
573 jmc 1.1
574 jmc 1.21 C-- Compute new bottom layer temperature.
575     k32 = 2. _d 0*kIce / hIce(i,j)
576     tIc2(i,j) = ( 2. _d 0*dt*k32*(tIc1(i,j)+2. _d 0*tFrz(i,j))
577     & + rhoi*cpIce*hIce(i,j)*tIc2(i,j))
578     & /(6. _d 0*dt*k32 + rhoi*cpIce*hIce(i,j))
579 jmc 1.8 #ifdef ALLOW_DBUG_THSICE
580 jmc 1.27 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,1010)
581 jmc 1.21 & 'ThSI_SOLVE4T: k, Ts, Tice=',k,Tsf(i,j),tIc1(i,j),tIc2(i,j)
582     netSW = flxAtm(i,j)
583 jmc 1.8 #endif
584 jmc 1.1
585 jmc 1.21 C-- Compute final flux values at surfaces.
586 heimbach 1.31 tSrf1(i,j) = Tsf(i,j)
587 jmc 1.21 fct = k12(i,j)*(Tsf(i,j)-tIc1(i,j))
588     flxCnB(i,j) = 4. _d 0*kIce *(tIc2(i,j)-tFrz(i,j))/hIce(i,j)
589     flxNet = sHeat(i,j) + flxTexSW(i,j)
590 heimbach 1.31 flxNet = flxNet + dFlxdT(i,j)*dTsrf1(i,j)
591     #ifndef ALLOW_AUTODIFF
592 jmc 1.21 IF ( useBlkFlx ) THEN
593 heimbach 1.31 #endif
594 jmc 1.21 C- needs to update also Evap (Tsf changes) since Latent heat has been updated
595 heimbach 1.31 evpAtm(i,j) = evapT(i,j) + dEvdT(i,j)*dTsrf1(i,j)
596     #ifndef ALLOW_AUTODIFF
597 jmc 1.21 ELSE
598 jmc 1.7 C- WARNING: Evap & +Evap*Lfresh are missing ! (but only affects Diagnostics)
599 jmc 1.21 evpAtm(i,j) = 0.
600     ENDIF
601 heimbach 1.31 #endif
602 jmc 1.21 C- Update energy flux to Atmos with other than SW contributions;
603 jmc 1.7 C use latent heat = Lvap (energy=0 for liq. water at 0.oC)
604 jmc 1.21 flxAtm(i,j) = flxAtm(i,j) + flxTexSW(i,j)
605 heimbach 1.31 & + dFlxdT(i,j)*dTsrf1(i,j) + evpAtm(i,j)*Lfresh
606 jmc 1.7 C- excess of energy @ surface (used for surface melting):
607 jmc 1.21 sHeat(i,j) = flxNet - fct
608 jmc 1.1
609 jmc 1.8 #ifdef ALLOW_DBUG_THSICE
610 jmc 1.27 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,1020)
611 jmc 1.21 & 'ThSI_SOLVE4T: flxNet,fct,Dif,flxCnB=',
612     & flxNet,fct,flxNet-fct,flxCnB(i,j)
613 jmc 1.8 #endif
614 jmc 1.1
615 jmc 1.21 C-- Compute new enthalpy for each layer.
616     qIc1(i,j) = -cpWater*Tmlt1 + cpIce *(Tmlt1-tIc1(i,j))
617     & + Lfresh*(1. _d 0-Tmlt1/tIc1(i,j))
618     qIc2(i,j) = -cpIce *tIc2(i,j) + Lfresh
619    
620 mlosch 1.22 #ifdef ALLOW_DBUG_THSICE
621 jmc 1.21 C-- Make sure internal ice temperatures do not exceed Tmlt.
622     C (This should not happen for reasonable values of i0swFrac)
623     IF (tIc1(i,j) .GE. Tmlt1) THEN
624 jmc 1.27 WRITE(stdUnit,'(A,2I4,2I3,1P2E14.6)')
625 jmc 1.21 & ' BBerr - Bug: IceT(1) > Tmlt',i,j,bi,bj,tIc1(i,j),Tmlt1
626     ENDIF
627     IF (tIc2(i,j) .GE. 0. _d 0) THEN
628 jmc 1.27 WRITE(stdUnit,'(A,2I4,2I3,1P2E14.6)')
629 jmc 1.21 & ' BBerr - Bug: IceT(2) > 0',i,j,bi,bj,tIc2(i,j)
630     ENDIF
631 jmc 1.1
632 jmc 1.8 IF ( dBug(i,j,bi,bj) ) THEN
633 jmc 1.27 WRITE(stdUnit,1020) 'ThSI_SOLV_4T: Tsf, Tice(1,2), dTsurf=',
634 heimbach 1.31 & Tsf(i,j), tIc1(i,j), tIc2(i,j), dTsrf1(i,j)
635 jmc 1.27 WRITE(stdUnit,1020) 'ThSI_SOLV_4T: sHeat, flxCndBt, Qice =',
636 jmc 1.21 & sHeat(i,j), flxCnB(i,j), qIc1(i,j), qIc2(i,j)
637 jmc 1.27 WRITE(stdUnit,1020) 'ThSI_SOLV_4T: flxA, evpA, fxSW_bf,af=',
638 jmc 1.8 & flxAtm(i,j), evpAtm(i,j), netSW, flxSW(i,j)
639     ENDIF
640     #endif
641 jmc 1.21
642 jmc 1.8 ELSE
643 jmc 1.21 C-- ice-free grid point:
644     c tIc1 (i,j) = 0. _d 0
645     c tIc2 (i,j) = 0. _d 0
646 heimbach 1.31 dTsrf1(i,j) = 0. _d 0
647 jmc 1.21 c sHeat (i,j) = 0. _d 0
648     c flxCnB(i,j) = 0. _d 0
649     c flxAtm(i,j) = 0. _d 0
650     c evpAtm(i,j) = 0. _d 0
651    
652 jmc 1.8 ENDIF
653     ENDDO
654     ENDDO
655 jmc 1.1 #endif /* ALLOW_THSICE */
656    
657 heimbach 1.24 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|
658 jmc 1.1
659     RETURN
660     END

  ViewVC Help
Powered by ViewVC 1.1.22