/[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.6 - (hide annotations) (download)
Tue Apr 17 23:42:33 2007 UTC (17 years, 1 month ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint59
Changes since 1.5: +45 -1 lines
2nd set of modifs for thsice adjoint.

1 heimbach 1.6 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_get_exf.F,v 1.5 2007/04/16 23:37:48 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 jmc 1.5 # include "EXF_CONSTANTS.h"
33     # include "EXF_PARAM.h"
34     # include "EXF_FIELDS.h"
35 mlosch 1.1 #endif
36 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
37     # include "tamc.h"
38     # include "tamc_keys.h"
39     #endif
40 mlosch 1.1
41     C !INPUT/OUTPUT PARAMETERS:
42     C === Routine arguments ===
43     C iceornot :: 0=open water, 1=ice cover
44 jmc 1.3 C tsfCel :: surface (ice or snow) temperature (oC)
45 mlosch 1.1 C flxExceptSw :: net (downward) surface heat flux, except short-wave [W/m2]
46     C df0dT :: deriv of flx with respect to Tsf [W/m/K]
47     C evapLoc :: surface evaporation (>0 if evaporate) [kg/m2/s]
48     C dEvdT :: deriv of evap. with respect to Tsf [kg/m2/s/K]
49     C i,j, bi,bj :: current grid point indices
50     C myThid :: Thread no. that called this routine.
51     INTEGER i,j, bi,bj
52     INTEGER myThid
53     INTEGER iceornot
54 jmc 1.3 _RL tsfCel
55 mlosch 1.1 _RL flxExceptSw
56     _RL df0dT
57     _RL evapLoc
58     _RL dEvdT
59     CEOP
60    
61     #ifdef ALLOW_THSICE
62     #ifdef ALLOW_EXF
63    
64     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
65     C === Local variables ===
66 jmc 1.4 C hsLocal, hlLocal :: sensible & latent heat flux over sea-ice
67 mlosch 1.1
68     _RL aln
69    
70 jmc 1.4 _RL hsLocal, hlLocal
71 mlosch 1.1 integer iter
72     _RL delq
73     _RL deltap
74     _RL hqol
75     _RL htol
76     _RL huol
77     _RL psimh
78     _RL psixh
79     _RL qstar
80     _RL rd
81     _RL re
82     _RL rdn
83     _RL rh
84     _RL ssq
85     _RL stable
86     _RL tstar
87     _RL t0
88     _RL ustar
89     _RL uzn
90     _RL shn
91     _RL xsq
92     _RL x
93     _RL tau
94     _RL tmpbulk
95    
96     C additional variables that are copied from bulkf_formula_lay:
97     C upward LW at surface (W m-2)
98     _RL flwup
99     C net (downward) LW at surface (W m-2)
100     _RL flwNet_dwn
101 jmc 1.3 C gradients of latent/sensible net upward heat flux
102 mlosch 1.1 C w/ respect to temperature
103     _RL dflhdT, dfshdT, dflwupdT
104     C emissivities, called emittance in exf
105     _RL emiss
106 jmc 1.3 C Tsf :: surface temperature [K]
107     C Ts2 :: surface temperature square [K^2]
108     _RL Tsf
109 mlosch 1.1 _RL Ts2
110 jmc 1.3 C latent heat of evaporation or sublimation [J/kg]
111     _RL lath
112 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
113     integer ikey_1
114     integer ikey_2
115     #endif
116 mlosch 1.1
117 jmc 1.3 C == external functions ==
118 mlosch 1.1
119 jmc 1.3 c _RL exf_BulkqSat
120     c external exf_BulkqSat
121 mlosch 1.1 _RL exf_BulkCdn
122     external exf_BulkCdn
123     _RL exf_BulkRhn
124     external exf_BulkRhn
125    
126 jmc 1.3 C == end of interface ==
127 mlosch 1.1
128 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
129     act1 = bi - myBxLo(myThid)
130     max1 = myBxHi(myThid) - myBxLo(myThid) + 1
131     act2 = bj - myByLo(myThid)
132     max2 = myByHi(myThid) - myByLo(myThid) + 1
133     act3 = myThid - 1
134     max3 = nTx*nTy
135     act4 = ikey_dynamics - 1
136    
137     ikey_1 = i
138     & + sNx*(j-1)
139     & + sNx*sNy*act1
140     & + sNx*sNy*max1*act2
141     & + sNx*sNy*max1*max2*act3
142     & + sNx*sNy*max1*max2*max3*act4
143     #endif
144    
145 mlosch 1.1 C copy a few variables to names used in bulkf_formula_lay
146 jmc 1.3 Tsf = tsfCel+cen2kel
147     Ts2 = Tsf*Tsf
148     IF ( iceornot.EQ.0 ) THEN
149     lath = flamb
150     dEvdT = cvapor_exp
151     ELSE
152     lath = flamb+flami
153     dEvdT = cvapor_exp_ice
154     ENDIF
155 mlosch 1.1
156 jmc 1.3 Cph This statement cannot be a PARAMETER statement in the header,
157     Cph but must come here; it is not fortran77 standard
158 mlosch 1.1 aln = log(ht/zref)
159    
160 jmc 1.3 C-- Use atmospheric state to compute surface fluxes.
161 mlosch 1.1
162 jmc 1.3 C-- Compute the turbulent surface fluxes.
163 mlosch 1.1
164 jmc 1.3 C Initial guess: z/l=0.0; hu=ht=hq=z
165     C Iterations: converge on z/l and hence the fluxes.
166     C t0 : virtual temperature (K)
167     C ssq : sea surface humidity (kg/kg)
168     C deltap : potential temperature diff (K)
169 mlosch 1.1
170     if ( atemp(i,j,bi,bj) .ne. 0. _d 0 ) then
171     t0 = atemp(i,j,bi,bj)*
172     & (exf_one + humid_fac*aqh(i,j,bi,bj))
173 jmc 1.3 c tmpbulk= exf_BulkqSat(Tsf)
174     c ssq = saltsat*tmpbulk/atmrho
175     tmpbulk = cvapor_fac_ice/exp(cvapor_exp_ice/Tsf)
176     ssq = tmpbulk/atmrho
177     deltap = atemp(i,j,bi,bj) + gamma_blk*ht - Tsf
178 mlosch 1.1 delq = aqh(i,j,bi,bj) - ssq
179     stable = exf_half + sign(exf_half, deltap)
180 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
181     CADJ STORE sh(i,j,bi,bj) = comlev1_exf_1, key = ikey_1
182     #endif
183 mlosch 1.1 tmpbulk= exf_BulkCdn(sh(i,j,bi,bj))
184     rdn = sqrt(tmpbulk)
185     ustar = rdn*sh(i,j,bi,bj)
186     tmpbulk= exf_BulkRhn(stable)
187 jmc 1.3 tstar = tmpbulk*deltap
188     qstar = cdalton*delq
189 mlosch 1.1
190     do iter = 1,niter_bulk
191    
192 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
193     ikey_2 = iter
194     & + niter_bulk*(i-1)
195     & + niter_bulk*sNx*(j-1)
196     & + niter_bulk*sNx*sNy*act1
197     & + niter_bulk*sNx*sNy*max1*act2
198     & + niter_bulk*sNx*sNy*max1*max2*act3
199     & + niter_bulk*sNx*sNy*max1*max2*max3*act4
200    
201     CADJ STORE rdn = comlev1_exf_2, key = ikey_2
202     CADJ STORE ustar = comlev1_exf_2, key = ikey_2
203     CADJ STORE qstar = comlev1_exf_2, key = ikey_2
204     CADJ STORE tstar = comlev1_exf_2, key = ikey_2
205     CADJ STORE sh(i,j,bi,bj) = comlev1_exf_2, key = ikey_2
206     #endif
207    
208 mlosch 1.1 huol = czol*(tstar/t0 +
209     & qstar/(exf_one/humid_fac+aqh(i,j,bi,bj)))/
210     & ustar**2
211     huol = max(huol,zolmin)
212     stable = exf_half + sign(exf_half, huol)
213     htol = huol*ht/hu
214     hqol = huol*hq/hu
215 jmc 1.3
216     C Evaluate all stability functions assuming hq = ht.
217 mlosch 1.1 xsq = max(sqrt(abs(exf_one - 16.*huol)),exf_one)
218     x = sqrt(xsq)
219     psimh = -psim_fac*huol*stable +
220     & (exf_one - stable)*
221     & (log((exf_one + x*(exf_two + x))*
222     & (exf_one + xsq)/8.) - exf_two*atan(x) +
223     & pi*exf_half)
224     xsq = max(sqrt(abs(exf_one - 16.*htol)),exf_one)
225     psixh = -psim_fac*htol*stable + (exf_one - stable)*
226     & exf_two*log((exf_one + xsq)/exf_two)
227 jmc 1.3
228     C Shift wind speed using old coefficient
229 mlosch 1.1 ccc rd = rdn/(exf_one + rdn/karman*
230     ccc & (log(hu/zref) - psimh) )
231     rd = rdn/(exf_one - rdn/karman*psimh )
232     shn = sh(i,j,bi,bj)*rd/rdn
233     uzn = max(shn, umin)
234 jmc 1.3
235     C Update the transfer coefficients at 10 meters
236     C and neutral stability.
237    
238 mlosch 1.1 tmpbulk= exf_BulkCdn(uzn)
239     rdn = sqrt(tmpbulk)
240 jmc 1.3
241     C Shift all coefficients to the measurement height
242     C and stability.
243 mlosch 1.1 c rd = rdn/(exf_one + rdn/karman*(log(hu/zref) - psimh))
244     rd = rdn/(exf_one - rdn/karman*psimh)
245     tmpbulk= exf_BulkRhn(stable)
246 jmc 1.3 rh = tmpbulk/( exf_one +
247 mlosch 1.1 & tmpbulk/karman*(aln - psixh) )
248 jmc 1.3 re = cdalton/( exf_one +
249 mlosch 1.1 & cdalton/karman*(aln - psixh) )
250 jmc 1.3
251     C Update ustar, tstar, qstar using updated, shifted
252     C coefficients.
253 mlosch 1.1 ustar = rd*sh(i,j,bi,bj)
254 jmc 1.3 qstar = re*delq
255 mlosch 1.1 tstar = rh*deltap
256     enddo
257    
258 jmc 1.3 tau = atmrho*ustar**2
259     tau = tau*us(i,j,bi,bj)/sh(i,j,bi,bj)
260 mlosch 1.1
261 jmc 1.3 evapLoc = -tau*qstar/ustar
262 jmc 1.4 hlLocal = -lath*evapLoc
263     hsLocal = atmcp*tau*tstar/ustar
264 mlosch 1.1 #ifndef EXF_READ_EVAP
265     cdm evap(i,j,bi,bj) = tau*qstar/ustar
266     cdm !!! need to change sign and to convert from kg/m^2/s to m/s !!!
267 jmc 1.4 C jmc: do not reset evap which contains evaporation over ice-free ocean fraction
268     c evap(i,j,bi,bj) = -recip_rhonil*evapLoc
269 mlosch 1.1 #endif
270    
271     C--- surf.Temp derivative of turbulent Fluxes
272 jmc 1.3 dEvdT = (tau*re/ustar)*ssq*dEvdT/Ts2
273 mlosch 1.1 dflhdT = -lath*dEvdT
274 jmc 1.3 dfshdT = -atmcp*tau*rh/ustar
275 mlosch 1.1
276     C--- Upward long wave radiation
277     IF ( iceornot.EQ.0 ) THEN
278     emiss = ocean_emissivity
279     ELSEIF (iceornot.EQ.2) THEN
280     emiss = snow_emissivity
281     ELSE
282     emiss = ice_emissivity
283     ENDIF
284     flwup = emiss*stefanBoltzmann*Ts2*Ts2
285 jmc 1.3 dflwupdT = emiss*stefanBoltzmann*Ts2*Tsf * 4. _d 0
286    
287 mlosch 1.1 C-- Total derivative with respect to surface temperature
288     df0dT = -dflwupdT+dfshdT+dflhdT
289 jmc 1.3
290 mlosch 1.1 flwNet_dwn = lwdown(i,j,bi,bj) - flwup
291 jmc 1.4 flxExceptSw = flwNet_dwn + hsLocal + hlLocal
292 mlosch 1.1
293     endif
294    
295     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
296    
297     #endif /* ALLOW_EXF */
298     #endif /* ALLOW_THSICE */
299    
300     RETURN
301     END

  ViewVC Help
Powered by ViewVC 1.1.22