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

  ViewVC Help
Powered by ViewVC 1.1.21