/[lmdze]/trunk/phylmd/Interface_surf/interfsurf_hq.f
ViewVC logotype

Contents of /trunk/phylmd/Interface_surf/interfsurf_hq.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 116 - (show annotations)
Thu Dec 4 16:35:03 2014 UTC (9 years, 5 months ago) by guez
File size: 16339 byte(s)
In test_disvert, write output files before testing order of pressure
values, so we have more information if there is a problem.

1 module interfsurf_hq_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE interfsurf_hq(itime, dtime, jour, rmu0, nisurf, knon, knindex, &
8 pctsrf, rlat, debut, nsoilmx, tsoil, qsol, u1_lay, v1_lay, temp_air, &
9 spechum, tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
10 precip_rain, precip_snow, fder, rugos, rugoro, snow, qsurf, tsurf, &
11 p1lay, ps, radsol, evap, fluxsens, fluxlat, dflux_l, dflux_s, &
12 tsurf_new, alb_new, alblw, z0_new, pctsrf_new, agesno, fqcalving, &
13 ffonte, run_off_lic_0, flux_o, flux_g)
14
15 ! Cette routine sert d'aiguillage entre l'atmosphère et la surface
16 ! en général (sols continentaux, océans, glaces) pour les flux de
17 ! chaleur et d'humidité.
18
19 ! Laurent Fairhead, February 2000
20
21 USE abort_gcm_m, ONLY: abort_gcm
22 USE albsno_m, ONLY: albsno
23 use calbeta_m, only: calbeta
24 USE calcul_fluxs_m, ONLY: calcul_fluxs
25 use clesphys2, only: soil_model
26 USE dimphy, ONLY: klon
27 USE fonte_neige_m, ONLY: fonte_neige
28 USE indicesol, ONLY: epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf
29 USE interface_surf, ONLY: run_off, run_off_lic, conf_interface
30 USE interfoce_lim_m, ONLY: interfoce_lim
31 USE interfsur_lim_m, ONLY: interfsur_lim
32 use soil_m, only: soil
33 USE suphec_m, ONLY: rcpd, rlstt, rlvtt, rtt
34
35 integer, intent(IN):: itime ! numero du pas de temps
36 real, intent(IN):: dtime ! pas de temps de la physique (en s)
37 integer, intent(IN):: jour ! jour dans l'annee en cours
38 real, intent(IN):: rmu0(klon) ! cosinus de l'angle solaire zenithal
39 integer, intent(IN):: nisurf ! index de la surface a traiter
40 integer, intent(IN):: knon ! nombre de points de la surface a traiter
41
42 integer, intent(in):: knindex(:) ! (knon)
43 ! index des points de la surface a traiter
44
45 real, intent(IN):: pctsrf(klon, nbsrf)
46 ! tableau des pourcentages de surface de chaque maille
47
48 real, intent(IN):: rlat(klon) ! latitudes
49
50 logical, intent(IN):: debut ! 1er appel a la physique
51 ! (si false calcul simplifie des fluxs sur les continents)
52
53 integer, intent(in):: nsoilmx
54 REAL tsoil(klon, nsoilmx)
55
56 REAL, intent(INOUT):: qsol(klon)
57 ! column-density of water in soil, in kg m-2
58
59 real, dimension(klon), intent(IN):: u1_lay, v1_lay
60 ! u1_lay vitesse u 1ere couche
61 ! v1_lay vitesse v 1ere couche
62 real, dimension(klon), intent(IN):: temp_air, spechum
63 ! temp_air temperature de l'air 1ere couche
64 ! spechum humidite specifique 1ere couche
65 real, dimension(klon), intent(INOUT):: tq_cdrag
66 ! tq_cdrag cdrag
67 real, dimension(klon), intent(IN):: petAcoef, peqAcoef
68 ! petAcoef coeff. A de la resolution de la CL pour t
69 ! peqAcoef coeff. A de la resolution de la CL pour q
70 real, dimension(klon), intent(IN):: petBcoef, peqBcoef
71 ! petBcoef coeff. B de la resolution de la CL pour t
72 ! peqBcoef coeff. B de la resolution de la CL pour q
73
74 real, intent(IN):: precip_rain(klon)
75 ! precipitation, liquid water mass flux (kg/m2/s), positive down
76
77 real, intent(IN):: precip_snow(klon)
78 ! precipitation, solid water mass flux (kg/m2/s), positive down
79
80 REAL, DIMENSION(klon), INTENT(INOUT):: fder
81 ! fder derivee des flux (pour le couplage)
82 real, dimension(klon), intent(IN):: rugos, rugoro
83 ! rugos rugosite
84 ! rugoro rugosite orographique
85 real, intent(INOUT):: snow(klon), qsurf(klon)
86 real, intent(IN):: tsurf(:) ! (knon) température de surface
87 real, dimension(klon), intent(IN):: p1lay
88 ! p1lay pression 1er niveau (milieu de couche)
89 real, dimension(klon), intent(IN):: ps
90 ! ps pression au sol
91 REAL, DIMENSION(klon), INTENT(INOUT):: radsol
92 ! radsol rayonnement net aus sol (LW + SW)
93 real, intent(INOUT):: evap(klon) ! evaporation totale
94 real, dimension(klon), intent(OUT):: fluxsens, fluxlat
95 ! fluxsens flux de chaleur sensible
96 ! fluxlat flux de chaleur latente
97 real, dimension(klon), intent(OUT):: dflux_l, dflux_s
98 real, intent(OUT):: tsurf_new(knon) ! température au sol
99 real, intent(OUT):: alb_new(klon) ! albedo
100 real, dimension(klon), intent(OUT):: alblw
101 real, dimension(klon), intent(OUT):: z0_new
102 ! z0_new surface roughness
103 real, dimension(klon, nbsrf), intent(OUT):: pctsrf_new
104 ! pctsrf_new nouvelle repartition des surfaces
105 real, dimension(klon), intent(INOUT):: agesno
106
107 ! Flux d'eau "perdue" par la surface et nécessaire pour que limiter la
108 ! hauteur de neige, en kg/m2/s
109 !jld a rajouter real, dimension(klon), intent(INOUT):: fqcalving
110 real, dimension(klon), intent(INOUT):: fqcalving
111
112 ! Flux thermique utiliser pour fondre la neige
113 !jld a rajouter real, dimension(klon), intent(INOUT):: ffonte
114 real, dimension(klon), intent(INOUT):: ffonte
115
116 real, dimension(klon), intent(INOUT):: run_off_lic_0
117 ! run_off_lic_0 runoff glacier du pas de temps precedent
118
119 !IM: "slab" ocean
120 real, dimension(klon), intent(OUT):: flux_o, flux_g
121
122 ! Local:
123
124 REAL, dimension(klon):: soilcap
125 REAL, dimension(klon):: soilflux
126
127 !IM: "slab" ocean
128 real, parameter:: t_grnd=271.35
129 real, dimension(klon):: zx_sl
130 integer i
131
132 character (len = 20), save:: modname = 'interfsurf_hq'
133 character (len = 80):: abort_message
134 logical, save:: first_call = .true.
135 integer:: ii
136 real, dimension(klon):: cal, beta, dif_grnd, capsol
137 real, parameter:: calice=1.0/(5.1444e6 * 0.15), tau_gl=86400.*5.
138 real, parameter:: calsno=1./(2.3867e6 * 0.15)
139 real tsurf_temp(knon)
140 real, dimension(klon):: alb_neig, alb_eau
141 real, DIMENSION(klon):: zfra
142 INTEGER, dimension(1):: iloc
143 real, dimension(klon):: fder_prev
144
145 !-------------------------------------------------------------
146
147 ! On doit commencer par appeler les schemas de surfaces continentales
148 ! car l'ocean a besoin du ruissellement qui est y calcule
149
150 if (first_call) then
151 call conf_interface
152 if (nisurf /= is_ter .and. klon > 1) then
153 print *, ' Warning:'
154 print *, ' nisurf = ', nisurf, ' /= is_ter = ', is_ter
155 print *, 'or on doit commencer par les surfaces continentales'
156 abort_message='voir ci-dessus'
157 call abort_gcm(modname, abort_message, 1)
158 endif
159 if (is_oce > is_sic) then
160 print *, 'Warning:'
161 print *, ' Pour des raisons de sequencement dans le code'
162 print *, ' l''ocean doit etre traite avant la banquise'
163 print *, ' or is_oce = ', is_oce, '> is_sic = ', is_sic
164 abort_message='voir ci-dessus'
165 call abort_gcm(modname, abort_message, 1)
166 endif
167 endif
168 first_call = .false.
169
170 ! Initialisations diverses
171
172 ffonte(1:knon)=0.
173 fqcalving(1:knon)=0.
174 cal = 999999.
175 beta = 999999.
176 dif_grnd = 999999.
177 capsol = 999999.
178 alb_new = 999999.
179 z0_new = 999999.
180 alb_neig = 999999.
181 tsurf_new = 999999.
182 alblw = 999999.
183
184 !IM: "slab" ocean; initialisations
185 flux_o = 0.
186 flux_g = 0.
187
188 ! Aiguillage vers les differents schemas de surface
189
190 select case (nisurf)
191 case (is_ter)
192 ! Surface "terre" appel a l'interface avec les sols continentaux
193
194 ! allocation du run-off
195 if (.not. allocated(run_off)) then
196 allocate(run_off(knon))
197 run_off = 0.
198 else if (size(run_off) /= knon) then
199 print *, 'Bizarre, le nombre de points continentaux'
200 print *, 'a change entre deux appels. J''arrete '
201 abort_message='voir ci-dessus'
202 call abort_gcm(modname, abort_message, 1)
203 endif
204
205 ! Calcul age de la neige
206
207 ! calcul albedo: lecture albedo fichier boundary conditions
208 ! puis ajout albedo neige
209 call interfsur_lim(itime, dtime, jour, nisurf, knindex, debut, &
210 alb_new, z0_new)
211
212 ! calcul snow et qsurf, hydrol adapté
213 CALL calbeta(nisurf, snow(:knon), qsol(:knon), beta(:knon), &
214 capsol(:knon), dif_grnd(:knon))
215
216 IF (soil_model) THEN
217 CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, soilflux)
218 cal(1:knon) = RCPD / soilcap(1:knon)
219 radsol(1:knon) = radsol(1:knon) + soilflux(:knon)
220 ELSE
221 cal = RCPD * capsol
222 ENDIF
223 CALL calcul_fluxs(nisurf, dtime, tsurf, p1lay(:knon), cal(:knon), &
224 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
225 radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
226 u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
227 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), &
228 fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), dflux_l(:knon))
229
230 CALL fonte_neige(nisurf, dtime, tsurf, p1lay(:knon), beta(:knon), &
231 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
232 precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
233 spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
234 peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, &
235 evap(:knon), fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
236
237 call albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
238 where (snow(1 : knon) < 0.0001) agesno(1 : knon) = 0.
239 zfra(1:knon) = max(0.0, min(1.0, snow(1:knon)/(snow(1:knon) + 10.0)))
240 alb_new(1 : knon) = alb_neig(1 : knon) *zfra(1:knon) + &
241 alb_new(1 : knon)*(1.0-zfra(1:knon))
242 z0_new = sqrt(z0_new**2 + rugoro**2)
243 alblw(1 : knon) = alb_new(1 : knon)
244
245 ! Remplissage des pourcentages de surface
246 pctsrf_new(:, nisurf) = pctsrf(:, nisurf)
247 case (is_oce)
248 ! Surface "ocean" appel à l'interface avec l'océan
249 ! lecture conditions limites
250 call interfoce_lim(itime, dtime, jour, knindex, debut, tsurf_temp, &
251 pctsrf_new)
252
253 cal = 0.
254 beta = 1.
255 dif_grnd = 0.
256 alb_neig = 0.
257 agesno = 0.
258 call calcul_fluxs(nisurf, dtime, tsurf_temp, p1lay(:knon), &
259 cal(:knon), beta(:knon), tq_cdrag(:knon), ps(:knon), &
260 qsurf(:knon), radsol(:knon), dif_grnd(:knon), temp_air(:knon), &
261 spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
262 peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), &
263 tsurf_new, evap(:knon), fluxlat(:knon), fluxsens(:knon), &
264 dflux_s(:knon), dflux_l(:knon))
265 fder_prev = fder
266 fder = fder_prev + dflux_s + dflux_l
267 iloc = maxloc(fder(1:klon))
268
269 !IM: flux ocean-atmosphere utile pour le "slab" ocean
270 DO i=1, knon
271 zx_sl(i) = RLVTT
272 if (tsurf_new(i) < RTT) zx_sl(i) = RLSTT
273 flux_o(i) = fluxsens(i)-evap(i)*zx_sl(i)
274 ENDDO
275
276 ! calcul albedo
277 if (minval(rmu0) == maxval(rmu0) .and. minval(rmu0) == -999.999) then
278 CALL alboc(FLOAT(jour), rlat, alb_eau)
279 else ! cycle diurne
280 CALL alboc_cd(rmu0, alb_eau)
281 endif
282 DO ii =1, knon
283 alb_new(ii) = alb_eau(knindex(ii))
284 enddo
285
286 z0_new = sqrt(rugos**2 + rugoro**2)
287 alblw(1:knon) = alb_new(1:knon)
288 case (is_sic)
289 ! Surface "glace de mer" appel a l'interface avec l'ocean
290
291 ! ! lecture conditions limites
292 CALL interfoce_lim(itime, dtime, jour, knindex, debut, tsurf_new, &
293 pctsrf_new)
294
295 DO ii = 1, knon
296 tsurf_new(ii) = tsurf(ii)
297 IF (pctsrf_new(knindex(ii), nisurf) < EPSFRA) then
298 snow(ii) = 0.0
299 tsurf_new(ii) = RTT - 1.8
300 IF (soil_model) tsoil(ii, :) = RTT -1.8
301 endif
302 enddo
303
304 CALL calbeta(nisurf, snow(:knon), qsol(:knon), beta(:knon), &
305 capsol(:knon), dif_grnd(:knon))
306
307 IF (soil_model) THEN
308 CALL soil(dtime, nisurf, knon, snow, tsurf_new, tsoil, soilcap, &
309 soilflux)
310 cal(1:knon) = RCPD / soilcap(1:knon)
311 radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
312 dif_grnd = 0.
313 ELSE
314 dif_grnd = 1.0 / tau_gl
315 cal = RCPD * calice
316 WHERE (snow > 0.0) cal = RCPD * calsno
317 ENDIF
318 tsurf_temp = tsurf_new
319 beta = 1.0
320
321 CALL calcul_fluxs(nisurf, dtime, tsurf_temp, p1lay(:knon), cal(:knon), &
322 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
323 radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
324 u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
325 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), &
326 fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), dflux_l(:knon))
327
328 !IM: flux entre l'ocean et la glace de mer pour le "slab" ocean
329 DO i = 1, knon
330 flux_g(i) = 0.0
331 IF (cal(i) > 1e-15) flux_g(i) = (tsurf_new(i) - t_grnd) &
332 * dif_grnd(i) * RCPD / cal(i)
333 ENDDO
334
335 CALL fonte_neige(nisurf, dtime, tsurf_temp, p1lay(:knon), beta(:knon), &
336 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
337 precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
338 spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
339 peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, &
340 evap(:knon), fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
341
342 ! calcul albedo
343
344 CALL albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
345 WHERE (snow(1 : knon) < 0.0001) agesno(1 : knon) = 0.
346 zfra(1:knon) = MAX(0.0, MIN(1.0, snow(1:knon)/(snow(1:knon) + 10.0)))
347 alb_new(1 : knon) = alb_neig(1 : knon) *zfra(1:knon) + &
348 0.6 * (1.0-zfra(1:knon))
349
350 fder_prev = fder
351 fder = fder_prev + dflux_s + dflux_l
352
353 iloc = maxloc(fder(1:klon))
354
355 ! 2eme appel a interfoce pour le cumul et le passage des flux a l'ocean
356
357 z0_new = 0.002
358 z0_new = SQRT(z0_new**2 + rugoro**2)
359 alblw(1:knon) = alb_new(1:knon)
360
361 case (is_lic)
362 if (.not. allocated(run_off_lic)) then
363 allocate(run_off_lic(knon))
364 run_off_lic = 0.
365 endif
366
367 ! Surface "glacier continentaux" appel a l'interface avec le sol
368
369 IF (soil_model) THEN
370 CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, soilflux)
371 cal(1:knon) = RCPD / soilcap(1:knon)
372 radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
373 ELSE
374 cal = RCPD * calice
375 WHERE (snow > 0.0) cal = RCPD * calsno
376 ENDIF
377 beta = 1.0
378 dif_grnd = 0.0
379
380 call calcul_fluxs(nisurf, dtime, tsurf, p1lay(:knon), cal(:knon), &
381 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
382 radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
383 u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
384 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), &
385 fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), dflux_l(:knon))
386
387 call fonte_neige(nisurf, dtime, tsurf, p1lay(:knon), beta(:knon), &
388 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
389 precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
390 spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
391 peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, &
392 evap(:knon), fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
393
394 ! calcul albedo
395 CALL albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
396 WHERE (snow(1 : knon) < 0.0001) agesno(1 : knon) = 0.
397 zfra(1:knon) = MAX(0.0, MIN(1.0, snow(1:knon)/(snow(1:knon) + 10.0)))
398 alb_new(1 : knon) = alb_neig(1 : knon)*zfra(1:knon) + &
399 0.6 * (1.0-zfra(1:knon))
400
401 !IM: plusieurs choix/tests sur l'albedo des "glaciers continentaux"
402 !IM: KstaTER0.77 & LMD_ARMIP6
403 alb_new(1 : knon) = 0.77
404
405 ! Rugosite
406 z0_new = rugoro
407
408 ! Remplissage des pourcentages de surface
409 pctsrf_new(:, nisurf) = pctsrf(:, nisurf)
410
411 alblw(1:knon) = alb_new(1:knon)
412 case default
413 print *, 'Index surface = ', nisurf
414 abort_message = 'Index surface non valable'
415 call abort_gcm(modname, abort_message, 1)
416 end select
417
418 END SUBROUTINE interfsurf_hq
419
420 end module interfsurf_hq_m

  ViewVC Help
Powered by ViewVC 1.1.21