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

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

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


Revision 1.3 - (show annotations) (download)
Tue Jun 6 22:27:18 2006 UTC (18 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58h_post, checkpoint58j_post, checkpoint58i_post, checkpoint58g_post
Changes since 1.2: +67 -178 lines
use coeff & formulae specific to ice & snow.

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_get_exf.F,v 1.2 2006/06/06 18:52:13 mlosch Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5 #ifdef ALLOW_EXF
6 #include "EXF_OPTIONS.h"
7 #endif
8
9 CBOP
10 C !ROUTINE: THSICE_GET_EXF
11 C !INTERFACE:
12 SUBROUTINE THSICE_GET_EXF(
13 I iceornot, tsfCel,
14 O flxExceptSw, df0dT, evapLoc, dEvdT,
15 I i,j,bi,bj,myThid )
16 C !DESCRIPTION: \bv
17 C *==========================================================*
18 C | S/R THSICE_GET_EXF
19 C *==========================================================*
20 C | Interface S/R : get Surface Fluxes from pkg EXF
21 C *==========================================================*
22 C \ev
23
24 C !USES:
25 IMPLICIT NONE
26
27 C == Global data ==
28 #ifdef ALLOW_EXF
29 # include "SIZE.h"
30 # include "EEPARAMS.h"
31 # include "PARAMS.h"
32 # include "exf_constants.h"
33 # include "exf_param.h"
34 # include "exf_fields.h"
35 #endif
36
37 C !INPUT/OUTPUT PARAMETERS:
38 C === Routine arguments ===
39 C iceornot :: 0=open water, 1=ice cover
40 C tsfCel :: surface (ice or snow) temperature (oC)
41 C flxExceptSw :: net (downward) surface heat flux, except short-wave [W/m2]
42 C df0dT :: deriv of flx with respect to Tsf [W/m/K]
43 C evapLoc :: surface evaporation (>0 if evaporate) [kg/m2/s]
44 C dEvdT :: deriv of evap. with respect to Tsf [kg/m2/s/K]
45 C i,j, bi,bj :: current grid point indices
46 C myThid :: Thread no. that called this routine.
47 INTEGER i,j, bi,bj
48 INTEGER myThid
49 INTEGER iceornot
50 _RL tsfCel
51 _RL flxExceptSw
52 _RL df0dT
53 _RL evapLoc
54 _RL dEvdT
55 CEOP
56
57 #ifdef ALLOW_THSICE
58 #ifdef ALLOW_EXF
59
60 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
61 C === Local variables ===
62
63 _RL aln
64
65 integer iter
66 _RL delq
67 _RL deltap
68 _RL hqol
69 _RL htol
70 _RL huol
71 _RL psimh
72 _RL psixh
73 _RL qstar
74 _RL rd
75 _RL re
76 _RL rdn
77 _RL rh
78 _RL ssq
79 _RL stable
80 _RL tstar
81 _RL t0
82 _RL ustar
83 _RL uzn
84 _RL shn
85 _RL xsq
86 _RL x
87 _RL tau
88 _RL tmpbulk
89
90 C additional variables that are copied from bulkf_formula_lay:
91 C upward LW at surface (W m-2)
92 _RL flwup
93 C net (downward) LW at surface (W m-2)
94 _RL flwNet_dwn
95 C gradients of latent/sensible net upward heat flux
96 C w/ respect to temperature
97 _RL dflhdT, dfshdT, dflwupdT
98 C emissivities, called emittance in exf
99 _RL emiss
100 C Tsf :: surface temperature [K]
101 C Ts2 :: surface temperature square [K^2]
102 _RL Tsf
103 _RL Ts2
104 C latent heat of evaporation or sublimation [J/kg]
105 _RL lath
106
107 C == external functions ==
108
109 c _RL exf_BulkqSat
110 c external exf_BulkqSat
111 _RL exf_BulkCdn
112 external exf_BulkCdn
113 _RL exf_BulkRhn
114 external exf_BulkRhn
115
116 C == end of interface ==
117
118 C copy a few variables to names used in bulkf_formula_lay
119 Tsf = tsfCel+cen2kel
120 Ts2 = Tsf*Tsf
121 IF ( iceornot.EQ.0 ) THEN
122 lath = flamb
123 dEvdT = cvapor_exp
124 ELSE
125 lath = flamb+flami
126 dEvdT = cvapor_exp_ice
127 ENDIF
128
129 Cph This statement cannot be a PARAMETER statement in the header,
130 Cph but must come here; it is not fortran77 standard
131 aln = log(ht/zref)
132
133 C-- Use atmospheric state to compute surface fluxes.
134
135 C-- Compute the turbulent surface fluxes.
136
137 C Initial guess: z/l=0.0; hu=ht=hq=z
138 C Iterations: converge on z/l and hence the fluxes.
139 C t0 : virtual temperature (K)
140 C ssq : sea surface humidity (kg/kg)
141 C deltap : potential temperature diff (K)
142
143 if ( atemp(i,j,bi,bj) .ne. 0. _d 0 ) then
144 t0 = atemp(i,j,bi,bj)*
145 & (exf_one + humid_fac*aqh(i,j,bi,bj))
146 c tmpbulk= exf_BulkqSat(Tsf)
147 c ssq = saltsat*tmpbulk/atmrho
148 tmpbulk = cvapor_fac_ice/exp(cvapor_exp_ice/Tsf)
149 ssq = tmpbulk/atmrho
150 deltap = atemp(i,j,bi,bj) + gamma_blk*ht - Tsf
151 delq = aqh(i,j,bi,bj) - ssq
152 stable = exf_half + sign(exf_half, deltap)
153 tmpbulk= exf_BulkCdn(sh(i,j,bi,bj))
154 rdn = sqrt(tmpbulk)
155 ustar = rdn*sh(i,j,bi,bj)
156 tmpbulk= exf_BulkRhn(stable)
157 tstar = tmpbulk*deltap
158 qstar = cdalton*delq
159
160 do iter = 1,niter_bulk
161
162 huol = czol*(tstar/t0 +
163 & qstar/(exf_one/humid_fac+aqh(i,j,bi,bj)))/
164 & ustar**2
165 huol = max(huol,zolmin)
166 stable = exf_half + sign(exf_half, huol)
167 htol = huol*ht/hu
168 hqol = huol*hq/hu
169
170 C Evaluate all stability functions assuming hq = ht.
171 xsq = max(sqrt(abs(exf_one - 16.*huol)),exf_one)
172 x = sqrt(xsq)
173 psimh = -psim_fac*huol*stable +
174 & (exf_one - stable)*
175 & (log((exf_one + x*(exf_two + x))*
176 & (exf_one + xsq)/8.) - exf_two*atan(x) +
177 & pi*exf_half)
178 xsq = max(sqrt(abs(exf_one - 16.*htol)),exf_one)
179 psixh = -psim_fac*htol*stable + (exf_one - stable)*
180 & exf_two*log((exf_one + xsq)/exf_two)
181
182 C Shift wind speed using old coefficient
183 ccc rd = rdn/(exf_one + rdn/karman*
184 ccc & (log(hu/zref) - psimh) )
185 rd = rdn/(exf_one - rdn/karman*psimh )
186 shn = sh(i,j,bi,bj)*rd/rdn
187 uzn = max(shn, umin)
188
189 C Update the transfer coefficients at 10 meters
190 C and neutral stability.
191
192 tmpbulk= exf_BulkCdn(uzn)
193 rdn = sqrt(tmpbulk)
194
195 C Shift all coefficients to the measurement height
196 C and stability.
197 c rd = rdn/(exf_one + rdn/karman*(log(hu/zref) - psimh))
198 rd = rdn/(exf_one - rdn/karman*psimh)
199 tmpbulk= exf_BulkRhn(stable)
200 rh = tmpbulk/( exf_one +
201 & tmpbulk/karman*(aln - psixh) )
202 re = cdalton/( exf_one +
203 & cdalton/karman*(aln - psixh) )
204
205 C Update ustar, tstar, qstar using updated, shifted
206 C coefficients.
207 ustar = rd*sh(i,j,bi,bj)
208 qstar = re*delq
209 tstar = rh*deltap
210 enddo
211
212 tau = atmrho*ustar**2
213 tau = tau*us(i,j,bi,bj)/sh(i,j,bi,bj)
214
215 evapLoc = -tau*qstar/ustar
216 hl(i,j,bi,bj) = -lath*evapLoc
217 hs(i,j,bi,bj) = atmcp*tau*tstar/ustar
218 #ifndef EXF_READ_EVAP
219 cdm evap(i,j,bi,bj) = tau*qstar/ustar
220 cdm !!! need to change sign and to convert from kg/m^2/s to m/s !!!
221 evap(i,j,bi,bj) = -recip_rhonil*evapLoc
222 #endif
223
224 C--- surf.Temp derivative of turbulent Fluxes
225 dEvdT = (tau*re/ustar)*ssq*dEvdT/Ts2
226 dflhdT = -lath*dEvdT
227 dfshdT = -atmcp*tau*rh/ustar
228
229 C--- Upward long wave radiation
230 IF ( iceornot.EQ.0 ) THEN
231 emiss = ocean_emissivity
232 ELSEIF (iceornot.EQ.2) THEN
233 emiss = snow_emissivity
234 ELSE
235 emiss = ice_emissivity
236 ENDIF
237 flwup = emiss*stefanBoltzmann*Ts2*Ts2
238 dflwupdT = emiss*stefanBoltzmann*Ts2*Tsf * 4. _d 0
239
240 C-- Total derivative with respect to surface temperature
241 df0dT = -dflwupdT+dfshdT+dflhdT
242
243 flwNet_dwn = lwdown(i,j,bi,bj) - flwup
244 flxExceptSw = flwNet_dwn + hs(i,j,bi,bj) + hl(i,j,bi,bj)
245
246 endif
247
248 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
249
250 #endif /* ALLOW_EXF */
251 #endif /* ALLOW_THSICE */
252
253 RETURN
254 END

  ViewVC Help
Powered by ViewVC 1.1.22