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

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

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


Revision 1.4 - (hide annotations) (download)
Sun Jun 25 22:22:38 2006 UTC (17 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58q_post, checkpoint58o_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58m_post
Changes since 1.3: +8 -5 lines
do not update exf flux array (to keep ice-free ocean fluxes valid)

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_get_exf.F,v 1.3 2006/06/06 22:27:18 jmc Exp $
2 mlosch 1.1 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 jmc 1.3 I iceornot, tsfCel,
14 mlosch 1.1 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 jmc 1.3 C tsfCel :: surface (ice or snow) temperature (oC)
41 mlosch 1.1 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 jmc 1.3 _RL tsfCel
51 mlosch 1.1 _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 jmc 1.4 C hsLocal, hlLocal :: sensible & latent heat flux over sea-ice
63 mlosch 1.1
64     _RL aln
65    
66 jmc 1.4 _RL hsLocal, hlLocal
67 mlosch 1.1 integer iter
68     _RL delq
69     _RL deltap
70     _RL hqol
71     _RL htol
72     _RL huol
73     _RL psimh
74     _RL psixh
75     _RL qstar
76     _RL rd
77     _RL re
78     _RL rdn
79     _RL rh
80     _RL ssq
81     _RL stable
82     _RL tstar
83     _RL t0
84     _RL ustar
85     _RL uzn
86     _RL shn
87     _RL xsq
88     _RL x
89     _RL tau
90     _RL tmpbulk
91    
92     C additional variables that are copied from bulkf_formula_lay:
93     C upward LW at surface (W m-2)
94     _RL flwup
95     C net (downward) LW at surface (W m-2)
96     _RL flwNet_dwn
97 jmc 1.3 C gradients of latent/sensible net upward heat flux
98 mlosch 1.1 C w/ respect to temperature
99     _RL dflhdT, dfshdT, dflwupdT
100     C emissivities, called emittance in exf
101     _RL emiss
102 jmc 1.3 C Tsf :: surface temperature [K]
103     C Ts2 :: surface temperature square [K^2]
104     _RL Tsf
105 mlosch 1.1 _RL Ts2
106 jmc 1.3 C latent heat of evaporation or sublimation [J/kg]
107     _RL lath
108 mlosch 1.1
109 jmc 1.3 C == external functions ==
110 mlosch 1.1
111 jmc 1.3 c _RL exf_BulkqSat
112     c external exf_BulkqSat
113 mlosch 1.1 _RL exf_BulkCdn
114     external exf_BulkCdn
115     _RL exf_BulkRhn
116     external exf_BulkRhn
117    
118 jmc 1.3 C == end of interface ==
119 mlosch 1.1
120     C copy a few variables to names used in bulkf_formula_lay
121 jmc 1.3 Tsf = tsfCel+cen2kel
122     Ts2 = Tsf*Tsf
123     IF ( iceornot.EQ.0 ) THEN
124     lath = flamb
125     dEvdT = cvapor_exp
126     ELSE
127     lath = flamb+flami
128     dEvdT = cvapor_exp_ice
129     ENDIF
130 mlosch 1.1
131 jmc 1.3 Cph This statement cannot be a PARAMETER statement in the header,
132     Cph but must come here; it is not fortran77 standard
133 mlosch 1.1 aln = log(ht/zref)
134    
135 jmc 1.3 C-- Use atmospheric state to compute surface fluxes.
136 mlosch 1.1
137 jmc 1.3 C-- Compute the turbulent surface fluxes.
138 mlosch 1.1
139 jmc 1.3 C Initial guess: z/l=0.0; hu=ht=hq=z
140     C Iterations: converge on z/l and hence the fluxes.
141     C t0 : virtual temperature (K)
142     C ssq : sea surface humidity (kg/kg)
143     C deltap : potential temperature diff (K)
144 mlosch 1.1
145     if ( atemp(i,j,bi,bj) .ne. 0. _d 0 ) then
146     t0 = atemp(i,j,bi,bj)*
147     & (exf_one + humid_fac*aqh(i,j,bi,bj))
148 jmc 1.3 c tmpbulk= exf_BulkqSat(Tsf)
149     c ssq = saltsat*tmpbulk/atmrho
150     tmpbulk = cvapor_fac_ice/exp(cvapor_exp_ice/Tsf)
151     ssq = tmpbulk/atmrho
152     deltap = atemp(i,j,bi,bj) + gamma_blk*ht - Tsf
153 mlosch 1.1 delq = aqh(i,j,bi,bj) - ssq
154     stable = exf_half + sign(exf_half, deltap)
155     tmpbulk= exf_BulkCdn(sh(i,j,bi,bj))
156     rdn = sqrt(tmpbulk)
157     ustar = rdn*sh(i,j,bi,bj)
158     tmpbulk= exf_BulkRhn(stable)
159 jmc 1.3 tstar = tmpbulk*deltap
160     qstar = cdalton*delq
161 mlosch 1.1
162     do iter = 1,niter_bulk
163    
164     huol = czol*(tstar/t0 +
165     & qstar/(exf_one/humid_fac+aqh(i,j,bi,bj)))/
166     & ustar**2
167     huol = max(huol,zolmin)
168     stable = exf_half + sign(exf_half, huol)
169     htol = huol*ht/hu
170     hqol = huol*hq/hu
171 jmc 1.3
172     C Evaluate all stability functions assuming hq = ht.
173 mlosch 1.1 xsq = max(sqrt(abs(exf_one - 16.*huol)),exf_one)
174     x = sqrt(xsq)
175     psimh = -psim_fac*huol*stable +
176     & (exf_one - stable)*
177     & (log((exf_one + x*(exf_two + x))*
178     & (exf_one + xsq)/8.) - exf_two*atan(x) +
179     & pi*exf_half)
180     xsq = max(sqrt(abs(exf_one - 16.*htol)),exf_one)
181     psixh = -psim_fac*htol*stable + (exf_one - stable)*
182     & exf_two*log((exf_one + xsq)/exf_two)
183 jmc 1.3
184     C Shift wind speed using old coefficient
185 mlosch 1.1 ccc rd = rdn/(exf_one + rdn/karman*
186     ccc & (log(hu/zref) - psimh) )
187     rd = rdn/(exf_one - rdn/karman*psimh )
188     shn = sh(i,j,bi,bj)*rd/rdn
189     uzn = max(shn, umin)
190 jmc 1.3
191     C Update the transfer coefficients at 10 meters
192     C and neutral stability.
193    
194 mlosch 1.1 tmpbulk= exf_BulkCdn(uzn)
195     rdn = sqrt(tmpbulk)
196 jmc 1.3
197     C Shift all coefficients to the measurement height
198     C and stability.
199 mlosch 1.1 c rd = rdn/(exf_one + rdn/karman*(log(hu/zref) - psimh))
200     rd = rdn/(exf_one - rdn/karman*psimh)
201     tmpbulk= exf_BulkRhn(stable)
202 jmc 1.3 rh = tmpbulk/( exf_one +
203 mlosch 1.1 & tmpbulk/karman*(aln - psixh) )
204 jmc 1.3 re = cdalton/( exf_one +
205 mlosch 1.1 & cdalton/karman*(aln - psixh) )
206 jmc 1.3
207     C Update ustar, tstar, qstar using updated, shifted
208     C coefficients.
209 mlosch 1.1 ustar = rd*sh(i,j,bi,bj)
210 jmc 1.3 qstar = re*delq
211 mlosch 1.1 tstar = rh*deltap
212     enddo
213    
214 jmc 1.3 tau = atmrho*ustar**2
215     tau = tau*us(i,j,bi,bj)/sh(i,j,bi,bj)
216 mlosch 1.1
217 jmc 1.3 evapLoc = -tau*qstar/ustar
218 jmc 1.4 hlLocal = -lath*evapLoc
219     hsLocal = atmcp*tau*tstar/ustar
220 mlosch 1.1 #ifndef EXF_READ_EVAP
221     cdm evap(i,j,bi,bj) = tau*qstar/ustar
222     cdm !!! need to change sign and to convert from kg/m^2/s to m/s !!!
223 jmc 1.4 C jmc: do not reset evap which contains evaporation over ice-free ocean fraction
224     c evap(i,j,bi,bj) = -recip_rhonil*evapLoc
225 mlosch 1.1 #endif
226    
227     C--- surf.Temp derivative of turbulent Fluxes
228 jmc 1.3 dEvdT = (tau*re/ustar)*ssq*dEvdT/Ts2
229 mlosch 1.1 dflhdT = -lath*dEvdT
230 jmc 1.3 dfshdT = -atmcp*tau*rh/ustar
231 mlosch 1.1
232     C--- Upward long wave radiation
233     IF ( iceornot.EQ.0 ) THEN
234     emiss = ocean_emissivity
235     ELSEIF (iceornot.EQ.2) THEN
236     emiss = snow_emissivity
237     ELSE
238     emiss = ice_emissivity
239     ENDIF
240     flwup = emiss*stefanBoltzmann*Ts2*Ts2
241 jmc 1.3 dflwupdT = emiss*stefanBoltzmann*Ts2*Tsf * 4. _d 0
242    
243 mlosch 1.1 C-- Total derivative with respect to surface temperature
244     df0dT = -dflwupdT+dfshdT+dflhdT
245 jmc 1.3
246 mlosch 1.1 flwNet_dwn = lwdown(i,j,bi,bj) - flwup
247 jmc 1.4 flxExceptSw = flwNet_dwn + hsLocal + hlLocal
248 mlosch 1.1
249     endif
250    
251     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
252    
253     #endif /* ALLOW_EXF */
254     #endif /* ALLOW_THSICE */
255    
256     RETURN
257     END

  ViewVC Help
Powered by ViewVC 1.1.22