/[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 178 - (show annotations)
Fri Mar 11 18:47:26 2016 UTC (8 years, 1 month ago) by guez
File size: 14023 byte(s)
Moved variables date0, deltat, datasz_max, ncvar_ids, point, buff_pos,
buffer, regular from module histcom_var to modules where they are
defined.

Removed procedure ioipslmpp, useless for a sequential program.

Added argument datasz_max to histwrite_real (to avoid circular
dependency with histwrite).

Removed useless variables and computations everywhere.

Changed real litteral constants from default kind to double precision
in lwb, lwu, lwvn, sw1s, swtt, swtt1, swu.

Removed unused arguments: paer of sw, sw1s, sw2s, swclr; pcldsw of
sw1s, sw2s; pdsig, prayl of swr; co2_ppm of clmain, clqh; tsol of
transp_lay; nsrf of screenp; kcrit and kknu of gwstress; pstd of
orosetup.

Added output of relative humidity.

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, albedo, z0_new, pctsrf_new, agesno, fqcalving, ffonte, &
13 run_off_lic_0)
14
15 ! 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
19 ! Laurent Fairhead, February 2000
20
21 USE abort_gcm_m, ONLY: abort_gcm
22 use alboc_cd_m, only: alboc_cd
23 use alboc_m, only: alboc
24 USE albsno_m, ONLY: albsno
25 use calbeta_m, only: calbeta
26 USE calcul_fluxs_m, ONLY: calcul_fluxs
27 use clesphys2, only: soil_model, cycle_diurne
28 USE dimphy, ONLY: klon
29 USE fonte_neige_m, ONLY: fonte_neige
30 USE indicesol, ONLY: epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf
31 USE interface_surf, ONLY: run_off, run_off_lic, conf_interface
32 USE interfoce_lim_m, ONLY: interfoce_lim
33 USE interfsur_lim_m, ONLY: interfsur_lim
34 use soil_m, only: soil
35 USE suphec_m, ONLY: rcpd, rtt
36
37 integer, intent(IN):: itime ! numero du pas de temps
38 real, intent(IN):: dtime ! pas de temps de la physique (en s)
39 integer, intent(IN):: jour ! jour dans l'annee en cours
40 real, intent(IN):: rmu0(klon) ! cosinus de l'angle solaire zenithal
41 integer, intent(IN):: nisurf ! index de la surface a traiter
42 integer, intent(IN):: knon ! nombre de points de la surface a traiter
43
44 integer, intent(in):: knindex(:) ! (knon)
45 ! index des points de la surface a traiter
46
47 real, intent(IN):: pctsrf(klon, nbsrf)
48 ! tableau des pourcentages de surface de chaque maille
49
50 real, intent(IN):: rlat(klon) ! latitudes
51
52 logical, intent(IN):: debut ! 1er appel a la physique
53 ! (si false calcul simplifie des fluxs sur les continents)
54
55 integer, intent(in):: nsoilmx
56 REAL tsoil(klon, nsoilmx)
57
58 REAL, intent(INOUT):: qsol(klon)
59 ! column-density of water in soil, in kg m-2
60
61 real, dimension(klon), intent(IN):: u1_lay, v1_lay
62 ! u1_lay vitesse u 1ere couche
63 ! v1_lay vitesse v 1ere couche
64 real, dimension(klon), intent(IN):: temp_air, spechum
65 ! temp_air temperature de l'air 1ere couche
66 ! spechum humidite specifique 1ere couche
67 real, dimension(klon), intent(INOUT):: tq_cdrag
68 ! tq_cdrag cdrag
69 real, dimension(klon), intent(IN):: petAcoef, peqAcoef
70 ! petAcoef coeff. A de la resolution de la CL pour t
71 ! peqAcoef coeff. A de la resolution de la CL pour q
72 real, dimension(klon), intent(IN):: petBcoef, peqBcoef
73 ! petBcoef coeff. B de la resolution de la CL pour t
74 ! peqBcoef coeff. B de la resolution de la CL pour q
75
76 real, intent(IN):: precip_rain(klon)
77 ! precipitation, liquid water mass flux (kg / m2 / s), positive down
78
79 real, intent(IN):: precip_snow(klon)
80 ! precipitation, solid water mass flux (kg / m2 / s), positive down
81
82 REAL, INTENT(INOUT):: fder(klon) ! derivee des flux (pour le couplage)
83 real, intent(IN):: rugos(klon) ! rugosite
84 real, intent(IN):: rugoro(klon) ! rugosite orographique
85 real, intent(INOUT):: snow(klon), qsurf(klon)
86 real, intent(IN):: tsurf(:) ! (knon) temp\'erature 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
92 REAL, DIMENSION(klon), INTENT(INOUT):: radsol
93 ! rayonnement net au sol (LW + SW)
94
95 real, intent(INOUT):: evap(klon) ! evaporation totale
96 real, dimension(klon), intent(OUT):: fluxsens, fluxlat
97 ! fluxsens flux de chaleur sensible
98 ! fluxlat flux de chaleur latente
99 real, dimension(klon), intent(OUT):: dflux_l, dflux_s
100 real, intent(OUT):: tsurf_new(knon) ! temp\'erature au sol
101 real, intent(OUT):: albedo(:) ! (knon) albedo
102 real, intent(OUT):: z0_new(klon) ! surface roughness
103 real, dimension(klon, nbsrf), intent(OUT):: pctsrf_new
104 ! pctsrf_new nouvelle repartition des surfaces
105 real, intent(INOUT):: agesno(:) ! (knon)
106
107 ! Flux d'eau "perdue" par la surface et n\'ecessaire 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 ! Local:
120 REAL soilcap(klon)
121 REAL soilflux(klon)
122 logical:: first_call = .true.
123 integer ii
124 real, dimension(klon):: cal, beta, dif_grnd, capsol
125 real, parameter:: calice = 1. / (5.1444e6 * 0.15), tau_gl = 86400. * 5.
126 real, parameter:: calsno = 1. / (2.3867e6 * 0.15)
127 real tsurf_temp(knon)
128 real alb_neig(knon)
129 real zfra(knon)
130
131 !-------------------------------------------------------------
132
133 ! On doit commencer par appeler les schemas de surfaces continentales
134 ! car l'ocean a besoin du ruissellement qui est y calcule
135
136 if (first_call) then
137 call conf_interface
138
139 if (nisurf /= is_ter .and. klon > 1) then
140 print *, ' nisurf = ', nisurf, ' /= is_ter = ', is_ter
141 print *, 'or on doit commencer par les surfaces continentales'
142 call abort_gcm("interfsurf_hq", &
143 'On doit commencer par les surfaces continentales')
144 endif
145
146 if (is_oce > is_sic) then
147 print *, 'is_oce = ', is_oce, '> is_sic = ', is_sic
148 call abort_gcm("interfsurf_hq", &
149 'L''ocean doit etre traite avant la banquise')
150 endif
151
152 first_call = .false.
153 endif
154
155 ! Initialisations diverses
156
157 ffonte(1:knon) = 0.
158 fqcalving(1:knon) = 0.
159 cal = 999999.
160 beta = 999999.
161 dif_grnd = 999999.
162 capsol = 999999.
163 z0_new = 999999.
164 tsurf_new = 999999.
165
166 ! Aiguillage vers les differents schemas de surface
167
168 select case (nisurf)
169 case (is_ter)
170 ! Surface "terre", appel \`a l'interface avec les sols continentaux
171
172 ! allocation du run-off
173 if (.not. allocated(run_off)) then
174 allocate(run_off(knon))
175 run_off = 0.
176 else if (size(run_off) /= knon) then
177 call abort_gcm("interfsurf_hq", 'Something is wrong: the number of ' &
178 // 'continental points has changed since last call.')
179 endif
180
181 ! Calcul age de la neige
182
183 ! Read albedo from the file containing boundary conditions then
184 ! add the albedo of snow:
185
186 call interfsur_lim(itime, dtime, jour, knindex, debut, albedo, z0_new)
187
188 ! Calcul snow et qsurf, hydrologie adapt\'ee
189 CALL calbeta(nisurf, snow(:knon), qsol(:knon), beta(:knon), &
190 capsol(:knon), dif_grnd(:knon))
191
192 IF (soil_model) THEN
193 CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, soilflux)
194 cal(1:knon) = RCPD / soilcap(1:knon)
195 radsol(1:knon) = radsol(1:knon) + soilflux(:knon)
196 ELSE
197 cal = RCPD * capsol
198 ENDIF
199
200 CALL calcul_fluxs(dtime, tsurf, p1lay(:knon), cal(:knon), &
201 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
202 radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
203 u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
204 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), &
205 fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), dflux_l(:knon))
206
207 CALL fonte_neige(nisurf, dtime, tsurf, p1lay(:knon), beta(:knon), &
208 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
209 precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
210 spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
211 peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, &
212 evap(:knon), fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
213
214 call albsno(dtime, agesno, alb_neig, precip_snow(:knon))
215 where (snow(:knon) < 0.0001) agesno = 0.
216 zfra = max(0., min(1., snow(:knon) / (snow(:knon) + 10.)))
217 albedo = alb_neig * zfra + albedo * (1. - zfra)
218 z0_new = sqrt(z0_new**2 + rugoro**2)
219
220 ! Remplissage des pourcentages de surface
221 pctsrf_new(:, nisurf) = pctsrf(:, nisurf)
222 case (is_oce)
223 ! Surface "oc\'ean", appel \`a l'interface avec l'oc\'ean
224
225 call interfoce_lim(itime, dtime, jour, knindex, debut, tsurf_temp, &
226 pctsrf_new)
227
228 cal = 0.
229 beta = 1.
230 dif_grnd = 0.
231 agesno = 0.
232 call calcul_fluxs(dtime, tsurf_temp, p1lay(:knon), cal(:knon), &
233 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
234 radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
235 u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
236 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), &
237 fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), dflux_l(:knon))
238 fder = fder + dflux_s + dflux_l
239
240 ! Compute the albedo:
241 if (cycle_diurne) then
242 CALL alboc_cd(rmu0(knindex), albedo)
243 else
244 CALL alboc(jour, rlat(knindex), albedo)
245 endif
246
247 z0_new = sqrt(rugos**2 + rugoro**2)
248 case (is_sic)
249 ! Surface "glace de mer" appel a l'interface avec l'ocean
250
251 ! ! lecture conditions limites
252 CALL interfoce_lim(itime, dtime, jour, knindex, debut, tsurf_new, &
253 pctsrf_new)
254
255 DO ii = 1, knon
256 tsurf_new(ii) = tsurf(ii)
257 IF (pctsrf_new(knindex(ii), nisurf) < EPSFRA) then
258 snow(ii) = 0.
259 tsurf_new(ii) = RTT - 1.8
260 IF (soil_model) tsoil(ii, :) = RTT - 1.8
261 endif
262 enddo
263
264 CALL calbeta(nisurf, snow(:knon), qsol(:knon), beta(:knon), &
265 capsol(:knon), dif_grnd(:knon))
266
267 IF (soil_model) THEN
268 CALL soil(dtime, nisurf, knon, snow, tsurf_new, tsoil, soilcap, &
269 soilflux)
270 cal(1:knon) = RCPD / soilcap(1:knon)
271 radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
272 dif_grnd = 0.
273 ELSE
274 dif_grnd = 1. / tau_gl
275 cal = RCPD * calice
276 WHERE (snow > 0.) cal = RCPD * calsno
277 ENDIF
278 tsurf_temp = tsurf_new
279 beta = 1.
280
281 CALL calcul_fluxs(dtime, tsurf_temp, p1lay(:knon), cal(:knon), &
282 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
283 radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
284 u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
285 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), &
286 fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), dflux_l(:knon))
287
288 CALL fonte_neige(nisurf, dtime, tsurf_temp, p1lay(:knon), beta(:knon), &
289 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
290 precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
291 spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
292 peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, &
293 evap(:knon), fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
294
295 ! Compute the albedo:
296
297 CALL albsno(dtime, agesno, alb_neig, precip_snow(:knon))
298 WHERE (snow(:knon) < 0.0001) agesno = 0.
299 zfra = MAX(0., MIN(1., snow(:knon) / (snow(:knon) + 10.)))
300 albedo = alb_neig * zfra + 0.6 * (1. - zfra)
301
302 fder = fder + dflux_s + dflux_l
303
304 ! 2eme appel a interfoce pour le cumul et le passage des flux a l'ocean
305
306 z0_new = 0.002
307 z0_new = SQRT(z0_new**2 + rugoro**2)
308 case (is_lic)
309 if (.not. allocated(run_off_lic)) then
310 allocate(run_off_lic(knon))
311 run_off_lic = 0.
312 endif
313
314 ! Surface "glacier continentaux" appel a l'interface avec le sol
315
316 IF (soil_model) THEN
317 CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, soilflux)
318 cal(1:knon) = RCPD / soilcap(1:knon)
319 radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
320 ELSE
321 cal = RCPD * calice
322 WHERE (snow > 0.) cal = RCPD * calsno
323 ENDIF
324 beta = 1.
325 dif_grnd = 0.
326
327 call calcul_fluxs(dtime, tsurf, p1lay(:knon), cal(:knon), &
328 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
329 radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
330 u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
331 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap(:knon), &
332 fluxlat(:knon), fluxsens(:knon), dflux_s(:knon), dflux_l(:knon))
333
334 call fonte_neige(nisurf, dtime, tsurf, p1lay(:knon), beta(:knon), &
335 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
336 precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
337 spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
338 peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, &
339 evap(:knon), fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
340
341 ! calcul albedo
342 CALL albsno(dtime, agesno, alb_neig, precip_snow(:knon))
343 WHERE (snow(:knon) < 0.0001) agesno = 0.
344 albedo = 0.77
345
346 ! Rugosite
347 z0_new = rugoro
348
349 ! Remplissage des pourcentages de surface
350 pctsrf_new(:, nisurf) = pctsrf(:, nisurf)
351
352 case default
353 print *, 'Index surface = ', nisurf
354 call abort_gcm("interfsurf_hq", 'Index surface non valable')
355 end select
356
357 END SUBROUTINE interfsurf_hq
358
359 end module interfsurf_hq_m

  ViewVC Help
Powered by ViewVC 1.1.21