/[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 214 - (hide annotations)
Wed Mar 22 13:40:27 2017 UTC (7 years, 1 month ago) by guez
Original Path: trunk/Sources/phylmd/Interface_surf/interfsurf_hq.f
File size: 12708 byte(s)
fluxlat, not yfluxlat, should be set to 0 at the beginning of
clmain. So fluxlat is defined for a given type of surface even if
there is no point of this type at the current time step.

fluxlat is defined at each time step in physiq, no need for the save
attribute.

1 guez 54 module interfsurf_hq_m
2    
3     implicit none
4    
5     contains
6    
7 guez 209 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 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 72 USE albsno_m, ONLY: albsno
23 guez 101 use calbeta_m, only: calbeta
24 guez 72 USE calcul_fluxs_m, ONLY: calcul_fluxs
25 guez 209 use clesphys2, only: soil_model
26 guez 98 USE dimphy, ONLY: klon
27 guez 72 USE fonte_neige_m, ONLY: fonte_neige
28 guez 207 USE indicesol, ONLY: epsfra, is_lic, is_oce, is_sic, is_ter
29 guez 202 USE interface_surf, ONLY: run_off_lic, conf_interface
30 guez 72 USE interfsur_lim_m, ONLY: interfsur_lim
31 guez 202 use read_sst_m, only: read_sst
32 guez 101 use soil_m, only: soil
33 guez 178 USE suphec_m, ONLY: rcpd, rtt
34 guez 54
35 guez 99 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 guez 101 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 guez 106 integer, intent(in):: knindex(:) ! (knon)
42 guez 101 ! index des points de la surface a traiter
43    
44     logical, intent(IN):: debut ! 1er appel a la physique
45 guez 54 ! (si false calcul simplifie des fluxs sur les continents)
46 guez 101
47 guez 208 REAL, intent(inout):: tsoil(:, :) ! (knon, nsoilmx)
48 guez 101
49     REAL, intent(INOUT):: qsol(klon)
50     ! column-density of water in soil, in kg m-2
51    
52 guez 99 real, dimension(klon), intent(IN):: u1_lay, v1_lay
53 guez 54 ! u1_lay vitesse u 1ere couche
54     ! v1_lay vitesse v 1ere couche
55 guez 99 real, dimension(klon), intent(IN):: temp_air, spechum
56 guez 54 ! temp_air temperature de l'air 1ere couche
57     ! spechum humidite specifique 1ere couche
58 guez 99 real, dimension(klon), intent(INOUT):: tq_cdrag
59 guez 54 ! tq_cdrag cdrag
60 guez 99 real, dimension(klon), intent(IN):: petAcoef, peqAcoef
61 guez 54 ! petAcoef coeff. A de la resolution de la CL pour t
62     ! peqAcoef coeff. A de la resolution de la CL pour q
63 guez 99 real, dimension(klon), intent(IN):: petBcoef, peqBcoef
64 guez 54 ! petBcoef coeff. B de la resolution de la CL pour t
65     ! peqBcoef coeff. B de la resolution de la CL pour q
66 guez 101
67     real, intent(IN):: precip_rain(klon)
68 guez 175 ! precipitation, liquid water mass flux (kg / m2 / s), positive down
69 guez 101
70     real, intent(IN):: precip_snow(klon)
71 guez 175 ! precipitation, solid water mass flux (kg / m2 / s), positive down
72 guez 101
73 guez 154 REAL, INTENT(INOUT):: fder(klon) ! derivee des flux (pour le couplage)
74     real, intent(IN):: rugos(klon) ! rugosite
75     real, intent(IN):: rugoro(klon) ! rugosite orographique
76 guez 101 real, intent(INOUT):: snow(klon), qsurf(klon)
77 guez 150 real, intent(IN):: tsurf(:) ! (knon) temp\'erature de surface
78 guez 104 real, dimension(klon), intent(IN):: p1lay
79 guez 54 ! p1lay pression 1er niveau (milieu de couche)
80 guez 99 real, dimension(klon), intent(IN):: ps
81 guez 54 ! ps pression au sol
82 guez 175
83 guez 99 REAL, DIMENSION(klon), INTENT(INOUT):: radsol
84 guez 175 ! rayonnement net au sol (LW + SW)
85    
86 guez 206 real, intent(OUT):: evap(:) ! (knon) evaporation totale
87 guez 214
88 guez 206 real, intent(OUT):: flux_t(:) ! (knon) flux de chaleur sensible
89 guez 214 ! (Cp T) à la surface, positif vers le bas, W / m2
90    
91     real, intent(OUT):: fluxlat(:) ! (knon) flux de chaleur latente
92 guez 99 real, dimension(klon), intent(OUT):: dflux_l, dflux_s
93 guez 207 real, intent(OUT):: tsurf_new(:) ! (knon) temp\'erature au sol
94 guez 156 real, intent(OUT):: albedo(:) ! (knon) albedo
95 guez 154 real, intent(OUT):: z0_new(klon) ! surface roughness
96 guez 202
97     real, intent(in):: pctsrf_new_sic(:) ! (klon)
98     ! nouvelle repartition des surfaces
99    
100 guez 175 real, intent(INOUT):: agesno(:) ! (knon)
101 guez 54
102 guez 150 ! Flux d'eau "perdue" par la surface et n\'ecessaire pour que limiter la
103 guez 175 ! hauteur de neige, en kg / m2 / s
104 guez 54 !jld a rajouter real, dimension(klon), intent(INOUT):: fqcalving
105     real, dimension(klon), intent(INOUT):: fqcalving
106 guez 99
107     ! Flux thermique utiliser pour fondre la neige
108     !jld a rajouter real, dimension(klon), intent(INOUT):: ffonte
109     real, dimension(klon), intent(INOUT):: ffonte
110    
111     real, dimension(klon), intent(INOUT):: run_off_lic_0
112     ! run_off_lic_0 runoff glacier du pas de temps precedent
113    
114     ! Local:
115 guez 207 REAL soilcap(knon)
116     REAL soilflux(knon)
117 guez 175 logical:: first_call = .true.
118     integer ii
119 guez 54 real, dimension(klon):: cal, beta, dif_grnd, capsol
120 guez 175 real, parameter:: calice = 1. / (5.1444e6 * 0.15), tau_gl = 86400. * 5.
121     real, parameter:: calsno = 1. / (2.3867e6 * 0.15)
122 guez 104 real tsurf_temp(knon)
123 guez 174 real alb_neig(knon)
124     real zfra(knon)
125 guez 208 REAL, PARAMETER:: fmagic = 1. ! facteur magique pour r\'egler l'alb\'edo
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 guez 208 "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 208 CALL soil(dtime, is_ter, snow(:knon), tsurf, tsoil, soilcap, soilflux)
181 guez 207 cal(1:knon) = RCPD / soilcap
182     radsol(1:knon) = radsol(1:knon) + soilflux
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 guez 214 fluxlat, 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 cal = 0.
211     beta = 1.
212     dif_grnd = 0.
213     agesno = 0.
214 guez 175 call calcul_fluxs(dtime, tsurf_temp, p1lay(:knon), cal(:knon), &
215     beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
216     radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
217     u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
218 guez 206 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap, &
219 guez 214 fluxlat, flux_t, dflux_s(:knon), dflux_l(:knon))
220 guez 154 fder = fder + dflux_s + dflux_l
221 guez 209 albedo = alboc_cd(rmu0(knindex)) * fmagic
222 guez 54 z0_new = sqrt(rugos**2 + rugoro**2)
223 guez 104 case (is_sic)
224 guez 54 ! Surface "glace de mer" appel a l'interface avec l'ocean
225    
226 guez 99 DO ii = 1, knon
227     tsurf_new(ii) = tsurf(ii)
228 guez 202 IF (pctsrf_new_sic(knindex(ii)) < EPSFRA) then
229 guez 175 snow(ii) = 0.
230 guez 99 tsurf_new(ii) = RTT - 1.8
231 guez 154 IF (soil_model) tsoil(ii, :) = RTT - 1.8
232 guez 99 endif
233     enddo
234 guez 54
235 guez 202 CALL calbeta(is_sic, snow(:knon), qsol(:knon), beta(:knon), &
236 guez 101 capsol(:knon), dif_grnd(:knon))
237 guez 54
238 guez 99 IF (soil_model) THEN
239 guez 208 CALL soil(dtime, is_sic, snow(:knon), tsurf_new, tsoil, soilcap, &
240     soilflux)
241 guez 207 cal(1:knon) = RCPD / soilcap
242     radsol(1:knon) = radsol(1:knon) + soilflux
243 guez 99 dif_grnd = 0.
244 guez 54 ELSE
245 guez 175 dif_grnd = 1. / tau_gl
246 guez 99 cal = RCPD * calice
247 guez 175 WHERE (snow > 0.) cal = RCPD * calsno
248 guez 54 ENDIF
249 guez 99 tsurf_temp = tsurf_new
250 guez 175 beta = 1.
251 guez 54
252 guez 171 CALL calcul_fluxs(dtime, tsurf_temp, p1lay(:knon), cal(:knon), &
253 guez 104 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
254 guez 116 radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
255     u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
256 guez 206 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap, &
257 guez 214 fluxlat, flux_t, dflux_s(:knon), dflux_l(:knon))
258 guez 54
259 guez 202 CALL fonte_neige(is_sic, dtime, tsurf_temp, p1lay(:knon), beta(:knon), &
260 guez 116 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
261     precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
262     spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
263     peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, &
264 guez 206 evap, fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
265 guez 54
266 guez 174 ! Compute the albedo:
267 guez 54
268 guez 175 CALL albsno(dtime, agesno, alb_neig, precip_snow(:knon))
269     WHERE (snow(:knon) < 0.0001) agesno = 0.
270     zfra = MAX(0., MIN(1., snow(:knon) / (snow(:knon) + 10.)))
271     albedo = alb_neig * zfra + 0.6 * (1. - zfra)
272 guez 54
273 guez 154 fder = fder + dflux_s + dflux_l
274 guez 191 z0_new = SQRT(0.002**2 + rugoro**2)
275 guez 104 case (is_lic)
276 guez 54 if (.not. allocated(run_off_lic)) then
277 guez 101 allocate(run_off_lic(knon))
278 guez 54 run_off_lic = 0.
279     endif
280    
281     ! Surface "glacier continentaux" appel a l'interface avec le sol
282    
283     IF (soil_model) THEN
284 guez 208 CALL soil(dtime, is_lic, snow(:knon), tsurf, tsoil, soilcap, soilflux)
285 guez 207 cal(1:knon) = RCPD / soilcap
286     radsol(1:knon) = radsol(1:knon) + soilflux
287 guez 54 ELSE
288     cal = RCPD * calice
289 guez 175 WHERE (snow > 0.) cal = RCPD * calsno
290 guez 54 ENDIF
291 guez 175 beta = 1.
292     dif_grnd = 0.
293 guez 54
294 guez 171 call calcul_fluxs(dtime, tsurf, p1lay(:knon), cal(:knon), &
295 guez 116 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
296     radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
297     u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
298 guez 206 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap, &
299 guez 214 fluxlat, flux_t, dflux_s(:knon), dflux_l(:knon))
300 guez 54
301 guez 202 call fonte_neige(is_lic, dtime, tsurf, p1lay(:knon), beta(:knon), &
302 guez 116 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
303     precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
304     spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
305     peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, &
306 guez 206 evap, fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
307 guez 54
308     ! calcul albedo
309 guez 175 CALL albsno(dtime, agesno, alb_neig, precip_snow(:knon))
310     WHERE (snow(:knon) < 0.0001) agesno = 0.
311 guez 156 albedo = 0.77
312 guez 54
313     ! Rugosite
314     z0_new = rugoro
315 guez 104 case default
316 guez 101 print *, 'Index surface = ', nisurf
317 guez 175 call abort_gcm("interfsurf_hq", 'Index surface non valable')
318 guez 104 end select
319 guez 54
320     END SUBROUTINE interfsurf_hq
321    
322     end module interfsurf_hq_m

  ViewVC Help
Powered by ViewVC 1.1.21