/[lmdze]/trunk/phylmd/Interface_surf/interface_surf.f
ViewVC logotype

Annotation of /trunk/phylmd/Interface_surf/interface_surf.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 53 - (hide annotations)
Fri Oct 7 13:11:58 2011 UTC (12 years, 7 months ago) by guez
Original Path: trunk/libf/phylmd/interface_surf.f90
File size: 59922 byte(s)


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

  ViewVC Help
Powered by ViewVC 1.1.21