/[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 215 - (show annotations)
Tue Mar 28 12:46:28 2017 UTC (7 years, 1 month ago) by guez
Original Path: trunk/Sources/phylmd/Interface_surf/interfsurf_hq.f
File size: 11668 byte(s)
size(snow) is now knon in interfsurf_hq.

Renamed snow to fsnow in clmain, same name as corresponding actual
argument. We can then rename ysnow to simply snow in clmain, same name
as corresponding dummy argument of clqh. No need to initialize local
snow to 0 since it is only used with indices 1:knon and already
initialized from fsnow for each type of surface. If there is no point
for a given type of surface, fsnow should be reset to 0 for this
type. We need to give a valid value to fsnow in this case even if it
will be multiplied by pctsrf = 0 in physiq.

In physiq, no need for intermediate zxsnow for output.

Removed unused arguments tsurf, p1lay, beta, coef1lay, ps, t1lay,
q1lay, u1lay, v1lay, petAcoef, peqAcoef, petBcoef, peqBcoef of
fonte_neige, with unused computations of zx_qs and zcor. (Same was
done in LMDZ.)

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

  ViewVC Help
Powered by ViewVC 1.1.21