/[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 99 - (show annotations)
Wed Jul 2 18:39:15 2014 UTC (9 years, 10 months ago) by guez
File size: 21506 byte(s)
Created procedure test_disvert (following LMDZ). Added procedures
hybrid and funcd in module disvert_m. Upgraded compute_ab from
internal procedure of disvert to module procedure. Added variables y,
ya in module disvert_m. Upgraded s from local variable of procedure
disvert to module variable.

Renamed allowed value of variable vert_sampling in procedure disvert
from "read" to "read_hybrid". Added possibility to read pressure
values, value "read_pressure". Replaced vertical distribution for
value "param" by the distribution "strato_correct" from LMDZ (but kept
the value "param"). In case "tropo", replaced 1 by dsigmin (following
LMDZ). In case "strato", replaced 0.3 by dsigmin (following LMDZ).

Changed computation of bp in procedure compute_ab.

Removed debugindex case in clmain. Removed useless argument rlon of
procedure clmain. Removed useless variables ytaux, ytauy of procedure
clmain.

Removed intermediary variables tsol, qsol, tsolsrf, tslab in procedure
etat0.

Removed variable ok_veget:. coupling with the model Orchid is not
possible. Removed variable ocean: modeling an ocean slab is not
possible.

Removed useless variables tmp_rriv and tmp_rcoa from module
interface_surf.

Moved initialization of variables da, mp, phi in procedure physiq to
to inside the test iflag_con >= 3.

1 module interfsurf_hq_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE interfsurf_hq(itime, dtime, jour, rmu0, iim, jjm, nisurf, knon, &
8 knindex, pctsrf, rlat, debut, soil_model, nsoilmx, tsoil, qsol, &
9 u1_lay, v1_lay, temp_air, spechum, tq_cdrag, petAcoef, peqAcoef, &
10 petBcoef, peqBcoef, precip_rain, precip_snow, fder, rugos, rugoro, &
11 snow, qsurf, tsurf, p1lay, ps, radsol, evap, fluxsens, fluxlat, &
12 dflux_l, dflux_s, tsurf_new, alb_new, alblw, z0_new, pctsrf_new, &
13 agesno, fqcalving, ffonte, run_off_lic_0, flux_o, flux_g, tslab, seaice)
14
15 ! Cette routine sert d'aiguillage entre l'atmosphère et la surface
16 ! en général (sols continentaux, océans, glaces) pour les flux de
17 ! chaleur et d'humidité.
18
19 ! Laurent Fairhead, 02/2000
20
21 USE abort_gcm_m, ONLY: abort_gcm
22 USE albsno_m, ONLY: albsno
23 USE calcul_fluxs_m, ONLY: calcul_fluxs
24 USE dimphy, ONLY: klon
25 USE fonte_neige_m, ONLY: fonte_neige
26 USE gath2cpl_m, ONLY: gath2cpl
27 USE indicesol, ONLY: epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf
28 USE interface_surf, ONLY: coastalflow, riverflow, run_off, &
29 run_off_lic, conf_interface, tmp_rlic
30 USE interfoce_lim_m, ONLY: interfoce_lim
31 USE interfoce_slab_m, ONLY: interfoce_slab
32 USE interfsur_lim_m, ONLY: interfsur_lim
33 USE suphec_m, ONLY: rcpd, rlstt, rlvtt, rtt
34
35 integer, intent(IN):: itime ! numero du pas de temps
36 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 integer, intent(IN):: iim, jjm
40 ! iim, jjm nbres de pts de grille
41 integer, intent(IN):: nisurf
42 ! nisurf index de la surface a traiter (1 = sol continental)
43 integer, intent(IN):: knon
44 ! knon nombre de points de la surface a traiter
45 integer, intent(in):: knindex(klon)
46 ! knindex index des points de la surface a traiter
47 real, intent(IN):: pctsrf(klon, nbsrf)
48 ! pctsrf tableau des pourcentages de surface de chaque maille
49 real, dimension(klon), intent(IN):: rlat
50 ! rlat latitudes
51 logical, intent(IN):: debut
52 ! debut logical: 1er appel a la physique
53 ! (si false calcul simplifie des fluxs sur les continents)
54 !! PB ajout pour soil
55 logical, intent(in):: soil_model
56 integer:: nsoilmx
57 REAL, DIMENSION(klon, nsoilmx):: tsoil
58 REAL, dimension(klon), intent(INOUT):: qsol
59 real, dimension(klon), intent(IN):: u1_lay, v1_lay
60 ! u1_lay vitesse u 1ere couche
61 ! v1_lay vitesse v 1ere couche
62 real, dimension(klon), intent(IN):: temp_air, spechum
63 ! temp_air temperature de l'air 1ere couche
64 ! spechum humidite specifique 1ere couche
65 real, dimension(klon), intent(INOUT):: tq_cdrag
66 ! tq_cdrag cdrag
67 real, dimension(klon), intent(IN):: petAcoef, peqAcoef
68 ! petAcoef coeff. A de la resolution de la CL pour t
69 ! peqAcoef coeff. A de la resolution de la CL pour q
70 real, dimension(klon), intent(IN):: petBcoef, peqBcoef
71 ! petBcoef coeff. B de la resolution de la CL pour t
72 ! peqBcoef coeff. B de la resolution de la CL pour q
73 real, dimension(klon), intent(IN):: precip_rain, precip_snow
74 ! precip_rain precipitation liquide
75 ! precip_snow precipitation solide
76 REAL, DIMENSION(klon), INTENT(INOUT):: fder
77 ! fder derivee des flux (pour le couplage)
78 real, dimension(klon), intent(IN):: rugos, rugoro
79 ! rugos rugosite
80 ! rugoro rugosite orographique
81 real, dimension(klon), intent(INOUT):: snow, qsurf
82 real, dimension(klon), intent(IN):: tsurf, p1lay
83 ! tsurf temperature de surface
84 ! p1lay pression 1er niveau (milieu de couche)
85 real, dimension(klon), intent(IN):: ps
86 ! ps pression au sol
87 REAL, DIMENSION(klon), INTENT(INOUT):: radsol
88 ! radsol rayonnement net aus sol (LW + SW)
89 real, dimension(klon), intent(INOUT):: evap
90 ! evap evaporation totale
91 real, dimension(klon), intent(OUT):: fluxsens, fluxlat
92 ! fluxsens flux de chaleur sensible
93 ! fluxlat flux de chaleur latente
94 real, dimension(klon), intent(OUT):: dflux_l, dflux_s
95 real, dimension(klon), intent(OUT):: tsurf_new, alb_new
96 ! tsurf_new temperature au sol
97 ! alb_new albedo
98 real, dimension(klon), intent(OUT):: alblw
99 real, dimension(klon), intent(OUT):: z0_new
100 ! z0_new surface roughness
101 real, dimension(klon, nbsrf), intent(OUT):: pctsrf_new
102 ! pctsrf_new nouvelle repartition des surfaces
103 real, dimension(klon), intent(INOUT):: agesno
104
105 ! Flux d'eau "perdue" par la surface et nécessaire pour que limiter la
106 ! hauteur de neige, en kg/m2/s
107 !jld a rajouter real, dimension(klon), intent(INOUT):: fqcalving
108 real, dimension(klon), intent(INOUT):: fqcalving
109
110 ! Flux thermique utiliser pour fondre la neige
111 !jld a rajouter real, dimension(klon), intent(INOUT):: ffonte
112 real, dimension(klon), intent(INOUT):: ffonte
113
114 real, dimension(klon), intent(INOUT):: run_off_lic_0
115 ! run_off_lic_0 runoff glacier du pas de temps precedent
116
117 !IM: "slab" ocean
118 real, dimension(klon), intent(OUT):: flux_o, flux_g
119 real, dimension(klon), intent(INOUT):: tslab
120 ! tslab temperature slab ocean
121 real, dimension(klon), intent(INOUT):: seaice ! glace de mer (kg/m2)
122
123 ! Local:
124
125 real, allocatable, dimension(:), save:: tmp_tslab
126 REAL, dimension(klon):: soilcap
127 REAL, dimension(klon):: soilflux
128
129 !IM: "slab" ocean
130 real, parameter:: t_grnd=271.35
131 real, dimension(klon):: zx_sl
132 integer i
133 real, allocatable, dimension(:), save:: tmp_flux_o, tmp_flux_g
134 real, allocatable, dimension(:), save:: tmp_radsol
135 real, allocatable, dimension(:, :), save:: tmp_pctsrf_slab
136 ! pctsrf_slab pourcentages (0-1) des sous-surfaces dans le slab
137 ! tmp_pctsrf_slab = pctsrf_slab
138 real, allocatable, dimension(:), save:: tmp_seaice
139
140 character (len = 20), save:: modname = 'interfsurf_hq'
141 character (len = 80):: abort_message
142 logical, save:: first_call = .true.
143 integer, save:: error
144 integer:: ii
145 logical, save:: check = .false.
146 real, dimension(klon):: cal, beta, dif_grnd, capsol
147 real, parameter:: calice=1.0/(5.1444e+06*0.15), tau_gl=86400.*5.
148 real, parameter:: calsno=1./(2.3867e+06*.15)
149 real, dimension(klon):: tsurf_temp
150 real, dimension(klon):: alb_neig, alb_eau
151 real, DIMENSION(klon):: zfra
152 INTEGER, dimension(1):: iloc
153 real, dimension(klon):: fder_prev
154 REAL, dimension(klon):: bidule
155
156 !-------------------------------------------------------------
157
158 if (check) write(*, *) 'Entree ', modname
159
160 ! On doit commencer par appeler les schemas de surfaces continentales
161 ! car l'ocean a besoin du ruissellement qui est y calcule
162
163 if (first_call) then
164 call conf_interface
165 if (nisurf /= is_ter .and. klon > 1) then
166 write(*, *)' *** Warning ***'
167 write(*, *)' nisurf = ', nisurf, ' /= is_ter = ', is_ter
168 write(*, *)'or on doit commencer par les surfaces continentales'
169 abort_message='voir ci-dessus'
170 call abort_gcm(modname, abort_message, 1)
171 endif
172 if ( is_oce > is_sic ) then
173 write(*, *)' *** Warning ***'
174 write(*, *)' Pour des raisons de sequencement dans le code'
175 write(*, *)' l''ocean doit etre traite avant la banquise'
176 write(*, *)' or is_oce = ', is_oce, '> is_sic = ', is_sic
177 abort_message='voir ci-dessus'
178 call abort_gcm(modname, abort_message, 1)
179 endif
180 endif
181 first_call = .false.
182
183 ! Initialisations diverses
184
185 ffonte(1:knon)=0.
186 fqcalving(1:knon)=0.
187
188 cal = 999999.
189 beta = 999999.
190 dif_grnd = 999999.
191 capsol = 999999.
192 alb_new = 999999.
193 z0_new = 999999.
194 alb_neig = 999999.
195 tsurf_new = 999999.
196 alblw = 999999.
197
198 !IM: "slab" ocean; initialisations
199 flux_o = 0.
200 flux_g = 0.
201
202 if (.not. allocated(tmp_flux_o)) then
203 allocate(tmp_flux_o(klon), stat = error)
204 DO i=1, knon
205 tmp_flux_o(knindex(i))=flux_o(i)
206 ENDDO
207 if (error /= 0) then
208 abort_message='Pb allocation tmp_flux_o'
209 call abort_gcm(modname, abort_message, 1)
210 endif
211 endif
212 if (.not. allocated(tmp_flux_g)) then
213 allocate(tmp_flux_g(klon), stat = error)
214 DO i=1, knon
215 tmp_flux_g(knindex(i))=flux_g(i)
216 ENDDO
217 if (error /= 0) then
218 abort_message='Pb allocation tmp_flux_g'
219 call abort_gcm(modname, abort_message, 1)
220 endif
221 endif
222 if (.not. allocated(tmp_radsol)) then
223 allocate(tmp_radsol(klon), stat = error)
224 if (error /= 0) then
225 abort_message='Pb allocation tmp_radsol'
226 call abort_gcm(modname, abort_message, 1)
227 endif
228 endif
229 DO i=1, knon
230 tmp_radsol(knindex(i))=radsol(i)
231 ENDDO
232 if (.not. allocated(tmp_pctsrf_slab)) then
233 allocate(tmp_pctsrf_slab(klon, nbsrf), stat = error)
234 if (error /= 0) then
235 abort_message='Pb allocation tmp_pctsrf_slab'
236 call abort_gcm(modname, abort_message, 1)
237 endif
238 DO i=1, klon
239 tmp_pctsrf_slab(i, 1:nbsrf)=pctsrf(i, 1:nbsrf)
240 ENDDO
241 endif
242
243 if (.not. allocated(tmp_seaice)) then
244 allocate(tmp_seaice(klon), stat = error)
245 if (error /= 0) then
246 abort_message='Pb allocation tmp_seaice'
247 call abort_gcm(modname, abort_message, 1)
248 endif
249 DO i=1, klon
250 tmp_seaice(i)=seaice(i)
251 ENDDO
252 endif
253
254 if (.not. allocated(tmp_tslab)) then
255 allocate(tmp_tslab(klon), stat = error)
256 if (error /= 0) then
257 abort_message='Pb allocation tmp_tslab'
258 call abort_gcm(modname, abort_message, 1)
259 endif
260 endif
261 DO i=1, klon
262 tmp_tslab(i)=tslab(i)
263 ENDDO
264
265 ! Aiguillage vers les differents schemas de surface
266
267 if (nisurf == is_ter) then
268 ! Surface "terre" appel a l'interface avec les sols continentaux
269
270 ! allocation du run-off
271 if (.not. allocated(coastalflow)) then
272 allocate(coastalflow(knon), stat = error)
273 if (error /= 0) then
274 abort_message='Pb allocation coastalflow'
275 call abort_gcm(modname, abort_message, 1)
276 endif
277 allocate(riverflow(knon), stat = error)
278 if (error /= 0) then
279 abort_message='Pb allocation riverflow'
280 call abort_gcm(modname, abort_message, 1)
281 endif
282 allocate(run_off(knon), stat = error)
283 if (error /= 0) then
284 abort_message='Pb allocation run_off'
285 call abort_gcm(modname, abort_message, 1)
286 endif
287 !cym
288 run_off=0.0
289 !cym
290
291 ALLOCATE (tmp_rlic(iim, jjm+1))
292 tmp_rlic = 0.0
293 else if (size(coastalflow) /= knon) then
294 write(*, *)'Bizarre, le nombre de points continentaux'
295 write(*, *)'a change entre deux appels. J''arrete ...'
296 abort_message='voir ci-dessus'
297 call abort_gcm(modname, abort_message, 1)
298 endif
299 coastalflow = 0.
300 riverflow = 0.
301
302 ! Calcul age de la neige
303
304 ! calcul albedo: lecture albedo fichier boundary conditions
305 ! puis ajout albedo neige
306 call interfsur_lim(itime, dtime, jour, nisurf, knon, knindex, &
307 debut, alb_new, z0_new)
308
309 ! calcul snow et qsurf, hydrol adapté
310 CALL calbeta(dtime, nisurf, knon, snow, qsol, beta, capsol, dif_grnd)
311
312 IF (soil_model) THEN
313 CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, &
314 soilflux)
315 cal(1:knon) = RCPD / soilcap(1:knon)
316 radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
317 ELSE
318 cal = RCPD * capsol
319 ENDIF
320 CALL calcul_fluxs( klon, knon, nisurf, dtime, &
321 tsurf, p1lay, cal, beta, tq_cdrag, ps, &
322 precip_rain, precip_snow, snow, qsurf, &
323 radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
324 petAcoef, peqAcoef, petBcoef, peqBcoef, &
325 tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
326
327 CALL fonte_neige( klon, knon, nisurf, dtime, &
328 tsurf, p1lay, cal, beta, tq_cdrag, ps, &
329 precip_rain, precip_snow, snow, qsol, &
330 radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
331 petAcoef, peqAcoef, petBcoef, peqBcoef, &
332 tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
333 fqcalving, ffonte, run_off_lic_0)
334
335 call albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
336 where (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
337 zfra(1:knon) = max(0.0, min(1.0, snow(1:knon)/(snow(1:knon)+10.0)))
338 alb_new(1 : knon) = alb_neig(1 : knon) *zfra(1:knon) + &
339 alb_new(1 : knon)*(1.0-zfra(1:knon))
340 z0_new = sqrt(z0_new**2+rugoro**2)
341 alblw(1 : knon) = alb_new(1 : knon)
342
343 ! Remplissage des pourcentages de surface
344 pctsrf_new(:, nisurf) = pctsrf(:, nisurf)
345 else if (nisurf == is_oce) then
346 ! Surface "ocean" appel a l'interface avec l'ocean
347 ! lecture conditions limites
348 call interfoce_lim(itime, dtime, jour, klon, nisurf, knon, knindex, &
349 debut, tsurf_new, pctsrf_new)
350
351 tsurf_temp = tsurf_new
352 cal = 0.
353 beta = 1.
354 dif_grnd = 0.
355 alb_neig = 0.
356 agesno = 0.
357
358 call calcul_fluxs( klon, knon, nisurf, dtime, &
359 tsurf_temp, p1lay, cal, beta, tq_cdrag, ps, &
360 precip_rain, precip_snow, snow, qsurf, &
361 radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
362 petAcoef, peqAcoef, petBcoef, peqBcoef, &
363 tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
364
365 fder_prev = fder
366 fder = fder_prev + dflux_s + dflux_l
367
368 iloc = maxloc(fder(1:klon))
369 if (check.and.fder(iloc(1))> 0.) then
370 WRITE(*, *)'**** Debug fder****'
371 WRITE(*, *)'max fder(', iloc(1), ') = ', fder(iloc(1))
372 WRITE(*, *)'fder_prev, dflux_s, dflux_l', fder_prev(iloc(1)), &
373 dflux_s(iloc(1)), dflux_l(iloc(1))
374 endif
375
376 !IM: flux ocean-atmosphere utile pour le "slab" ocean
377 DO i=1, knon
378 zx_sl(i) = RLVTT
379 if (tsurf_new(i) .LT. RTT) zx_sl(i) = RLSTT
380 flux_o(i) = fluxsens(i)-evap(i)*zx_sl(i)
381 tmp_flux_o(knindex(i)) = flux_o(i)
382 tmp_radsol(knindex(i))=radsol(i)
383 ENDDO
384
385 ! calcul albedo
386 if ( minval(rmu0) == maxval(rmu0) .and. minval(rmu0) == -999.999 ) then
387 CALL alboc(FLOAT(jour), rlat, alb_eau)
388 else ! cycle diurne
389 CALL alboc_cd(rmu0, alb_eau)
390 endif
391 DO ii =1, knon
392 alb_new(ii) = alb_eau(knindex(ii))
393 enddo
394
395 z0_new = sqrt(rugos**2 + rugoro**2)
396 alblw(1:knon) = alb_new(1:knon)
397 else if (nisurf == is_sic) then
398 if (check) write(*, *)'sea ice, nisurf = ', nisurf
399
400 ! Surface "glace de mer" appel a l'interface avec l'ocean
401
402 ! ! lecture conditions limites
403 CALL interfoce_lim(itime, dtime, jour, &
404 klon, nisurf, knon, knindex, &
405 debut, &
406 tsurf_new, pctsrf_new)
407
408 !IM cf LF
409 DO ii = 1, knon
410 tsurf_new(ii) = tsurf(ii)
411 !IMbad IF (pctsrf_new(ii, nisurf) < EPSFRA) then
412 IF (pctsrf_new(knindex(ii), nisurf) < EPSFRA) then
413 snow(ii) = 0.0
414 !IM cf LF/JLD tsurf(ii) = RTT - 1.8
415 tsurf_new(ii) = RTT - 1.8
416 IF (soil_model) tsoil(ii, :) = RTT -1.8
417 endif
418 enddo
419
420 CALL calbeta(dtime, nisurf, knon, snow, qsol, beta, capsol, dif_grnd)
421
422 IF (soil_model) THEN
423 CALL soil(dtime, nisurf, knon, snow, tsurf_new, tsoil, soilcap, &
424 soilflux)
425 cal(1:knon) = RCPD / soilcap(1:knon)
426 radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
427 dif_grnd = 0.
428 ELSE
429 dif_grnd = 1.0 / tau_gl
430 cal = RCPD * calice
431 WHERE (snow > 0.0) cal = RCPD * calsno
432 ENDIF
433 !IMbadtsurf_temp = tsurf
434 tsurf_temp = tsurf_new
435 beta = 1.0
436
437 CALL calcul_fluxs( klon, knon, nisurf, dtime, &
438 tsurf_temp, p1lay, cal, beta, tq_cdrag, ps, &
439 precip_rain, precip_snow, snow, qsurf, &
440 radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
441 petAcoef, peqAcoef, petBcoef, peqBcoef, &
442 tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
443
444 !IM: flux entre l'ocean et la glace de mer pour le "slab" ocean
445 DO i = 1, knon
446 flux_g(i) = 0.0
447
448 !IM: faire dependre le coefficient de conduction de la glace de mer
449 ! de l'epaisseur de la glace de mer, dans l'hypothese ou le coeff.
450 ! actuel correspond a 3m de glace de mer, cf. L.Li
451
452 ! IF(1.EQ.0) THEN
453 ! IF(siceh(i).GT.0.) THEN
454 ! new_dif_grnd(i) = dif_grnd(i)*3./siceh(i)
455 ! ELSE
456 ! new_dif_grnd(i) = 0.
457 ! ENDIF
458 ! ENDIF !(1.EQ.0) THEN
459
460 IF (cal(i).GT.1.0e-15) flux_g(i)=(tsurf_new(i)-t_grnd) &
461 * dif_grnd(i) *RCPD/cal(i)
462 ! & * new_dif_grnd(i) *RCPD/cal(i)
463 tmp_flux_g(knindex(i))=flux_g(i)
464 tmp_radsol(knindex(i))=radsol(i)
465 ENDDO
466
467 CALL fonte_neige( klon, knon, nisurf, dtime, &
468 tsurf_temp, p1lay, cal, beta, tq_cdrag, ps, &
469 precip_rain, precip_snow, snow, qsol, &
470 radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
471 petAcoef, peqAcoef, petBcoef, peqBcoef, &
472 tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
473 fqcalving, ffonte, run_off_lic_0)
474
475 ! calcul albedo
476
477 CALL albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
478 WHERE (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
479 zfra(1:knon) = MAX(0.0, MIN(1.0, snow(1:knon)/(snow(1:knon)+10.0)))
480 alb_new(1 : knon) = alb_neig(1 : knon) *zfra(1:knon) + &
481 0.6 * (1.0-zfra(1:knon))
482
483 fder_prev = fder
484 fder = fder_prev + dflux_s + dflux_l
485
486 iloc = maxloc(fder(1:klon))
487 if (check.and.fder(iloc(1))> 0.) then
488 WRITE(*, *)'**** Debug fder ****'
489 WRITE(*, *)'max fder(', iloc(1), ') = ', fder(iloc(1))
490 WRITE(*, *)'fder_prev, dflux_s, dflux_l', fder_prev(iloc(1)), &
491 dflux_s(iloc(1)), dflux_l(iloc(1))
492 endif
493
494
495 ! 2eme appel a interfoce pour le cumul et le passage des flux a l'ocean
496
497 z0_new = 0.002
498 z0_new = SQRT(z0_new**2+rugoro**2)
499 alblw(1:knon) = alb_new(1:knon)
500
501 else if (nisurf == is_lic) then
502
503 if (check) write(*, *)'glacier, nisurf = ', nisurf
504
505 if (.not. allocated(run_off_lic)) then
506 allocate(run_off_lic(knon), stat = error)
507 if (error /= 0) then
508 abort_message='Pb allocation run_off_lic'
509 call abort_gcm(modname, abort_message, 1)
510 endif
511 run_off_lic = 0.
512 endif
513
514 ! Surface "glacier continentaux" appel a l'interface avec le sol
515
516 IF (soil_model) THEN
517 CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, soilflux)
518 cal(1:knon) = RCPD / soilcap(1:knon)
519 radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
520 ELSE
521 cal = RCPD * calice
522 WHERE (snow > 0.0) cal = RCPD * calsno
523 ENDIF
524 beta = 1.0
525 dif_grnd = 0.0
526
527 call calcul_fluxs( klon, knon, nisurf, dtime, &
528 tsurf, p1lay, cal, beta, tq_cdrag, ps, &
529 precip_rain, precip_snow, snow, qsurf, &
530 radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
531 petAcoef, peqAcoef, petBcoef, peqBcoef, &
532 tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
533
534 call fonte_neige( klon, knon, nisurf, dtime, &
535 tsurf, p1lay, cal, beta, tq_cdrag, ps, &
536 precip_rain, precip_snow, snow, qsol, &
537 radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
538 petAcoef, peqAcoef, petBcoef, peqBcoef, &
539 tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
540 fqcalving, ffonte, run_off_lic_0)
541
542 ! passage du run-off des glaciers calcule dans fonte_neige au coupleur
543 bidule=0.
544 bidule(1:knon)= run_off_lic(1:knon)
545 call gath2cpl(bidule, tmp_rlic, klon, knon, iim, jjm, knindex)
546
547 ! calcul albedo
548
549 CALL albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
550 WHERE (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
551 zfra(1:knon) = MAX(0.0, MIN(1.0, snow(1:knon)/(snow(1:knon)+10.0)))
552 alb_new(1 : knon) = alb_neig(1 : knon)*zfra(1:knon) + &
553 0.6 * (1.0-zfra(1:knon))
554
555 !IM: plusieurs choix/tests sur l'albedo des "glaciers continentaux"
556 ! alb_new(1 : knon) = 0.6 !IM cf FH/GK
557 ! alb_new(1 : knon) = 0.82
558 ! alb_new(1 : knon) = 0.77 !211003 Ksta0.77
559 ! alb_new(1 : knon) = 0.8 !KstaTER0.8 & LMD_ARMIP5
560 !IM: KstaTER0.77 & LMD_ARMIP6
561 alb_new(1 : knon) = 0.77
562
563
564 ! Rugosite
565
566 z0_new = rugoro
567
568 ! Remplissage des pourcentages de surface
569
570 pctsrf_new(:, nisurf) = pctsrf(:, nisurf)
571
572 alblw(1:knon) = alb_new(1:knon)
573 else
574 write(*, *)'Index surface = ', nisurf
575 abort_message = 'Index surface non valable'
576 call abort_gcm(modname, abort_message, 1)
577 endif
578
579 END SUBROUTINE interfsurf_hq
580
581 end module interfsurf_hq_m

  ViewVC Help
Powered by ViewVC 1.1.21