/[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 100 - (hide annotations)
Wed Jul 2 19:07:58 2014 UTC (9 years, 10 months ago) by guez
File size: 21294 byte(s)
Removed unused variable tmp_rlic of module interface_surf.

Removed useless call to gath2cpl in procedure interfsurf_hq. Removed
then uncalled procedure gath2cpl.

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

  ViewVC Help
Powered by ViewVC 1.1.21