/[lmdze]/trunk/Sources/phylmd/Interface_surf/interfsurf_hq.f
ViewVC logotype

Annotation of /trunk/Sources/phylmd/Interface_surf/interfsurf_hq.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 202 - (hide annotations)
Wed Jun 8 12:23:41 2016 UTC (7 years, 11 months ago) by guez
File size: 12979 byte(s)
Promoted lmt_pas from local variable of physiq to variable of module
conf_gcm_m.

Removed variable run_off of module interface_surf. Was not
used. Called run_off_ter in LMDZ, but not used nor printed there
either.

Simplified logic in interfoce_lim. The way it was convoluted with
interfsurf_hq and clmain was quite a mess. Extracted reading of SST
into a separate procedure: read_sst. We do not need SST and pctsrf_new
at the same time: SST is not needed for sea-ice surface. I did not
like this programming: going through the procedure repeatedly for
different purposes and testing inside whether there was something to
do or it was already done. Reading is now only controlled by itap and
lmt_pas, instead of debut, jour, jour_lu and deja_lu. Now we do not
copy from pct_tmp to pctsrf_new every time step.

Simplified processing of pctsrf in clmain and below. It was quite
troubling: pctsrf_new was intent out in interfoce_lim but only defined
for ocean and sea-ice. Also the idea of having arrays for all
surfaces, pcsrf and pctsrf_new, in interfsurf_hq, which is called for
a particular surface, was troubling. pctsrf_new for all surfaces was
intent out in intefsurf_hq, but not defined for all surfaces at each
call. Removed argument pctsrf_new of clmain: was a duplicate of pctsrf
on output, and not used in physiq. Replaced pctsrf_new in clmain by
pctsrf_new_oce and pctsrf_new_sic, which were the only ones modified.

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

  ViewVC Help
Powered by ViewVC 1.1.21