/[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 106 - (show annotations)
Tue Sep 9 12:54:30 2014 UTC (9 years, 8 months ago) by guez
File size: 16213 byte(s)
Removed arguments klon, knon of interfoce_lim. Removed argument knon
of interfsur_lim.

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), beta(:knon), &
224 tq_cdrag(:knon), ps(:knon), qsurf(:knon), radsol(:knon), &
225 dif_grnd(:knon), temp_air(:knon), spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
226 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), &
227 dflux_l(:knon))
228
229 CALL fonte_neige(nisurf, dtime, tsurf, p1lay(:knon), beta(:knon), &
230 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), precip_snow(:knon), snow(:knon), qsol(:knon), &
231 temp_air(:knon), spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), petBcoef(:knon), &
232 peqBcoef(:knon), tsurf_new, evap(:knon), fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
233
234 call albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
235 where (snow(1 : knon) < 0.0001) agesno(1 : knon) = 0.
236 zfra(1:knon) = max(0.0, min(1.0, snow(1:knon)/(snow(1:knon) + 10.0)))
237 alb_new(1 : knon) = alb_neig(1 : knon) *zfra(1:knon) + &
238 alb_new(1 : knon)*(1.0-zfra(1:knon))
239 z0_new = sqrt(z0_new**2 + rugoro**2)
240 alblw(1 : knon) = alb_new(1 : knon)
241
242 ! Remplissage des pourcentages de surface
243 pctsrf_new(:, nisurf) = pctsrf(:, nisurf)
244 case (is_oce)
245 ! Surface "ocean" appel à l'interface avec l'océan
246 ! lecture conditions limites
247 call interfoce_lim(itime, dtime, jour, knindex, debut, tsurf_temp, &
248 pctsrf_new)
249
250 cal = 0.
251 beta = 1.
252 dif_grnd = 0.
253 alb_neig = 0.
254 agesno = 0.
255 call calcul_fluxs(nisurf, dtime, tsurf_temp, p1lay(:knon), &
256 cal(:knon), beta(:knon), tq_cdrag(:knon), ps(:knon), &
257 qsurf(:knon), radsol(:knon), dif_grnd(:knon), temp_air(:knon), &
258 spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
259 peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), &
260 tsurf_new, evap(:knon), fluxlat(:knon), fluxsens(:knon), &
261 dflux_s(:knon), dflux_l(:knon))
262 fder_prev = fder
263 fder = fder_prev + dflux_s + dflux_l
264 iloc = maxloc(fder(1:klon))
265
266 !IM: flux ocean-atmosphere utile pour le "slab" ocean
267 DO i=1, knon
268 zx_sl(i) = RLVTT
269 if (tsurf_new(i) < RTT) zx_sl(i) = RLSTT
270 flux_o(i) = fluxsens(i)-evap(i)*zx_sl(i)
271 ENDDO
272
273 ! calcul albedo
274 if (minval(rmu0) == maxval(rmu0) .and. minval(rmu0) == -999.999) then
275 CALL alboc(FLOAT(jour), rlat, alb_eau)
276 else ! cycle diurne
277 CALL alboc_cd(rmu0, alb_eau)
278 endif
279 DO ii =1, knon
280 alb_new(ii) = alb_eau(knindex(ii))
281 enddo
282
283 z0_new = sqrt(rugos**2 + rugoro**2)
284 alblw(1:knon) = alb_new(1:knon)
285 case (is_sic)
286 ! Surface "glace de mer" appel a l'interface avec l'ocean
287
288 ! ! lecture conditions limites
289 CALL interfoce_lim(itime, dtime, jour, knindex, debut, tsurf_new, &
290 pctsrf_new)
291
292 DO ii = 1, knon
293 tsurf_new(ii) = tsurf(ii)
294 IF (pctsrf_new(knindex(ii), nisurf) < EPSFRA) then
295 snow(ii) = 0.0
296 tsurf_new(ii) = RTT - 1.8
297 IF (soil_model) tsoil(ii, :) = RTT -1.8
298 endif
299 enddo
300
301 CALL calbeta(nisurf, snow(:knon), qsol(:knon), beta(:knon), &
302 capsol(:knon), dif_grnd(:knon))
303
304 IF (soil_model) THEN
305 CALL soil(dtime, nisurf, knon, snow, tsurf_new, tsoil, soilcap, &
306 soilflux)
307 cal(1:knon) = RCPD / soilcap(1:knon)
308 radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
309 dif_grnd = 0.
310 ELSE
311 dif_grnd = 1.0 / tau_gl
312 cal = RCPD * calice
313 WHERE (snow > 0.0) cal = RCPD * calsno
314 ENDIF
315 tsurf_temp = tsurf_new
316 beta = 1.0
317
318 CALL calcul_fluxs(nisurf, dtime, tsurf_temp, p1lay(:knon), cal(:knon), &
319 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
320 radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
321 peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), fluxlat(:knon), fluxsens(:knon), &
322 dflux_s(:knon), dflux_l(:knon))
323
324 !IM: flux entre l'ocean et la glace de mer pour le "slab" ocean
325 DO i = 1, knon
326 flux_g(i) = 0.0
327 IF (cal(i) > 1e-15) flux_g(i) = (tsurf_new(i) - t_grnd) &
328 * dif_grnd(i) * RCPD / cal(i)
329 ENDDO
330
331 CALL fonte_neige(nisurf, dtime, tsurf_temp, p1lay(:knon), beta(:knon), &
332 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), precip_snow(:knon), snow(:knon), qsol(:knon), &
333 temp_air(:knon), spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), petBcoef(:knon), &
334 peqBcoef(:knon), tsurf_new, evap(:knon), fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
335
336 ! calcul albedo
337
338 CALL albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
339 WHERE (snow(1 : knon) < 0.0001) agesno(1 : knon) = 0.
340 zfra(1:knon) = MAX(0.0, MIN(1.0, snow(1:knon)/(snow(1:knon) + 10.0)))
341 alb_new(1 : knon) = alb_neig(1 : knon) *zfra(1:knon) + &
342 0.6 * (1.0-zfra(1:knon))
343
344 fder_prev = fder
345 fder = fder_prev + dflux_s + dflux_l
346
347 iloc = maxloc(fder(1:klon))
348
349 ! 2eme appel a interfoce pour le cumul et le passage des flux a l'ocean
350
351 z0_new = 0.002
352 z0_new = SQRT(z0_new**2 + rugoro**2)
353 alblw(1:knon) = alb_new(1:knon)
354
355 case (is_lic)
356 if (.not. allocated(run_off_lic)) then
357 allocate(run_off_lic(knon))
358 run_off_lic = 0.
359 endif
360
361 ! Surface "glacier continentaux" appel a l'interface avec le sol
362
363 IF (soil_model) THEN
364 CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, soilflux)
365 cal(1:knon) = RCPD / soilcap(1:knon)
366 radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
367 ELSE
368 cal = RCPD * calice
369 WHERE (snow > 0.0) cal = RCPD * calsno
370 ENDIF
371 beta = 1.0
372 dif_grnd = 0.0
373
374 call calcul_fluxs(nisurf, dtime, tsurf, p1lay(:knon), cal(:knon), beta(:knon), &
375 tq_cdrag(:knon), ps(:knon), qsurf(:knon), radsol(:knon), &
376 dif_grnd(:knon), temp_air(:knon), spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
377 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), &
378 dflux_l(:knon))
379
380 call fonte_neige(nisurf, dtime, tsurf, p1lay(:knon), beta(:knon), &
381 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), precip_snow(:knon), snow(:knon), qsol(:knon), &
382 temp_air(:knon), spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), petBcoef(:knon), &
383 peqBcoef(:knon), tsurf_new, evap(:knon), fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
384
385 ! calcul albedo
386 CALL albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
387 WHERE (snow(1 : knon) < 0.0001) agesno(1 : knon) = 0.
388 zfra(1:knon) = MAX(0.0, MIN(1.0, snow(1:knon)/(snow(1:knon) + 10.0)))
389 alb_new(1 : knon) = alb_neig(1 : knon)*zfra(1:knon) + &
390 0.6 * (1.0-zfra(1:knon))
391
392 !IM: plusieurs choix/tests sur l'albedo des "glaciers continentaux"
393 !IM: KstaTER0.77 & LMD_ARMIP6
394 alb_new(1 : knon) = 0.77
395
396 ! Rugosite
397 z0_new = rugoro
398
399 ! Remplissage des pourcentages de surface
400 pctsrf_new(:, nisurf) = pctsrf(:, nisurf)
401
402 alblw(1:knon) = alb_new(1:knon)
403 case default
404 print *, 'Index surface = ', nisurf
405 abort_message = 'Index surface non valable'
406 call abort_gcm(modname, abort_message, 1)
407 end select
408
409 END SUBROUTINE interfsurf_hq
410
411 end module interfsurf_hq_m

  ViewVC Help
Powered by ViewVC 1.1.21