/[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 209 - (hide annotations)
Wed Dec 7 17:37:21 2016 UTC (7 years, 5 months ago) by guez
Original Path: trunk/Sources/phylmd/Interface_surf/interfsurf_hq.f
File size: 12681 byte(s)
The program did not work with cycle_diurne set to false. mu0 in
physiq, which is supposed to be a cosine, was set to -999.999. So prmu
in swu had a value of the order of 1e3. So zrmum1 in sw2s had a value
of the order of 1e3. So zrayl in sw2s had a value of the order of
1e15. So ztray and ptauaz in swclr also had a large value. So zcorae
at line 138 in swclr had a large negative value, which resulted in
overflow at line 138.

This assignment of -999.999 to mu0 dates from somewhere between
revisions 348 and 524 of LMDZ. It was corrected in revision 1068 of
LMDZ with a call to angle which was present in revision 348. However,
procedure angle was removed from LMDZE in revision 22 because it was
not used. Hesitated to bring back angle but, finally, just removed the
option of having no diurnal cycle.

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     real, intent(OUT):: flux_t(:) ! (knon) flux de chaleur sensible
88     real, dimension(klon), intent(OUT):: fluxlat ! flux de chaleur latente
89 guez 99 real, dimension(klon), intent(OUT):: dflux_l, dflux_s
90 guez 207 real, intent(OUT):: tsurf_new(:) ! (knon) temp\'erature au sol
91 guez 156 real, intent(OUT):: albedo(:) ! (knon) albedo
92 guez 154 real, intent(OUT):: z0_new(klon) ! surface roughness
93 guez 202
94     real, intent(in):: pctsrf_new_sic(:) ! (klon)
95     ! nouvelle repartition des surfaces
96    
97 guez 175 real, intent(INOUT):: agesno(:) ! (knon)
98 guez 54
99 guez 150 ! Flux d'eau "perdue" par la surface et n\'ecessaire pour que limiter la
100 guez 175 ! hauteur de neige, en kg / m2 / s
101 guez 54 !jld a rajouter real, dimension(klon), intent(INOUT):: fqcalving
102     real, dimension(klon), intent(INOUT):: fqcalving
103 guez 99
104     ! Flux thermique utiliser pour fondre la neige
105     !jld a rajouter real, dimension(klon), intent(INOUT):: ffonte
106     real, dimension(klon), intent(INOUT):: ffonte
107    
108     real, dimension(klon), intent(INOUT):: run_off_lic_0
109     ! run_off_lic_0 runoff glacier du pas de temps precedent
110    
111     ! Local:
112 guez 207 REAL soilcap(knon)
113     REAL soilflux(knon)
114 guez 175 logical:: first_call = .true.
115     integer ii
116 guez 54 real, dimension(klon):: cal, beta, dif_grnd, capsol
117 guez 175 real, parameter:: calice = 1. / (5.1444e6 * 0.15), tau_gl = 86400. * 5.
118     real, parameter:: calsno = 1. / (2.3867e6 * 0.15)
119 guez 104 real tsurf_temp(knon)
120 guez 174 real alb_neig(knon)
121     real zfra(knon)
122 guez 208 REAL, PARAMETER:: fmagic = 1. ! facteur magique pour r\'egler l'alb\'edo
123 guez 54
124     !-------------------------------------------------------------
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 guez 72 call conf_interface
131 guez 175
132 guez 54 if (nisurf /= is_ter .and. klon > 1) then
133 guez 101 print *, ' nisurf = ', nisurf, ' /= is_ter = ', is_ter
134     print *, 'or on doit commencer par les surfaces continentales'
135 guez 175 call abort_gcm("interfsurf_hq", &
136     'On doit commencer par les surfaces continentales')
137 guez 54 endif
138 guez 175
139 guez 101 if (is_oce > is_sic) then
140 guez 175 print *, 'is_oce = ', is_oce, '> is_sic = ', is_sic
141     call abort_gcm("interfsurf_hq", &
142 guez 208 "L'ocean doit etre traite avant la banquise")
143 guez 54 endif
144 guez 175
145     first_call = .false.
146 guez 54 endif
147    
148     ! Initialisations diverses
149    
150 guez 175 ffonte(1:knon) = 0.
151     fqcalving(1:knon) = 0.
152 guez 54 cal = 999999.
153     beta = 999999.
154     dif_grnd = 999999.
155     capsol = 999999.
156     z0_new = 999999.
157     tsurf_new = 999999.
158    
159     ! Aiguillage vers les differents schemas de surface
160    
161 guez 104 select case (nisurf)
162     case (is_ter)
163 guez 171 ! Surface "terre", appel \`a l'interface avec les sols continentaux
164 guez 54
165     ! Calcul age de la neige
166    
167 guez 174 ! Read albedo from the file containing boundary conditions then
168     ! add the albedo of snow:
169    
170 guez 191 call interfsur_lim(dtime, jour, knindex, debut, albedo, z0_new)
171 guez 54
172 guez 174 ! Calcul snow et qsurf, hydrologie adapt\'ee
173 guez 202 CALL calbeta(is_ter, snow(:knon), qsol(:knon), beta(:knon), &
174 guez 101 capsol(:knon), dif_grnd(:knon))
175 guez 54
176 guez 99 IF (soil_model) THEN
177 guez 208 CALL soil(dtime, is_ter, snow(:knon), tsurf, tsoil, soilcap, soilflux)
178 guez 207 cal(1:knon) = RCPD / soilcap
179     radsol(1:knon) = radsol(1:knon) + soilflux
180 guez 99 ELSE
181     cal = RCPD * capsol
182     ENDIF
183 guez 171
184     CALL calcul_fluxs(dtime, tsurf, p1lay(:knon), cal(:knon), &
185 guez 116 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
186     radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
187     u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
188 guez 206 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap, &
189     fluxlat(:knon), flux_t, dflux_s(:knon), dflux_l(:knon))
190 guez 54
191 guez 202 CALL fonte_neige(is_ter, dtime, tsurf, p1lay(:knon), beta(:knon), &
192 guez 116 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
193     precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
194     spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
195     peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, &
196 guez 206 evap, fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
197 guez 54
198 guez 175 call albsno(dtime, agesno, alb_neig, precip_snow(:knon))
199     where (snow(:knon) < 0.0001) agesno = 0.
200     zfra = max(0., min(1., snow(:knon) / (snow(:knon) + 10.)))
201 guez 174 albedo = alb_neig * zfra + albedo * (1. - zfra)
202 guez 101 z0_new = sqrt(z0_new**2 + rugoro**2)
203 guez 104 case (is_oce)
204 guez 175 ! Surface "oc\'ean", appel \`a l'interface avec l'oc\'ean
205    
206 guez 202 call read_sst(dtime, jour, knindex, debut, tsurf_temp)
207 guez 54 cal = 0.
208     beta = 1.
209     dif_grnd = 0.
210     agesno = 0.
211 guez 175 call calcul_fluxs(dtime, tsurf_temp, p1lay(:knon), cal(:knon), &
212     beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
213     radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
214     u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
215 guez 206 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap, &
216     fluxlat(:knon), flux_t, dflux_s(:knon), dflux_l(:knon))
217 guez 154 fder = fder + dflux_s + dflux_l
218 guez 209 albedo = alboc_cd(rmu0(knindex)) * fmagic
219 guez 54 z0_new = sqrt(rugos**2 + rugoro**2)
220 guez 104 case (is_sic)
221 guez 54 ! Surface "glace de mer" appel a l'interface avec l'ocean
222    
223 guez 99 DO ii = 1, knon
224     tsurf_new(ii) = tsurf(ii)
225 guez 202 IF (pctsrf_new_sic(knindex(ii)) < EPSFRA) then
226 guez 175 snow(ii) = 0.
227 guez 99 tsurf_new(ii) = RTT - 1.8
228 guez 154 IF (soil_model) tsoil(ii, :) = RTT - 1.8
229 guez 99 endif
230     enddo
231 guez 54
232 guez 202 CALL calbeta(is_sic, snow(:knon), qsol(:knon), beta(:knon), &
233 guez 101 capsol(:knon), dif_grnd(:knon))
234 guez 54
235 guez 99 IF (soil_model) THEN
236 guez 208 CALL soil(dtime, is_sic, snow(:knon), tsurf_new, tsoil, soilcap, &
237     soilflux)
238 guez 207 cal(1:knon) = RCPD / soilcap
239     radsol(1:knon) = radsol(1:knon) + soilflux
240 guez 99 dif_grnd = 0.
241 guez 54 ELSE
242 guez 175 dif_grnd = 1. / tau_gl
243 guez 99 cal = RCPD * calice
244 guez 175 WHERE (snow > 0.) cal = RCPD * calsno
245 guez 54 ENDIF
246 guez 99 tsurf_temp = tsurf_new
247 guez 175 beta = 1.
248 guez 54
249 guez 171 CALL calcul_fluxs(dtime, tsurf_temp, p1lay(:knon), cal(:knon), &
250 guez 104 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
251 guez 116 radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
252     u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
253 guez 206 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap, &
254     fluxlat(:knon), flux_t, dflux_s(:knon), dflux_l(:knon))
255 guez 54
256 guez 202 CALL fonte_neige(is_sic, dtime, tsurf_temp, p1lay(:knon), beta(:knon), &
257 guez 116 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
258     precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
259     spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
260     peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, &
261 guez 206 evap, fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
262 guez 54
263 guez 174 ! Compute the albedo:
264 guez 54
265 guez 175 CALL albsno(dtime, agesno, alb_neig, precip_snow(:knon))
266     WHERE (snow(:knon) < 0.0001) agesno = 0.
267     zfra = MAX(0., MIN(1., snow(:knon) / (snow(:knon) + 10.)))
268     albedo = alb_neig * zfra + 0.6 * (1. - zfra)
269 guez 54
270 guez 154 fder = fder + dflux_s + dflux_l
271 guez 191 z0_new = SQRT(0.002**2 + rugoro**2)
272 guez 104 case (is_lic)
273 guez 54 if (.not. allocated(run_off_lic)) then
274 guez 101 allocate(run_off_lic(knon))
275 guez 54 run_off_lic = 0.
276     endif
277    
278     ! Surface "glacier continentaux" appel a l'interface avec le sol
279    
280     IF (soil_model) THEN
281 guez 208 CALL soil(dtime, is_lic, snow(:knon), tsurf, tsoil, soilcap, soilflux)
282 guez 207 cal(1:knon) = RCPD / soilcap
283     radsol(1:knon) = radsol(1:knon) + soilflux
284 guez 54 ELSE
285     cal = RCPD * calice
286 guez 175 WHERE (snow > 0.) cal = RCPD * calsno
287 guez 54 ENDIF
288 guez 175 beta = 1.
289     dif_grnd = 0.
290 guez 54
291 guez 171 call calcul_fluxs(dtime, tsurf, p1lay(:knon), cal(:knon), &
292 guez 116 beta(:knon), tq_cdrag(:knon), ps(:knon), qsurf(:knon), &
293     radsol(:knon), dif_grnd(:knon), temp_air(:knon), spechum(:knon), &
294     u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), peqAcoef(:knon), &
295 guez 206 petBcoef(:knon), peqBcoef(:knon), tsurf_new, evap, &
296     fluxlat(:knon), flux_t, dflux_s(:knon), dflux_l(:knon))
297 guez 54
298 guez 202 call fonte_neige(is_lic, dtime, tsurf, p1lay(:knon), beta(:knon), &
299 guez 116 tq_cdrag(:knon), ps(:knon), precip_rain(:knon), &
300     precip_snow(:knon), snow(:knon), qsol(:knon), temp_air(:knon), &
301     spechum(:knon), u1_lay(:knon), v1_lay(:knon), petAcoef(:knon), &
302     peqAcoef(:knon), petBcoef(:knon), peqBcoef(:knon), tsurf_new, &
303 guez 206 evap, fqcalving(:knon), ffonte(:knon), run_off_lic_0(:knon))
304 guez 54
305     ! calcul albedo
306 guez 175 CALL albsno(dtime, agesno, alb_neig, precip_snow(:knon))
307     WHERE (snow(:knon) < 0.0001) agesno = 0.
308 guez 156 albedo = 0.77
309 guez 54
310     ! Rugosite
311     z0_new = rugoro
312 guez 104 case default
313 guez 101 print *, 'Index surface = ', nisurf
314 guez 175 call abort_gcm("interfsurf_hq", 'Index surface non valable')
315 guez 104 end select
316 guez 54
317     END SUBROUTINE interfsurf_hq
318    
319     end module interfsurf_hq_m

  ViewVC Help
Powered by ViewVC 1.1.21