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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 101 - (show annotations)
Mon Jul 7 17:45:21 2014 UTC (9 years, 10 months ago) by guez
Original Path: trunk/phylmd/Interface_surf/interfsurf_hq.f
File size: 15716 byte(s)
Removed unused files "interfoce_slab.f" and "gath2cpl.f". Removed
unused variables coastalflow and riverflow of module
interface_surf. Removed unused arguments cal, radsol, dif_grnd,
fluxlat, fluxsens, dflux_s, dflux_l of procedure fonte_neige. Removed
unused arguments tslab, seaice of procedure interfsurf_hq and
clqh. Removed unused arguments seaice of procedure clmain.

In interfsurf_hq, used variable soil_model of module clesphys2 instead
of cascading it as an argument from physiq.

In phyetat0, stop if masque not found.

Variable TS instead of "TS[0-9][0-9]" in "(re)startphy.nc", with
additional dimension nbsrf.

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

  ViewVC Help
Powered by ViewVC 1.1.21