/[lmdze]/trunk/libf/phylmd/interface_surf.f90
ViewVC logotype

Annotation of /trunk/libf/phylmd/interface_surf.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 14 - (hide annotations)
Mon Jul 28 14:48:09 2008 UTC (15 years, 10 months ago) by guez
File size: 63372 byte(s)
Corrected bug as directed by Jean-Yves Grandpeix. "nent" in
"cv3_mixing" is an argument instead of a local variable.
1 guez 3 MODULE interface_surf
2    
3 guez 14 ! From phylmd/interface_surf.F90, version 1.8 2005/05/25 13:10:09
4 guez 3
5     ! Ce module regroupe toutes les routines gérant l'interface entre le modèle
6     ! atmosphérique et les modèles de surface (sols continentaux,
7     ! océans, glaces).
8     ! Les routines sont les suivantes:
9     ! interfsurf_hq : routine d'aiguillage vers les interfaces avec les
10     ! différents modèles de surface
11     ! interfoce_* : routines d'interface proprement dites
12    
13     ! L. Fairhead, LMD, 02/2000
14    
15     IMPLICIT none
16    
17     PRIVATE
18     PUBLIC :: interfsurf_hq
19    
20     ! run_off ruissellement total
21 guez 14 REAL, ALLOCATABLE, DIMENSION(:), SAVE :: run_off, run_off_lic
22     real, allocatable, dimension(:), save :: coastalflow, riverflow
23 guez 3
24 guez 14 REAL, ALLOCATABLE, DIMENSION(:, :), SAVE :: tmp_rriv, tmp_rcoa, tmp_rlic
25 guez 3 !! pour simuler la fonte des glaciers antarctiques
26 guez 14 REAL, ALLOCATABLE, DIMENSION(:, :), SAVE :: coeff_iceberg
27 guez 3 real, save :: surf_maille
28     real, save :: cte_flux_iceberg = 6.3e7
29     integer, save :: num_antarctic = 1
30     REAL, save :: tau_calv
31    
32     CONTAINS
33    
34     SUBROUTINE interfsurf_hq(itime, dtime, date0, jour, rmu0, &
35     & klon, iim, jjm, nisurf, knon, knindex, pctsrf, &
36 guez 14 & rlon, rlat, cufi, cvfi, &
37     & debut, lafin, ok_veget, soil_model, nsoilmx, tsoil, qsol, &
38 guez 3 & zlev, u1_lay, v1_lay, temp_air, spechum, epot_air, ccanopy, &
39     & tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
40     & precip_rain, precip_snow, sollw, sollwdown, swnet, swdown, &
41     & fder, taux, tauy, &
42     & windsp, &
43     & rugos, rugoro, &
44     & albedo, snow, qsurf, &
45     & tsurf, p1lay, ps, radsol, &
46     & ocean, npas, nexca, zmasq, &
47     & evap, fluxsens, fluxlat, dflux_l, dflux_s, &
48     & tsol_rad, tsurf_new, alb_new, alblw, emis_new, &
49 guez 14 & z0_new, pctsrf_new, agesno, fqcalving, ffonte, run_off_lic_0, &
50 guez 3 !IM "slab" ocean
51     & flux_o, flux_g, tslab, seaice)
52    
53     ! Cette routine sert d'aiguillage entre l'atmosphère et la surface
54 guez 14 ! en général (sols continentaux, océans, glaces) pour les flux de
55 guez 3 ! chaleur et d'humidité.
56     ! En pratique l'interface se fait entre la couche limite du modèle
57     ! atmosphérique ("clmain.F") et les routines de surface
58     ! ("sechiba", "oasis"...).
59    
60     ! L.Fairhead 02/2000
61    
62 guez 14 use abort_gcm_m, only: abort_gcm
63     use gath_cpl, only: gath2cpl
64     use indicesol
65     use YOMCST
66     use albsno_m, only: albsno
67    
68     ! Parametres d'entree
69 guez 3 ! input:
70     ! klon nombre total de points de grille
71     ! iim, jjm nbres de pts de grille
72     ! dtime pas de temps de la physique (en s)
73     ! date0 jour initial
74     ! jour jour dans l'annee en cours,
75     ! rmu0 cosinus de l'angle solaire zenithal
76     ! nexca pas de temps couplage
77     ! nisurf index de la surface a traiter (1 = sol continental)
78     ! knon nombre de points de la surface a traiter
79     ! knindex index des points de la surface a traiter
80     ! pctsrf tableau des pourcentages de surface de chaque maille
81     ! rlon longitudes
82     ! rlat latitudes
83 guez 14 ! cufi, cvfi resolution des mailles en x et y (m)
84 guez 3 ! debut logical: 1er appel a la physique
85     ! lafin logical: dernier appel a la physique
86     ! ok_veget logical: appel ou non au schema de surface continental
87     ! (si false calcul simplifie des fluxs sur les continents)
88     ! zlev hauteur de la premiere couche
89     ! u1_lay vitesse u 1ere couche
90     ! v1_lay vitesse v 1ere couche
91     ! temp_air temperature de l'air 1ere couche
92     ! spechum humidite specifique 1ere couche
93     ! epot_air temp potentielle de l'air
94     ! ccanopy concentration CO2 canopee
95     ! tq_cdrag cdrag
96     ! petAcoef coeff. A de la resolution de la CL pour t
97     ! peqAcoef coeff. A de la resolution de la CL pour q
98     ! petBcoef coeff. B de la resolution de la CL pour t
99     ! peqBcoef coeff. B de la resolution de la CL pour q
100     ! precip_rain precipitation liquide
101     ! precip_snow precipitation solide
102     ! sollw flux IR net a la surface
103     ! sollwdown flux IR descendant a la surface
104     ! swnet flux solaire net
105     ! swdown flux solaire entrant a la surface
106     ! albedo albedo de la surface
107     ! tsurf temperature de surface
108     ! tslab temperature slab ocean
109     ! pctsrf_slab pourcentages (0-1) des sous-surfaces dans le slab
110     ! tmp_pctsrf_slab = pctsrf_slab
111     ! p1lay pression 1er niveau (milieu de couche)
112     ! ps pression au sol
113     ! radsol rayonnement net aus sol (LW + SW)
114 guez 12 ! ocean type d'ocean utilise ("force" ou "slab" mais pas "couple")
115 guez 3 ! fder derivee des flux (pour le couplage)
116     ! taux, tauy tension de vents
117     ! windsp module du vent a 10m
118     ! rugos rugosite
119     ! zmasq masque terre/ocean
120     ! rugoro rugosite orographique
121     ! run_off_lic_0 runoff glacier du pas de temps precedent
122     integer, intent(IN) :: itime ! numero du pas de temps
123     integer, intent(IN) :: iim, jjm
124     integer, intent(IN) :: klon
125     real, intent(IN) :: dtime
126     real, intent(IN) :: date0
127     integer, intent(IN) :: jour
128     real, intent(IN) :: rmu0(klon)
129     integer, intent(IN) :: nisurf
130     integer, intent(IN) :: knon
131     integer, dimension(klon), intent(in) :: knindex
132 guez 14 real, dimension(klon, nbsrf), intent(IN) :: pctsrf
133 guez 3 logical, intent(IN) :: debut, lafin, ok_veget
134     real, dimension(klon), intent(IN) :: rlon, rlat
135     real, dimension(klon), intent(IN) :: cufi, cvfi
136     real, dimension(klon), intent(INOUT) :: tq_cdrag
137     real, dimension(klon), intent(IN) :: zlev
138     real, dimension(klon), intent(IN) :: u1_lay, v1_lay
139     real, dimension(klon), intent(IN) :: temp_air, spechum
140     real, dimension(klon), intent(IN) :: epot_air, ccanopy
141     real, dimension(klon), intent(IN) :: petAcoef, peqAcoef
142     real, dimension(klon), intent(IN) :: petBcoef, peqBcoef
143     real, dimension(klon), intent(IN) :: precip_rain, precip_snow
144     real, dimension(klon), intent(IN) :: sollw, sollwdown, swnet, swdown
145     real, dimension(klon), intent(IN) :: ps, albedo
146     real, dimension(klon), intent(IN) :: tsurf, p1lay
147     !IM: "slab" ocean
148     real, dimension(klon), intent(INOUT) :: tslab
149     real, allocatable, dimension(:), save :: tmp_tslab
150     real, dimension(klon), intent(OUT) :: flux_o, flux_g
151     real, dimension(klon), intent(INOUT) :: seaice ! glace de mer (kg/m2)
152 guez 14 REAL, DIMENSION(klon), INTENT(INOUT) :: radsol, fder
153 guez 3 real, dimension(klon), intent(IN) :: zmasq
154     real, dimension(klon), intent(IN) :: taux, tauy, rugos, rugoro
155     real, dimension(klon), intent(IN) :: windsp
156 guez 12 character(len=*), intent(IN):: ocean
157 guez 3 integer :: npas, nexca ! nombre et pas de temps couplage
158     real, dimension(klon), intent(INOUT) :: evap, snow, qsurf
159     !! PB ajout pour soil
160 guez 12 logical, intent(in):: soil_model
161 guez 3 integer :: nsoilmx
162     REAL, DIMENSION(klon, nsoilmx) :: tsoil
163     REAL, dimension(klon), intent(INOUT) :: qsol
164     REAL, dimension(klon) :: soilcap
165     REAL, dimension(klon) :: soilflux
166 guez 14
167 guez 3 ! Parametres de sortie
168 guez 14 ! output:
169     ! evap evaporation totale
170     ! fluxsens flux de chaleur sensible
171     ! fluxlat flux de chaleur latente
172     ! tsol_rad
173     ! tsurf_new temperature au sol
174     ! alb_new albedo
175     ! emis_new emissivite
176     ! z0_new surface roughness
177     ! pctsrf_new nouvelle repartition des surfaces
178 guez 3 real, dimension(klon), intent(OUT):: fluxsens, fluxlat
179     real, dimension(klon), intent(OUT):: tsol_rad, tsurf_new, alb_new
180     real, dimension(klon), intent(OUT):: alblw
181     real, dimension(klon), intent(OUT):: emis_new, z0_new
182     real, dimension(klon), intent(OUT):: dflux_l, dflux_s
183 guez 14 real, dimension(klon, nbsrf), intent(OUT) :: pctsrf_new
184 guez 3 real, dimension(klon), intent(INOUT):: agesno
185     real, dimension(klon), intent(INOUT):: run_off_lic_0
186    
187     ! Flux thermique utiliser pour fondre la neige
188     !jld a rajouter real, dimension(klon), intent(INOUT):: ffonte
189     real, dimension(klon), intent(INOUT):: ffonte
190     ! Flux d'eau "perdue" par la surface et nécessaire pour que limiter la
191     ! hauteur de neige, en kg/m2/s
192     !jld a rajouter real, dimension(klon), intent(INOUT):: fqcalving
193     real, dimension(klon), intent(INOUT):: fqcalving
194     !IM: "slab" ocean - Local
195     real, parameter :: t_grnd=271.35
196     real, dimension(klon) :: zx_sl
197     integer i
198     real, allocatable, dimension(:), save :: tmp_flux_o, tmp_flux_g
199     real, allocatable, dimension(:), save :: tmp_radsol
200 guez 14 real, allocatable, dimension(:, :), save :: tmp_pctsrf_slab
201 guez 3 real, allocatable, dimension(:), save :: tmp_seaice
202    
203     ! Local
204 guez 14 character (len = 20), save :: modname = 'interfsurf_hq'
205 guez 3 character (len = 80) :: abort_message
206     logical, save :: first_call = .true.
207     integer, save :: error
208     integer :: ii
209 guez 14 logical, save :: check = .false.
210 guez 3 real, dimension(klon):: cal, beta, dif_grnd, capsol
211     real, parameter :: calice=1.0/(5.1444e+06*0.15), tau_gl=86400.*5.
212     real, parameter :: calsno=1./(2.3867e+06*.15)
213     real, dimension(klon):: tsurf_temp
214     real, dimension(klon):: alb_neig, alb_eau
215     real, DIMENSION(klon):: zfra
216     logical :: cumul = .false.
217 guez 14 INTEGER, dimension(1) :: iloc
218 guez 3 real, dimension(klon):: fder_prev
219     REAL, dimension(klon) :: bidule
220    
221     !-------------------------------------------------------------
222    
223 guez 14 if (check) write(*, *) 'Entree ', modname
224 guez 3
225     ! On doit commencer par appeler les schemas de surfaces continentales
226     ! car l'ocean a besoin du ruissellement qui est y calcule
227    
228     if (first_call) then
229     call conf_interface(tau_calv)
230     if (nisurf /= is_ter .and. klon > 1) then
231 guez 14 write(*, *)' *** Warning ***'
232     write(*, *)' nisurf = ', nisurf, ' /= is_ter = ', is_ter
233     write(*, *)'or on doit commencer par les surfaces continentales'
234 guez 3 abort_message='voir ci-dessus'
235 guez 14 call abort_gcm(modname, abort_message, 1)
236 guez 3 endif
237 guez 12 if (ocean /= 'slab' .and. ocean /= 'force') then
238 guez 14 write(*, *)' *** Warning ***'
239     write(*, *)'Option couplage pour l''ocean = ', ocean
240 guez 3 abort_message='option pour l''ocean non valable'
241 guez 14 call abort_gcm(modname, abort_message, 1)
242 guez 3 endif
243     if ( is_oce > is_sic ) then
244 guez 14 write(*, *)' *** Warning ***'
245     write(*, *)' Pour des raisons de sequencement dans le code'
246     write(*, *)' l''ocean doit etre traite avant la banquise'
247     write(*, *)' or is_oce = ', is_oce, '> is_sic = ', is_sic
248 guez 3 abort_message='voir ci-dessus'
249 guez 14 call abort_gcm(modname, abort_message, 1)
250 guez 3 endif
251     endif
252     first_call = .false.
253    
254     ! Initialisations diverses
255 guez 14
256 guez 3 ffonte(1:knon)=0.
257     fqcalving(1:knon)=0.
258    
259     cal = 999999. ; beta = 999999. ; dif_grnd = 999999. ; capsol = 999999.
260     alb_new = 999999. ; z0_new = 999999. ; alb_neig = 999999.
261     tsurf_new = 999999.
262     alblw = 999999.
263    
264     !IM: "slab" ocean; initialisations
265     flux_o = 0.
266     flux_g = 0.
267 guez 14
268 guez 3 if (.not. allocated(tmp_flux_o)) then
269     allocate(tmp_flux_o(klon), stat = error)
270     DO i=1, knon
271     tmp_flux_o(knindex(i))=flux_o(i)
272     ENDDO
273     if (error /= 0) then
274     abort_message='Pb allocation tmp_flux_o'
275 guez 14 call abort_gcm(modname, abort_message, 1)
276 guez 3 endif
277     endif
278     if (.not. allocated(tmp_flux_g)) then
279     allocate(tmp_flux_g(klon), stat = error)
280     DO i=1, knon
281     tmp_flux_g(knindex(i))=flux_g(i)
282     ENDDO
283     if (error /= 0) then
284     abort_message='Pb allocation tmp_flux_g'
285 guez 14 call abort_gcm(modname, abort_message, 1)
286 guez 3 endif
287     endif
288     if (.not. allocated(tmp_radsol)) then
289     allocate(tmp_radsol(klon), stat = error)
290     if (error /= 0) then
291     abort_message='Pb allocation tmp_radsol'
292 guez 14 call abort_gcm(modname, abort_message, 1)
293 guez 3 endif
294     endif
295     DO i=1, knon
296     tmp_radsol(knindex(i))=radsol(i)
297     ENDDO
298     if (.not. allocated(tmp_pctsrf_slab)) then
299 guez 14 allocate(tmp_pctsrf_slab(klon, nbsrf), stat = error)
300 guez 3 if (error /= 0) then
301     abort_message='Pb allocation tmp_pctsrf_slab'
302 guez 14 call abort_gcm(modname, abort_message, 1)
303 guez 3 endif
304     DO i=1, klon
305 guez 14 tmp_pctsrf_slab(i, 1:nbsrf)=pctsrf(i, 1:nbsrf)
306 guez 3 ENDDO
307     endif
308 guez 14
309 guez 3 if (.not. allocated(tmp_seaice)) then
310     allocate(tmp_seaice(klon), stat = error)
311     if (error /= 0) then
312     abort_message='Pb allocation tmp_seaice'
313 guez 14 call abort_gcm(modname, abort_message, 1)
314 guez 3 endif
315     DO i=1, klon
316     tmp_seaice(i)=seaice(i)
317     ENDDO
318     endif
319 guez 14
320 guez 3 if (.not. allocated(tmp_tslab)) then
321     allocate(tmp_tslab(klon), stat = error)
322     if (error /= 0) then
323     abort_message='Pb allocation tmp_tslab'
324 guez 14 call abort_gcm(modname, abort_message, 1)
325 guez 3 endif
326     endif
327     DO i=1, klon
328     tmp_tslab(i)=tslab(i)
329     ENDDO
330 guez 14
331 guez 3 ! Aiguillage vers les differents schemas de surface
332    
333     if (nisurf == is_ter) then
334 guez 14
335 guez 3 ! Surface "terre" appel a l'interface avec les sols continentaux
336 guez 14
337 guez 3 ! allocation du run-off
338     if (.not. allocated(coastalflow)) then
339     allocate(coastalflow(knon), stat = error)
340     if (error /= 0) then
341     abort_message='Pb allocation coastalflow'
342 guez 14 call abort_gcm(modname, abort_message, 1)
343 guez 3 endif
344     allocate(riverflow(knon), stat = error)
345     if (error /= 0) then
346     abort_message='Pb allocation riverflow'
347 guez 14 call abort_gcm(modname, abort_message, 1)
348 guez 3 endif
349     allocate(run_off(knon), stat = error)
350     if (error /= 0) then
351     abort_message='Pb allocation run_off'
352 guez 14 call abort_gcm(modname, abort_message, 1)
353 guez 3 endif
354     !cym
355     run_off=0.0
356     !cym
357    
358     !!$PB
359 guez 14 ALLOCATE (tmp_rriv(iim, jjm+1), stat=error)
360 guez 3 if (error /= 0) then
361     abort_message='Pb allocation tmp_rriv'
362 guez 14 call abort_gcm(modname, abort_message, 1)
363 guez 3 endif
364 guez 14 ALLOCATE (tmp_rcoa(iim, jjm+1), stat=error)
365 guez 3 if (error /= 0) then
366     abort_message='Pb allocation tmp_rcoa'
367 guez 14 call abort_gcm(modname, abort_message, 1)
368 guez 3 endif
369 guez 14 ALLOCATE (tmp_rlic(iim, jjm+1), stat=error)
370 guez 3 if (error /= 0) then
371     abort_message='Pb allocation tmp_rlic'
372 guez 14 call abort_gcm(modname, abort_message, 1)
373 guez 3 endif
374     tmp_rriv = 0.0
375     tmp_rcoa = 0.0
376     tmp_rlic = 0.0
377    
378     !!$
379     else if (size(coastalflow) /= knon) then
380 guez 14 write(*, *)'Bizarre, le nombre de points continentaux'
381     write(*, *)'a change entre deux appels. J''arrete ...'
382 guez 3 abort_message='voir ci-dessus'
383 guez 14 call abort_gcm(modname, abort_message, 1)
384 guez 3 endif
385     coastalflow = 0.
386     riverflow = 0.
387 guez 14
388 guez 3 ! Calcul age de la neige
389    
390     if (.not. ok_veget) then
391 guez 14 ! calcul albedo: lecture albedo fichier boundary conditions
392     ! puis ajout albedo neige
393     call interfsur_lim(itime, dtime, jour, klon, nisurf, knon, knindex, &
394     debut, alb_new, z0_new)
395    
396 guez 3 ! calcul snow et qsurf, hydrol adapté
397     CALL calbeta(dtime, nisurf, knon, snow, qsol, beta, capsol, dif_grnd)
398    
399     IF (soil_model) THEN
400 guez 14 CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, &
401     soilflux)
402 guez 3 cal(1:knon) = RCPD / soilcap(1:knon)
403     radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
404     ELSE
405     cal = RCPD * capsol
406     ENDIF
407     CALL calcul_fluxs( klon, knon, nisurf, dtime, &
408     & tsurf, p1lay, cal, beta, tq_cdrag, ps, &
409     & precip_rain, precip_snow, snow, qsurf, &
410     & radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
411     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
412     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
413    
414     CALL fonte_neige( klon, knon, nisurf, dtime, &
415     & tsurf, p1lay, cal, beta, tq_cdrag, ps, &
416     & precip_rain, precip_snow, snow, qsol, &
417     & radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
418     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
419     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
420 guez 14 & fqcalving, ffonte, run_off_lic_0)
421 guez 3
422 guez 14 call albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
423 guez 3 where (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
424 guez 14 zfra(1:knon) = max(0.0, min(1.0, snow(1:knon)/(snow(1:knon)+10.0)))
425 guez 3 alb_new(1 : knon) = alb_neig(1 : knon) *zfra(1:knon) + &
426 guez 14 alb_new(1 : knon)*(1.0-zfra(1:knon))
427 guez 3 z0_new = sqrt(z0_new**2+rugoro**2)
428     alblw(1 : knon) = alb_new(1 : knon)
429 guez 14 endif
430 guez 3
431     ! Remplissage des pourcentages de surface
432 guez 14 pctsrf_new(:, nisurf) = pctsrf(:, nisurf)
433 guez 3 else if (nisurf == is_oce) then
434     ! Surface "ocean" appel a l'interface avec l'ocean
435 guez 14 if (ocean == 'slab') then
436 guez 3 tsurf_new = tsurf
437     pctsrf_new = tmp_pctsrf_slab
438 guez 14 else
439     ! lecture conditions limites
440     call interfoce_lim(itime, dtime, jour, klon, nisurf, knon, knindex, &
441     debut, tsurf_new, pctsrf_new)
442 guez 3 endif
443    
444     tsurf_temp = tsurf_new
445     cal = 0.
446     beta = 1.
447     dif_grnd = 0.
448 guez 14 alb_neig = 0.
449     agesno = 0.
450 guez 3
451     call calcul_fluxs( klon, knon, nisurf, dtime, &
452     & tsurf_temp, p1lay, cal, beta, tq_cdrag, ps, &
453     & precip_rain, precip_snow, snow, qsurf, &
454     & radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
455     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
456     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
457    
458     fder_prev = fder
459     fder = fder_prev + dflux_s + dflux_l
460    
461     iloc = maxloc(fder(1:klon))
462     if (check.and.fder(iloc(1))> 0.) then
463 guez 14 WRITE(*, *)'**** Debug fder****'
464     WRITE(*, *)'max fder(', iloc(1), ') = ', fder(iloc(1))
465     WRITE(*, *)'fder_prev, dflux_s, dflux_l', fder_prev(iloc(1)), &
466 guez 3 & dflux_s(iloc(1)), dflux_l(iloc(1))
467     endif
468    
469     !IM: flux ocean-atmosphere utile pour le "slab" ocean
470     DO i=1, knon
471     zx_sl(i) = RLVTT
472     if (tsurf_new(i) .LT. RTT) zx_sl(i) = RLSTT
473     flux_o(i) = fluxsens(i)-evap(i)*zx_sl(i)
474     tmp_flux_o(knindex(i)) = flux_o(i)
475     tmp_radsol(knindex(i))=radsol(i)
476     ENDDO
477 guez 14
478 guez 3 ! 2eme appel a interfoce pour le cumul des champs (en particulier
479     ! fluxsens et fluxlat calcules dans calcul_fluxs)
480 guez 14
481 guez 12 if (ocean == 'slab ') then
482 guez 3 seaice=tmp_seaice
483     cumul = .true.
484     call interfoce_slab(klon, debut, itime, dtime, jour, &
485     & tmp_radsol, tmp_flux_o, tmp_flux_g, pctsrf, &
486     & tslab, seaice, pctsrf_new)
487 guez 14
488 guez 3 tmp_pctsrf_slab=pctsrf_new
489     DO i=1, knon
490     tsurf_new(i)=tslab(knindex(i))
491 guez 14 ENDDO
492 guez 3 endif
493    
494     ! calcul albedo
495     if ( minval(rmu0) == maxval(rmu0) .and. minval(rmu0) == -999.999 ) then
496 guez 14 CALL alboc(FLOAT(jour), rlat, alb_eau)
497 guez 3 else ! cycle diurne
498 guez 14 CALL alboc_cd(rmu0, alb_eau)
499 guez 3 endif
500     DO ii =1, knon
501     alb_new(ii) = alb_eau(knindex(ii))
502     enddo
503    
504     z0_new = sqrt(rugos**2 + rugoro**2)
505     alblw(1:knon) = alb_new(1:knon)
506     else if (nisurf == is_sic) then
507 guez 14 if (check) write(*, *)'sea ice, nisurf = ', nisurf
508 guez 3
509 guez 14 ! Surface "glace de mer" appel a l'interface avec l'ocean
510 guez 3
511 guez 14
512 guez 12 if (ocean == 'slab ') then
513 guez 3 pctsrf_new=tmp_pctsrf_slab
514 guez 14
515 guez 3 DO ii = 1, knon
516     tsurf_new(ii) = tsurf(ii)
517 guez 14 IF (pctsrf_new(knindex(ii), nisurf) < EPSFRA) then
518 guez 3 snow(ii) = 0.0
519     tsurf_new(ii) = RTT - 1.8
520 guez 14 IF (soil_model) tsoil(ii, :) = RTT -1.8
521 guez 3 ENDIF
522     ENDDO
523    
524     CALL calbeta(dtime, nisurf, knon, snow, qsol, beta, capsol, dif_grnd)
525    
526     IF (soil_model) THEN
527 guez 14 CALL soil(dtime, nisurf, knon, snow, tsurf_new, tsoil, soilcap, soilflux)
528 guez 3 cal(1:knon) = RCPD / soilcap(1:knon)
529     radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
530     ELSE
531     dif_grnd = 1.0 / tau_gl
532     cal = RCPD * calice
533     WHERE (snow > 0.0) cal = RCPD * calsno
534     ENDIF
535     tsurf_temp = tsurf_new
536     beta = 1.0
537 guez 14
538 guez 3 ELSE
539     ! ! lecture conditions limites
540     CALL interfoce_lim(itime, dtime, jour, &
541     & klon, nisurf, knon, knindex, &
542     & debut, &
543     & tsurf_new, pctsrf_new)
544    
545     !IM cf LF
546     DO ii = 1, knon
547     tsurf_new(ii) = tsurf(ii)
548 guez 14 !IMbad IF (pctsrf_new(ii, nisurf) < EPSFRA) then
549     IF (pctsrf_new(knindex(ii), nisurf) < EPSFRA) then
550 guez 3 snow(ii) = 0.0
551     !IM cf LF/JLD tsurf(ii) = RTT - 1.8
552     tsurf_new(ii) = RTT - 1.8
553 guez 14 IF (soil_model) tsoil(ii, :) = RTT -1.8
554 guez 3 endif
555     enddo
556    
557     CALL calbeta(dtime, nisurf, knon, snow, qsol, beta, capsol, dif_grnd)
558    
559     IF (soil_model) THEN
560 guez 14 !IM cf LF/JLD CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, soilflux)
561     CALL soil(dtime, nisurf, knon, snow, tsurf_new, tsoil, soilcap, soilflux)
562 guez 3 cal(1:knon) = RCPD / soilcap(1:knon)
563     radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
564     dif_grnd = 0.
565     ELSE
566     dif_grnd = 1.0 / tau_gl
567     cal = RCPD * calice
568     WHERE (snow > 0.0) cal = RCPD * calsno
569     ENDIF
570     !IMbadtsurf_temp = tsurf
571     tsurf_temp = tsurf_new
572     beta = 1.0
573     ENDIF
574    
575     CALL calcul_fluxs( klon, knon, nisurf, dtime, &
576     & tsurf_temp, p1lay, cal, beta, tq_cdrag, ps, &
577     & precip_rain, precip_snow, snow, qsurf, &
578     & radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
579     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
580     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
581 guez 14
582 guez 3 !IM: flux entre l'ocean et la glace de mer pour le "slab" ocean
583     DO i = 1, knon
584     flux_g(i) = 0.0
585 guez 14
586 guez 3 !IM: faire dependre le coefficient de conduction de la glace de mer
587     ! de l'epaisseur de la glace de mer, dans l'hypothese ou le coeff.
588     ! actuel correspond a 3m de glace de mer, cf. L.Li
589 guez 14
590 guez 3 ! IF(1.EQ.0) THEN
591     ! IF(siceh(i).GT.0.) THEN
592     ! new_dif_grnd(i) = dif_grnd(i)*3./siceh(i)
593     ! ELSE
594     ! new_dif_grnd(i) = 0.
595     ! ENDIF
596     ! ENDIF !(1.EQ.0) THEN
597 guez 14
598 guez 3 IF (cal(i).GT.1.0e-15) flux_g(i)=(tsurf_new(i)-t_grnd) &
599     & * dif_grnd(i) *RCPD/cal(i)
600     ! & * new_dif_grnd(i) *RCPD/cal(i)
601     tmp_flux_g(knindex(i))=flux_g(i)
602     tmp_radsol(knindex(i))=radsol(i)
603     ENDDO
604    
605 guez 12 CALL fonte_neige( klon, knon, nisurf, dtime, &
606     & tsurf_temp, p1lay, cal, beta, tq_cdrag, ps, &
607     & precip_rain, precip_snow, snow, qsol, &
608     & radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
609     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
610     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
611 guez 14 & fqcalving, ffonte, run_off_lic_0)
612 guez 3
613 guez 12 ! calcul albedo
614 guez 3
615 guez 14 CALL albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
616 guez 12 WHERE (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
617 guez 14 zfra(1:knon) = MAX(0.0, MIN(1.0, snow(1:knon)/(snow(1:knon)+10.0)))
618 guez 12 alb_new(1 : knon) = alb_neig(1 : knon) *zfra(1:knon) + &
619     0.6 * (1.0-zfra(1:knon))
620 guez 3
621     fder_prev = fder
622     fder = fder_prev + dflux_s + dflux_l
623    
624     iloc = maxloc(fder(1:klon))
625     if (check.and.fder(iloc(1))> 0.) then
626 guez 14 WRITE(*, *)'**** Debug fder ****'
627     WRITE(*, *)'max fder(', iloc(1), ') = ', fder(iloc(1))
628     WRITE(*, *)'fder_prev, dflux_s, dflux_l', fder_prev(iloc(1)), &
629 guez 3 & dflux_s(iloc(1)), dflux_l(iloc(1))
630     endif
631    
632 guez 14
633 guez 3 ! 2eme appel a interfoce pour le cumul et le passage des flux a l'ocean
634 guez 14
635 guez 3 z0_new = 0.002
636     z0_new = SQRT(z0_new**2+rugoro**2)
637     alblw(1:knon) = alb_new(1:knon)
638    
639     else if (nisurf == is_lic) then
640    
641 guez 14 if (check) write(*, *)'glacier, nisurf = ', nisurf
642 guez 3
643     if (.not. allocated(run_off_lic)) then
644     allocate(run_off_lic(knon), stat = error)
645     if (error /= 0) then
646     abort_message='Pb allocation run_off_lic'
647 guez 14 call abort_gcm(modname, abort_message, 1)
648 guez 3 endif
649     run_off_lic = 0.
650     endif
651 guez 14
652 guez 3 ! Surface "glacier continentaux" appel a l'interface avec le sol
653 guez 14
654 guez 3 IF (soil_model) THEN
655 guez 14 CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil, soilcap, soilflux)
656 guez 3 cal(1:knon) = RCPD / soilcap(1:knon)
657     radsol(1:knon) = radsol(1:knon) + soilflux(1:knon)
658     ELSE
659     cal = RCPD * calice
660     WHERE (snow > 0.0) cal = RCPD * calsno
661     ENDIF
662     beta = 1.0
663     dif_grnd = 0.0
664    
665     call calcul_fluxs( klon, knon, nisurf, dtime, &
666     & tsurf, p1lay, cal, beta, tq_cdrag, ps, &
667     & precip_rain, precip_snow, snow, qsurf, &
668     & radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
669     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
670     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
671    
672     call fonte_neige( klon, knon, nisurf, dtime, &
673     & tsurf, p1lay, cal, beta, tq_cdrag, ps, &
674     & precip_rain, precip_snow, snow, qsol, &
675     & radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
676     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
677     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
678 guez 14 & fqcalving, ffonte, run_off_lic_0)
679 guez 3
680     ! passage du run-off des glaciers calcule dans fonte_neige au coupleur
681     bidule=0.
682     bidule(1:knon)= run_off_lic(1:knon)
683 guez 14 call gath2cpl(bidule, tmp_rlic, klon, knon, iim, jjm, knindex)
684    
685 guez 3 ! calcul albedo
686 guez 14
687     CALL albsno(klon, knon, dtime, agesno, alb_neig, precip_snow)
688 guez 3 WHERE (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
689 guez 14 zfra(1:knon) = MAX(0.0, MIN(1.0, snow(1:knon)/(snow(1:knon)+10.0)))
690 guez 3 alb_new(1 : knon) = alb_neig(1 : knon)*zfra(1:knon) + &
691     & 0.6 * (1.0-zfra(1:knon))
692 guez 14
693 guez 3 !IM: plusieurs choix/tests sur l'albedo des "glaciers continentaux"
694     ! alb_new(1 : knon) = 0.6 !IM cf FH/GK
695     ! alb_new(1 : knon) = 0.82
696     ! alb_new(1 : knon) = 0.77 !211003 Ksta0.77
697     ! alb_new(1 : knon) = 0.8 !KstaTER0.8 & LMD_ARMIP5
698     !IM: KstaTER0.77 & LMD_ARMIP6
699     alb_new(1 : knon) = 0.77
700    
701 guez 14
702 guez 3 ! Rugosite
703 guez 14
704 guez 3 z0_new = rugoro
705 guez 14
706 guez 3 ! Remplissage des pourcentages de surface
707    
708 guez 14 pctsrf_new(:, nisurf) = pctsrf(:, nisurf)
709    
710 guez 3 alblw(1:knon) = alb_new(1:knon)
711     else
712 guez 14 write(*, *)'Index surface = ', nisurf
713 guez 3 abort_message = 'Index surface non valable'
714 guez 14 call abort_gcm(modname, abort_message, 1)
715 guez 3 endif
716    
717     END SUBROUTINE interfsurf_hq
718    
719     !************************
720    
721     SUBROUTINE interfoce_slab(klon, debut, itap, dtime, ijour, &
722     & radsol, fluxo, fluxg, pctsrf, &
723     & tslab, seaice, pctsrf_slab)
724 guez 14
725 guez 3 ! Cette routine calcule la temperature d'un slab ocean, la glace de mer
726     ! et les pourcentages de la maille couverte par l'ocean libre et/ou
727     ! la glace de mer pour un "slab" ocean de 50m
728 guez 14
729 guez 3 ! I. Musat 04.02.2005
730 guez 14
731 guez 3 ! input:
732     ! klon nombre total de points de grille
733     ! debut logical: 1er appel a la physique
734     ! itap numero du pas de temps
735     ! dtime pas de temps de la physique (en s)
736     ! ijour jour dans l'annee en cours
737     ! radsol rayonnement net au sol (LW + SW)
738     ! fluxo flux turbulent (sensible + latent) sur les mailles oceaniques
739     ! fluxg flux de conduction entre la surface de la glace de mer et l'ocean
740     ! pctsrf tableau des pourcentages de surface de chaque maille
741     ! output:
742     ! tslab temperature de l'ocean libre
743     ! seaice glace de mer (kg/m2)
744     ! pctsrf_slab "pourcentages" (valeurs entre 0. et 1.) surfaces issus du slab
745 guez 14
746 guez 3 use indicesol
747     use clesphys
748     use abort_gcm_m, only: abort_gcm
749     use YOMCST
750    
751     ! Parametres d'entree
752     integer, intent(IN) :: klon
753     logical, intent(IN) :: debut
754     INTEGER, intent(IN) :: itap
755     REAL, intent(IN) :: dtime
756     INTEGER, intent(IN) :: ijour
757     REAL, dimension(klon), intent(IN) :: radsol
758     REAL, dimension(klon), intent(IN) :: fluxo
759     REAL, dimension(klon), intent(IN) :: fluxg
760     real, dimension(klon, nbsrf), intent(IN) :: pctsrf
761     ! Parametres de sortie
762     real, dimension(klon), intent(INOUT) :: tslab
763     real, dimension(klon), intent(INOUT) :: seaice ! glace de mer (kg/m2)
764     real, dimension(klon, nbsrf), intent(OUT) :: pctsrf_slab
765 guez 14
766 guez 3 ! Variables locales :
767     INTEGER, save :: lmt_pas, julien, idayvrai
768     REAL, parameter :: unjour=86400.
769     real, allocatable, dimension(:), save :: tmp_tslab, tmp_seaice
770     REAL, allocatable, dimension(:), save :: slab_bils
771     REAL, allocatable, dimension(:), save :: lmt_bils
772 guez 14 logical, save :: check = .false.
773    
774 guez 3 REAL, parameter :: cyang=50.0 * 4.228e+06 ! capacite calorifique volumetrique de l'eau J/(m2 K)
775     REAL, parameter :: cbing=0.334e+05 ! J/kg
776     real, dimension(klon) :: siceh !hauteur de la glace de mer (m)
777     INTEGER :: i
778     integer :: sum_error, error
779     REAL :: zz, za, zb
780 guez 14
781 guez 3 character (len = 80) :: abort_message
782     character (len = 20) :: modname = 'interfoce_slab'
783 guez 14
784     julien = MOD(ijour, 360)
785 guez 3 sum_error = 0
786     IF (debut) THEN
787     allocate(slab_bils(klon), stat = error); sum_error = sum_error + error
788     allocate(lmt_bils(klon), stat = error); sum_error = sum_error + error
789     allocate(tmp_tslab(klon), stat = error); sum_error = sum_error + error
790     allocate(tmp_seaice(klon), stat = error); sum_error = sum_error + error
791     if (sum_error /= 0) then
792 guez 14 abort_message='Pb allocation var. slab_bils, lmt_bils, tmp_tslab, tmp_seaice'
793     call abort_gcm(modname, abort_message, 1)
794 guez 3 endif
795     tmp_tslab=tslab
796     tmp_seaice=seaice
797     lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour
798 guez 14
799 guez 3 IF (check) THEN
800 guez 14 PRINT*, 'interfoce_slab klon, debut, itap, dtime, ijour, &
801 guez 3 & lmt_pas ', klon, debut, itap, dtime, ijour, &
802     & lmt_pas
803     ENDIF !check
804 guez 14
805 guez 3 PRINT*, '************************'
806     PRINT*, 'SLAB OCEAN est actif, prenez precautions !'
807     PRINT*, '************************'
808 guez 14
809 guez 3 ! a mettre un slab_bils aussi en force !!!
810 guez 14
811 guez 3 DO i = 1, klon
812     slab_bils(i) = 0.0
813     ENDDO
814 guez 14
815 guez 3 ENDIF !debut
816 guez 14 pctsrf_slab(1:klon, 1:nbsrf) = pctsrf(1:klon, 1:nbsrf)
817    
818 guez 3 ! lecture du bilan au sol lmt_bils issu d'une simulation forcee en debut de journee
819 guez 14
820     IF (MOD(itap, lmt_pas) .EQ. 1) THEN !1er pas de temps de la journee
821 guez 3 idayvrai = ijour
822 guez 14 CALL condsurf(julien, idayvrai, lmt_bils)
823     ENDIF !(MOD(itap-1, lmt_pas) .EQ. 0) THEN
824 guez 3
825     DO i = 1, klon
826 guez 14 IF((pctsrf_slab(i, is_oce).GT.epsfra).OR. &
827     & (pctsrf_slab(i, is_sic).GT.epsfra)) THEN
828    
829 guez 3 ! fabriquer de la glace si congelation atteinte:
830 guez 14
831 guez 3 IF (tmp_tslab(i).LT.(RTT-1.8)) THEN
832     zz = (RTT-1.8)-tmp_tslab(i)
833     tmp_seaice(i) = tmp_seaice(i) + cyang/cbing * zz
834     seaice(i) = tmp_seaice(i)
835     tmp_tslab(i) = RTT-1.8
836     ENDIF
837 guez 14
838 guez 3 ! faire fondre de la glace si temperature est superieure a 0:
839 guez 14
840 guez 3 IF ((tmp_tslab(i).GT.RTT) .AND. (tmp_seaice(i).GT.0.0)) THEN
841     zz = cyang/cbing * (tmp_tslab(i)-RTT)
842 guez 14 zz = MIN(zz, tmp_seaice(i))
843 guez 3 tmp_seaice(i) = tmp_seaice(i) - zz
844     seaice(i) = tmp_seaice(i)
845     tmp_tslab(i) = tmp_tslab(i) - zz*cbing/cyang
846     ENDIF
847 guez 14
848 guez 3 ! limiter la glace de mer a 10 metres (10000 kg/m2)
849 guez 14
850 guez 3 IF(tmp_seaice(i).GT.45.) THEN
851 guez 14 tmp_seaice(i) = MIN(tmp_seaice(i), 10000.0)
852 guez 3 ELSE
853     tmp_seaice(i) = 0.
854     ENDIF
855     seaice(i) = tmp_seaice(i)
856     siceh(i)=tmp_seaice(i)/1000. !en metres
857 guez 14
858 guez 3 ! determiner la nature du sol (glace de mer ou ocean libre):
859 guez 14
860     ! on fait dependre la fraction de seaice "pctsrf(i, is_sic)"
861 guez 3 ! de l'epaisseur de seaice :
862 guez 14 ! pctsrf(i, is_sic)=1. si l'epaisseur de la glace de mer est >= a 20cm
863     ! et pctsrf(i, is_sic) croit lineairement avec seaice de 0. a 20cm d'epaisseur
864    
865     pctsrf_slab(i, is_sic)=MIN(siceh(i)/0.20, &
866     & 1.-(pctsrf_slab(i, is_ter)+pctsrf_slab(i, is_lic)))
867     pctsrf_slab(i, is_oce)=1.0 - &
868     & (pctsrf_slab(i, is_ter)+pctsrf_slab(i, is_lic)+pctsrf_slab(i, is_sic))
869 guez 3 ENDIF !pctsrf
870     ENDDO
871 guez 14
872 guez 3 ! Calculer le bilan du flux de chaleur au sol :
873 guez 14
874 guez 3 DO i = 1, klon
875     za = radsol(i) + fluxo(i)
876     zb = fluxg(i)
877 guez 14 IF((pctsrf_slab(i, is_oce).GT.epsfra).OR. &
878     & (pctsrf_slab(i, is_sic).GT.epsfra)) THEN
879     slab_bils(i)=slab_bils(i)+(za*pctsrf_slab(i, is_oce) &
880     & +zb*pctsrf_slab(i, is_sic))/ FLOAT(lmt_pas)
881 guez 3 ENDIF
882     ENDDO !klon
883 guez 14
884 guez 3 ! calcul tslab
885 guez 14
886     IF (MOD(itap, lmt_pas).EQ.0) THEN !fin de journee
887 guez 3 DO i = 1, klon
888 guez 14 IF ((pctsrf_slab(i, is_oce).GT.epsfra).OR. &
889     & (pctsrf_slab(i, is_sic).GT.epsfra)) THEN
890 guez 3 tmp_tslab(i) = tmp_tslab(i) + &
891     & (slab_bils(i)-lmt_bils(i)) &
892     & /cyang*unjour
893     ! on remet l'accumulation a 0
894     slab_bils(i) = 0.
895     ENDIF !pctsrf
896     ENDDO !klon
897 guez 14 ENDIF !(MOD(itap, lmt_pas).EQ.0) THEN
898    
899 guez 3 tslab = tmp_tslab
900     seaice = tmp_seaice
901     END SUBROUTINE interfoce_slab
902    
903     !************************
904    
905     SUBROUTINE interfoce_lim(itime, dtime, jour, &
906     & klon, nisurf, knon, knindex, &
907     & debut, &
908     & lmt_sst, pctsrf_new)
909    
910 guez 14 ! Cette routine sert d'interface entre le modele atmospherique et
911     ! un fichier de conditions aux limites
912    
913 guez 3 ! L. Fairhead 02/2000
914    
915     use abort_gcm_m, only: abort_gcm
916     use indicesol
917    
918 guez 14 integer, intent(IN) :: itime ! numero du pas de temps courant
919     real , intent(IN) :: dtime ! pas de temps de la physique (en s)
920     integer, intent(IN) :: jour ! jour a lire dans l'annee
921     integer, intent(IN) :: nisurf ! index de la surface a traiter (1 = sol continental)
922     integer, intent(IN) :: knon ! nombre de points dans le domaine a traiter
923     integer, intent(IN) :: klon ! taille de la grille
924     integer, dimension(klon), intent(in) :: knindex ! index des points de la surface a traiter
925     logical, intent(IN) :: debut ! logical: 1er appel a la physique (initialisation)
926 guez 3
927     ! Parametres de sortie
928 guez 14 ! output:
929     ! lmt_sst SST lues dans le fichier de CL
930     ! pctsrf_new sous-maille fractionnelle
931 guez 3 real, intent(out), dimension(klon) :: lmt_sst
932 guez 14 real, intent(out), dimension(klon, nbsrf) :: pctsrf_new
933 guez 3
934     ! Variables locales
935     integer :: ii
936 guez 14 INTEGER, save :: lmt_pas ! frequence de lecture des conditions limites
937 guez 3 ! (en pas de physique)
938 guez 14 logical, save :: deja_lu ! pour indiquer que le jour a lire a deja
939 guez 3 ! lu pour une surface precedente
940 guez 14 integer, save :: jour_lu
941 guez 3 integer :: ierr
942     character (len = 20) :: modname = 'interfoce_lim'
943     character (len = 80) :: abort_message
944     logical, save :: newlmt = .TRUE.
945     logical, save :: check = .FALSE.
946     ! Champs lus dans le fichier de CL
947     real, allocatable , save, dimension(:) :: sst_lu, rug_lu, nat_lu
948 guez 14 real, allocatable , save, dimension(:, :) :: pct_tmp
949    
950 guez 3 ! quelques variables pour netcdf
951 guez 14
952 guez 3 include "netcdf.inc"
953     integer :: nid, nvarid
954     integer, dimension(2) :: start, epais
955    
956 guez 14 ! --------------------------------------------------
957    
958 guez 3 if (debut .and. .not. allocated(sst_lu)) then
959     lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour
960     jour_lu = jour - 1
961     allocate(sst_lu(klon))
962     allocate(nat_lu(klon))
963 guez 14 allocate(pct_tmp(klon, nbsrf))
964 guez 3 endif
965    
966     if ((jour - jour_lu) /= 0) deja_lu = .false.
967    
968 guez 14 if (check) write(*, *)modname, ' :: jour, jour_lu, deja_lu', jour, jour_lu, &
969 guez 3 deja_lu
970 guez 14 if (check) write(*, *)modname, ' :: itime, lmt_pas ', itime, lmt_pas, dtime
971 guez 3
972     ! Tester d'abord si c'est le moment de lire le fichier
973     if (mod(itime-1, lmt_pas) == 0 .and. .not. deja_lu) then
974 guez 14
975 guez 3 ! Ouverture du fichier
976 guez 14
977     ierr = NF_OPEN ('limit.nc', NF_NOWRITE, nid)
978 guez 3 if (ierr.NE.NF_NOERR) then
979     abort_message &
980     = 'Pb d''ouverture du fichier de conditions aux limites'
981 guez 14 call abort_gcm(modname, abort_message, 1)
982 guez 3 endif
983 guez 14
984 guez 3 ! La tranche de donnees a lire:
985 guez 14
986 guez 3 start(1) = 1
987     start(2) = jour
988     epais(1) = klon
989     epais(2) = 1
990 guez 14
991 guez 3 if (newlmt) then
992 guez 14
993 guez 3 ! Fraction "ocean"
994 guez 14
995 guez 3 ierr = NF_INQ_VARID(nid, 'FOCE', nvarid)
996     if (ierr /= NF_NOERR) then
997     abort_message = 'Le champ <FOCE> est absent'
998 guez 14 call abort_gcm(modname, abort_message, 1)
999 guez 3 endif
1000 guez 14 ierr = NF_GET_VARA_REAL(nid, nvarid, start, epais, pct_tmp(1, is_oce))
1001 guez 3 if (ierr /= NF_NOERR) then
1002     abort_message = 'Lecture echouee pour <FOCE>'
1003 guez 14 call abort_gcm(modname, abort_message, 1)
1004 guez 3 endif
1005 guez 14
1006 guez 3 ! Fraction "glace de mer"
1007 guez 14
1008 guez 3 ierr = NF_INQ_VARID(nid, 'FSIC', nvarid)
1009     if (ierr /= NF_NOERR) then
1010     abort_message = 'Le champ <FSIC> est absent'
1011 guez 14 call abort_gcm(modname, abort_message, 1)
1012 guez 3 endif
1013 guez 14 ierr = NF_GET_VARA_REAL(nid, nvarid, start, epais, pct_tmp(1, is_sic))
1014 guez 3 if (ierr /= NF_NOERR) then
1015     abort_message = 'Lecture echouee pour <FSIC>'
1016 guez 14 call abort_gcm(modname, abort_message, 1)
1017 guez 3 endif
1018 guez 14
1019 guez 3 ! Fraction "terre"
1020 guez 14
1021 guez 3 ierr = NF_INQ_VARID(nid, 'FTER', nvarid)
1022     if (ierr /= NF_NOERR) then
1023     abort_message = 'Le champ <FTER> est absent'
1024 guez 14 call abort_gcm(modname, abort_message, 1)
1025 guez 3 endif
1026 guez 14 ierr = NF_GET_VARA_REAL(nid, nvarid, start, epais, pct_tmp(1, is_ter))
1027 guez 3 if (ierr /= NF_NOERR) then
1028     abort_message = 'Lecture echouee pour <FTER>'
1029 guez 14 call abort_gcm(modname, abort_message, 1)
1030 guez 3 endif
1031 guez 14
1032 guez 3 ! Fraction "glacier terre"
1033 guez 14
1034 guez 3 ierr = NF_INQ_VARID(nid, 'FLIC', nvarid)
1035     if (ierr /= NF_NOERR) then
1036     abort_message = 'Le champ <FLIC> est absent'
1037 guez 14 call abort_gcm(modname, abort_message, 1)
1038 guez 3 endif
1039 guez 14 ierr = NF_GET_VARA_REAL(nid, nvarid, start, epais, pct_tmp(1, is_lic))
1040 guez 3 if (ierr /= NF_NOERR) then
1041     abort_message = 'Lecture echouee pour <FLIC>'
1042 guez 14 call abort_gcm(modname, abort_message, 1)
1043 guez 3 endif
1044 guez 14
1045 guez 3 else ! on en est toujours a rnatur
1046 guez 14
1047 guez 3 ierr = NF_INQ_VARID(nid, 'NAT', nvarid)
1048     if (ierr /= NF_NOERR) then
1049     abort_message = 'Le champ <NAT> est absent'
1050 guez 14 call abort_gcm(modname, abort_message, 1)
1051 guez 3 endif
1052 guez 14 ierr = NF_GET_VARA_REAL(nid, nvarid, start, epais, nat_lu)
1053 guez 3 if (ierr /= NF_NOERR) then
1054     abort_message = 'Lecture echouee pour <NAT>'
1055 guez 14 call abort_gcm(modname, abort_message, 1)
1056 guez 3 endif
1057 guez 14
1058 guez 3 ! Remplissage des fractions de surface
1059     ! nat = 0, 1, 2, 3 pour ocean, terre, glacier, seaice
1060 guez 14
1061 guez 3 pct_tmp = 0.0
1062     do ii = 1, klon
1063 guez 14 pct_tmp(ii, nint(nat_lu(ii)) + 1) = 1.
1064 guez 3 enddo
1065    
1066 guez 14
1067 guez 3 ! On se retrouve avec ocean en 1 et terre en 2 alors qu'on veut le contraire
1068 guez 14
1069 guez 3 pctsrf_new = pct_tmp
1070 guez 14 pctsrf_new (:, 2)= pct_tmp (:, 1)
1071     pctsrf_new (:, 1)= pct_tmp (:, 2)
1072 guez 3 pct_tmp = pctsrf_new
1073     endif ! fin test sur newlmt
1074 guez 14
1075 guez 3 ! Lecture SST
1076 guez 14
1077 guez 3 ierr = NF_INQ_VARID(nid, 'SST', nvarid)
1078     if (ierr /= NF_NOERR) then
1079     abort_message = 'Le champ <SST> est absent'
1080 guez 14 call abort_gcm(modname, abort_message, 1)
1081 guez 3 endif
1082 guez 14 ierr = NF_GET_VARA_REAL(nid, nvarid, start, epais, sst_lu)
1083 guez 3 if (ierr /= NF_NOERR) then
1084     abort_message = 'Lecture echouee pour <SST>'
1085 guez 14 call abort_gcm(modname, abort_message, 1)
1086 guez 3 endif
1087    
1088 guez 14
1089 guez 3 ! Fin de lecture
1090 guez 14
1091 guez 3 ierr = NF_CLOSE(nid)
1092     deja_lu = .true.
1093     jour_lu = jour
1094     endif
1095 guez 14
1096 guez 3 ! Recopie des variables dans les champs de sortie
1097 guez 14
1098 guez 3 lmt_sst = 999999999.
1099     do ii = 1, knon
1100     lmt_sst(ii) = sst_lu(knindex(ii))
1101     enddo
1102    
1103 guez 14 pctsrf_new(:, is_oce) = pct_tmp(:, is_oce)
1104     pctsrf_new(:, is_sic) = pct_tmp(:, is_sic)
1105 guez 3
1106     END SUBROUTINE interfoce_lim
1107    
1108     !************************
1109    
1110     SUBROUTINE interfsur_lim(itime, dtime, jour, &
1111     & klon, nisurf, knon, knindex, &
1112     & debut, &
1113     & lmt_alb, lmt_rug)
1114    
1115     ! Cette routine sert d'interface entre le modèle atmosphérique et
1116     ! un fichier de conditions aux limites.
1117 guez 14
1118 guez 3 ! L. Fairhead 02/2000
1119 guez 14
1120     use abort_gcm_m, only: abort_gcm
1121    
1122     ! Parametres d'entree
1123 guez 3 ! input:
1124     ! itime numero du pas de temps courant
1125     ! dtime pas de temps de la physique (en s)
1126     ! jour jour a lire dans l'annee
1127     ! nisurf index de la surface a traiter (1 = sol continental)
1128     ! knon nombre de points dans le domaine a traiter
1129     ! knindex index des points de la surface a traiter
1130     ! klon taille de la grille
1131     ! debut logical: 1er appel a la physique (initialisation)
1132     integer, intent(IN) :: itime
1133     real , intent(IN) :: dtime
1134     integer, intent(IN) :: jour
1135     integer, intent(IN) :: nisurf
1136     integer, intent(IN) :: knon
1137     integer, intent(IN) :: klon
1138     integer, dimension(klon), intent(in) :: knindex
1139     logical, intent(IN) :: debut
1140    
1141     ! Parametres de sortie
1142 guez 14 ! output:
1143     ! lmt_sst SST lues dans le fichier de CL
1144     ! lmt_alb Albedo lu
1145     ! lmt_rug longueur de rugosité lue
1146     ! pctsrf_new sous-maille fractionnelle
1147 guez 3 real, intent(out), dimension(klon) :: lmt_alb
1148     real, intent(out), dimension(klon) :: lmt_rug
1149    
1150     ! Variables locales
1151     integer :: ii
1152 guez 14 integer, save :: lmt_pas ! frequence de lecture des conditions limites
1153 guez 3 ! (en pas de physique)
1154 guez 14 logical, save :: deja_lu_sur! pour indiquer que le jour a lire a deja
1155 guez 3 ! lu pour une surface precedente
1156 guez 14 integer, save :: jour_lu_sur
1157 guez 3 integer :: ierr
1158     character (len = 20) :: modname = 'interfsur_lim'
1159     character (len = 80) :: abort_message
1160 guez 14 logical, save :: newlmt = .false.
1161     logical, save :: check = .false.
1162 guez 3 ! Champs lus dans le fichier de CL
1163     real, allocatable , save, dimension(:) :: alb_lu, rug_lu
1164 guez 14
1165 guez 3 ! quelques variables pour netcdf
1166 guez 14
1167 guez 3 include "netcdf.inc"
1168 guez 14 integer , save :: nid, nvarid
1169     integer, dimension(2), save :: start, epais
1170 guez 3
1171 guez 14 !------------------------------------------------------------
1172    
1173 guez 3 if (debut) then
1174     lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour
1175     jour_lu_sur = jour - 1
1176     allocate(alb_lu(klon))
1177     allocate(rug_lu(klon))
1178     endif
1179    
1180     if ((jour - jour_lu_sur) /= 0) deja_lu_sur = .false.
1181    
1182 guez 14 if (check) write(*, *)modname, ':: jour_lu_sur, deja_lu_sur', jour_lu_sur, &
1183 guez 3 deja_lu_sur
1184 guez 14 if (check) write(*, *)modname, ':: itime, lmt_pas', itime, lmt_pas
1185 guez 3
1186     ! Tester d'abord si c'est le moment de lire le fichier
1187     if (mod(itime-1, lmt_pas) == 0 .and. .not. deja_lu_sur) then
1188 guez 14
1189 guez 3 ! Ouverture du fichier
1190 guez 14
1191     ierr = NF_OPEN ('limit.nc', NF_NOWRITE, nid)
1192 guez 3 if (ierr.NE.NF_NOERR) then
1193     abort_message &
1194     = 'Pb d''ouverture du fichier de conditions aux limites'
1195 guez 14 call abort_gcm(modname, abort_message, 1)
1196 guez 3 endif
1197 guez 14
1198 guez 3 ! La tranche de donnees a lire:
1199    
1200     start(1) = 1
1201     start(2) = jour
1202     epais(1) = klon
1203     epais(2) = 1
1204 guez 14
1205 guez 3 ! Lecture Albedo
1206 guez 14
1207 guez 3 ierr = NF_INQ_VARID(nid, 'ALB', nvarid)
1208     if (ierr /= NF_NOERR) then
1209     abort_message = 'Le champ <ALB> est absent'
1210 guez 14 call abort_gcm(modname, abort_message, 1)
1211 guez 3 endif
1212 guez 14 ierr = NF_GET_VARA_REAL(nid, nvarid, start, epais, alb_lu)
1213 guez 3 if (ierr /= NF_NOERR) then
1214     abort_message = 'Lecture echouee pour <ALB>'
1215 guez 14 call abort_gcm(modname, abort_message, 1)
1216 guez 3 endif
1217 guez 14
1218 guez 3 ! Lecture rugosité
1219 guez 14
1220 guez 3 ierr = NF_INQ_VARID(nid, 'RUG', nvarid)
1221     if (ierr /= NF_NOERR) then
1222     abort_message = 'Le champ <RUG> est absent'
1223 guez 14 call abort_gcm(modname, abort_message, 1)
1224 guez 3 endif
1225 guez 14 ierr = NF_GET_VARA_REAL(nid, nvarid, start, epais, rug_lu)
1226 guez 3 if (ierr /= NF_NOERR) then
1227     abort_message = 'Lecture echouee pour <RUG>'
1228 guez 14 call abort_gcm(modname, abort_message, 1)
1229 guez 3 endif
1230    
1231 guez 14
1232 guez 3 ! Fin de lecture
1233 guez 14
1234 guez 3 ierr = NF_CLOSE(nid)
1235     deja_lu_sur = .true.
1236     jour_lu_sur = jour
1237     endif
1238 guez 14
1239 guez 3 ! Recopie des variables dans les champs de sortie
1240 guez 14
1241     !!$ lmt_alb = 0.0
1242     !!$ lmt_rug = 0.0
1243     lmt_alb = 999999.
1244     lmt_rug = 999999.
1245 guez 3 DO ii = 1, knon
1246     lmt_alb(ii) = alb_lu(knindex(ii))
1247     lmt_rug(ii) = rug_lu(knindex(ii))
1248     enddo
1249    
1250     END SUBROUTINE interfsur_lim
1251    
1252     !************************
1253    
1254     SUBROUTINE calcul_fluxs( klon, knon, nisurf, dtime, &
1255     & tsurf, p1lay, cal, beta, coef1lay, ps, &
1256     & precip_rain, precip_snow, snow, qsurf, &
1257     & radsol, dif_grnd, t1lay, q1lay, u1lay, v1lay, &
1258     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
1259     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
1260    
1261     ! Cette routine calcule les fluxs en h et q a l'interface et eventuellement
1262     ! une temperature de surface (au cas ou ok_veget = false)
1263 guez 14
1264 guez 3 ! L. Fairhead 4/2000
1265 guez 14
1266 guez 3 ! input:
1267     ! knon nombre de points a traiter
1268     ! nisurf surface a traiter
1269     ! tsurf temperature de surface
1270     ! p1lay pression 1er niveau (milieu de couche)
1271     ! cal capacite calorifique du sol
1272     ! beta evap reelle
1273     ! coef1lay coefficient d'echange
1274     ! ps pression au sol
1275     ! precip_rain precipitations liquides
1276     ! precip_snow precipitations solides
1277     ! snow champs hauteur de neige
1278     ! runoff runoff en cas de trop plein
1279     ! petAcoef coeff. A de la resolution de la CL pour t
1280     ! peqAcoef coeff. A de la resolution de la CL pour q
1281     ! petBcoef coeff. B de la resolution de la CL pour t
1282     ! peqBcoef coeff. B de la resolution de la CL pour q
1283     ! radsol rayonnement net aus sol (LW + SW)
1284     ! dif_grnd coeff. diffusion vers le sol profond
1285 guez 14
1286 guez 3 ! output:
1287     ! tsurf_new temperature au sol
1288     ! qsurf humidite de l'air au dessus du sol
1289     ! fluxsens flux de chaleur sensible
1290     ! fluxlat flux de chaleur latente
1291     ! dflux_s derivee du flux de chaleur sensible / Ts
1292     ! dflux_l derivee du flux de chaleur latente / Ts
1293    
1294 guez 14
1295 guez 3 use indicesol
1296     use abort_gcm_m, only: abort_gcm
1297     use yoethf
1298     use fcttre, only: thermcep, foeew, qsats, qsatl, foede, dqsats, dqsatl
1299     use YOMCST
1300    
1301     ! Parametres d'entree
1302     integer, intent(IN) :: knon, nisurf, klon
1303     real , intent(IN) :: dtime
1304     real, dimension(klon), intent(IN) :: petAcoef, peqAcoef
1305     real, dimension(klon), intent(IN) :: petBcoef, peqBcoef
1306     real, dimension(klon), intent(IN) :: ps, q1lay
1307     real, dimension(klon), intent(IN) :: tsurf, p1lay, cal, beta, coef1lay
1308     real, dimension(klon), intent(IN) :: precip_rain, precip_snow
1309     real, dimension(klon), intent(IN) :: radsol, dif_grnd
1310     real, dimension(klon), intent(IN) :: t1lay, u1lay, v1lay
1311     real, dimension(klon), intent(INOUT) :: snow, qsurf
1312    
1313     ! Parametres sorties
1314     real, dimension(klon), intent(OUT):: tsurf_new, evap, fluxsens, fluxlat
1315     real, dimension(klon), intent(OUT):: dflux_s, dflux_l
1316    
1317     ! Variables locales
1318     integer :: i
1319     real, dimension(klon) :: zx_mh, zx_nh, zx_oh
1320     real, dimension(klon) :: zx_mq, zx_nq, zx_oq
1321     real, dimension(klon) :: zx_pkh, zx_dq_s_dt, zx_qsat, zx_coef
1322     real, dimension(klon) :: zx_sl, zx_k1
1323     real, dimension(klon) :: zx_q_0 , d_ts
1324     real :: zdelta, zcvm5, zx_qs, zcor, zx_dq_s_dh
1325     real :: bilan_f, fq_fonte
1326     REAL :: subli, fsno
1327     REAL :: qsat_new, q1_new
1328     real, parameter :: t_grnd = 271.35, t_coup = 273.15
1329     !! PB temporaire en attendant mieux pour le modele de neige
1330     REAL, parameter :: chasno = 3.334E+05/(2.3867E+06*0.15)
1331 guez 14
1332 guez 3 logical, save :: check = .false.
1333     character (len = 20) :: modname = 'calcul_fluxs'
1334     logical, save :: fonte_neige = .false.
1335     real, save :: max_eau_sol = 150.0
1336     character (len = 80) :: abort_message
1337 guez 14 logical, save :: first = .true., second=.false.
1338 guez 3
1339 guez 14 if (check) write(*, *)'Entree ', modname, ' surface = ', nisurf
1340 guez 3
1341     IF (check) THEN
1342 guez 14 WRITE(*, *)' radsol (min, max)' &
1343 guez 3 & , MINVAL(radsol(1:knon)), MAXVAL(radsol(1:knon))
1344     !!CALL flush(6)
1345     ENDIF
1346    
1347     if (size(coastalflow) /= knon .AND. nisurf == is_ter) then
1348 guez 14 write(*, *)'Bizarre, le nombre de points continentaux'
1349     write(*, *)'a change entre deux appels. J''arrete ...'
1350 guez 3 abort_message='Pb run_off'
1351 guez 14 call abort_gcm(modname, abort_message, 1)
1352 guez 3 endif
1353 guez 14
1354 guez 3 ! Traitement neige et humidite du sol
1355 guez 14
1356     !!$ WRITE(*, *)'test calcul_flux, surface ', nisurf
1357 guez 3 !!PB test
1358     !!$ if (nisurf == is_oce) then
1359     !!$ snow = 0.
1360     !!$ qsol = max_eau_sol
1361     !!$ else
1362     !!$ where (precip_snow > 0.) snow = snow + (precip_snow * dtime)
1363     !!$ where (snow > epsilon(snow)) snow = max(0.0, snow - (evap * dtime))
1364     !!$! snow = max(0.0, snow + (precip_snow - evap) * dtime)
1365     !!$ where (precip_rain > 0.) qsol = qsol + (precip_rain - evap) * dtime
1366     !!$ endif
1367     !!$ IF (nisurf /= is_ter) qsol = max_eau_sol
1368    
1369 guez 14
1370 guez 3 ! Initialisation
1371 guez 14
1372 guez 3 evap = 0.
1373     fluxsens=0.
1374     fluxlat=0.
1375     dflux_s = 0.
1376     dflux_l = 0.
1377 guez 14
1378 guez 3 ! zx_qs = qsat en kg/kg
1379 guez 14
1380 guez 3 DO i = 1, knon
1381     zx_pkh(i) = (ps(i)/ps(i))**RKAPPA
1382     IF (thermcep) THEN
1383 guez 14 zdelta=MAX(0., SIGN(1., rtt-tsurf(i)))
1384 guez 3 zcvm5 = R5LES*RLVTT*(1.-zdelta) + R5IES*RLSTT*zdelta
1385     zcvm5 = zcvm5 / RCPD / (1.0+RVTMP2*q1lay(i))
1386 guez 14 zx_qs= r2es * FOEEW(tsurf(i), zdelta)/ps(i)
1387     zx_qs=MIN(0.5, zx_qs)
1388 guez 3 zcor=1./(1.-retv*zx_qs)
1389     zx_qs=zx_qs*zcor
1390 guez 14 zx_dq_s_dh = FOEDE(tsurf(i), zdelta, zcvm5, zx_qs, zcor) &
1391 guez 3 & /RLVTT / zx_pkh(i)
1392     ELSE
1393     IF (tsurf(i).LT.t_coup) THEN
1394     zx_qs = qsats(tsurf(i)) / ps(i)
1395 guez 14 zx_dq_s_dh = dqsats(tsurf(i), zx_qs)/RLVTT &
1396 guez 3 & / zx_pkh(i)
1397     ELSE
1398     zx_qs = qsatl(tsurf(i)) / ps(i)
1399 guez 14 zx_dq_s_dh = dqsatl(tsurf(i), zx_qs)/RLVTT &
1400 guez 3 & / zx_pkh(i)
1401     ENDIF
1402     ENDIF
1403     zx_dq_s_dt(i) = RCPD * zx_pkh(i) * zx_dq_s_dh
1404     zx_qsat(i) = zx_qs
1405     zx_coef(i) = coef1lay(i) &
1406     & * (1.0+SQRT(u1lay(i)**2+v1lay(i)**2)) &
1407     & * p1lay(i)/(RD*t1lay(i))
1408    
1409     ENDDO
1410    
1411     ! === Calcul de la temperature de surface ===
1412 guez 14
1413 guez 3 ! zx_sl = chaleur latente d'evaporation ou de sublimation
1414 guez 14
1415 guez 3 do i = 1, knon
1416     zx_sl(i) = RLVTT
1417     if (tsurf(i) .LT. RTT) zx_sl(i) = RLSTT
1418     zx_k1(i) = zx_coef(i)
1419     enddo
1420    
1421     do i = 1, knon
1422     ! Q
1423     zx_oq(i) = 1. - (beta(i) * zx_k1(i) * peqBcoef(i) * dtime)
1424     zx_mq(i) = beta(i) * zx_k1(i) * &
1425     & (peqAcoef(i) - zx_qsat(i) &
1426     & + zx_dq_s_dt(i) * tsurf(i)) &
1427     & / zx_oq(i)
1428     zx_nq(i) = beta(i) * zx_k1(i) * (-1. * zx_dq_s_dt(i)) &
1429     & / zx_oq(i)
1430    
1431     ! H
1432     zx_oh(i) = 1. - (zx_k1(i) * petBcoef(i) * dtime)
1433     zx_mh(i) = zx_k1(i) * petAcoef(i) / zx_oh(i)
1434     zx_nh(i) = - (zx_k1(i) * RCPD * zx_pkh(i))/ zx_oh(i)
1435    
1436     ! Tsurface
1437     tsurf_new(i) = (tsurf(i) + cal(i)/(RCPD * zx_pkh(i)) * dtime * &
1438     & (radsol(i) + zx_mh(i) + zx_sl(i) * zx_mq(i)) &
1439     & + dif_grnd(i) * t_grnd * dtime)/ &
1440     & ( 1. - dtime * cal(i)/(RCPD * zx_pkh(i)) * ( &
1441     & zx_nh(i) + zx_sl(i) * zx_nq(i)) &
1442     & + dtime * dif_grnd(i))
1443    
1444 guez 14
1445 guez 3 ! Y'a-t-il fonte de neige?
1446 guez 14
1447 guez 3 ! fonte_neige = (nisurf /= is_oce) .AND. &
1448     ! & (snow(i) > epsfra .OR. nisurf == is_sic .OR. nisurf == is_lic) &
1449     ! & .AND. (tsurf_new(i) >= RTT)
1450     ! if (fonte_neige) tsurf_new(i) = RTT
1451     d_ts(i) = tsurf_new(i) - tsurf(i)
1452     ! zx_h_ts(i) = tsurf_new(i) * RCPD * zx_pkh(i)
1453     ! zx_q_0(i) = zx_qsat(i) + zx_dq_s_dt(i) * d_ts(i)
1454     !== flux_q est le flux de vapeur d'eau: kg/(m**2 s) positive vers bas
1455     !== flux_t est le flux de cpt (energie sensible): j/(m**2 s)
1456     evap(i) = - zx_mq(i) - zx_nq(i) * tsurf_new(i)
1457     fluxlat(i) = - evap(i) * zx_sl(i)
1458     fluxsens(i) = zx_mh(i) + zx_nh(i) * tsurf_new(i)
1459     ! Derives des flux dF/dTs (W m-2 K-1):
1460     dflux_s(i) = zx_nh(i)
1461     dflux_l(i) = (zx_sl(i) * zx_nq(i))
1462     ! Nouvelle valeure de l'humidite au dessus du sol
1463     qsat_new=zx_qsat(i) + zx_dq_s_dt(i) * d_ts(i)
1464     q1_new = peqAcoef(i) - peqBcoef(i)*evap(i)*dtime
1465     qsurf(i)=q1_new*(1.-beta(i)) + beta(i)*qsat_new
1466     ENDDO
1467    
1468     END SUBROUTINE calcul_fluxs
1469    
1470     !************************
1471    
1472     SUBROUTINE fonte_neige( klon, knon, nisurf, dtime, &
1473     & tsurf, p1lay, cal, beta, coef1lay, ps, &
1474     & precip_rain, precip_snow, snow, qsol, &
1475     & radsol, dif_grnd, t1lay, q1lay, u1lay, v1lay, &
1476     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
1477     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
1478 guez 14 & fqcalving, ffonte, run_off_lic_0)
1479 guez 3
1480     ! Routine de traitement de la fonte de la neige dans le cas du traitement
1481     ! de sol simplifié
1482 guez 14
1483 guez 3 ! LF 03/2001
1484     ! input:
1485     ! knon nombre de points a traiter
1486     ! nisurf surface a traiter
1487     ! tsurf temperature de surface
1488     ! p1lay pression 1er niveau (milieu de couche)
1489     ! cal capacite calorifique du sol
1490     ! beta evap reelle
1491     ! coef1lay coefficient d'echange
1492     ! ps pression au sol
1493     ! precip_rain precipitations liquides
1494     ! precip_snow precipitations solides
1495     ! snow champs hauteur de neige
1496     ! qsol hauteur d'eau contenu dans le sol
1497     ! runoff runoff en cas de trop plein
1498     ! petAcoef coeff. A de la resolution de la CL pour t
1499     ! peqAcoef coeff. A de la resolution de la CL pour q
1500     ! petBcoef coeff. B de la resolution de la CL pour t
1501     ! peqBcoef coeff. B de la resolution de la CL pour q
1502     ! radsol rayonnement net aus sol (LW + SW)
1503     ! dif_grnd coeff. diffusion vers le sol profond
1504 guez 14
1505 guez 3 ! output:
1506     ! tsurf_new temperature au sol
1507     ! fluxsens flux de chaleur sensible
1508     ! fluxlat flux de chaleur latente
1509     ! dflux_s derivee du flux de chaleur sensible / Ts
1510     ! dflux_l derivee du flux de chaleur latente / Ts
1511     ! in/out:
1512     ! run_off_lic_0 run off glacier du pas de temps précedent
1513    
1514 guez 14
1515 guez 3 use indicesol
1516     use YOMCST
1517     use yoethf
1518     use fcttre
1519     !IM cf JLD
1520    
1521     ! Parametres d'entree
1522     integer, intent(IN) :: knon, nisurf, klon
1523     real , intent(IN) :: dtime
1524     real, dimension(klon), intent(IN) :: petAcoef, peqAcoef
1525     real, dimension(klon), intent(IN) :: petBcoef, peqBcoef
1526     real, dimension(klon), intent(IN) :: ps, q1lay
1527     real, dimension(klon), intent(IN) :: tsurf, p1lay, cal, beta, coef1lay
1528     real, dimension(klon), intent(IN) :: precip_rain, precip_snow
1529     real, dimension(klon), intent(IN) :: radsol, dif_grnd
1530     real, dimension(klon), intent(IN) :: t1lay, u1lay, v1lay
1531     real, dimension(klon), intent(INOUT) :: snow, qsol
1532    
1533     ! Parametres sorties
1534     real, dimension(klon), intent(INOUT):: tsurf_new, evap, fluxsens, fluxlat
1535     real, dimension(klon), intent(INOUT):: dflux_s, dflux_l
1536     ! Flux thermique utiliser pour fondre la neige
1537     real, dimension(klon), intent(INOUT):: ffonte
1538     ! Flux d'eau "perdue" par la surface et necessaire pour que limiter la
1539     ! hauteur de neige, en kg/m2/s
1540     real, dimension(klon), intent(INOUT):: fqcalving
1541     real, dimension(klon), intent(INOUT):: run_off_lic_0
1542     ! Variables locales
1543     ! Masse maximum de neige (kg/m2). Au dessus de ce seuil, la neige
1544     ! en exces "s'ecoule" (calving)
1545     ! real, parameter :: snow_max=1.
1546     !IM cf JLD/GK
1547     real, parameter :: snow_max=3000.
1548     integer :: i
1549     real, dimension(klon) :: zx_mh, zx_nh, zx_oh
1550     real, dimension(klon) :: zx_mq, zx_nq, zx_oq
1551     real, dimension(klon) :: zx_pkh, zx_dq_s_dt, zx_qsat, zx_coef
1552     real, dimension(klon) :: zx_sl, zx_k1
1553     real, dimension(klon) :: zx_q_0 , d_ts
1554     real :: zdelta, zcvm5, zx_qs, zcor, zx_dq_s_dh
1555     real :: bilan_f, fq_fonte
1556     REAL :: subli, fsno
1557     REAL, DIMENSION(klon) :: bil_eau_s, snow_evap
1558     real, parameter :: t_grnd = 271.35, t_coup = 273.15
1559     !! PB temporaire en attendant mieux pour le modele de neige
1560     ! REAL, parameter :: chasno = RLMLT/(2.3867E+06*0.15)
1561     REAL, parameter :: chasno = 3.334E+05/(2.3867E+06*0.15)
1562     !IM cf JLD/ GKtest
1563     REAL, parameter :: chaice = 3.334E+05/(2.3867E+06*0.15)
1564     ! fin GKtest
1565 guez 14
1566 guez 3 logical, save :: check = .FALSE.
1567     character (len = 20) :: modname = 'fonte_neige'
1568     logical, save :: neige_fond = .false.
1569     real, save :: max_eau_sol = 150.0
1570     character (len = 80) :: abort_message
1571 guez 14 logical, save :: first = .true., second=.false.
1572 guez 3 real :: coeff_rel
1573    
1574 guez 14 if (check) write(*, *)'Entree ', modname, ' surface = ', nisurf
1575 guez 3
1576     ! Initialisations
1577     coeff_rel = dtime/(tau_calv * rday)
1578 guez 14 bil_eau_s = 0.
1579 guez 3 DO i = 1, knon
1580     zx_pkh(i) = (ps(i)/ps(i))**RKAPPA
1581     IF (thermcep) THEN
1582 guez 14 zdelta=MAX(0., SIGN(1., rtt-tsurf(i)))
1583 guez 3 zcvm5 = R5LES*RLVTT*(1.-zdelta) + R5IES*RLSTT*zdelta
1584     zcvm5 = zcvm5 / RCPD / (1.0+RVTMP2*q1lay(i))
1585 guez 14 zx_qs= r2es * FOEEW(tsurf(i), zdelta)/ps(i)
1586     zx_qs=MIN(0.5, zx_qs)
1587 guez 3 zcor=1./(1.-retv*zx_qs)
1588     zx_qs=zx_qs*zcor
1589 guez 14 zx_dq_s_dh = FOEDE(tsurf(i), zdelta, zcvm5, zx_qs, zcor) &
1590 guez 3 & /RLVTT / zx_pkh(i)
1591     ELSE
1592     IF (tsurf(i).LT.t_coup) THEN
1593     zx_qs = qsats(tsurf(i)) / ps(i)
1594 guez 14 zx_dq_s_dh = dqsats(tsurf(i), zx_qs)/RLVTT &
1595 guez 3 & / zx_pkh(i)
1596     ELSE
1597     zx_qs = qsatl(tsurf(i)) / ps(i)
1598 guez 14 zx_dq_s_dh = dqsatl(tsurf(i), zx_qs)/RLVTT &
1599 guez 3 & / zx_pkh(i)
1600     ENDIF
1601     ENDIF
1602     zx_dq_s_dt(i) = RCPD * zx_pkh(i) * zx_dq_s_dh
1603     zx_qsat(i) = zx_qs
1604     zx_coef(i) = coef1lay(i) &
1605     & * (1.0+SQRT(u1lay(i)**2+v1lay(i)**2)) &
1606     & * p1lay(i)/(RD*t1lay(i))
1607     ENDDO
1608    
1609     ! === Calcul de la temperature de surface ===
1610 guez 14
1611 guez 3 ! zx_sl = chaleur latente d'evaporation ou de sublimation
1612 guez 14
1613 guez 3 do i = 1, knon
1614     zx_sl(i) = RLVTT
1615     if (tsurf(i) .LT. RTT) zx_sl(i) = RLSTT
1616     zx_k1(i) = zx_coef(i)
1617     enddo
1618    
1619     do i = 1, knon
1620     ! Q
1621     zx_oq(i) = 1. - (beta(i) * zx_k1(i) * peqBcoef(i) * dtime)
1622     zx_mq(i) = beta(i) * zx_k1(i) * &
1623     & (peqAcoef(i) - zx_qsat(i) &
1624     & + zx_dq_s_dt(i) * tsurf(i)) &
1625     & / zx_oq(i)
1626     zx_nq(i) = beta(i) * zx_k1(i) * (-1. * zx_dq_s_dt(i)) &
1627     & / zx_oq(i)
1628    
1629     ! H
1630     zx_oh(i) = 1. - (zx_k1(i) * petBcoef(i) * dtime)
1631     zx_mh(i) = zx_k1(i) * petAcoef(i) / zx_oh(i)
1632     zx_nh(i) = - (zx_k1(i) * RCPD * zx_pkh(i))/ zx_oh(i)
1633     enddo
1634    
1635     WHERE (precip_snow > 0.) snow = snow + (precip_snow * dtime)
1636     snow_evap = 0.
1637     WHERE (evap > 0. )
1638     snow_evap = MIN (snow / dtime, evap)
1639     snow = snow - snow_evap * dtime
1640     snow = MAX(0.0, snow)
1641     end where
1642    
1643     ! bil_eau_s = bil_eau_s + (precip_rain * dtime) - (evap - snow_evap) * dtime
1644     bil_eau_s = (precip_rain * dtime) - (evap - snow_evap) * dtime
1645    
1646 guez 14
1647 guez 3 ! Y'a-t-il fonte de neige?
1648 guez 14
1649 guez 3 ffonte=0.
1650     do i = 1, knon
1651     neige_fond = ((snow(i) > epsfra .OR. nisurf == is_sic .OR. nisurf == is_lic) &
1652     & .AND. tsurf_new(i) >= RTT)
1653     if (neige_fond) then
1654 guez 14 fq_fonte = MIN( MAX((tsurf_new(i)-RTT )/chasno, 0.0), snow(i))
1655 guez 3 ffonte(i) = fq_fonte * RLMLT/dtime
1656     snow(i) = max(0., snow(i) - fq_fonte)
1657     bil_eau_s(i) = bil_eau_s(i) + fq_fonte
1658     tsurf_new(i) = tsurf_new(i) - fq_fonte * chasno
1659     !IM cf JLD OK
1660     !IM cf JLD/ GKtest fonte aussi pour la glace
1661     IF (nisurf == is_sic .OR. nisurf == is_lic ) THEN
1662 guez 14 fq_fonte = MAX((tsurf_new(i)-RTT )/chaice, 0.0)
1663 guez 3 ffonte(i) = ffonte(i) + fq_fonte * RLMLT/dtime
1664     bil_eau_s(i) = bil_eau_s(i) + fq_fonte
1665     tsurf_new(i) = RTT
1666     ENDIF
1667     d_ts(i) = tsurf_new(i) - tsurf(i)
1668     endif
1669 guez 14
1670 guez 3 ! s'il y a une hauteur trop importante de neige, elle s'coule
1671     fqcalving(i) = max(0., snow(i) - snow_max)/dtime
1672 guez 14 snow(i)=min(snow(i), snow_max)
1673    
1674 guez 3 IF (nisurf == is_ter) then
1675     qsol(i) = qsol(i) + bil_eau_s(i)
1676     run_off(i) = run_off(i) + MAX(qsol(i) - max_eau_sol, 0.0)
1677     qsol(i) = MIN(qsol(i), max_eau_sol)
1678     else if (nisurf == is_lic) then
1679     run_off_lic(i) = (coeff_rel * fqcalving(i)) + &
1680     & (1. - coeff_rel) * run_off_lic_0(i)
1681     run_off_lic_0(i) = run_off_lic(i)
1682     run_off_lic(i) = run_off_lic(i) + bil_eau_s(i)/dtime
1683     endif
1684     enddo
1685    
1686     END SUBROUTINE fonte_neige
1687    
1688     END MODULE interface_surf

  ViewVC Help
Powered by ViewVC 1.1.21