/[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 206 - (hide annotations)
Tue Aug 30 12:52:46 2016 UTC (7 years, 8 months ago) by guez
Original Path: trunk/Sources/phylmd/Interface_surf/interfsurf_hq.f
File size: 12900 byte(s)
Removed dimension klev of flux_[tquv] and y_flux_[tquv] in
clmain. Removed dimension klev of flux_[tquv] in physiq. Removed
dimension klev of flux_[tq] in hbtm. Removed dimension klev of
flux_[tq] in clqh and computations for layers other than the surface
layer. Removed dimension klev of flux_v in clvent and computations for
layers other than the surface layer. Values for layers other than the
surface layer were not used nor output (not even in LMDZ).

Removed argument dnwd0 of concvl. Simply write - mp in physiq
(following LMDZ).

Removed useless intermediary variables zxflux[tquv] in physiq.

1 guez 54 module interfsurf_hq_m
2    
3     implicit none
4    
5     contains
6    
7 guez 202 SUBROUTINE interfsurf_hq(dtime, jour, rmu0, nisurf, knon, knindex, rlat, &
8     debut, nsoilmx, tsoil, qsol, u1_lay, v1_lay, temp_air, spechum, &
9 guez 191 tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, precip_rain, &
10     precip_snow, fder, rugos, rugoro, snow, qsurf, tsurf, p1lay, ps, &
11 guez 206 radsol, evap, flux_t, fluxlat, dflux_l, dflux_s, tsurf_new, albedo, &
12 guez 202 z0_new, pctsrf_new_sic, agesno, fqcalving, ffonte, run_off_lic_0)
13 guez 54
14 guez 150 ! Cette routine sert d'aiguillage entre l'atmosph\`ere et la surface
15     ! en g\'en\'eral (sols continentaux, oc\'eans, glaces) pour les flux de
16     ! chaleur et d'humidit\'e.
17 guez 54
18 guez 104 ! Laurent Fairhead, February 2000
19 guez 54
20 guez 72 USE abort_gcm_m, ONLY: abort_gcm
21 guez 154 use alboc_cd_m, only: alboc_cd
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 154 use clesphys2, only: soil_model, cycle_diurne
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 202 USE interface_surf, ONLY: run_off_lic, conf_interface
31 guez 72 USE interfsur_lim_m, ONLY: interfsur_lim
32 guez 202 use read_sst_m, only: read_sst
33 guez 101 use soil_m, only: soil
34 guez 178 USE suphec_m, ONLY: rcpd, rtt
35 guez 54
36 guez 99 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 guez 101 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 guez 106 integer, intent(in):: knindex(:) ! (knon)
43 guez 101 ! index des points de la surface a traiter
44    
45     real, intent(IN):: rlat(klon) ! latitudes
46    
47     logical, intent(IN):: debut ! 1er appel a la physique
48 guez 54 ! (si false calcul simplifie des fluxs sur les continents)
49 guez 101
50     integer, intent(in):: nsoilmx
51     REAL tsoil(klon, nsoilmx)
52    
53     REAL, intent(INOUT):: qsol(klon)
54     ! column-density of water in soil, in kg m-2
55    
56 guez 99 real, dimension(klon), intent(IN):: u1_lay, v1_lay
57 guez 54 ! u1_lay vitesse u 1ere couche
58     ! v1_lay vitesse v 1ere couche
59 guez 99 real, dimension(klon), intent(IN):: temp_air, spechum
60 guez 54 ! temp_air temperature de l'air 1ere couche
61     ! spechum humidite specifique 1ere couche
62 guez 99 real, dimension(klon), intent(INOUT):: tq_cdrag
63 guez 54 ! tq_cdrag cdrag
64 guez 99 real, dimension(klon), intent(IN):: petAcoef, peqAcoef
65 guez 54 ! petAcoef coeff. A de la resolution de la CL pour t
66     ! peqAcoef coeff. A de la resolution de la CL pour q
67 guez 99 real, dimension(klon), intent(IN):: petBcoef, peqBcoef
68 guez 54 ! petBcoef coeff. B de la resolution de la CL pour t
69     ! peqBcoef coeff. B de la resolution de la CL pour q
70 guez 101
71     real, intent(IN):: precip_rain(klon)
72 guez 175 ! precipitation, liquid water mass flux (kg / m2 / s), positive down
73 guez 101
74     real, intent(IN):: precip_snow(klon)
75 guez 175 ! precipitation, solid water mass flux (kg / m2 / s), positive down
76 guez 101
77 guez 154 REAL, INTENT(INOUT):: fder(klon) ! derivee des flux (pour le couplage)
78     real, intent(IN):: rugos(klon) ! rugosite
79     real, intent(IN):: rugoro(klon) ! rugosite orographique
80 guez 101 real, intent(INOUT):: snow(klon), qsurf(klon)
81 guez 150 real, intent(IN):: tsurf(:) ! (knon) temp\'erature de surface
82 guez 104 real, dimension(klon), intent(IN):: p1lay
83 guez 54 ! p1lay pression 1er niveau (milieu de couche)
84 guez 99 real, dimension(klon), intent(IN):: ps
85 guez 54 ! ps pression au sol
86 guez 175
87 guez 99 REAL, DIMENSION(klon), INTENT(INOUT):: radsol
88 guez 175 ! rayonnement net au sol (LW + SW)
89    
90 guez 206 real, intent(OUT):: evap(:) ! (knon) evaporation totale
91     real, intent(OUT):: flux_t(:) ! (knon) flux de chaleur sensible
92     real, dimension(klon), intent(OUT):: fluxlat ! flux de chaleur latente
93 guez 99 real, dimension(klon), intent(OUT):: dflux_l, dflux_s
94 guez 150 real, intent(OUT):: tsurf_new(knon) ! temp\'erature au sol
95 guez 156 real, intent(OUT):: albedo(:) ! (knon) albedo
96 guez 154 real, intent(OUT):: z0_new(klon) ! surface roughness
97 guez 202
98     real, intent(in):: pctsrf_new_sic(:) ! (klon)
99     ! nouvelle repartition des surfaces
100    
101 guez 175 real, intent(INOUT):: agesno(:) ! (knon)
102 guez 54
103 guez 150 ! Flux d'eau "perdue" par la surface et n\'ecessaire pour que limiter la
104 guez 175 ! hauteur de neige, en kg / m2 / s
105 guez 54 !jld a rajouter real, dimension(klon), intent(INOUT):: fqcalving
106     real, dimension(klon), intent(INOUT):: fqcalving
107 guez 99
108     ! Flux thermique utiliser pour fondre la neige
109     !jld a rajouter real, dimension(klon), intent(INOUT):: ffonte
110     real, dimension(klon), intent(INOUT):: ffonte
111    
112     real, dimension(klon), intent(INOUT):: run_off_lic_0
113     ! run_off_lic_0 runoff glacier du pas de temps precedent
114    
115     ! Local:
116 guez 175 REAL soilcap(klon)
117     REAL soilflux(klon)
118     logical:: first_call = .true.
119     integer ii
120 guez 54 real, dimension(klon):: cal, beta, dif_grnd, capsol
121 guez 175 real, parameter:: calice = 1. / (5.1444e6 * 0.15), tau_gl = 86400. * 5.
122     real, parameter:: calsno = 1. / (2.3867e6 * 0.15)
123 guez 104 real tsurf_temp(knon)
124 guez 174 real alb_neig(knon)
125     real zfra(knon)
126 guez 54
127     !-------------------------------------------------------------
128    
129     ! On doit commencer par appeler les schemas de surfaces continentales
130     ! car l'ocean a besoin du ruissellement qui est y calcule
131    
132     if (first_call) then
133 guez 72 call conf_interface
134 guez 175
135 guez 54 if (nisurf /= is_ter .and. klon > 1) then
136 guez 101 print *, ' nisurf = ', nisurf, ' /= is_ter = ', is_ter
137     print *, 'or on doit commencer par les surfaces continentales'
138 guez 175 call abort_gcm("interfsurf_hq", &
139     'On doit commencer par les surfaces continentales')
140 guez 54 endif
141 guez 175
142 guez 101 if (is_oce > is_sic) then
143 guez 175 print *, 'is_oce = ', is_oce, '> is_sic = ', is_sic
144     call abort_gcm("interfsurf_hq", &
145     'L''ocean doit etre traite avant la banquise')
146 guez 54 endif
147 guez 175
148     first_call = .false.
149 guez 54 endif
150    
151     ! Initialisations diverses
152    
153 guez 175 ffonte(1:knon) = 0.
154     fqcalving(1:knon) = 0.
155 guez 54 cal = 999999.
156     beta = 999999.
157     dif_grnd = 999999.
158     capsol = 999999.
159     z0_new = 999999.
160     tsurf_new = 999999.
161    
162     ! Aiguillage vers les differents schemas de surface
163    
164 guez 104 select case (nisurf)
165     case (is_ter)
166 guez 171 ! Surface "terre", appel \`a l'interface avec les sols continentaux
167 guez 54
168     ! Calcul age de la neige
169    
170 guez 174 ! Read albedo from the file containing boundary conditions then
171     ! add the albedo of snow:
172    
173 guez 191 call interfsur_lim(dtime, jour, knindex, debut, albedo, z0_new)
174 guez 54
175 guez 174 ! Calcul snow et qsurf, hydrologie adapt\'ee
176 guez 202 CALL calbeta(is_ter, snow(:knon), qsol(:knon), beta(:knon), &
177 guez 101 capsol(:knon), dif_grnd(:knon))
178 guez 54
179 guez 99 IF (soil_model) THEN
180 guez 202 CALL soil(dtime, is_ter, knon, snow, tsurf, tsoil, soilcap, soilflux)
181 guez 99 cal(1:knon) = RCPD / soilcap(1:knon)
182 guez 104 radsol(1:knon) = radsol(1:knon) + soilflux(:knon)
183 guez 99 ELSE
184     cal = RCPD * capsol
185     ENDIF
186 guez 171
187     CALL calcul_fluxs(dtime, tsurf, p1lay(:knon), cal(:knon), &
188 guez 116 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
189     radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
190     u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
191 guez 206 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap, &
192     fluxlat(:knon), flux_t, dflux_s(:knon), dflux_l(:knon))
193 guez 54
194 guez 202 CALL fonte_neige(is_ter, dtime, tsurf, p1lay(:knon), beta(:knon), &
195 guez 116 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
196     precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
197     spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
198     peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, &
199 guez 206 evap, fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
200 guez 54
201 guez 175 call albsno(dtime, agesno, alb_neig, precip_snow(:knon))
202     where (snow(:knon) < 0.0001) agesno = 0.
203     zfra = max(0., min(1., snow(:knon) / (snow(:knon) + 10.)))
204 guez 174 albedo = alb_neig * zfra + albedo * (1. - zfra)
205 guez 101 z0_new = sqrt(z0_new**2 + rugoro**2)
206 guez 104 case (is_oce)
207 guez 175 ! Surface "oc\'ean", appel \`a l'interface avec l'oc\'ean
208    
209 guez 202 call read_sst(dtime, jour, knindex, debut, tsurf_temp)
210 guez 54
211     cal = 0.
212     beta = 1.
213     dif_grnd = 0.
214     agesno = 0.
215 guez 175 call calcul_fluxs(dtime, tsurf_temp, p1lay(:knon), cal(:knon), &
216     beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
217     radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
218     u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
219 guez 206 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap, &
220     fluxlat(:knon), flux_t, dflux_s(:knon), dflux_l(:knon))
221 guez 154 fder = fder + dflux_s + dflux_l
222 guez 54
223 guez 174 ! Compute the albedo:
224 guez 154 if (cycle_diurne) then
225 guez 156 CALL alboc_cd(rmu0(knindex), albedo)
226 guez 154 else
227 guez 156 CALL alboc(jour, rlat(knindex), albedo)
228 guez 54 endif
229    
230     z0_new = sqrt(rugos**2 + rugoro**2)
231 guez 104 case (is_sic)
232 guez 54 ! Surface "glace de mer" appel a l'interface avec l'ocean
233    
234 guez 99 DO ii = 1, knon
235     tsurf_new(ii) = tsurf(ii)
236 guez 202 IF (pctsrf_new_sic(knindex(ii)) < EPSFRA) then
237 guez 175 snow(ii) = 0.
238 guez 99 tsurf_new(ii) = RTT - 1.8
239 guez 154 IF (soil_model) tsoil(ii, :) = RTT - 1.8
240 guez 99 endif
241     enddo
242 guez 54
243 guez 202 CALL calbeta(is_sic, snow(:knon), qsol(:knon), beta(:knon), &
244 guez 101 capsol(:knon), dif_grnd(:knon))
245 guez 54
246 guez 99 IF (soil_model) THEN
247 guez 202 CALL soil(dtime, is_sic, knon, snow, tsurf_new, tsoil, soilcap, &
248 guez 99 soilflux)
249     cal(1:knon) = RCPD / soilcap(1:knon)
250     radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
251     dif_grnd = 0.
252 guez 54 ELSE
253 guez 175 dif_grnd = 1. / tau_gl
254 guez 99 cal = RCPD * calice
255 guez 175 WHERE (snow > 0.) cal = RCPD * calsno
256 guez 54 ENDIF
257 guez 99 tsurf_temp = tsurf_new
258 guez 175 beta = 1.
259 guez 54
260 guez 171 CALL calcul_fluxs(dtime, tsurf_temp, p1lay(:knon), cal(:knon), &
261 guez 104 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
262 guez 116 radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
263     u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
264 guez 206 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap, &
265     fluxlat(:knon), flux_t, dflux_s(:knon), dflux_l(:knon))
266 guez 54
267 guez 202 CALL fonte_neige(is_sic, dtime, tsurf_temp, p1lay(:knon), beta(:knon), &
268 guez 116 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
269     precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
270     spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
271     peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, &
272 guez 206 evap, fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
273 guez 54
274 guez 174 ! Compute the albedo:
275 guez 54
276 guez 175 CALL albsno(dtime, agesno, alb_neig, precip_snow(:knon))
277     WHERE (snow(:knon) < 0.0001) agesno = 0.
278     zfra = MAX(0., MIN(1., snow(:knon) / (snow(:knon) + 10.)))
279     albedo = alb_neig * zfra + 0.6 * (1. - zfra)
280 guez 54
281 guez 154 fder = fder + dflux_s + dflux_l
282 guez 191 z0_new = SQRT(0.002**2 + rugoro**2)
283 guez 104 case (is_lic)
284 guez 54 if (.not. allocated(run_off_lic)) then
285 guez 101 allocate(run_off_lic(knon))
286 guez 54 run_off_lic = 0.
287     endif
288    
289     ! Surface "glacier continentaux" appel a l'interface avec le sol
290    
291     IF (soil_model) THEN
292 guez 202 CALL soil(dtime, is_lic, knon, snow, tsurf, tsoil, soilcap, soilflux)
293 guez 54 cal(1:knon) = RCPD / soilcap(1:knon)
294     radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
295     ELSE
296     cal = RCPD * calice
297 guez 175 WHERE (snow > 0.) cal = RCPD * calsno
298 guez 54 ENDIF
299 guez 175 beta = 1.
300     dif_grnd = 0.
301 guez 54
302 guez 171 call calcul_fluxs(dtime, tsurf, p1lay(:knon), cal(:knon), &
303 guez 116 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
304     radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
305     u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
306 guez 206 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap, &
307     fluxlat(:knon), flux_t, dflux_s(:knon), dflux_l(:knon))
308 guez 54
309 guez 202 call fonte_neige(is_lic, dtime, tsurf, p1lay(:knon), beta(:knon), &
310 guez 116 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
311     precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
312     spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
313     peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, &
314 guez 206 evap, fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
315 guez 54
316     ! calcul albedo
317 guez 175 CALL albsno(dtime, agesno, alb_neig, precip_snow(:knon))
318     WHERE (snow(:knon) < 0.0001) agesno = 0.
319 guez 156 albedo = 0.77
320 guez 54
321     ! Rugosite
322     z0_new = rugoro
323 guez 104 case default
324 guez 101 print *, 'Index surface = ', nisurf
325 guez 175 call abort_gcm("interfsurf_hq", 'Index surface non valable')
326 guez 104 end select
327 guez 54
328     END SUBROUTINE interfsurf_hq
329    
330     end module interfsurf_hq_m

  ViewVC Help
Powered by ViewVC 1.1.21