/[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 104 - (show annotations)
Thu Sep 4 10:05:52 2014 UTC (9 years, 8 months ago) by guez
File size: 16257 byte(s)
Removed procedure sortvarc0. Called sortvarc with an additional
argument resetvarc instead. (Following LMDZ.) Moved current time
computations and some printing statements from sortvarc to
caldyn. Could then remove arguments itau and time_0 of sortvarc, and
could remove "use dynetat0". Better to keep "dynetat0.f" as a gcm-only
file.

Moved some variables from module ener to module sortvarc.

Split file "mathelp.f" into single-procedure files.

Removed unused argument nadv of adaptdt. Removed dimension arguments
of bernoui.

Removed unused argument nisurf of interfoce_lim. Changed the size of
argument lmt_sst of interfoce_lim from klon to knon. Removed case when
newlmt is false.

dynredem1 is called only once in each run, either ce0l or gcm. So
variable nb in call to nf95_put_var was always 1. Removed variable nb.

Removed dimension arguments of calcul_fluxs. Removed unused arguments
precip_rain, precip_snow, snow of calcul_fluxs. Changed the size of
all the arrays in calcul_fluxs from klon to knon.

Removed dimension arguments of fonte_neige. Changed the size of all
the arrays in fonte_neige from klon to knon.

Changed the size of arguments tsurf and tsurf_new of interfsurf_hq
from klon to knon. Changed the size of argument ptsrf of soil from
klon to knon.

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(klon)
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, dimension(klon), intent(INOUT):: evap
94 ! evap evaporation totale
95 real, dimension(klon), intent(OUT):: fluxsens, fluxlat
96 ! fluxsens flux de chaleur sensible
97 ! fluxlat flux de chaleur latente
98 real, dimension(klon), intent(OUT):: dflux_l, dflux_s
99 real, intent(OUT):: tsurf_new(knon) ! température au sol
100 real, intent(OUT):: alb_new(klon) ! albedo
101 real, dimension(klon), intent(OUT):: alblw
102 real, dimension(klon), intent(OUT):: z0_new
103 ! z0_new surface roughness
104 real, dimension(klon, nbsrf), intent(OUT):: pctsrf_new
105 ! pctsrf_new nouvelle repartition des surfaces
106 real, dimension(klon), intent(INOUT):: agesno
107
108 ! Flux d'eau "perdue" par la surface et nécessaire pour que limiter la
109 ! hauteur de neige, en kg/m2/s
110 !jld a rajouter real, dimension(klon), intent(INOUT):: fqcalving
111 real, dimension(klon), intent(INOUT):: fqcalving
112
113 ! Flux thermique utiliser pour fondre la neige
114 !jld a rajouter real, dimension(klon), intent(INOUT):: ffonte
115 real, dimension(klon), intent(INOUT):: ffonte
116
117 real, dimension(klon), intent(INOUT):: run_off_lic_0
118 ! run_off_lic_0 runoff glacier du pas de temps precedent
119
120 !IM: "slab" ocean
121 real, dimension(klon), intent(OUT):: flux_o, flux_g
122
123 ! Local:
124
125 REAL, dimension(klon):: soilcap
126 REAL, dimension(klon):: soilflux
127
128 !IM: "slab" ocean
129 real, parameter:: t_grnd=271.35
130 real, dimension(klon):: zx_sl
131 integer i
132
133 character (len = 20), save:: modname = 'interfsurf_hq'
134 character (len = 80):: abort_message
135 logical, save:: first_call = .true.
136 integer:: ii
137 real, dimension(klon):: cal, beta, dif_grnd, capsol
138 real, parameter:: calice=1.0/(5.1444e6 * 0.15), tau_gl=86400.*5.
139 real, parameter:: calsno=1./(2.3867e6 * 0.15)
140 real tsurf_temp(knon)
141 real, dimension(klon):: alb_neig, alb_eau
142 real, DIMENSION(klon):: zfra
143 INTEGER, dimension(1):: iloc
144 real, dimension(klon):: fder_prev
145
146 !-------------------------------------------------------------
147
148 ! On doit commencer par appeler les schemas de surfaces continentales
149 ! car l'ocean a besoin du ruissellement qui est y calcule
150
151 if (first_call) then
152 call conf_interface
153 if (nisurf /= is_ter .and. klon > 1) then
154 print *, ' Warning:'
155 print *, ' nisurf = ', nisurf, ' /= is_ter = ', is_ter
156 print *, 'or on doit commencer par les surfaces continentales'
157 abort_message='voir ci-dessus'
158 call abort_gcm(modname, abort_message, 1)
159 endif
160 if (is_oce > is_sic) then
161 print *, 'Warning:'
162 print *, ' Pour des raisons de sequencement dans le code'
163 print *, ' l''ocean doit etre traite avant la banquise'
164 print *, ' or is_oce = ', is_oce, '> is_sic = ', is_sic
165 abort_message='voir ci-dessus'
166 call abort_gcm(modname, abort_message, 1)
167 endif
168 endif
169 first_call = .false.
170
171 ! Initialisations diverses
172
173 ffonte(1:knon)=0.
174 fqcalving(1:knon)=0.
175 cal = 999999.
176 beta = 999999.
177 dif_grnd = 999999.
178 capsol = 999999.
179 alb_new = 999999.
180 z0_new = 999999.
181 alb_neig = 999999.
182 tsurf_new = 999999.
183 alblw = 999999.
184
185 !IM: "slab" ocean; initialisations
186 flux_o = 0.
187 flux_g = 0.
188
189 ! Aiguillage vers les differents schemas de surface
190
191 select case (nisurf)
192 case (is_ter)
193 ! Surface "terre" appel a l'interface avec les sols continentaux
194
195 ! allocation du run-off
196 if (.not. allocated(run_off)) then
197 allocate(run_off(knon))
198 run_off = 0.
199 else if (size(run_off) /= knon) then
200 print *, 'Bizarre, le nombre de points continentaux'
201 print *, 'a change entre deux appels. J''arrete '
202 abort_message='voir ci-dessus'
203 call abort_gcm(modname, abort_message, 1)
204 endif
205
206 ! Calcul age de la neige
207
208 ! calcul albedo: lecture albedo fichier boundary conditions
209 ! puis ajout albedo neige
210 call interfsur_lim(itime, dtime, jour, nisurf, knon, knindex, &
211 debut, alb_new, z0_new)
212
213 ! calcul snow et qsurf, hydrol adapté
214 CALL calbeta(nisurf, snow(:knon), qsol(:knon), beta(:knon), &
215 capsol(:knon), dif_grnd(:knon))
216
217 IF (soil_model) THEN
218 CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, soilflux)
219 cal(1:knon) = RCPD / soilcap(1:knon)
220 radsol(1:knon) = radsol(1:knon) + soilflux(:knon)
221 ELSE
222 cal = RCPD * capsol
223 ENDIF
224 CALL calcul_fluxs(nisurf, dtime, tsurf, p1lay(:knon), cal(:knon), beta(:knon), &
225 tq_cdrag(:knon), ps(:knon), qsurf(:knon), radsol(:knon), &
226 dif_grnd(:knon), temp_air(:knon), spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
227 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), &
228 dflux_l(:knon))
229
230 CALL fonte_neige(nisurf, dtime, tsurf, p1lay(:knon), beta(:knon), &
231 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), precip_snow(:knon), snow(:knon), qsol(:knon), &
232 temp_air(:knon), spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), petBcoef(:knon), &
233 peqBcoef(:knon), tsurf_new, evap(:knon), fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
234
235 call albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
236 where (snow(1 : knon) < 0.0001) agesno(1 : knon) = 0.
237 zfra(1:knon) = max(0.0, min(1.0, snow(1:knon)/(snow(1:knon) + 10.0)))
238 alb_new(1 : knon) = alb_neig(1 : knon) *zfra(1:knon) + &
239 alb_new(1 : knon)*(1.0-zfra(1:knon))
240 z0_new = sqrt(z0_new**2 + rugoro**2)
241 alblw(1 : knon) = alb_new(1 : knon)
242
243 ! Remplissage des pourcentages de surface
244 pctsrf_new(:, nisurf) = pctsrf(:, nisurf)
245 case (is_oce)
246 ! Surface "ocean" appel à l'interface avec l'océan
247 ! lecture conditions limites
248 call interfoce_lim(itime, dtime, jour, klon, knon, knindex, debut, &
249 tsurf_temp, pctsrf_new)
250
251 cal = 0.
252 beta = 1.
253 dif_grnd = 0.
254 alb_neig = 0.
255 agesno = 0.
256 call calcul_fluxs(nisurf, dtime, tsurf_temp, p1lay(:knon), &
257 cal(:knon), beta(:knon), tq_cdrag(:knon), ps(:knon), &
258 qsurf(:knon), radsol(:knon), dif_grnd(:knon), temp_air(:knon), &
259 spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
260 peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), &
261 tsurf_new, evap(:knon), fluxlat(:knon), fluxsens(:knon), &
262 dflux_s(:knon), dflux_l(:knon))
263 fder_prev = fder
264 fder = fder_prev + dflux_s + dflux_l
265 iloc = maxloc(fder(1:klon))
266
267 !IM: flux ocean-atmosphere utile pour le "slab" ocean
268 DO i=1, knon
269 zx_sl(i) = RLVTT
270 if (tsurf_new(i) < RTT) zx_sl(i) = RLSTT
271 flux_o(i) = fluxsens(i)-evap(i)*zx_sl(i)
272 ENDDO
273
274 ! calcul albedo
275 if (minval(rmu0) == maxval(rmu0) .and. minval(rmu0) == -999.999) then
276 CALL alboc(FLOAT(jour), rlat, alb_eau)
277 else ! cycle diurne
278 CALL alboc_cd(rmu0, alb_eau)
279 endif
280 DO ii =1, knon
281 alb_new(ii) = alb_eau(knindex(ii))
282 enddo
283
284 z0_new = sqrt(rugos**2 + rugoro**2)
285 alblw(1:knon) = alb_new(1:knon)
286 case (is_sic)
287 ! Surface "glace de mer" appel a l'interface avec l'ocean
288
289 ! ! lecture conditions limites
290 CALL interfoce_lim(itime, dtime, jour, klon, knon, knindex, &
291 debut, tsurf_new, pctsrf_new)
292
293 DO ii = 1, knon
294 tsurf_new(ii) = tsurf(ii)
295 IF (pctsrf_new(knindex(ii), nisurf) < EPSFRA) then
296 snow(ii) = 0.0
297 tsurf_new(ii) = RTT - 1.8
298 IF (soil_model) tsoil(ii, :) = RTT -1.8
299 endif
300 enddo
301
302 CALL calbeta(nisurf, snow(:knon), qsol(:knon), beta(:knon), &
303 capsol(:knon), dif_grnd(:knon))
304
305 IF (soil_model) THEN
306 CALL soil(dtime, nisurf, knon, snow, tsurf_new, tsoil, soilcap, &
307 soilflux)
308 cal(1:knon) = RCPD / soilcap(1:knon)
309 radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
310 dif_grnd = 0.
311 ELSE
312 dif_grnd = 1.0 / tau_gl
313 cal = RCPD * calice
314 WHERE (snow > 0.0) cal = RCPD * calsno
315 ENDIF
316 tsurf_temp = tsurf_new
317 beta = 1.0
318
319 CALL calcul_fluxs(nisurf, dtime, tsurf_temp, p1lay(:knon), cal(:knon), &
320 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
321 radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
322 peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), fluxlat(:knon), fluxsens(:knon), &
323 dflux_s(:knon), dflux_l(:knon))
324
325 !IM: flux entre l'ocean et la glace de mer pour le "slab" ocean
326 DO i = 1, knon
327 flux_g(i) = 0.0
328 IF (cal(i) > 1e-15) flux_g(i) = (tsurf_new(i) - t_grnd) &
329 * dif_grnd(i) * RCPD / cal(i)
330 ENDDO
331
332 CALL fonte_neige(nisurf, dtime, tsurf_temp, p1lay(:knon), beta(:knon), &
333 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), precip_snow(:knon), snow(:knon), qsol(:knon), &
334 temp_air(:knon), spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), petBcoef(:knon), &
335 peqBcoef(:knon), tsurf_new, evap(:knon), fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
336
337 ! calcul albedo
338
339 CALL albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
340 WHERE (snow(1 : knon) < 0.0001) agesno(1 : knon) = 0.
341 zfra(1:knon) = MAX(0.0, MIN(1.0, snow(1:knon)/(snow(1:knon) + 10.0)))
342 alb_new(1 : knon) = alb_neig(1 : knon) *zfra(1:knon) + &
343 0.6 * (1.0-zfra(1:knon))
344
345 fder_prev = fder
346 fder = fder_prev + dflux_s + dflux_l
347
348 iloc = maxloc(fder(1:klon))
349
350 ! 2eme appel a interfoce pour le cumul et le passage des flux a l'ocean
351
352 z0_new = 0.002
353 z0_new = SQRT(z0_new**2 + rugoro**2)
354 alblw(1:knon) = alb_new(1:knon)
355
356 case (is_lic)
357 if (.not. allocated(run_off_lic)) then
358 allocate(run_off_lic(knon))
359 run_off_lic = 0.
360 endif
361
362 ! Surface "glacier continentaux" appel a l'interface avec le sol
363
364 IF (soil_model) THEN
365 CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, soilflux)
366 cal(1:knon) = RCPD / soilcap(1:knon)
367 radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
368 ELSE
369 cal = RCPD * calice
370 WHERE (snow > 0.0) cal = RCPD * calsno
371 ENDIF
372 beta = 1.0
373 dif_grnd = 0.0
374
375 call calcul_fluxs(nisurf, dtime, tsurf, p1lay(:knon), cal(:knon), beta(:knon), &
376 tq_cdrag(:knon), ps(:knon), qsurf(:knon), radsol(:knon), &
377 dif_grnd(:knon), temp_air(:knon), spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
378 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), &
379 dflux_l(:knon))
380
381 call fonte_neige(nisurf, dtime, tsurf, p1lay(:knon), beta(:knon), &
382 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), precip_snow(:knon), snow(:knon), qsol(:knon), &
383 temp_air(:knon), spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), petBcoef(:knon), &
384 peqBcoef(:knon), tsurf_new, evap(:knon), fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
385
386 ! calcul albedo
387 CALL albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
388 WHERE (snow(1 : knon) < 0.0001) agesno(1 : knon) = 0.
389 zfra(1:knon) = MAX(0.0, MIN(1.0, snow(1:knon)/(snow(1:knon) + 10.0)))
390 alb_new(1 : knon) = alb_neig(1 : knon)*zfra(1:knon) + &
391 0.6 * (1.0-zfra(1:knon))
392
393 !IM: plusieurs choix/tests sur l'albedo des "glaciers continentaux"
394 !IM: KstaTER0.77 & LMD_ARMIP6
395 alb_new(1 : knon) = 0.77
396
397 ! Rugosite
398 z0_new = rugoro
399
400 ! Remplissage des pourcentages de surface
401 pctsrf_new(:, nisurf) = pctsrf(:, nisurf)
402
403 alblw(1:knon) = alb_new(1:knon)
404 case default
405 print *, 'Index surface = ', nisurf
406 abort_message = 'Index surface non valable'
407 call abort_gcm(modname, abort_message, 1)
408 end select
409
410 END SUBROUTINE interfsurf_hq
411
412 end module interfsurf_hq_m

  ViewVC Help
Powered by ViewVC 1.1.21