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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 150 - (hide annotations)
Thu Jun 18 13:49:26 2015 UTC (8 years, 11 months ago) by guez
Original Path: trunk/Sources/phylmd/Interface_surf/interfsurf_hq.f
File size: 16361 byte(s)
Removed unused arguments of groupe, cv3_undilute2, cv_undilute2,
interfsur_lim, drag_noro, orodrag, gwprofil

Chickened out of revision 148: back to double precision in
invert_zoom_x (and overloaded rtsafe).

1 guez 54 module interfsurf_hq_m
2    
3     implicit none
4    
5     contains
6    
7 guez 104 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 guez 54
15 guez 150 ! Cette routine sert d'aiguillage entre l'atmosph\`ere et la surface
16     ! en g\'en\'eral (sols continentaux, oc\'eans, glaces) pour les flux de
17     ! chaleur et d'humidit\'e.
18 guez 54
19 guez 104 ! Laurent Fairhead, February 2000
20 guez 54
21 guez 72 USE abort_gcm_m, ONLY: abort_gcm
22 guez 125 use alboc_m, only: alboc
23 guez 72 USE albsno_m, ONLY: albsno
24 guez 101 use calbeta_m, only: calbeta
25 guez 72 USE calcul_fluxs_m, ONLY: calcul_fluxs
26 guez 101 use clesphys2, only: soil_model
27 guez 98 USE dimphy, ONLY: klon
28 guez 72 USE fonte_neige_m, ONLY: fonte_neige
29     USE indicesol, ONLY: epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf
30 guez 101 USE interface_surf, ONLY: run_off, run_off_lic, conf_interface
31 guez 72 USE interfoce_lim_m, ONLY: interfoce_lim
32     USE interfsur_lim_m, ONLY: interfsur_lim
33 guez 101 use soil_m, only: soil
34 guez 72 USE suphec_m, ONLY: rcpd, rlstt, rlvtt, rtt
35 guez 54
36 guez 99 integer, intent(IN):: itime ! numero du pas de temps
37     real, intent(IN):: dtime ! pas de temps de la physique (en s)
38     integer, intent(IN):: jour ! jour dans l'annee en cours
39     real, intent(IN):: rmu0(klon) ! cosinus de l'angle solaire zenithal
40 guez 101 integer, intent(IN):: nisurf ! index de la surface a traiter
41     integer, intent(IN):: knon ! nombre de points de la surface a traiter
42    
43 guez 106 integer, intent(in):: knindex(:) ! (knon)
44 guez 101 ! index des points de la surface a traiter
45    
46 guez 99 real, intent(IN):: pctsrf(klon, nbsrf)
47 guez 101 ! tableau des pourcentages de surface de chaque maille
48    
49     real, intent(IN):: rlat(klon) ! latitudes
50    
51     logical, intent(IN):: debut ! 1er appel a la physique
52 guez 54 ! (si false calcul simplifie des fluxs sur les continents)
53 guez 101
54     integer, intent(in):: nsoilmx
55     REAL tsoil(klon, nsoilmx)
56    
57     REAL, intent(INOUT):: qsol(klon)
58     ! column-density of water in soil, in kg m-2
59    
60 guez 99 real, dimension(klon), intent(IN):: u1_lay, v1_lay
61 guez 54 ! u1_lay vitesse u 1ere couche
62     ! v1_lay vitesse v 1ere couche
63 guez 99 real, dimension(klon), intent(IN):: temp_air, spechum
64 guez 54 ! temp_air temperature de l'air 1ere couche
65     ! spechum humidite specifique 1ere couche
66 guez 99 real, dimension(klon), intent(INOUT):: tq_cdrag
67 guez 54 ! tq_cdrag cdrag
68 guez 99 real, dimension(klon), intent(IN):: petAcoef, peqAcoef
69 guez 54 ! petAcoef coeff. A de la resolution de la CL pour t
70     ! peqAcoef coeff. A de la resolution de la CL pour q
71 guez 99 real, dimension(klon), intent(IN):: petBcoef, peqBcoef
72 guez 54 ! petBcoef coeff. B de la resolution de la CL pour t
73     ! peqBcoef coeff. B de la resolution de la CL pour q
74 guez 101
75     real, intent(IN):: precip_rain(klon)
76     ! precipitation, liquid water mass flux (kg/m2/s), positive down
77    
78     real, intent(IN):: precip_snow(klon)
79     ! precipitation, solid water mass flux (kg/m2/s), positive down
80    
81 guez 99 REAL, DIMENSION(klon), INTENT(INOUT):: fder
82     ! fder derivee des flux (pour le couplage)
83     real, dimension(klon), intent(IN):: rugos, rugoro
84     ! rugos rugosite
85     ! rugoro rugosite orographique
86 guez 101 real, intent(INOUT):: snow(klon), qsurf(klon)
87 guez 150 real, intent(IN):: tsurf(:) ! (knon) temp\'erature de surface
88 guez 104 real, dimension(klon), intent(IN):: p1lay
89 guez 54 ! p1lay pression 1er niveau (milieu de couche)
90 guez 99 real, dimension(klon), intent(IN):: ps
91 guez 54 ! ps pression au sol
92 guez 99 REAL, DIMENSION(klon), INTENT(INOUT):: radsol
93 guez 54 ! radsol rayonnement net aus sol (LW + SW)
94 guez 106 real, intent(INOUT):: evap(klon) ! evaporation totale
95 guez 99 real, dimension(klon), intent(OUT):: fluxsens, fluxlat
96 guez 54 ! fluxsens flux de chaleur sensible
97     ! fluxlat flux de chaleur latente
98 guez 99 real, dimension(klon), intent(OUT):: dflux_l, dflux_s
99 guez 150 real, intent(OUT):: tsurf_new(knon) ! temp\'erature au sol
100 guez 104 real, intent(OUT):: alb_new(klon) ! albedo
101 guez 54 real, dimension(klon), intent(OUT):: alblw
102 guez 72 real, dimension(klon), intent(OUT):: z0_new
103 guez 99 ! z0_new surface roughness
104 guez 72 real, dimension(klon, nbsrf), intent(OUT):: pctsrf_new
105 guez 99 ! pctsrf_new nouvelle repartition des surfaces
106 guez 54 real, dimension(klon), intent(INOUT):: agesno
107    
108 guez 150 ! Flux d'eau "perdue" par la surface et n\'ecessaire pour que limiter la
109 guez 54 ! 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 guez 99
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 guez 72 real, parameter:: t_grnd=271.35
130     real, dimension(klon):: zx_sl
131 guez 54 integer i
132    
133 guez 72 character (len = 20), save:: modname = 'interfsurf_hq'
134     character (len = 80):: abort_message
135     logical, save:: first_call = .true.
136     integer:: ii
137 guez 54 real, dimension(klon):: cal, beta, dif_grnd, capsol
138 guez 101 real, parameter:: calice=1.0/(5.1444e6 * 0.15), tau_gl=86400.*5.
139     real, parameter:: calsno=1./(2.3867e6 * 0.15)
140 guez 104 real tsurf_temp(knon)
141 guez 54 real, dimension(klon):: alb_neig, alb_eau
142     real, DIMENSION(klon):: zfra
143 guez 72 INTEGER, dimension(1):: iloc
144 guez 54 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 guez 72 call conf_interface
153 guez 54 if (nisurf /= is_ter .and. klon > 1) then
154 guez 101 print *, ' Warning:'
155     print *, ' nisurf = ', nisurf, ' /= is_ter = ', is_ter
156     print *, 'or on doit commencer par les surfaces continentales'
157 guez 54 abort_message='voir ci-dessus'
158     call abort_gcm(modname, abort_message, 1)
159     endif
160 guez 101 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 guez 54 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 guez 104 select case (nisurf)
192     case (is_ter)
193 guez 54 ! Surface "terre" appel a l'interface avec les sols continentaux
194    
195     ! allocation du run-off
196 guez 101 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 guez 54 abort_message='voir ci-dessus'
203     call abort_gcm(modname, abort_message, 1)
204     endif
205    
206     ! Calcul age de la neige
207    
208 guez 99 ! calcul albedo: lecture albedo fichier boundary conditions
209     ! puis ajout albedo neige
210 guez 150 call interfsur_lim(itime, dtime, jour, knindex, debut, alb_new, z0_new)
211 guez 54
212 guez 150 ! calcul snow et qsurf, hydrol adapt\'e
213 guez 101 CALL calbeta(nisurf, snow(:knon), qsol(:knon), beta(:knon), &
214     capsol(:knon), dif_grnd(:knon))
215 guez 54
216 guez 99 IF (soil_model) THEN
217 guez 101 CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, soilflux)
218 guez 99 cal(1:knon) = RCPD / soilcap(1:knon)
219 guez 104 radsol(1:knon) = radsol(1:knon) + soilflux(:knon)
220 guez 99 ELSE
221     cal = RCPD * capsol
222     ENDIF
223 guez 116 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 guez 54
230 guez 104 CALL fonte_neige(nisurf, dtime, tsurf, p1lay(:knon), beta(:knon), &
231 guez 116 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 guez 54
237 guez 99 call albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
238 guez 104 where (snow(1 : knon) < 0.0001) agesno(1 : knon) = 0.
239 guez 101 zfra(1:knon) = max(0.0, min(1.0, snow(1:knon)/(snow(1:knon) + 10.0)))
240 guez 99 alb_new(1 : knon) = alb_neig(1 : knon) *zfra(1:knon) + &
241     alb_new(1 : knon)*(1.0-zfra(1:knon))
242 guez 101 z0_new = sqrt(z0_new**2 + rugoro**2)
243 guez 99 alblw(1 : knon) = alb_new(1 : knon)
244 guez 54
245     ! Remplissage des pourcentages de surface
246     pctsrf_new(:, nisurf) = pctsrf(:, nisurf)
247 guez 104 case (is_oce)
248 guez 150 ! Surface "ocean" appel \`a l'interface avec l'oc\'ean
249 guez 99 ! lecture conditions limites
250 guez 106 call interfoce_lim(itime, dtime, jour, knindex, debut, tsurf_temp, &
251     pctsrf_new)
252 guez 54
253     cal = 0.
254     beta = 1.
255     dif_grnd = 0.
256     alb_neig = 0.
257     agesno = 0.
258 guez 104 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 guez 54 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 guez 104 if (tsurf_new(i) < RTT) zx_sl(i) = RLSTT
273 guez 54 flux_o(i) = fluxsens(i)-evap(i)*zx_sl(i)
274     ENDDO
275    
276     ! calcul albedo
277 guez 101 if (minval(rmu0) == maxval(rmu0) .and. minval(rmu0) == -999.999) then
278 guez 130 CALL alboc(jour, rlat, alb_eau)
279 guez 54 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 guez 104 case (is_sic)
289 guez 54 ! Surface "glace de mer" appel a l'interface avec l'ocean
290    
291 guez 99 ! ! lecture conditions limites
292 guez 106 CALL interfoce_lim(itime, dtime, jour, knindex, debut, tsurf_new, &
293     pctsrf_new)
294 guez 54
295 guez 99 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 guez 54
304 guez 101 CALL calbeta(nisurf, snow(:knon), qsol(:knon), beta(:knon), &
305     capsol(:knon), dif_grnd(:knon))
306 guez 54
307 guez 99 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 guez 54 ELSE
314 guez 99 dif_grnd = 1.0 / tau_gl
315     cal = RCPD * calice
316     WHERE (snow > 0.0) cal = RCPD * calsno
317 guez 54 ENDIF
318 guez 99 tsurf_temp = tsurf_new
319     beta = 1.0
320 guez 54
321 guez 104 CALL calcul_fluxs(nisurf, dtime, tsurf_temp, p1lay(:knon), cal(:knon), &
322     beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
323 guez 116 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 guez 54
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 guez 101 IF (cal(i) > 1e-15) flux_g(i) = (tsurf_new(i) - t_grnd) &
332     * dif_grnd(i) * RCPD / cal(i)
333 guez 54 ENDDO
334    
335 guez 104 CALL fonte_neige(nisurf, dtime, tsurf_temp, p1lay(:knon), beta(:knon), &
336 guez 116 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 guez 54
342     ! calcul albedo
343    
344     CALL albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
345 guez 104 WHERE (snow(1 : knon) < 0.0001) agesno(1 : knon) = 0.
346 guez 101 zfra(1:knon) = MAX(0.0, MIN(1.0, snow(1:knon)/(snow(1:knon) + 10.0)))
347 guez 54 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 guez 101 z0_new = SQRT(z0_new**2 + rugoro**2)
359 guez 54 alblw(1:knon) = alb_new(1:knon)
360    
361 guez 104 case (is_lic)
362 guez 54 if (.not. allocated(run_off_lic)) then
363 guez 101 allocate(run_off_lic(knon))
364 guez 54 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 guez 116 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 guez 54
387 guez 104 call fonte_neige(nisurf, dtime, tsurf, p1lay(:knon), beta(:knon), &
388 guez 116 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 guez 54
394     ! calcul albedo
395     CALL albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
396 guez 104 WHERE (snow(1 : knon) < 0.0001) agesno(1 : knon) = 0.
397 guez 101 zfra(1:knon) = MAX(0.0, MIN(1.0, snow(1:knon)/(snow(1:knon) + 10.0)))
398 guez 54 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 guez 104 case default
413 guez 101 print *, 'Index surface = ', nisurf
414 guez 54 abort_message = 'Index surface non valable'
415     call abort_gcm(modname, abort_message, 1)
416 guez 104 end select
417 guez 54
418     END SUBROUTINE interfsurf_hq
419    
420     end module interfsurf_hq_m

  ViewVC Help
Powered by ViewVC 1.1.21