/[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 222 - (show annotations)
Tue Apr 25 15:31:48 2017 UTC (7 years ago) by guez
File size: 11328 byte(s)
In interfsurf_hq, changed names of variables : tsurf becomes ts (name of
actual argument), tsurf_temp  can then become simply tsurf.

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

  ViewVC Help
Powered by ViewVC 1.1.21