source: LMDZ.3.3/tags/IPSL-CM4_0x2/libf/phylmd/interface_surf.F90 @ 2054

Last change on this file since 2054 was 366, checked in by lmdzadmin, 22 years ago

Oublie declaration de qsol_new
LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 88.8 KB
Line 
1! $Header$
2
3  MODULE interface_surf
4
5! Ce module regroupe toutes les routines gerant l'interface entre le modele
6! atmospherique et les modeles de surface (sols continentaux, oceans, glaces)
7! Les routines sont les suivantes:
8!
9!   interfsurf_*: routines d'aiguillage vers les interfaces avec les
10!                 differents modeles de surface
11!   interfsol\
12!             > routines d'interface proprement dite
13!   interfoce/
14!
15!   interfstart: routine d'initialisation et de lecture de l'etat initial
16!                "interface"
17!   interffin  : routine d'ecriture de l'etat de redemmarage de l'interface
18!
19!
20! L. Fairhead, LMD, 02/2000
21
22  USE ioipsl
23
24  IMPLICIT none
25
26  PRIVATE
27  PUBLIC :: interfsurf,interfsurf_hq, gath2cpl
28
29  INTERFACE interfsurf
30    module procedure interfsurf_hq, interfsurf_vent
31  END INTERFACE
32
33  INTERFACE interfoce
34    module procedure interfoce_cpl, interfoce_slab, interfoce_lim
35  END INTERFACE
36
37#include "YOMCST.inc"
38#include "indicesol.inc"
39
40
41! run_off      ruissellement total
42  real, allocatable, dimension(:),save    :: run_off
43  real, allocatable, dimension(:),save    :: coastalflow, riverflow
44!!$PB
45  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: tmp_rriv, tmp_rcoa
46!! pour simuler la fonte des glaciers antarctiques
47  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: coeff_iceberg
48  real, save                              :: surf_maille
49  real, save                              :: cte_flux_iceberg = 6.3e7
50  integer, save                           :: num_antarctic = 1
51!!$
52  CONTAINS
53!
54!############################################################################
55!
56  SUBROUTINE interfsurf_hq(itime, dtime, date0, jour, rmu0, &
57      & klon, iim, jjm, nisurf, knon, knindex, pctsrf, &
58      & rlon, rlat, cufi, cvfi,&
59      & debut, lafin, ok_veget, soil_model, nsoilmx, tsoil,&
60      & zlev,  u1_lay, v1_lay, temp_air, spechum, epot_air, ccanopy, &
61      & tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
62      & precip_rain, precip_snow, sollw, sollwdown, swnet, swdown, &
63      & fder, taux, tauy, rugos, rugoro, &
64      & albedo, snow, qsol, &
65      & tsurf, p1lay, ps, radsol, &
66      & ocean, npas, nexca, zmasq, &
67      & evap, fluxsens, fluxlat, dflux_l, dflux_s, &             
68      & tsol_rad, tsurf_new, alb_new, alblw, emis_new, &
69      & z0_new, pctsrf_new, agesno)
70
71
72! Cette routine sert d'aiguillage entre l'atmosphere et la surface en general
73! (sols continentaux, oceans, glaces) pour les fluxs de chaleur et d'humidite.
74! En pratique l'interface se fait entre la couche limite du modele
75! atmospherique (clmain.F) et les routines de surface (sechiba, oasis, ...)
76!
77!
78! L.Fairhead 02/2000
79!
80! input:
81!   itime        numero du pas de temps
82!   klon         nombre total de points de grille
83!   iim, jjm     nbres de pts de grille
84!   dtime        pas de temps de la physique (en s)
85!   date0        jour initial
86!   jour         jour dans l'annee en cours,
87!   rmu0         cosinus de l'angle solaire zenithal
88!   nexca        pas de temps couplage
89!   nisurf       index de la surface a traiter (1 = sol continental)
90!   knon         nombre de points de la surface a traiter
91!   knindex      index des points de la surface a traiter
92!   pctsrf       tableau des pourcentages de surface de chaque maille
93!   rlon         longitudes
94!   rlat         latitudes
95!   cufi,cvfi    resolution des mailles en x et y (m)
96!   debut        logical: 1er appel a la physique
97!   lafin        logical: dernier appel a la physique
98!   ok_veget     logical: appel ou non au schema de surface continental
99!                     (si false calcul simplifie des fluxs sur les continents)
100!   zlev         hauteur de la premiere couche
101!   u1_lay       vitesse u 1ere couche
102!   v1_lay       vitesse v 1ere couche
103!   temp_air     temperature de l'air 1ere couche
104!   spechum      humidite specifique 1ere couche
105!   epot_air     temp potentielle de l'air
106!   ccanopy      concentration CO2 canopee
107!   tq_cdrag     cdrag
108!   petAcoef     coeff. A de la resolution de la CL pour t
109!   peqAcoef     coeff. A de la resolution de la CL pour q
110!   petBcoef     coeff. B de la resolution de la CL pour t
111!   peqBcoef     coeff. B de la resolution de la CL pour q
112!   precip_rain  precipitation liquide
113!   precip_snow  precipitation solide
114!   sollw        flux IR net a la surface
115!   sollwdown    flux IR descendant a la surface
116!   swnet        flux solaire net
117!   swdown       flux solaire entrant a la surface
118!   albedo       albedo de la surface
119!   tsurf        temperature de surface
120!   p1lay        pression 1er niveau (milieu de couche)
121!   ps           pression au sol
122!   radsol       rayonnement net aus sol (LW + SW)
123!   ocean        type d'ocean utilise (force, slab, couple)
124!   fder         derivee des flux (pour le couplage)
125!   taux, tauy   tension de vents
126!   rugos        rugosite
127!   zmasq        masque terre/ocean
128!   rugoro       rugosite orographique
129!
130! output:
131!   evap         evaporation totale
132!   fluxsens     flux de chaleur sensible
133!   fluxlat      flux de chaleur latente
134!   tsol_rad     
135!   tsurf_new    temperature au sol
136!   alb_new      albedo
137!   emis_new     emissivite
138!   z0_new       surface roughness
139!   pctsrf_new   nouvelle repartition des surfaces
140
141
142! Parametres d'entree
143  integer, intent(IN) :: itime
144  integer, intent(IN) :: iim, jjm
145  integer, intent(IN) :: klon
146  real, intent(IN) :: dtime
147  real, intent(IN) :: date0
148  integer, intent(IN) :: jour
149  real, intent(IN)    :: rmu0(klon)
150  integer, intent(IN) :: nisurf
151  integer, intent(IN) :: knon
152  integer, dimension(klon), intent(in) :: knindex
153  real, dimension(klon,nbsrf), intent(IN) :: pctsrf
154  logical, intent(IN) :: debut, lafin, ok_veget
155  real, dimension(klon), intent(IN) :: rlon, rlat
156  real, dimension(klon), intent(IN) :: cufi, cvfi
157  real, dimension(klon), intent(INOUT) :: tq_cdrag
158  real, dimension(klon), intent(IN) :: zlev
159  real, dimension(klon), intent(IN) :: u1_lay, v1_lay
160  real, dimension(klon), intent(IN) :: temp_air, spechum
161  real, dimension(klon), intent(IN) :: epot_air, ccanopy
162  real, dimension(klon), intent(IN) :: petAcoef, peqAcoef
163  real, dimension(klon), intent(IN) :: petBcoef, peqBcoef
164  real, dimension(klon), intent(IN) :: precip_rain, precip_snow
165  real, dimension(klon), intent(IN) :: sollw, sollwdown, swnet, swdown
166  real, dimension(klon), intent(IN) :: ps, albedo
167  real, dimension(klon), intent(IN) :: tsurf, p1lay
168  REAL, DIMENSION(klon), INTENT(INOUT) :: radsol,fder
169  real, dimension(klon), intent(IN) :: zmasq
170  real, dimension(klon), intent(IN) :: taux, tauy, rugos, rugoro
171  character (len = 6)  :: ocean
172  integer              :: npas, nexca ! nombre et pas de temps couplage
173  real, dimension(klon), intent(INOUT) :: evap, snow, qsol
174!! PB ajout pour soil
175  logical          :: soil_model
176  integer          :: nsoilmx
177  REAL, DIMENSION(klon, nsoilmx) :: tsoil
178  REAL, dimension(klon)          :: soilcap
179  REAL, dimension(klon)          :: soilflux
180! Parametres de sortie
181  real, dimension(klon), intent(OUT):: fluxsens, fluxlat
182  real, dimension(klon), intent(OUT):: tsol_rad, tsurf_new, alb_new
183  real, dimension(klon), intent(OUT):: alblw
184  real, dimension(klon), intent(OUT):: emis_new, z0_new
185  real, dimension(klon), intent(OUT):: dflux_l, dflux_s
186  real, dimension(klon,nbsrf), intent(OUT) :: pctsrf_new
187  real, dimension(klon), intent(INOUT):: agesno
188
189! Local
190  character (len = 20),save :: modname = 'interfsurf_hq'
191  character (len = 80) :: abort_message
192  logical, save        :: first_call = .true.
193  integer, save        :: error
194  integer              :: ii, index
195  logical,save              :: check = .false.
196  real, dimension(klon):: cal, beta, dif_grnd, capsol
197!!$PB  real, parameter      :: calice=1.0/(5.1444e+06*0.15), tau_gl=86400.*5.
198  real, parameter      :: calice=1.0/(5.1444e+06*0.15), tau_gl=86400.*5.
199  real, parameter      :: calsno=1./(2.3867e+06*.15)
200  real, dimension(klon):: alb_ice
201  real, dimension(klon):: tsurf_temp
202  real, dimension(klon):: qsol_new
203!!  real, allocatable, dimension(:), save :: alb_neig_grid
204  real, dimension(klon):: alb_neig, alb_eau
205  real, DIMENSION(klon):: zfra
206  logical              :: cumul = .false.
207
208  if (check) write(*,*) 'Entree ', modname
209!
210! On doit commencer par appeler les schemas de surfaces continentales
211! car l'ocean a besoin du ruissellement qui est y calcule
212!
213  if (first_call) then
214    if (nisurf /= is_ter .and. klon > 1) then
215      write(*,*)' *** Warning ***'
216      write(*,*)' nisurf = ',nisurf,' /= is_ter = ',is_ter
217      write(*,*)'or on doit commencer par les surfaces continentales'
218      abort_message='voir ci-dessus'
219      call abort_gcm(modname,abort_message,1)
220    endif
221    if (ocean /= 'slab  ' .and. ocean /= 'force ' .and. ocean /= 'couple') then
222      write(*,*)' *** Warning ***'
223      write(*,*)'Option couplage pour l''ocean = ', ocean
224      abort_message='option pour l''ocean non valable'
225      call abort_gcm(modname,abort_message,1)
226    endif
227    if ( is_oce > is_sic ) then
228      write(*,*)' *** Warning ***'
229      write(*,*)' Pour des raisons de sequencement dans le code'
230      write(*,*)' l''ocean doit etre traite avant la banquise'
231      write(*,*)' or is_oce = ',is_oce, '> is_sic = ',is_sic
232      abort_message='voir ci-dessus'
233      call abort_gcm(modname,abort_message,1)
234    endif
235!    allocate(alb_neig_grid(klon), stat = error)
236!    if (error /= 0) then
237!      abort_message='Pb allocation alb_neig_grid'
238!      call abort_gcm(modname,abort_message,1)
239!    endif
240  endif
241  first_call = .false.
242 
243! Initialisations diverses
244!
245!!$  cal=0.; beta=1.; dif_grnd=0.; capsol=0.
246!!$  alb_new = 0.; z0_new = 0.; alb_neig = 0.0
247!!$! PB
248!!$  tsurf_new = 0.
249
250  cal = 999999. ; beta = 999999. ; dif_grnd = 999999. ; capsol = 999999.
251  alb_new = 999999. ; z0_new = 999999. ; alb_neig = 999999.
252  tsurf_new = 999999.
253  alblw = 999999.
254! Aiguillage vers les differents schemas de surface
255
256  if (nisurf == is_ter) then
257!
258! Surface "terre" appel a l'interface avec les sols continentaux
259!
260! allocation du run-off
261    if (.not. allocated(coastalflow)) then
262      allocate(coastalflow(knon), stat = error)
263      if (error /= 0) then
264        abort_message='Pb allocation coastalflow'
265        call abort_gcm(modname,abort_message,1)
266      endif
267      allocate(riverflow(knon), stat = error)
268      if (error /= 0) then
269        abort_message='Pb allocation riverflow'
270        call abort_gcm(modname,abort_message,1)
271      endif
272      allocate(run_off(knon), stat = error)
273      if (error /= 0) then
274        abort_message='Pb allocation run_off'
275        call abort_gcm(modname,abort_message,1)
276      endif
277!!$PB
278      ALLOCATE (tmp_rriv(iim,jjm+1), stat=error)
279      if (error /= 0) then
280        abort_message='Pb allocation tmp_rriv'
281        call abort_gcm(modname,abort_message,1)
282      endif
283      ALLOCATE (tmp_rcoa(iim,jjm+1), stat=error)
284      if (error /= 0) then
285        abort_message='Pb allocation tmp_rcoa'
286        call abort_gcm(modname,abort_message,1)
287      endif
288!!$
289    else if (size(coastalflow) /= knon) then
290      write(*,*)'Bizarre, le nombre de points continentaux'
291      write(*,*)'a change entre deux appels. J''arrete ...'
292      abort_message='voir ci-dessus'
293      call abort_gcm(modname,abort_message,1)
294    endif
295    coastalflow = 0.
296    riverflow = 0.
297!
298! Calcul age de la neige
299!
300!!$ PB ATTENTION changement ordre des appels
301!!$    CALL albsno(klon,agesno,alb_neig_grid) 
302
303    if (.not. ok_veget) then
304!
305! calcul albedo: lecture albedo fichier CL puis ajout albedo neige
306!
307       call interfsur_lim(itime, dtime, jour, &
308     & klon, nisurf, knon, knindex, debut,  &
309     & alb_new, z0_new)
310
311! calcul snow et qsol, hydrol adapté
312!
313       CALL calbeta(dtime, nisurf, knon, snow, qsol, beta, capsol, dif_grnd)
314
315       IF (soil_model) THEN
316           CALL soil(dtime, nisurf, knon,snow, tsurf, tsoil,soilcap, soilflux)
317           cal(1:knon) = RCPD / soilcap(1:knon)
318           radsol(1:knon) = radsol(1:knon)  + soilflux(1:knon)
319       ELSE
320           cal = RCPD * capsol
321!!$      cal = capsol
322       ENDIF
323       CALL calcul_fluxs( klon, knon, nisurf, dtime, &
324     &   tsurf, p1lay, cal, beta, tq_cdrag, ps, &
325     &   precip_rain, precip_snow, snow, qsol,  &
326     &   radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
327     &   petAcoef, peqAcoef, petBcoef, peqBcoef, &
328     &   tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
329
330       CALL fonte_neige( klon, knon, nisurf, dtime, &
331     &   tsurf, p1lay, cal, beta, tq_cdrag, ps, &
332     &   precip_rain, precip_snow, snow, qsol,  &
333     &   radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
334     &   petAcoef, peqAcoef, petBcoef, peqBcoef, &
335     &   tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
336
337
338     call albsno(klon,knon,dtime,agesno(:),alb_neig(:), precip_snow(:)) 
339     where (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
340     zfra(1:knon) = max(0.0,min(1.0,snow(1:knon)/(snow(1:knon)+10.0)))
341     alb_new(1 : knon)  = alb_neig(1 : knon) *zfra(1:knon) + &
342    &                     alb_new(1 : knon)*(1.0-zfra(1:knon))
343     z0_new = sqrt(z0_new**2+rugoro**2)
344     alblw(1 : knon) = alb_new(1 : knon)
345
346    else
347!!      CALL albsno(klon,agesno,alb_neig_grid) 
348!
349!  appel a sechiba
350!
351      call interfsol(itime, klon, dtime, date0, nisurf, knon, &
352     &  knindex, rlon, rlat, cufi, cvfi, iim, jjm, pctsrf, &
353     &  debut, lafin, ok_veget, &
354     &  zlev,  u1_lay, v1_lay, temp_air, spechum, epot_air, ccanopy, &
355     &  tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
356     &  precip_rain, precip_snow, sollwdown, swnet, swdown, &
357     &  tsurf, p1lay/100., ps/100., radsol, &
358     &  evap, fluxsens, fluxlat, &             
359     &  tsol_rad, tsurf_new, alb_new, alblw, &
360     &  emis_new, z0_new, dflux_l, dflux_s, qsol_new)
361
362
363! ajout de la contribution du relief
364
365      z0_new = SQRT(z0_new**2+rugoro**2)
366!
367! mise a jour de l'humidite saturante calculee par ORCHIDEE
368      qsol(1:knon) = qsol_new(1:knon)
369
370    endif   
371!
372! Remplissage des pourcentages de surface
373!
374    pctsrf_new(:,nisurf) = pctsrf(:,nisurf)
375
376  else if (nisurf == is_oce) then
377
378    if (check) write(*,*)'ocean, nisurf = ',nisurf
379
380
381!
382! Surface "ocean" appel a l'interface avec l'ocean
383!
384    if (ocean == 'couple') then
385      if (nexca == 0) then
386        abort_message='nexca = 0 dans interfoce_cpl'
387        call abort_gcm(modname,abort_message,1)
388      endif
389
390      cumul = .false.
391
392      call interfoce(itime, dtime, cumul, &
393      & klon, iim, jjm, nisurf, pctsrf, knon, knindex, rlon, rlat, &
394      & ocean, npas, nexca, debut, lafin, &
395      & swdown, sollw, precip_rain, precip_snow, evap, tsurf, &
396      & fluxlat, fluxsens, fder, albedo, taux, tauy, zmasq, &
397      & tsurf_new, alb_new, pctsrf_new)
398
399!    else if (ocean == 'slab  ') then
400!      call interfoce(nisurf)
401    else                              ! lecture conditions limites
402      call interfoce(itime, dtime, jour, &
403     &  klon, nisurf, knon, knindex, &
404     &  debut, &
405     &  tsurf_new, pctsrf_new)
406
407    endif
408
409    tsurf_temp = tsurf_new
410    cal = 0.
411    beta = 1.
412    dif_grnd = 0.
413    alb_neig(:) = 0.
414    agesno(:) = 0.
415
416    call calcul_fluxs( klon, knon, nisurf, dtime, &
417     &   tsurf_temp, p1lay, cal, beta, tq_cdrag, ps, &
418     &   precip_rain, precip_snow, snow, qsol,  &
419     &   radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
420     &   petAcoef, peqAcoef, petBcoef, peqBcoef, &
421     &   tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
422   
423    fder = fder + dflux_s + dflux_l
424
425!
426! 2eme appel a interfoce pour le cumul des champs (en particulier
427! fluxsens et fluxlat calcules dans calcul_fluxs)
428!
429    if (ocean == 'couple') then
430
431      cumul = .true.
432
433      call interfoce(itime, dtime, cumul, &
434      & klon, iim, jjm, nisurf, pctsrf, knon, knindex, rlon, rlat, &
435      & ocean, npas, nexca, debut, lafin, &
436      & swdown, sollw, precip_rain, precip_snow, evap, tsurf, &
437      & fluxlat, fluxsens, fder, albedo, taux, tauy, zmasq, &
438      & tsurf_new, alb_new, pctsrf_new)
439
440!    else if (ocean == 'slab  ') then
441!      call interfoce(nisurf)
442
443    endif
444
445!
446! calcul albedo
447!
448
449    if ( minval(rmu0) == maxval(rmu0) .and. minval(rmu0) == -999.999 ) then
450      CALL alboc(FLOAT(jour),rlat,alb_eau)
451    else  ! cycle diurne
452      CALL alboc_cd(rmu0,alb_eau)
453    endif
454    DO ii =1, knon
455      alb_new(ii) = alb_eau(knindex(ii))
456    enddo
457
458    z0_new = sqrt(rugos**2 + rugoro**2)
459    alblw(1:knon) = alb_new(1:knon)
460
461!
462  else if (nisurf == is_sic) then
463
464    if (check) write(*,*)'sea ice, nisurf = ',nisurf
465
466!
467! Surface "glace de mer" appel a l'interface avec l'ocean
468!
469!
470    if (ocean == 'couple') then
471
472      cumul =.false.
473
474      call interfoce(itime, dtime, cumul, &
475      & klon, iim, jjm, nisurf, pctsrf, knon, knindex, rlon, rlat, &
476      & ocean, npas, nexca, debut, lafin, &
477      & swdown, sollw, precip_rain, precip_snow, evap, tsurf, &
478      & fluxlat, fluxsens, fder, albedo, taux, tauy, zmasq, &
479      & tsurf_new, alb_new, pctsrf_new)
480
481      tsurf_temp = tsurf_new
482      cal = 0.
483      dif_grnd = 0.
484      beta = 1.0
485
486!    else if (ocean == 'slab  ') then
487!      call interfoce(nisurf)
488    ELSE
489!                              ! lecture conditions limites
490      CALL interfoce(itime, dtime, jour, &
491             &  klon, nisurf, knon, knindex, &
492             &  debut, &
493             &  tsurf_new, pctsrf_new)
494
495      CALL calbeta(dtime, nisurf, knon, snow, qsol, beta, capsol, dif_grnd)
496     
497      IF (soil_model) THEN
498         CALL soil(dtime, nisurf, knon,snow, tsurf, tsoil,soilcap, soilflux)
499         cal(1:knon) = RCPD / soilcap(1:knon)
500         radsol(1:knon) = radsol(1:knon)  + soilflux(1:knon)
501         dif_grnd = 0.
502      ELSE
503         dif_grnd = 1.0 / tau_gl
504         cal = RCPD * calice
505         WHERE (snow > 0.0) cal = RCPD * calsno
506      ENDIF
507      tsurf_temp = tsurf
508      beta = 1.0
509    ENDIF
510
511    CALL calcul_fluxs( klon, knon, nisurf, dtime, &
512         &   tsurf_temp, p1lay, cal, beta, tq_cdrag, ps, &
513         &   precip_rain, precip_snow, snow, qsol,  &
514         &   radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
515         &   petAcoef, peqAcoef, petBcoef, peqBcoef, &
516         &   tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
517
518    IF (ocean /= 'couple') THEN
519      CALL fonte_neige( klon, knon, nisurf, dtime, &
520             &   tsurf_temp, p1lay, cal, beta, tq_cdrag, ps, &
521             &   precip_rain, precip_snow, snow, qsol,  &
522             &   radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
523             &   petAcoef, peqAcoef, petBcoef, peqBcoef, &
524             &   tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
525
526!     calcul albedo
527
528      CALL albsno(klon,knon,dtime,agesno(:),alb_neig(:), precip_snow(:)) 
529      WHERE (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
530      zfra(1:knon) = MAX(0.0,MIN(1.0,snow(1:knon)/(snow(1:knon)+10.0)))
531      alb_new(1 : knon) = alb_neig(1 : knon) *zfra(1:knon) + &
532     &                    0.6 * (1.0-zfra(1:knon))
533!!      alb_new(1 : knon) = 0.6
534    ENDIF
535
536    fder = fder + dflux_s + dflux_l
537
538!
539! 2eme appel a interfoce pour le cumul et le passage des flux a l'ocean
540!
541    if (ocean == 'couple') then
542
543      cumul =.true.
544
545      call interfoce(itime, dtime, cumul, &
546      & klon, iim, jjm, nisurf, pctsrf, knon, knindex, rlon, rlat, &
547      & ocean, npas, nexca, debut, lafin, &
548      & swdown, sollw, precip_rain, precip_snow, evap, tsurf, &
549      & fluxlat, fluxsens, fder, albedo, taux, tauy, zmasq, &
550      & tsurf_new, alb_new, pctsrf_new)
551
552!    else if (ocean == 'slab  ') then
553!      call interfoce(nisurf)
554
555    endif
556
557     
558    z0_new = 0.001
559    z0_new = SQRT(z0_new**2+rugoro**2)
560    alblw(1:knon) = alb_new(1:knon)
561
562  else if (nisurf == is_lic) then
563
564    if (check) write(*,*)'glacier, nisurf = ',nisurf
565
566!
567! Surface "glacier continentaux" appel a l'interface avec le sol
568!
569!    call interfsol(nisurf)
570    IF (soil_model) THEN
571        CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil,soilcap, soilflux)
572        cal(1:knon) = RCPD / soilcap(1:knon)
573        radsol(1:knon)  = radsol(1:knon) + soilflux(1:knon)
574    ELSE
575        cal = RCPD * calice
576        WHERE (snow > 0.0) cal = RCPD * calsno
577    ENDIF
578    beta = 1.0
579    dif_grnd = 0.0
580
581    call calcul_fluxs( klon, knon, nisurf, dtime, &
582     &   tsurf, p1lay, cal, beta, tq_cdrag, ps, &
583     &   precip_rain, precip_snow, snow, qsol,  &
584     &   radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
585     &   petAcoef, peqAcoef, petBcoef, peqBcoef, &
586     &   tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
587
588    call fonte_neige( klon, knon, nisurf, dtime, &
589     &   tsurf, p1lay, cal, beta, tq_cdrag, ps, &
590     &   precip_rain, precip_snow, snow, qsol,  &
591     &   radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
592     &   petAcoef, peqAcoef, petBcoef, peqBcoef, &
593     &   tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
594
595!
596! calcul albedo
597!
598     CALL albsno(klon,knon,dtime,agesno(:),alb_neig(:), precip_snow(:)) 
599     WHERE (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
600     zfra(1:knon) = MAX(0.0,MIN(1.0,snow(1:knon)/(snow(1:knon)+10.0)))
601     alb_new(1 : knon)  = alb_neig(1 : knon)*zfra(1:knon) + &
602    &                     0.6 * (1.0-zfra(1:knon))
603!!     alb_new(1 : knon)  = 0.6
604!
605! Rugosite
606!
607    z0_new = rugoro
608!
609! Remplissage des pourcentages de surface
610!
611    pctsrf_new(:,nisurf) = pctsrf(:,nisurf)
612
613    alblw(1:knon) = alb_new(1:knon)
614  else
615    write(*,*)'Index surface = ',nisurf
616    abort_message = 'Index surface non valable'
617    call abort_gcm(modname,abort_message,1)
618  endif
619
620  END SUBROUTINE interfsurf_hq
621
622!
623!#########################################################################
624!
625  SUBROUTINE interfsurf_vent(nisurf, knon   &         
626  &                     )
627!
628! Cette routine sert d'aiguillage entre l'atmosphere et la surface en general
629! (sols continentaux, oceans, glaces) pour les tensions de vents.
630! En pratique l'interface se fait entre la couche limite du modele
631! atmospherique (clmain.F) et les routines de surface (sechiba, oasis, ...)
632!
633!
634! L.Fairhead 02/2000
635!
636! input:
637!   nisurf       index de la surface a traiter (1 = sol continental)
638!   knon         nombre de points de la surface a traiter
639
640! Parametres d'entree
641  integer, intent(IN) :: nisurf
642  integer, intent(IN) :: knon
643
644
645  return
646  END SUBROUTINE interfsurf_vent
647!
648!#########################################################################
649!
650  SUBROUTINE interfsol(itime, klon, dtime, date0, nisurf, knon, &
651     & knindex, rlon, rlat, cufi, cvfi, iim, jjm, pctsrf, &
652     & debut, lafin, ok_veget, &
653     & zlev,  u1_lay, v1_lay, temp_air, spechum, epot_air, ccanopy, &
654     & tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
655     & precip_rain, precip_snow, lwdown, swnet, swdown, &
656     & tsurf, p1lay, ps, radsol, &
657     & evap, fluxsens, fluxlat, &             
658     & tsol_rad, tsurf_new, alb_new, alblw, &
659     & emis_new, z0_new, dflux_l, dflux_s, qsurf)
660
661  USE intersurf
662
663! Cette routine sert d'interface entre le modele atmospherique et le
664! modele de sol continental. Appel a sechiba
665!
666! L. Fairhead 02/2000
667!
668! input:
669!   itime        numero du pas de temps
670!   klon         nombre total de points de grille
671!   dtime        pas de temps de la physique (en s)
672!   nisurf       index de la surface a traiter (1 = sol continental)
673!   knon         nombre de points de la surface a traiter
674!   knindex      index des points de la surface a traiter
675!   rlon         longitudes de la grille entiere
676!   rlat         latitudes de la grille entiere
677!   pctsrf       tableau des fractions de surface de chaque maille
678!   debut        logical: 1er appel a la physique (lire les restart)
679!   lafin        logical: dernier appel a la physique (ecrire les restart)
680!   ok_veget     logical: appel ou non au schema de surface continental
681!                     (si false calcul simplifie des fluxs sur les continents)
682!   zlev         hauteur de la premiere couche       
683!   u1_lay       vitesse u 1ere couche
684!   v1_lay       vitesse v 1ere couche
685!   temp_air     temperature de l'air 1ere couche
686!   spechum      humidite specifique 1ere couche
687!   epot_air     temp pot de l'air
688!   ccanopy      concentration CO2 canopee
689!   tq_cdrag     cdrag
690!   petAcoef     coeff. A de la resolution de la CL pour t
691!   peqAcoef     coeff. A de la resolution de la CL pour q
692!   petBcoef     coeff. B de la resolution de la CL pour t
693!   peqBcoef     coeff. B de la resolution de la CL pour q
694!   precip_rain  precipitation liquide
695!   precip_snow  precipitation solide
696!   lwdown       flux IR descendant a la surface
697!   swnet        flux solaire net
698!   swdown       flux solaire entrant a la surface
699!   tsurf        temperature de surface
700!   p1lay        pression 1er niveau (milieu de couche)
701!   ps           pression au sol
702!   radsol       rayonnement net aus sol (LW + SW)
703!   
704!
705! input/output
706!   run_off      ruissellement total
707!
708! output:
709!   evap         evaporation totale
710!   fluxsens     flux de chaleur sensible
711!   fluxlat      flux de chaleur latente
712!   tsol_rad     
713!   tsurf_new    temperature au sol
714!   alb_new      albedo
715!   emis_new     emissivite
716!   z0_new       surface roughness
717!   qsurf        saturated air moisture at surface
718
719! Parametres d'entree
720  integer, intent(IN) :: itime
721  integer, intent(IN) :: klon
722  real, intent(IN)    :: dtime
723  real, intent(IN)    :: date0
724  integer, intent(IN) :: nisurf
725  integer, intent(IN) :: knon
726  integer, intent(IN) :: iim, jjm
727  integer, dimension(klon), intent(IN) :: knindex
728  logical, intent(IN) :: debut, lafin, ok_veget
729  real, dimension(klon,nbsrf), intent(IN) :: pctsrf
730  real, dimension(klon), intent(IN) :: rlon, rlat
731  real, dimension(klon), intent(IN) :: cufi, cvfi
732  real, dimension(klon), intent(IN) :: zlev
733  real, dimension(klon), intent(IN) :: u1_lay, v1_lay
734  real, dimension(klon), intent(IN) :: temp_air, spechum
735  real, dimension(klon), intent(IN) :: epot_air, ccanopy
736  real, dimension(klon), intent(INOUT) :: tq_cdrag
737  real, dimension(klon), intent(IN) :: petAcoef, peqAcoef
738  real, dimension(klon), intent(IN) :: petBcoef, peqBcoef
739  real, dimension(klon), intent(IN) :: precip_rain, precip_snow
740  real, dimension(klon), intent(IN) :: lwdown, swnet, swdown, ps
741  real, dimension(klon), intent(IN) :: tsurf, p1lay
742  real, dimension(klon), intent(IN) :: radsol
743! Parametres de sortie
744  real, dimension(klon), intent(OUT):: evap, fluxsens, fluxlat, qsurf
745  real, dimension(klon), intent(OUT):: tsol_rad, tsurf_new, alb_new, alblw
746  real, dimension(klon), intent(OUT):: emis_new, z0_new
747  real, dimension(klon), intent(OUT):: dflux_s, dflux_l
748
749! Local
750!
751  integer              :: ii, ij, jj, igrid, ireal, i, index, iglob
752  integer              :: error
753  character (len = 20) :: modname = 'interfsol'
754  character (len = 80) :: abort_message
755  logical,save              :: check = .FALSE.
756  real, dimension(klon) :: cal, beta, dif_grnd, capsol
757! type de couplage dans sechiba
758!  character (len=10)   :: coupling = 'implicit'
759! drapeaux controlant les appels dans SECHIBA
760!  type(control_type), save   :: control_in
761! coordonnees geographiques
762  real, allocatable, dimension(:,:), save :: lalo
763! pts voisins
764  integer,allocatable, dimension(:,:), save :: neighbours
765! fractions continents
766  real,allocatable, dimension(:), save :: contfrac
767! resolution de la grille
768  real, allocatable, dimension (:,:), save :: resolution
769! correspondance point n -> indices (i,j)
770  integer, allocatable, dimension(:,:), save :: correspond
771! offset pour calculer les point voisins
772  integer, dimension(8,3), save :: off_ini
773  integer, dimension(8), save :: offset
774! Identifieurs des fichiers restart et histoire
775  integer, save          :: rest_id, hist_id
776  integer, save          :: rest_id_stom, hist_id_stom
777!
778  real, allocatable, dimension (:,:), save :: lon_scat, lat_scat 
779
780  logical, save          :: lrestart_read = .true. , lrestart_write = .false.
781
782  real, dimension(klon):: snow
783  real, dimension(knon,2) :: albedo_out
784! Pb de nomenclature
785  real, dimension(klon) :: petA_orc, peqA_orc
786  real, dimension(klon) :: petB_orc, peqB_orc
787! Pb de correspondances de grilles
788  integer, dimension(:), save, allocatable :: ig, jg
789  integer :: indi, indj
790  integer, dimension(klon) :: ktindex
791  REAL, dimension(klon) :: bidule
792! Essai cdrag
793  real, dimension(klon) :: cdrag
794
795  include 'temps.inc'
796
797  if (check) write(*,*)'Entree ', modname
798  if (check) write(*,*)'ok_veget = ',ok_veget
799
800  ktindex(:) = knindex(:) + iim - 1
801
802! initialisation
803  if (debut) then
804
805! Pb de correspondances de grilles
806   allocate(ig(klon))
807   allocate(jg(klon))
808   ig(1) = 1
809   jg(1) = 1
810   indi = 0
811   indj = 2
812   do igrid = 2, klon - 1
813     indi = indi + 1
814     if ( indi > iim) then
815       indi = 1
816       indj = indj + 1
817     endif
818     ig(igrid) = indi
819     jg(igrid) = indj
820   enddo
821   ig(klon) = 1
822   jg(klon) = jjm + 1
823!
824!  Initialisation des offset   
825!
826! offset bord ouest
827   off_ini(1,1) = - iim  ; off_ini(2,1) = - iim + 1; off_ini(3,1) = 1
828   off_ini(4,1) = iim + 1; off_ini(5,1) = iim      ; off_ini(6,1) = 2 * iim - 1
829   off_ini(7,1) = iim -1 ; off_ini(8,1) = - 1
830! offset point normal
831   off_ini(1,2) = - iim  ; off_ini(2,2) = - iim + 1; off_ini(3,2) = 1
832   off_ini(4,2) = iim + 1; off_ini(5,2) = iim      ; off_ini(6,2) = iim - 1
833   off_ini(7,2) = -1     ; off_ini(8,2) = - iim - 1
834! offset bord   est
835   off_ini(1,3) = - iim; off_ini(2,3) = - 2 * iim + 1; off_ini(3,3) = - iim + 1
836   off_ini(4,3) =  1   ; off_ini(5,3) = iim          ; off_ini(6,3) = iim - 1
837   off_ini(7,3) = -1   ; off_ini(8,3) = - iim - 1
838!
839! Initialisation des correspondances point -> indices i,j
840!
841    if (( .not. allocated(correspond))) then
842      allocate(correspond(iim,jjm+1), stat = error)
843      if (error /= 0) then
844        abort_message='Pb allocation correspond'
845        call abort_gcm(modname,abort_message,1)
846      endif     
847    endif
848!
849! Attention aux poles
850!
851    do igrid = 1, knon
852      index = ktindex(igrid)
853          jj = int((index - 1)/iim) + 1
854          ij = index - (jj - 1) * iim
855      correspond(ij,jj) = igrid
856    enddo
857
858! Allouer et initialiser le tableau de coordonnees du sol
859!
860    if ((.not. allocated(lalo))) then
861      allocate(lalo(knon,2), stat = error)
862      if (error /= 0) then
863        abort_message='Pb allocation lalo'
864        call abort_gcm(modname,abort_message,1)
865      endif     
866    endif
867    if ((.not. allocated(lon_scat))) then
868      allocate(lon_scat(iim,jjm+1), stat = error)
869      if (error /= 0) then
870        abort_message='Pb allocation lon_scat'
871        call abort_gcm(modname,abort_message,1)
872      endif     
873    endif
874    if ((.not. allocated(lat_scat))) then
875      allocate(lat_scat(iim,jjm+1), stat = error)
876      if (error /= 0) then
877        abort_message='Pb allocation lat_scat'
878        call abort_gcm(modname,abort_message,1)
879      endif     
880    endif
881    lon_scat = 0.
882    lat_scat = 0.
883    do igrid = 1, knon
884      index = knindex(igrid)
885      lalo(igrid,2) = rlon(index)
886      lalo(igrid,1) = rlat(index)
887      ij = index - int((index-1)/iim)*iim - 1
888      jj = 2 + int((index-1)/iim)
889      if (mod(index,iim) == 1 ) then
890        jj = 1 + int((index-1)/iim)
891        ij = iim
892      endif
893!      lon_scat(ij,jj) = rlon(index)
894!      lat_scat(ij,jj) = rlat(index)
895    enddo
896    index = 1
897    do jj = 2, jjm
898      do ij = 1, iim
899        index = index + 1
900        lon_scat(ij,jj) = rlon(index)
901        lat_scat(ij,jj) = rlat(index)
902      enddo
903    enddo
904    lon_scat(:,1) = lon_scat(:,2)
905    lat_scat(:,1) = rlat(1)
906    lon_scat(:,jjm+1) = lon_scat(:,2)
907    lat_scat(:,jjm+1) = rlat(klon)
908! Pb de correspondances de grilles!
909!    do igrid = 1, knon
910!      index = ktindex(igrid)
911!      ij = ig(index)
912!      jj = jg(index)
913!      lon_scat(ij,jj) = rlon(index)
914!      lat_scat(ij,jj) = rlat(index)
915!    enddo
916
917!
918! Allouer et initialiser le tableau des voisins et des fraction de continents
919!
920    if ( (.not.allocated(neighbours))) THEN
921      allocate(neighbours(knon,8), stat = error)
922      if (error /= 0) then
923        abort_message='Pb allocation neighbours'
924        call abort_gcm(modname,abort_message,1)
925      endif
926    endif
927    neighbours = -1.
928    if (( .not. allocated(contfrac))) then
929      allocate(contfrac(knon), stat = error)
930      if (error /= 0) then
931        abort_message='Pb allocation contfrac'
932        call abort_gcm(modname,abort_message,1)
933      endif     
934    endif
935
936    do igrid = 1, knon
937      ireal = knindex(igrid)
938      contfrac(igrid) = pctsrf(ireal,is_ter)
939    enddo
940
941    do igrid = 1, knon
942      iglob = ktindex(igrid)
943      if (mod(iglob, iim) == 1) then
944        offset = off_ini(:,1)
945      else if(mod(iglob, iim) == 0) then
946        offset = off_ini(:,3)
947      else
948        offset = off_ini(:,2)
949      endif
950      do i = 1, 8
951        index = iglob + offset(i)
952        ireal = (min(max(1, index - iim + 1), klon))
953        if (pctsrf(ireal, is_ter) > EPSFRA) then
954          jj = int((index - 1)/iim) + 1
955          ij = index - (jj - 1) * iim
956            neighbours(igrid, i) = correspond(ij, jj)
957        endif
958      enddo
959    enddo
960
961!
962!  Allocation et calcul resolutions
963    IF ( (.NOT.ALLOCATED(resolution))) THEN
964      ALLOCATE(resolution(knon,2), stat = error)
965      if (error /= 0) then
966        abort_message='Pb allocation resolution'
967        call abort_gcm(modname,abort_message,1)
968      endif
969    ENDIF
970    do igrid = 1, knon
971      ij = knindex(igrid)
972      resolution(igrid,1) = cufi(ij)
973      resolution(igrid,2) = cvfi(ij)
974    enddo 
975
976  endif                          ! (fin debut)
977
978!
979! Appel a la routine sols continentaux
980!
981  if (lafin) lrestart_write = .true.
982  if (check) write(*,*)'lafin ',lafin,lrestart_write
983
984  petA_orc = petBcoef * dtime
985  petB_orc = petAcoef
986  peqA_orc = peqBcoef * dtime
987  peqB_orc = peqAcoef
988
989  cdrag = 0.
990  cdrag(1:knon) = tq_cdrag(1:knon)
991
992   where(cdrag > 0.01)
993     cdrag = 0.01
994   endwhere
995!  write(*,*)'Cdrag = ',minval(cdrag),maxval(cdrag)
996
997!
998! Init Orchidee
999!
1000  if (debut) then
1001    call intersurf_main (itime+itau_phy-1, iim, jjm+1, knon, ktindex, dtime, &
1002     & lrestart_read, lrestart_write, lalo, &
1003     & contfrac, neighbours, resolution, date0, &
1004     & zlev,  u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, &
1005     & cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, &
1006     & precip_rain, precip_snow, lwdown, swnet, swdown, ps, &
1007     & evap, fluxsens, fluxlat, coastalflow, riverflow, &
1008     & tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, &
1009     & lon_scat, lat_scat)
1010  endif
1011
1012  call intersurf_main (itime+itau_phy, iim, jjm+1, knon, ktindex, dtime, &
1013     & lrestart_read, lrestart_write, lalo, &
1014     & contfrac, neighbours, resolution, date0, &
1015     & zlev,  u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, &
1016     & cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, &
1017     & precip_rain, precip_snow, lwdown, swnet, swdown, ps, &
1018     & evap, fluxsens, fluxlat, coastalflow, riverflow, &
1019     & tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, &
1020     & lon_scat, lat_scat)
1021
1022    bidule=0.
1023    bidule(1:knon)=riverflow(1:knon)
1024    call gath2cpl(bidule, tmp_rriv, klon, knon,iim,jjm,ktindex)
1025    bidule=0.
1026    bidule(1:knon)=coastalflow(1:knon)
1027    call gath2cpl(bidule, tmp_rcoa, klon, knon,iim,jjm,ktindex)
1028    alb_new(1:knon) = albedo_out(1:knon,1)
1029    alblw(1:knon) = albedo_out(1:knon,2)
1030
1031
1032! Convention orchidee: positif vers le haut
1033  fluxsens(1:knon) = -1. * fluxsens(1:knon)
1034  fluxlat(1:knon)  = -1. * fluxlat(1:knon)
1035
1036!  evap     = -1. * evap
1037
1038  if (debut) lrestart_read = .false.
1039
1040  END SUBROUTINE interfsol
1041!
1042!#########################################################################
1043!
1044  SUBROUTINE interfoce_cpl(itime, dtime, cumul, &
1045      & klon, iim, jjm, nisurf, pctsrf, knon, knindex, rlon, rlat, &
1046      & ocean, npas, nexca, debut, lafin, &
1047      & swdown, lwdown, precip_rain, precip_snow, evap, tsurf, &
1048      & fluxlat, fluxsens, fder, albsol, taux, tauy, zmasq, &
1049      & tsurf_new, alb_new, pctsrf_new)
1050
1051! Cette routine sert d'interface entre le modele atmospherique et un
1052! coupleur avec un modele d'ocean 'complet' derriere
1053!
1054! Le modele de glace qu'il est prevu d'utiliser etant couple directement a
1055! l'ocean presentement, on va passer deux fois dans cette routine par pas de
1056! temps physique, une fois avec les points oceans et l'autre avec les points
1057! glace. A chaque pas de temps de couplage, la lecture des champs provenant
1058! du coupleur se fera "dans" l'ocean et l'ecriture des champs a envoyer
1059! au coupleur "dans" la glace. Il faut donc des tableaux de travail "tampons"
1060! dimensionnes sur toute la grille qui remplissent les champs sur les
1061! domaines ocean/glace quand il le faut. Il est aussi necessaire que l'index
1062! ocean soit traiter avant l'index glace (sinon tout intervertir)
1063!
1064!
1065! L. Fairhead 02/2000
1066!
1067! input:
1068!   itime        numero du pas de temps
1069!   iim, jjm     nbres de pts de grille
1070!   dtime        pas de temps de la physique
1071!   klon         nombre total de points de grille
1072!   nisurf       index de la surface a traiter (1 = sol continental)
1073!   pctsrf       tableau des fractions de surface de chaque maille
1074!   knon         nombre de points de la surface a traiter
1075!   knindex      index des points de la surface a traiter
1076!   rlon         longitudes
1077!   rlat         latitudes
1078!   debut        logical: 1er appel a la physique
1079!   lafin        logical: dernier appel a la physique
1080!   ocean        type d'ocean
1081!   nexca        frequence de couplage
1082!   swdown       flux solaire entrant a la surface
1083!   lwdown       flux IR net a la surface
1084!   precip_rain  precipitation liquide
1085!   precip_snow  precipitation solide
1086!   evap         evaporation
1087!   tsurf        temperature de surface
1088!   fder         derivee dF/dT
1089!   albsol       albedo du sol (coherent avec swdown)
1090!   taux         tension de vent en x
1091!   tauy         tension de vent en y
1092!   nexca        frequence de couplage
1093!   zmasq        masque terre/ocean
1094!
1095!
1096! output:
1097!   tsurf_new    temperature au sol
1098!   alb_new      albedo
1099!   pctsrf_new   nouvelle repartition des surfaces
1100!   alb_ice      albedo de la glace
1101!
1102
1103
1104! Parametres d'entree
1105  integer, intent(IN) :: itime
1106  integer, intent(IN) :: iim, jjm
1107  real, intent(IN) :: dtime
1108  integer, intent(IN) :: klon
1109  integer, intent(IN) :: nisurf
1110  integer, intent(IN) :: knon
1111  real, dimension(klon,nbsrf), intent(IN) :: pctsrf
1112  integer, dimension(klon), intent(in) :: knindex
1113  logical, intent(IN) :: debut, lafin
1114  real, dimension(klon), intent(IN) :: rlon, rlat
1115  character (len = 6)  :: ocean
1116  real, dimension(klon), intent(IN) :: lwdown, swdown
1117  real, dimension(klon), intent(IN) :: precip_rain, precip_snow
1118  real, dimension(klon), intent(IN) :: tsurf, fder, albsol, taux, tauy
1119  INTEGER              :: nexca, npas, kstep
1120  real, dimension(klon), intent(IN) :: zmasq
1121  real, dimension(klon), intent(IN) :: fluxlat, fluxsens
1122  logical, intent(IN)               :: cumul
1123  real, dimension(klon), intent(INOUT) :: evap
1124
1125! Parametres de sortie
1126  real, dimension(klon), intent(OUT):: tsurf_new, alb_new
1127  real, dimension(klon,nbsrf), intent(OUT) :: pctsrf_new
1128
1129! Variables locales
1130  integer                    :: j, error, sum_error, ig, cpl_index,i
1131  character (len = 20) :: modname = 'interfoce_cpl'
1132  character (len = 80) :: abort_message
1133  logical,save              :: check = .FALSE.
1134! variables pour moyenner les variables de couplage
1135  real, allocatable, dimension(:,:),save :: cpl_sols, cpl_nsol, cpl_rain
1136  real, allocatable, dimension(:,:),save :: cpl_snow, cpl_evap, cpl_tsol
1137  real, allocatable, dimension(:,:),save :: cpl_fder, cpl_albe, cpl_taux
1138!!$PB  real, allocatable, dimension(:,:),save :: cpl_tauy, cpl_rriv, cpl_rcoa
1139  real, allocatable, dimension(:,:),save :: cpl_tauy
1140  real, allocatable, dimension(:,:),save :: cpl_rriv, cpl_rcoa
1141!!$
1142! variables tampons avant le passage au coupleur
1143  real, allocatable, dimension(:,:,:),save :: tmp_sols, tmp_nsol, tmp_rain
1144  real, allocatable, dimension(:,:,:),save :: tmp_snow, tmp_evap, tmp_tsol
1145  real, allocatable, dimension(:,:,:),save :: tmp_fder, tmp_albe, tmp_taux
1146!!$  real, allocatable, dimension(:,:,:),save :: tmp_tauy, tmp_rriv, tmp_rcoa
1147  REAL, ALLOCATABLE, DIMENSION(:,:,:),SAVE :: tmp_tauy
1148! variables a passer au coupleur
1149  real, dimension(iim, jjm+1) :: wri_sol_ice, wri_sol_sea, wri_nsol_ice
1150  real, dimension(iim, jjm+1) :: wri_nsol_sea, wri_fder_ice, wri_evap_ice
1151  REAL, DIMENSION(iim, jjm+1) :: wri_evap_sea, wri_rcoa, wri_rriv
1152  REAL, DIMENSION(iim, jjm+1) :: wri_rain, wri_snow, wri_taux, wri_tauy
1153  REAL, DIMENSION(iim, jjm+1) :: wri_tauxx, wri_tauyy, wri_tauzz
1154  REAL, DIMENSION(iim, jjm+1) :: tmp_lon, tmp_lat
1155! variables relues par le coupleur
1156! read_sic = fraction de glace
1157! read_sit = temperature de glace
1158  real, allocatable, dimension(:,:),save :: read_sst, read_sic, read_sit
1159  real, allocatable, dimension(:,:),save :: read_alb_sic
1160! variable tampon
1161  real, dimension(klon)       :: tamp_sic
1162! sauvegarde des fractions de surface d'un pas de temps a l'autre apres
1163! l'avoir lu
1164  real, allocatable,dimension(:,:),save :: pctsrf_sav
1165  real, dimension(iim, jjm+1, 2) :: tamp_srf
1166  integer, allocatable, dimension(:), save :: tamp_ind
1167  real, allocatable, dimension(:,:),save :: tamp_zmasq
1168  real, dimension(iim, jjm+1) :: deno
1169  integer                     :: idtime
1170  integer, allocatable,dimension(:),save :: unity
1171!
1172  logical, save    :: first_appel = .true.
1173  logical,save          :: print
1174!maf
1175! variables pour avoir une sortie IOIPSL des champs echanges
1176  CHARACTER*80,SAVE :: clintocplnam, clfromcplnam
1177  INTEGER, SAVE :: jf,nhoridct,nidct
1178  INTEGER, SAVE :: nhoridcs,nidcs
1179  INTEGER :: ndexct(iim*(jjm+1)),ndexcs(iim*(jjm+1))
1180  REAL :: zx_lon(iim,jjm+1), zx_lat(iim,jjm+1), zjulian
1181  integer :: idayref, itau_w
1182  include 'param_cou.h'
1183  include 'inc_cpl.h'
1184  include 'temps.inc'
1185!
1186! Initialisation
1187!
1188  if (check) write(*,*)'Entree ',modname,'nisurf = ',nisurf
1189 
1190  if (first_appel) then
1191    error = 0
1192    allocate(unity(klon), stat = error)
1193    if ( error  /=0) then
1194      abort_message='Pb allocation variable unity'
1195      call abort_gcm(modname,abort_message,1)
1196    endif
1197    allocate(pctsrf_sav(klon,nbsrf), stat = error)
1198    if ( error  /=0) then
1199      abort_message='Pb allocation variable pctsrf_sav'
1200      call abort_gcm(modname,abort_message,1)
1201    endif
1202    pctsrf_sav = 0.
1203
1204    do ig = 1, klon
1205      unity(ig) = ig
1206    enddo
1207    sum_error = 0
1208    allocate(cpl_sols(klon,2), stat = error); sum_error = sum_error + error
1209    allocate(cpl_nsol(klon,2), stat = error); sum_error = sum_error + error
1210    allocate(cpl_rain(klon,2), stat = error); sum_error = sum_error + error
1211    allocate(cpl_snow(klon,2), stat = error); sum_error = sum_error + error
1212    allocate(cpl_evap(klon,2), stat = error); sum_error = sum_error + error
1213    allocate(cpl_tsol(klon,2), stat = error); sum_error = sum_error + error
1214    allocate(cpl_fder(klon,2), stat = error); sum_error = sum_error + error
1215    allocate(cpl_albe(klon,2), stat = error); sum_error = sum_error + error
1216    allocate(cpl_taux(klon,2), stat = error); sum_error = sum_error + error
1217    allocate(cpl_tauy(klon,2), stat = error); sum_error = sum_error + error
1218!!$PB
1219!!$    allocate(cpl_rcoa(klon,2), stat = error); sum_error = sum_error + error
1220!!$    allocate(cpl_rriv(klon,2), stat = error); sum_error = sum_error + error
1221    ALLOCATE(cpl_rriv(iim,jjm+1), stat=error); sum_error = sum_error + error
1222    ALLOCATE(cpl_rcoa(iim,jjm+1), stat=error); sum_error = sum_error + error
1223!!
1224    allocate(read_sst(iim, jjm+1), stat = error); sum_error = sum_error + error
1225    allocate(read_sic(iim, jjm+1), stat = error); sum_error = sum_error + error
1226    allocate(read_sit(iim, jjm+1), stat = error); sum_error = sum_error + error
1227    allocate(read_alb_sic(iim, jjm+1), stat = error); sum_error = sum_error + error
1228
1229    if (sum_error /= 0) then
1230      abort_message='Pb allocation variables couplees'
1231      call abort_gcm(modname,abort_message,1)
1232    endif
1233    cpl_sols = 0.; cpl_nsol = 0.; cpl_rain = 0.; cpl_snow = 0.
1234    cpl_evap = 0.; cpl_tsol = 0.; cpl_fder = 0.; cpl_albe = 0.
1235    cpl_taux = 0.; cpl_tauy = 0.; cpl_rriv = 0.; cpl_rcoa = 0.
1236
1237    sum_error = 0
1238    allocate(tamp_ind(klon), stat = error); sum_error = sum_error + error
1239    allocate(tamp_zmasq(iim, jjm+1), stat = error); sum_error = sum_error + error   
1240    do ig = 1, klon
1241      tamp_ind(ig) = ig
1242    enddo
1243    call gath2cpl(zmasq, tamp_zmasq, klon, klon, iim, jjm, tamp_ind)
1244!
1245! initialisation couplage
1246!
1247    idtime = int(dtime)
1248    call inicma(npas , nexca, idtime,(jjm+1)*iim)
1249
1250!
1251! initialisation sorties netcdf
1252!
1253    idayref = day_ini
1254    CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
1255    CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlon,zx_lon)
1256    DO i = 1, iim
1257      zx_lon(i,1) = rlon(i+1)
1258      zx_lon(i,jjm+1) = rlon(i+1)
1259    ENDDO
1260    CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlat,zx_lat)
1261    clintocplnam="cpl_atm_tauflx"
1262    CALL histbeg(clintocplnam, iim,zx_lon(:,1),jjm+1,zx_lat(1,:),1,iim,1,jjm+1, &
1263       & itau_phy,zjulian,dtime,nhoridct,nidct)
1264! no vertical axis
1265    CALL histdef(nidct, 'tauxe','tauxe', &
1266         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1267    CALL histdef(nidct, 'tauyn','tauyn', &
1268         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1269    CALL histdef(nidct, 'tmp_lon','tmp_lon', &
1270         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1271    CALL histdef(nidct, 'tmp_lat','tmp_lat', &
1272         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1273    DO jf=1,jpflda2o1 + jpflda2o2
1274      CALL histdef(nidct, cl_writ(jf),cl_writ(jf), &
1275         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1276    END DO
1277    CALL histend(nidct)
1278    CALL histsync(nidct)
1279
1280    clfromcplnam="cpl_atm_sst"
1281    CALL histbeg(clfromcplnam, iim,zx_lon(:,1),jjm+1,zx_lat(1,:),1,iim,1,jjm+1, &
1282       & 0,zjulian,dtime,nhoridcs,nidcs)
1283! no vertical axis
1284    DO jf=1,jpfldo2a
1285      CALL histdef(nidcs, cl_read(jf),cl_read(jf), &
1286         & "-",iim, jjm+1, nhoridcs, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1287    END DO
1288    CALL histend(nidcs)
1289    CALL histsync(nidcs)
1290
1291! pour simuler la fonte des glaciers antarctiques
1292!
1293    surf_maille = (4. * rpi * ra**2) / (iim * (jjm +1))
1294    ALLOCATE(coeff_iceberg(iim,jjm+1), stat=error)
1295    if (error /= 0) then
1296      abort_message='Pb allocation variable coeff_iceberg'
1297      call abort_gcm(modname,abort_message,1)
1298    endif
1299    open (12,file='flux_iceberg',form='formatted',status='old')
1300    read (12,*) coeff_iceberg
1301    close (12)
1302    num_antarctic = max(1, count(coeff_iceberg > 0))
1303   
1304    first_appel = .false.
1305  endif ! fin if (first_appel)
1306
1307! Initialisations
1308
1309! calcul des fluxs a passer
1310
1311  cpl_index = 1
1312  if (nisurf == is_sic) cpl_index = 2
1313  if (cumul) then
1314    if (check) write(*,*) modname, 'cumul des champs'
1315    do ig = 1, knon
1316      cpl_sols(ig,cpl_index) = cpl_sols(ig,cpl_index) &
1317       &                          + swdown(ig)      / FLOAT(nexca)
1318      cpl_nsol(ig,cpl_index) = cpl_nsol(ig,cpl_index) &
1319       &                          + (lwdown(ig) + fluxlat(ig) +fluxsens(ig))&
1320       &                                / FLOAT(nexca)
1321      cpl_rain(ig,cpl_index) = cpl_rain(ig,cpl_index) &
1322       &                          + precip_rain(ig) / FLOAT(nexca)
1323      cpl_snow(ig,cpl_index) = cpl_snow(ig,cpl_index) &
1324       &                          + precip_snow(ig) / FLOAT(nexca)
1325      cpl_evap(ig,cpl_index) = cpl_evap(ig,cpl_index) &
1326       &                          + evap(ig)        / FLOAT(nexca)
1327      cpl_tsol(ig,cpl_index) = cpl_tsol(ig,cpl_index) &
1328       &                          + tsurf(ig)       / FLOAT(nexca)
1329      cpl_fder(ig,cpl_index) = cpl_fder(ig,cpl_index) &
1330       &                          + fder(ig)        / FLOAT(nexca)
1331      cpl_albe(ig,cpl_index) = cpl_albe(ig,cpl_index) &
1332       &                          + albsol(ig)      / FLOAT(nexca)
1333      cpl_taux(ig,cpl_index) = cpl_taux(ig,cpl_index) &
1334       &                          + taux(ig)        / FLOAT(nexca)
1335      cpl_tauy(ig,cpl_index) = cpl_tauy(ig,cpl_index) &
1336       &                          + tauy(ig)        / FLOAT(nexca)
1337!!$      cpl_rriv(ig,cpl_index) = cpl_rriv(ig,cpl_index) &
1338!!$       &                          + riverflow(ig)   / FLOAT(nexca)/dtime
1339!!$      cpl_rcoa(ig,cpl_index) = cpl_rcoa(ig,cpl_index) &
1340!!$       &                          + coastalflow(ig) / FLOAT(nexca)/dtime
1341    enddo
1342    IF (cpl_index .EQ. 1) THEN
1343        cpl_rriv(:,:) = cpl_rriv(:,:) + tmp_rriv(:,:) / FLOAT(nexca)
1344        cpl_rcoa(:,:) = cpl_rcoa(:,:) + tmp_rcoa(:,:) / FLOAT(nexca)
1345    ENDIF
1346  endif
1347
1348  if (mod(itime, nexca) == 1) then
1349!
1350! Demande des champs au coupleur
1351!
1352! Si le domaine considere est l'ocean, on lit les champs venant du coupleur
1353!
1354    if (nisurf == is_oce .and. .not. cumul) then
1355      if (check) write(*,*)'rentree fromcpl, itime-1 = ',itime-1
1356      call fromcpl(itime-1,(jjm+1)*iim,                                  &
1357     &        read_sst, read_sic, read_sit, read_alb_sic)
1358!
1359! sorties NETCDF des champs recus
1360!
1361      ndexcs(:)=0
1362      itau_w = itau_phy + itime
1363      CALL histwrite(nidcs,cl_read(1),itau_w,read_sst,iim*(jjm+1),ndexcs)
1364      CALL histwrite(nidcs,cl_read(2),itau_w,read_sic,iim*(jjm+1),ndexcs)
1365      CALL histwrite(nidcs,cl_read(3),itau_w,read_alb_sic,iim*(jjm+1),ndexcs)
1366      CALL histwrite(nidcs,cl_read(4),itau_w,read_sit,iim*(jjm+1),ndexcs)
1367      CALL histsync(nidcs)
1368! pas utile      IF (npas-itime.LT.nexca )CALL histclo(nidcs)
1369
1370      do j = 1, jjm + 1
1371        do ig = 1, iim
1372          if (abs(1. - read_sic(ig,j)) < 0.00001) then
1373            read_sst(ig,j) = RTT - 1.8
1374            read_sit(ig,j) = read_sit(ig,j) / read_sic(ig,j)
1375            read_alb_sic(ig,j) = read_alb_sic(ig,j) / read_sic(ig,j)
1376          else if (abs(read_sic(ig,j)) < 0.00001) then
1377            read_sst(ig,j) = read_sst(ig,j) / (1. - read_sic(ig,j))
1378            read_sit(ig,j) = read_sst(ig,j)
1379            read_alb_sic(ig,j) =  0.6
1380          else
1381            read_sst(ig,j) = read_sst(ig,j) / (1. - read_sic(ig,j))
1382            read_sit(ig,j) = read_sit(ig,j) / read_sic(ig,j)
1383            read_alb_sic(ig,j) = read_alb_sic(ig,j) / read_sic(ig,j)
1384          endif
1385        enddo
1386      enddo
1387!
1388! transformer read_sic en pctsrf_sav
1389!
1390      call cpl2gath(read_sic, tamp_sic , klon, klon,iim,jjm, unity)
1391      do ig = 1, klon
1392        IF (pctsrf(ig,is_oce) > epsfra .OR.            &
1393     &             pctsrf(ig,is_sic) > epsfra) THEN
1394          pctsrf_sav(ig,is_sic) = (pctsrf(ig,is_oce) + pctsrf(ig,is_sic)) &
1395     &                               * tamp_sic(ig)
1396          pctsrf_sav(ig,is_oce) = (pctsrf(ig,is_oce) + pctsrf(ig,is_sic)) &
1397     &                        - pctsrf_sav(ig,is_sic)
1398        endif
1399      enddo
1400!
1401! Pour rattraper des erreurs d'arrondis
1402!
1403      where (abs(pctsrf_sav(:,is_sic)) .le. 2.*epsilon(pctsrf_sav(1,is_sic)))
1404        pctsrf_sav(:,is_sic) = 0.
1405        pctsrf_sav(:,is_oce) = pctsrf(:,is_oce) + pctsrf(:,is_sic)
1406      endwhere
1407      where (abs(pctsrf_sav(:,is_oce)) .le. 2.*epsilon(pctsrf_sav(1,is_oce)))
1408        pctsrf_sav(:,is_sic) = pctsrf(:,is_oce) + pctsrf(:,is_sic)
1409        pctsrf_sav(:,is_oce) = 0.
1410      endwhere
1411      if (minval(pctsrf_sav(:,is_oce)) < 0.) then
1412        write(*,*)'Pb fraction ocean inferieure a 0'
1413        write(*,*)'au point ',minloc(pctsrf_sav(:,is_oce))
1414        write(*,*)'valeur = ',minval(pctsrf_sav(:,is_oce))
1415        abort_message = 'voir ci-dessus'
1416        call abort_gcm(modname,abort_message,1)
1417      endif
1418      if (minval(pctsrf_sav(:,is_sic)) < 0.) then
1419        write(*,*)'Pb fraction glace inferieure a 0'
1420        write(*,*)'au point ',minloc(pctsrf_sav(:,is_sic))
1421        write(*,*)'valeur = ',minval(pctsrf_sav(:,is_sic))
1422        abort_message = 'voir ci-dessus'
1423        call abort_gcm(modname,abort_message,1)
1424      endif
1425    endif
1426  endif                         ! fin mod(itime, nexca) == 1
1427
1428  if (mod(itime, nexca) == 0) then
1429!
1430! allocation memoire
1431    if (nisurf == is_oce .and. (.not. cumul) ) then
1432      sum_error = 0
1433      allocate(tmp_sols(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1434      allocate(tmp_nsol(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1435      allocate(tmp_rain(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1436      allocate(tmp_snow(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1437      allocate(tmp_evap(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1438      allocate(tmp_tsol(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1439      allocate(tmp_fder(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1440      allocate(tmp_albe(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1441      allocate(tmp_taux(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1442      allocate(tmp_tauy(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1443!!$      allocate(tmp_rriv(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1444!!$      allocate(tmp_rcoa(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1445      if (sum_error /= 0) then
1446        abort_message='Pb allocation variables couplees pour l''ecriture'
1447        call abort_gcm(modname,abort_message,1)
1448      endif
1449    endif
1450
1451!
1452! Mise sur la bonne grille des champs a passer au coupleur
1453!
1454    cpl_index = 1
1455    if (nisurf == is_sic) cpl_index = 2
1456    call gath2cpl(cpl_sols(1,cpl_index), tmp_sols(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1457    call gath2cpl(cpl_nsol(1,cpl_index), tmp_nsol(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1458    call gath2cpl(cpl_rain(1,cpl_index), tmp_rain(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1459    call gath2cpl(cpl_snow(1,cpl_index), tmp_snow(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1460    call gath2cpl(cpl_evap(1,cpl_index), tmp_evap(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1461    call gath2cpl(cpl_tsol(1,cpl_index), tmp_tsol(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1462    call gath2cpl(cpl_fder(1,cpl_index), tmp_fder(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1463    call gath2cpl(cpl_albe(1,cpl_index), tmp_albe(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1464    call gath2cpl(cpl_taux(1,cpl_index), tmp_taux(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1465    call gath2cpl(cpl_tauy(1,cpl_index), tmp_tauy(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1466!!$    call gath2cpl(cpl_rriv(1,cpl_index), tmp_rriv(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1467!!$    call gath2cpl(cpl_rcoa(1,cpl_index), tmp_rcoa(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1468
1469!
1470! Si le domaine considere est la banquise, on envoie les champs au coupleur
1471!
1472    if (nisurf == is_sic .and. cumul) then
1473      wri_rain = 0.; wri_snow = 0.; wri_rcoa = 0.; wri_rriv = 0.
1474      wri_taux = 0.; wri_tauy = 0.
1475      call gath2cpl(pctsrf(1,is_oce), tamp_srf(1,1,1), klon, klon, iim, jjm, tamp_ind)
1476      call gath2cpl(pctsrf(1,is_sic), tamp_srf(1,1,2), klon, klon, iim, jjm, tamp_ind)
1477
1478      wri_sol_ice = tmp_sols(:,:,2)
1479      wri_sol_sea = tmp_sols(:,:,1)
1480      wri_nsol_ice = tmp_nsol(:,:,2)
1481      wri_nsol_sea = tmp_nsol(:,:,1)
1482      wri_fder_ice = tmp_fder(:,:,2)
1483      wri_evap_ice = tmp_evap(:,:,2)
1484      wri_evap_sea = tmp_evap(:,:,1)
1485!!$PB
1486      wri_rriv = cpl_rriv(:,:)
1487      wri_rcoa = cpl_rcoa(:,:)
1488
1489      where (tamp_zmasq /= 1.)
1490        deno =  tamp_srf(:,:,1) + tamp_srf(:,:,2)
1491        wri_rain = tmp_rain(:,:,1) * tamp_srf(:,:,1) / deno +    &
1492      &            tmp_rain(:,:,2) * tamp_srf(:,:,2) / deno
1493        wri_snow = tmp_snow(:,:,1) * tamp_srf(:,:,1) / deno +    &
1494      &            tmp_snow(:,:,2) * tamp_srf(:,:,2) / deno
1495!!$PB
1496!!$        wri_rriv = tmp_rriv(:,:,1) * tamp_srf(:,:,1) / deno +    &
1497!!$      &            tmp_rriv(:,:,2) * tamp_srf(:,:,2) / deno
1498!!$        wri_rcoa = tmp_rcoa(:,:,1) * tamp_srf(:,:,1) / deno +    &
1499!!$      &            tmp_rcoa(:,:,2) * tamp_srf(:,:,2) / deno
1500        wri_taux = tmp_taux(:,:,1) * tamp_srf(:,:,1) / deno +    &
1501      &            tmp_taux(:,:,2) * tamp_srf(:,:,2) / deno
1502        wri_tauy = tmp_tauy(:,:,1) * tamp_srf(:,:,1) / deno +    &
1503      &            tmp_tauy(:,:,2) * tamp_srf(:,:,2) / deno
1504      endwhere
1505!
1506! pour simuler la fonte des glaciers antarctiques
1507!
1508        wri_rain = wri_rain      &
1509      &     + coeff_iceberg * cte_flux_iceberg / (num_antarctic * surf_maille)
1510
1511!
1512! on passe les coordonnées de la grille
1513!
1514
1515      CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlon,tmp_lon)
1516      CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlat,tmp_lat)
1517
1518      DO i = 1, iim
1519        tmp_lon(i,1) = rlon(i+1)
1520        tmp_lon(i,jjm + 1) = rlon(i+1)
1521      ENDDO
1522!
1523! sortie netcdf des champs pour le changement de repere
1524!
1525      ndexct(:)=0
1526      CALL histwrite(nidct,'tauxe',itau_w,wri_taux,iim*(jjm+1),ndexct)
1527      CALL histwrite(nidct,'tauyn',itau_w,wri_tauy,iim*(jjm+1),ndexct)
1528      CALL histwrite(nidct,'tmp_lon',itau_w,tmp_lon,iim*(jjm+1),ndexct)
1529      CALL histwrite(nidct,'tmp_lat',itau_w,tmp_lat,iim*(jjm+1),ndexct)
1530
1531!
1532! calcul 3 coordonnées du vent
1533!
1534      CALL atm2geo (iim , jjm + 1, wri_taux, wri_tauy, tmp_lon, tmp_lat, &
1535         & wri_tauxx, wri_tauyy, wri_tauzz )
1536!
1537! sortie netcdf des champs apres changement de repere et juste avant
1538! envoi au coupleur
1539!
1540      CALL histwrite(nidct,cl_writ(1),itau_w,wri_sol_ice,iim*(jjm+1),ndexct)
1541      CALL histwrite(nidct,cl_writ(2),itau_w,wri_sol_sea,iim*(jjm+1),ndexct)
1542      CALL histwrite(nidct,cl_writ(3),itau_w,wri_nsol_ice,iim*(jjm+1),ndexct)
1543      CALL histwrite(nidct,cl_writ(4),itau_w,wri_nsol_sea,iim*(jjm+1),ndexct)
1544      CALL histwrite(nidct,cl_writ(5),itau_w,wri_fder_ice,iim*(jjm+1),ndexct)
1545      CALL histwrite(nidct,cl_writ(6),itau_w,wri_evap_ice,iim*(jjm+1),ndexct)
1546      CALL histwrite(nidct,cl_writ(7),itau_w,wri_evap_sea,iim*(jjm+1),ndexct)
1547      CALL histwrite(nidct,cl_writ(8),itau_w,wri_rain,iim*(jjm+1),ndexct)
1548      CALL histwrite(nidct,cl_writ(9),itau_w,wri_snow,iim*(jjm+1),ndexct)
1549      CALL histwrite(nidct,cl_writ(10),itau_w,wri_rcoa,iim*(jjm+1),ndexct)
1550      CALL histwrite(nidct,cl_writ(11),itau_w,wri_rriv,iim*(jjm+1),ndexct)
1551      CALL histwrite(nidct,cl_writ(12),itau_w,wri_tauxx,iim*(jjm+1),ndexct)
1552      CALL histwrite(nidct,cl_writ(13),itau_w,wri_tauyy,iim*(jjm+1),ndexct)
1553      CALL histwrite(nidct,cl_writ(14),itau_w,wri_tauzz,iim*(jjm+1),ndexct)
1554      CALL histwrite(nidct,cl_writ(15),itau_w,wri_tauxx,iim*(jjm+1),ndexct)
1555      CALL histwrite(nidct,cl_writ(16),itau_w,wri_tauyy,iim*(jjm+1),ndexct)
1556      CALL histwrite(nidct,cl_writ(17),itau_w,wri_tauzz,iim*(jjm+1),ndexct)
1557      CALL histsync(nidct)
1558! pas utile      IF (lafin) CALL histclo(nidct)
1559
1560      call intocpl(itime, (jjm+1)*iim, wri_sol_ice, wri_sol_sea, wri_nsol_ice,&
1561      & wri_nsol_sea, wri_fder_ice, wri_evap_ice, wri_evap_sea, wri_rain, &
1562      & wri_snow, wri_rcoa, wri_rriv, wri_tauxx, wri_tauyy, wri_tauzz, &
1563      & wri_tauxx, wri_tauyy, wri_tauzz,lafin )
1564!
1565      cpl_sols = 0.; cpl_nsol = 0.; cpl_rain = 0.; cpl_snow = 0.
1566      cpl_evap = 0.; cpl_tsol = 0.; cpl_fder = 0.; cpl_albe = 0.
1567      cpl_taux = 0.; cpl_tauy = 0.; cpl_rriv = 0.; cpl_rcoa = 0.
1568!
1569! deallocation memoire variables temporaires
1570!
1571      sum_error = 0
1572      deallocate(tmp_sols, stat=error); sum_error = sum_error + error
1573      deallocate(tmp_nsol, stat=error); sum_error = sum_error + error
1574      deallocate(tmp_rain, stat=error); sum_error = sum_error + error
1575      deallocate(tmp_snow, stat=error); sum_error = sum_error + error
1576      deallocate(tmp_evap, stat=error); sum_error = sum_error + error
1577      deallocate(tmp_fder, stat=error); sum_error = sum_error + error
1578      deallocate(tmp_tsol, stat=error); sum_error = sum_error + error
1579      deallocate(tmp_albe, stat=error); sum_error = sum_error + error
1580      deallocate(tmp_taux, stat=error); sum_error = sum_error + error
1581      deallocate(tmp_tauy, stat=error); sum_error = sum_error + error
1582!!$PB
1583!!$      deallocate(tmp_rriv, stat=error); sum_error = sum_error + error
1584!!$      deallocate(tmp_rcoa, stat=error); sum_error = sum_error + error
1585      if (sum_error /= 0) then
1586        abort_message='Pb deallocation variables couplees'
1587        call abort_gcm(modname,abort_message,1)
1588      endif
1589
1590    endif
1591
1592  endif            ! fin (mod(itime, nexca) == 0)
1593!
1594! on range les variables lues/sauvegardees dans les bonnes variables de sortie
1595!
1596  if (nisurf == is_oce) then
1597    call cpl2gath(read_sst, tsurf_new, klon, knon,iim,jjm, knindex)
1598  else if (nisurf == is_sic) then
1599    call cpl2gath(read_sit, tsurf_new, klon, knon,iim,jjm, knindex)
1600    call cpl2gath(read_alb_sic, alb_new, klon, knon,iim,jjm, knindex)
1601  endif
1602  pctsrf_new(:,nisurf) = pctsrf_sav(:,nisurf)
1603 
1604!  if (lafin) call quitcpl
1605
1606  END SUBROUTINE interfoce_cpl
1607!
1608!#########################################################################
1609!
1610
1611  SUBROUTINE interfoce_slab(nisurf)
1612
1613! Cette routine sert d'interface entre le modele atmospherique et un
1614! modele de 'slab' ocean
1615!
1616! L. Fairhead 02/2000
1617!
1618! input:
1619!   nisurf       index de la surface a traiter (1 = sol continental)
1620!
1621! output:
1622!
1623
1624! Parametres d'entree
1625  integer, intent(IN) :: nisurf
1626
1627  END SUBROUTINE interfoce_slab
1628!
1629!#########################################################################
1630!
1631  SUBROUTINE interfoce_lim(itime, dtime, jour, &
1632     & klon, nisurf, knon, knindex, &
1633     & debut,  &
1634     & lmt_sst, pctsrf_new)
1635
1636! Cette routine sert d'interface entre le modele atmospherique et un fichier
1637! de conditions aux limites
1638!
1639! L. Fairhead 02/2000
1640!
1641! input:
1642!   itime        numero du pas de temps courant
1643!   dtime        pas de temps de la physique (en s)
1644!   jour         jour a lire dans l'annee
1645!   nisurf       index de la surface a traiter (1 = sol continental)
1646!   knon         nombre de points dans le domaine a traiter
1647!   knindex      index des points de la surface a traiter
1648!   klon         taille de la grille
1649!   debut        logical: 1er appel a la physique (initialisation)
1650!
1651! output:
1652!   lmt_sst      SST lues dans le fichier de CL
1653!   pctsrf_new   sous-maille fractionnelle
1654!
1655
1656
1657! Parametres d'entree
1658  integer, intent(IN) :: itime
1659  real   , intent(IN) :: dtime
1660  integer, intent(IN) :: jour
1661  integer, intent(IN) :: nisurf
1662  integer, intent(IN) :: knon
1663  integer, intent(IN) :: klon
1664  integer, dimension(klon), intent(in) :: knindex
1665  logical, intent(IN) :: debut
1666
1667! Parametres de sortie
1668  real, intent(out), dimension(klon) :: lmt_sst
1669  real, intent(out), dimension(klon,nbsrf) :: pctsrf_new
1670
1671! Variables locales
1672  integer     :: ii
1673  INTEGER,save :: lmt_pas     ! frequence de lecture des conditions limites
1674                             ! (en pas de physique)
1675  logical,save :: deja_lu    ! pour indiquer que le jour a lire a deja
1676                             ! lu pour une surface precedente
1677  integer,save :: jour_lu
1678  integer      :: ierr
1679  character (len = 20) :: modname = 'interfoce_lim'
1680  character (len = 80) :: abort_message
1681  character (len = 20),save :: fich ='limit.nc'
1682  logical, save     :: newlmt = .TRUE.
1683  logical, save     :: check = .FALSE.
1684! Champs lus dans le fichier de CL
1685  real, allocatable , save, dimension(:) :: sst_lu, rug_lu, nat_lu
1686  real, allocatable , save, dimension(:,:) :: pct_tmp
1687!
1688! quelques variables pour netcdf
1689!
1690#include "netcdf.inc"
1691  integer              :: nid, nvarid
1692  integer, dimension(2) :: start, epais
1693!
1694! Fin déclaration
1695!
1696   
1697  if (debut .and. .not. allocated(sst_lu)) then
1698    lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour
1699    jour_lu = jour - 1
1700    allocate(sst_lu(klon))
1701    allocate(nat_lu(klon))
1702    allocate(pct_tmp(klon,nbsrf))
1703  endif
1704
1705  if ((jour - jour_lu) /= 0) deja_lu = .false.
1706 
1707  if (check) write(*,*)modname,' :: jour, jour_lu, deja_lu', jour, jour_lu, deja_lu
1708  if (check) write(*,*)modname,' :: itime, lmt_pas ', itime, lmt_pas,dtime
1709
1710! Tester d'abord si c'est le moment de lire le fichier
1711  if (mod(itime-1, lmt_pas) == 0 .and. .not. deja_lu) then
1712!
1713! Ouverture du fichier
1714!
1715    fich = trim(fich)
1716    ierr = NF_OPEN (fich, NF_NOWRITE,nid)
1717    if (ierr.NE.NF_NOERR) then
1718      abort_message = 'Pb d''ouverture du fichier de conditions aux limites'
1719      call abort_gcm(modname,abort_message,1)
1720    endif
1721!
1722! La tranche de donnees a lire:
1723!
1724    start(1) = 1
1725    start(2) = jour + 1
1726    epais(1) = klon
1727    epais(2) = 1
1728!
1729    if (newlmt) then
1730!
1731! Fraction "ocean"
1732!
1733      ierr = NF_INQ_VARID(nid, 'FOCE', nvarid)
1734      if (ierr /= NF_NOERR) then
1735        abort_message = 'Le champ <FOCE> est absent'
1736        call abort_gcm(modname,abort_message,1)
1737      endif
1738#ifdef NC_DOUBLE
1739      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pct_tmp(1,is_oce))
1740#else
1741      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pct_tmp(1,is_oce))
1742#endif
1743      if (ierr /= NF_NOERR) then
1744        abort_message = 'Lecture echouee pour <FOCE>'
1745        call abort_gcm(modname,abort_message,1)
1746      endif
1747!
1748! Fraction "glace de mer"
1749!
1750      ierr = NF_INQ_VARID(nid, 'FSIC', nvarid)
1751      if (ierr /= NF_NOERR) then
1752        abort_message = 'Le champ <FSIC> est absent'
1753        call abort_gcm(modname,abort_message,1)
1754      endif
1755#ifdef NC_DOUBLE
1756      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pct_tmp(1,is_sic))
1757#else
1758      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pct_tmp(1,is_sic))
1759#endif
1760      if (ierr /= NF_NOERR) then
1761        abort_message = 'Lecture echouee pour <FSIC>'
1762        call abort_gcm(modname,abort_message,1)
1763      endif
1764!
1765! Fraction "terre"
1766!
1767      ierr = NF_INQ_VARID(nid, 'FTER', nvarid)
1768      if (ierr /= NF_NOERR) then
1769        abort_message = 'Le champ <FTER> est absent'
1770        call abort_gcm(modname,abort_message,1)
1771      endif
1772#ifdef NC_DOUBLE
1773      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pct_tmp(1,is_ter))
1774#else
1775      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pct_tmp(1,is_ter))
1776#endif
1777      if (ierr /= NF_NOERR) then
1778        abort_message = 'Lecture echouee pour <FTER>'
1779        call abort_gcm(modname,abort_message,1)
1780      endif
1781!
1782! Fraction "glacier terre"
1783!
1784      ierr = NF_INQ_VARID(nid, 'FLIC', nvarid)
1785      if (ierr /= NF_NOERR) then
1786        abort_message = 'Le champ <FLIC> est absent'
1787        call abort_gcm(modname,abort_message,1)
1788      endif
1789#ifdef NC_DOUBLE
1790      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pct_tmp(1,is_lic))
1791#else
1792      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pct_tmp(1,is_lic))
1793#endif
1794      if (ierr /= NF_NOERR) then
1795        abort_message = 'Lecture echouee pour <FLIC>'
1796        call abort_gcm(modname,abort_message,1)
1797      endif
1798!
1799    else  ! on en est toujours a rnatur
1800!
1801      ierr = NF_INQ_VARID(nid, 'NAT', nvarid)
1802      if (ierr /= NF_NOERR) then
1803        abort_message = 'Le champ <NAT> est absent'
1804        call abort_gcm(modname,abort_message,1)
1805      endif
1806#ifdef NC_DOUBLE
1807      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, nat_lu)
1808#else
1809      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, nat_lu)
1810#endif
1811      if (ierr /= NF_NOERR) then
1812        abort_message = 'Lecture echouee pour <NAT>'
1813        call abort_gcm(modname,abort_message,1)
1814      endif
1815!
1816! Remplissage des fractions de surface
1817! nat = 0, 1, 2, 3 pour ocean, terre, glacier, seaice
1818!
1819      pct_tmp = 0.0
1820      do ii = 1, klon
1821        pct_tmp(ii,nint(nat_lu(ii)) + 1) = 1.
1822      enddo
1823
1824!
1825!  On se retrouve avec ocean en 1 et terre en 2 alors qu'on veut le contraire
1826!
1827      pctsrf_new = pct_tmp
1828      pctsrf_new (:,2)= pct_tmp (:,1)
1829      pctsrf_new (:,1)= pct_tmp (:,2)
1830      pct_tmp = pctsrf_new
1831    endif ! fin test sur newlmt
1832!
1833! Lecture SST
1834!
1835    ierr = NF_INQ_VARID(nid, 'SST', nvarid)
1836    if (ierr /= NF_NOERR) then
1837      abort_message = 'Le champ <SST> est absent'
1838      call abort_gcm(modname,abort_message,1)
1839    endif
1840#ifdef NC_DOUBLE
1841    ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, sst_lu)
1842#else
1843    ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, sst_lu)
1844#endif
1845    if (ierr /= NF_NOERR) then
1846      abort_message = 'Lecture echouee pour <SST>'
1847      call abort_gcm(modname,abort_message,1)
1848    endif   
1849
1850!
1851! Fin de lecture
1852!
1853    ierr = NF_CLOSE(nid)
1854    deja_lu = .true.
1855    jour_lu = jour
1856  endif
1857!
1858! Recopie des variables dans les champs de sortie
1859!
1860  lmt_sst = 999999999.
1861  do ii = 1, knon
1862    lmt_sst(ii) = sst_lu(knindex(ii))
1863  enddo
1864
1865  pctsrf_new(:,is_oce) = pct_tmp(:,is_oce)
1866  pctsrf_new(:,is_sic) = pct_tmp(:,is_sic)
1867
1868  END SUBROUTINE interfoce_lim
1869
1870!
1871!#########################################################################
1872!
1873  SUBROUTINE interfsur_lim(itime, dtime, jour, &
1874     & klon, nisurf, knon, knindex, &
1875     & debut,  &
1876     & lmt_alb, lmt_rug)
1877
1878! Cette routine sert d'interface entre le modele atmospherique et un fichier
1879! de conditions aux limites
1880!
1881! L. Fairhead 02/2000
1882!
1883! input:
1884!   itime        numero du pas de temps courant
1885!   dtime        pas de temps de la physique (en s)
1886!   jour         jour a lire dans l'annee
1887!   nisurf       index de la surface a traiter (1 = sol continental)
1888!   knon         nombre de points dans le domaine a traiter
1889!   knindex      index des points de la surface a traiter
1890!   klon         taille de la grille
1891!   debut        logical: 1er appel a la physique (initialisation)
1892!
1893! output:
1894!   lmt_sst      SST lues dans le fichier de CL
1895!   lmt_alb      Albedo lu
1896!   lmt_rug      longueur de rugosité lue
1897!   pctsrf_new   sous-maille fractionnelle
1898!
1899
1900
1901! Parametres d'entree
1902  integer, intent(IN) :: itime
1903  real   , intent(IN) :: dtime
1904  integer, intent(IN) :: jour
1905  integer, intent(IN) :: nisurf
1906  integer, intent(IN) :: knon
1907  integer, intent(IN) :: klon
1908  integer, dimension(klon), intent(in) :: knindex
1909  logical, intent(IN) :: debut
1910
1911! Parametres de sortie
1912  real, intent(out), dimension(klon) :: lmt_alb
1913  real, intent(out), dimension(klon) :: lmt_rug
1914
1915! Variables locales
1916  integer     :: ii
1917  integer,save :: lmt_pas     ! frequence de lecture des conditions limites
1918                             ! (en pas de physique)
1919  logical,save :: deja_lu_sur! pour indiquer que le jour a lire a deja
1920                             ! lu pour une surface precedente
1921  integer,save :: jour_lu_sur
1922  integer      :: ierr
1923  character (len = 20) :: modname = 'interfsur_lim'
1924  character (len = 80) :: abort_message
1925  character (len = 20),save :: fich ='limit.nc'
1926  logical,save     :: newlmt = .false.
1927  logical,save     :: check = .FALSE.
1928! Champs lus dans le fichier de CL
1929  real, allocatable , save, dimension(:) :: alb_lu, rug_lu
1930!
1931! quelques variables pour netcdf
1932!
1933#include "netcdf.inc"
1934  integer ,save             :: nid, nvarid
1935  integer, dimension(2),save :: start, epais
1936!
1937! Fin déclaration
1938!
1939   
1940  if (debut) then
1941    lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour
1942    jour_lu_sur = jour - 1
1943    allocate(alb_lu(klon))
1944    allocate(rug_lu(klon))
1945  endif
1946
1947  if ((jour - jour_lu_sur) /= 0) deja_lu_sur = .false.
1948 
1949  if (check) write(*,*)modname,':: jour_lu_sur, deja_lu_sur', jour_lu_sur, deja_lu_sur
1950  if (check) write(*,*)modname,':: itime, lmt_pas', itime, lmt_pas
1951  call flush(6)
1952
1953! Tester d'abord si c'est le moment de lire le fichier
1954  if (mod(itime-1, lmt_pas) == 0 .and. .not. deja_lu_sur) then
1955!
1956! Ouverture du fichier
1957!
1958    fich = trim(fich)
1959    ierr = NF_OPEN (fich, NF_NOWRITE,nid)
1960    if (ierr.NE.NF_NOERR) then
1961      abort_message = 'Pb d''ouverture du fichier de conditions aux limites'
1962      call abort_gcm(modname,abort_message,1)
1963    endif
1964!
1965! La tranche de donnees a lire:
1966 
1967    start(1) = 1
1968    start(2) = jour + 1
1969    epais(1) = klon
1970    epais(2) = 1
1971!
1972! Lecture Albedo
1973!
1974    ierr = NF_INQ_VARID(nid, 'ALB', nvarid)
1975    if (ierr /= NF_NOERR) then
1976      abort_message = 'Le champ <ALB> est absent'
1977      call abort_gcm(modname,abort_message,1)
1978    endif
1979#ifdef NC_DOUBLE
1980    ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, alb_lu)
1981#else
1982    ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, alb_lu)
1983#endif
1984    if (ierr /= NF_NOERR) then
1985      abort_message = 'Lecture echouee pour <ALB>'
1986      call abort_gcm(modname,abort_message,1)
1987    endif
1988!
1989! Lecture rugosité
1990!
1991    ierr = NF_INQ_VARID(nid, 'RUG', nvarid)
1992    if (ierr /= NF_NOERR) then
1993      abort_message = 'Le champ <RUG> est absent'
1994      call abort_gcm(modname,abort_message,1)
1995    endif
1996#ifdef NC_DOUBLE
1997    ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, rug_lu)
1998#else
1999    ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, rug_lu)
2000#endif
2001    if (ierr /= NF_NOERR) then
2002      abort_message = 'Lecture echouee pour <RUG>'
2003      call abort_gcm(modname,abort_message,1)
2004    endif
2005
2006!
2007! Fin de lecture
2008!
2009    ierr = NF_CLOSE(nid)
2010    deja_lu_sur = .true.
2011    jour_lu_sur = jour
2012  endif
2013!
2014! Recopie des variables dans les champs de sortie
2015!
2016!!$  lmt_alb(:) = 0.0
2017!!$  lmt_rug(:) = 0.0
2018  lmt_alb(:) = 999999.
2019  lmt_rug(:) = 999999.
2020  DO ii = 1, knon
2021    lmt_alb(ii) = alb_lu(knindex(ii))
2022    lmt_rug(ii) = rug_lu(knindex(ii))
2023  enddo
2024
2025  END SUBROUTINE interfsur_lim
2026
2027!
2028!#########################################################################
2029!
2030
2031  SUBROUTINE calcul_fluxs( klon, knon, nisurf, dtime, &
2032     & tsurf, p1lay, cal, beta, coef1lay, ps, &
2033     & precip_rain, precip_snow, snow, qsol, &
2034     & radsol, dif_grnd, t1lay, q1lay, u1lay, v1lay, &
2035     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
2036     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
2037
2038! Cette routine calcule les fluxs en h et q a l'interface et eventuellement
2039! une temperature de surface (au cas ou ok_veget = false)
2040!
2041! L. Fairhead 4/2000
2042!
2043! input:
2044!   knon         nombre de points a traiter
2045!   nisurf       surface a traiter
2046!   tsurf        temperature de surface
2047!   p1lay        pression 1er niveau (milieu de couche)
2048!   cal          capacite calorifique du sol
2049!   beta         evap reelle
2050!   coef1lay     coefficient d'echange
2051!   ps           pression au sol
2052!   precip_rain  precipitations liquides
2053!   precip_snow  precipitations solides
2054!   snow         champs hauteur de neige
2055!   qsol         humidite du sol
2056!   runoff       runoff en cas de trop plein
2057!   petAcoef     coeff. A de la resolution de la CL pour t
2058!   peqAcoef     coeff. A de la resolution de la CL pour q
2059!   petBcoef     coeff. B de la resolution de la CL pour t
2060!   peqBcoef     coeff. B de la resolution de la CL pour q
2061!   radsol       rayonnement net aus sol (LW + SW)
2062!   dif_grnd     coeff. diffusion vers le sol profond
2063!
2064! output:
2065!   tsurf_new    temperature au sol
2066!   fluxsens     flux de chaleur sensible
2067!   fluxlat      flux de chaleur latente
2068!   dflux_s      derivee du flux de chaleur sensible / Ts
2069!   dflux_l      derivee du flux de chaleur latente  / Ts
2070!
2071
2072#include "YOETHF.inc"
2073#include "FCTTRE.inc"
2074#include "indicesol.inc"
2075
2076! Parametres d'entree
2077  integer, intent(IN) :: knon, nisurf, klon
2078  real   , intent(IN) :: dtime
2079  real, dimension(klon), intent(IN) :: petAcoef, peqAcoef
2080  real, dimension(klon), intent(IN) :: petBcoef, peqBcoef
2081  real, dimension(klon), intent(IN) :: ps, q1lay
2082  real, dimension(klon), intent(IN) :: tsurf, p1lay, cal, beta, coef1lay
2083  real, dimension(klon), intent(IN) :: precip_rain, precip_snow
2084  real, dimension(klon), intent(IN) :: radsol, dif_grnd
2085  real, dimension(klon), intent(IN) :: t1lay, u1lay, v1lay
2086  real, dimension(klon), intent(INOUT) :: snow, qsol
2087
2088! Parametres sorties
2089  real, dimension(klon), intent(OUT):: tsurf_new, evap, fluxsens, fluxlat
2090  real, dimension(klon), intent(OUT):: dflux_s, dflux_l
2091
2092! Variables locales
2093  integer :: i
2094  real, dimension(klon) :: zx_mh, zx_nh, zx_oh
2095  real, dimension(klon) :: zx_mq, zx_nq, zx_oq
2096  real, dimension(klon) :: zx_pkh, zx_dq_s_dt, zx_qsat, zx_coef
2097  real, dimension(klon) :: zx_sl, zx_k1
2098  real, dimension(klon) :: zx_q_0 , d_ts
2099  real                  :: zdelta, zcvm5, zx_qs, zcor, zx_dq_s_dh
2100  real                  :: bilan_f, fq_fonte
2101  REAL                  :: subli, fsno
2102  real, parameter :: t_grnd = 271.35, t_coup = 273.15
2103!! PB temporaire en attendant mieux pour le modele de neige
2104  REAL, parameter :: chasno = 3.334E+05/(2.3867E+06*0.15)
2105!
2106  logical, save         :: check = .FALSE.
2107  character (len = 20)  :: modname = 'calcul_fluxs'
2108  logical, save         :: fonte_neige = .false.
2109  real, save            :: max_eau_sol = 150.0
2110  character (len = 80) :: abort_message
2111  logical,save         :: first = .true.,second=.false.
2112
2113  if (check) write(*,*)'Entree ', modname,' surface = ',nisurf
2114
2115  if (size(coastalflow) /= knon .AND. nisurf == is_ter) then
2116    write(*,*)'Bizarre, le nombre de points continentaux'
2117    write(*,*)'a change entre deux appels. J''arrete ...'
2118    abort_message='Pb run_off'
2119    call abort_gcm(modname,abort_message,1)
2120  endif
2121!
2122! Traitement neige et humidite du sol
2123!
2124!!$  WRITE(*,*)'test calcul_flux, surface ', nisurf
2125!!PB test
2126!!$    if (nisurf == is_oce) then
2127!!$      snow = 0.
2128!!$      qsol = max_eau_sol
2129!!$    else
2130!!$      where (precip_snow > 0.) snow = snow + (precip_snow * dtime)
2131!!$      where (snow > epsilon(snow)) snow = max(0.0, snow - (evap * dtime))
2132!!$!      snow = max(0.0, snow + (precip_snow - evap) * dtime)
2133!!$      where (precip_rain > 0.) qsol = qsol + (precip_rain - evap) * dtime
2134!!$    endif
2135    IF (nisurf /= is_ter) qsol = max_eau_sol
2136
2137
2138!
2139! Initialisation
2140!
2141  evap = 0.
2142  fluxsens=0.
2143  fluxlat=0.
2144  dflux_s = 0.
2145  dflux_l = 0. 
2146!
2147! zx_qs = qsat en kg/kg
2148!
2149  DO i = 1, knon
2150    zx_pkh(i) = (ps(i)/ps(i))**RKAPPA
2151  IF (thermcep) THEN
2152      zdelta=MAX(0.,SIGN(1.,rtt-tsurf(i)))
2153      zcvm5 = R5LES*RLVTT*(1.-zdelta) + R5IES*RLSTT*zdelta
2154      zcvm5 = zcvm5 / RCPD / (1.0+RVTMP2*q1lay(i))
2155      zx_qs= r2es * FOEEW(tsurf(i),zdelta)/ps(i)
2156      zx_qs=MIN(0.5,zx_qs)
2157      zcor=1./(1.-retv*zx_qs)
2158      zx_qs=zx_qs*zcor
2159      zx_dq_s_dh = FOEDE(tsurf(i),zdelta,zcvm5,zx_qs,zcor) &
2160     &                 /RLVTT / zx_pkh(i)
2161    ELSE
2162      IF (tsurf(i).LT.t_coup) THEN
2163        zx_qs = qsats(tsurf(i)) / ps(i)
2164        zx_dq_s_dh = dqsats(tsurf(i),zx_qs)/RLVTT &
2165     &                    / zx_pkh(i)
2166      ELSE
2167        zx_qs = qsatl(tsurf(i)) / ps(i)
2168        zx_dq_s_dh = dqsatl(tsurf(i),zx_qs)/RLVTT &
2169     &               / zx_pkh(i)
2170      ENDIF
2171    ENDIF
2172    zx_dq_s_dt(i) = RCPD * zx_pkh(i) * zx_dq_s_dh
2173    zx_qsat(i) = zx_qs
2174    zx_coef(i) = coef1lay(i) &
2175     & * (1.0+SQRT(u1lay(i)**2+v1lay(i)**2)) &
2176     & * p1lay(i)/(RD*t1lay(i))
2177
2178  ENDDO
2179
2180
2181! === Calcul de la temperature de surface ===
2182!
2183! zx_sl = chaleur latente d'evaporation ou de sublimation
2184!
2185  do i = 1, knon
2186    zx_sl(i) = RLVTT
2187    if (tsurf(i) .LT. RTT) zx_sl(i) = RLSTT
2188    zx_k1(i) = zx_coef(i)
2189  enddo
2190
2191
2192  do i = 1, knon
2193! Q
2194    zx_oq(i) = 1. - (beta(i) * zx_k1(i) * peqBcoef(i) * dtime)
2195    zx_mq(i) = beta(i) * zx_k1(i) * &
2196     &             (peqAcoef(i) - zx_qsat(i) &
2197     &                          + zx_dq_s_dt(i) * tsurf(i)) &
2198     &             / zx_oq(i)
2199    zx_nq(i) = beta(i) * zx_k1(i) * (-1. * zx_dq_s_dt(i)) &
2200     &                              / zx_oq(i)
2201
2202! H
2203    zx_oh(i) = 1. - (zx_k1(i) * petBcoef(i) * dtime)
2204    zx_mh(i) = zx_k1(i) * petAcoef(i) / zx_oh(i)
2205    zx_nh(i) = - (zx_k1(i) * RCPD * zx_pkh(i))/ zx_oh(i)
2206
2207! Tsurface
2208    tsurf_new(i) = (tsurf(i) + cal(i)/(RCPD * zx_pkh(i)) * dtime * &
2209     &             (radsol(i) + zx_mh(i) + zx_sl(i) * zx_mq(i)) &
2210     &                 + dif_grnd(i) * t_grnd * dtime)/ &
2211     &          ( 1. - dtime * cal(i)/(RCPD * zx_pkh(i)) * ( &
2212     &                       zx_nh(i) + zx_sl(i) * zx_nq(i)) & 
2213     &                     + dtime * dif_grnd(i))
2214
2215!
2216! Y'a-t-il fonte de neige?
2217!
2218!    fonte_neige = (nisurf /= is_oce) .AND. &
2219!     & (snow(i) > epsfra .OR. nisurf == is_sic .OR. nisurf == is_lic) &
2220!     & .AND. (tsurf_new(i) >= RTT)
2221!    if (fonte_neige) tsurf_new(i) = RTT 
2222    d_ts(i) = tsurf_new(i) - tsurf(i)
2223!    zx_h_ts(i) = tsurf_new(i) * RCPD * zx_pkh(i)
2224!    zx_q_0(i) = zx_qsat(i) + zx_dq_s_dt(i) * d_ts(i)
2225!== flux_q est le flux de vapeur d'eau: kg/(m**2 s)  positive vers bas
2226!== flux_t est le flux de cpt (energie sensible): j/(m**2 s)
2227    evap(i) = - zx_mq(i) - zx_nq(i) * tsurf_new(i)
2228    fluxlat(i) = - evap(i) * zx_sl(i)
2229    fluxsens(i) = zx_mh(i) + zx_nh(i) * tsurf_new(i)
2230! Derives des flux dF/dTs (W m-2 K-1):
2231    dflux_s(i) = zx_nh(i)
2232    dflux_l(i) = (zx_sl(i) * zx_nq(i))
2233
2234!
2235! en cas de fonte de neige
2236!
2237!    if (fonte_neige) then
2238!      bilan_f = radsol(i) + fluxsens(i) - (zx_sl(i) * evap (i)) - &
2239!     &          dif_grnd(i) * (tsurf_new(i) - t_grnd) - &
2240!     &          RCPD * (zx_pkh(i))/cal(i)/dtime * (tsurf_new(i) - tsurf(i))
2241!      bilan_f = max(0., bilan_f)
2242!      fq_fonte = bilan_f / zx_sl(i)
2243!      snow(i) = max(0., snow(i) - fq_fonte * dtime)
2244!      qsol(i) = qsol(i) + (fq_fonte * dtime)
2245!    endif
2246!!$    if (nisurf == is_ter)  &
2247!!$     &  run_off(i) = run_off(i) + max(qsol(i) - max_eau_sol, 0.0)
2248!!$    qsol(i) = min(qsol(i), max_eau_sol)
2249  ENDDO
2250
2251  END SUBROUTINE calcul_fluxs
2252!
2253!#########################################################################
2254!
2255  SUBROUTINE gath2cpl(champ_in, champ_out, klon, knon, iim, jjm, knindex)
2256
2257! Cette routine ecrit un champ 'gathered' sur la grille 2D pour le passer
2258! au coupleur.
2259!
2260!
2261! input:         
2262!   champ_in     champ sur la grille gathere       
2263!   knon         nombre de points dans le domaine a traiter
2264!   knindex      index des points de la surface a traiter
2265!   klon         taille de la grille
2266!   iim,jjm      dimension de la grille 2D
2267!
2268! output:
2269!   champ_out    champ sur la grille 2D
2270!
2271! input
2272  integer                   :: klon, knon, iim, jjm
2273  real, dimension(klon)     :: champ_in
2274  integer, dimension(klon)  :: knindex
2275! output
2276  real, dimension(iim,jjm+1)  :: champ_out
2277! local
2278  integer                   :: i, ig, j
2279  real, dimension(klon)     :: tamp
2280
2281  tamp = 0.
2282  do i = 1, knon
2283    ig = knindex(i)
2284    tamp(ig) = champ_in(i)
2285  enddo   
2286  ig = 1
2287  champ_out(:,1) = tamp(ig)
2288  do j = 2, jjm
2289    do i = 1, iim
2290      ig = ig + 1
2291      champ_out(i,j) = tamp(ig)
2292    enddo
2293  enddo
2294  ig = ig + 1
2295  champ_out(:,jjm+1) = tamp(ig)
2296
2297  END SUBROUTINE gath2cpl
2298!
2299!#########################################################################
2300!
2301  SUBROUTINE cpl2gath(champ_in, champ_out, klon, knon, iim, jjm, knindex)
2302
2303! Cette routine ecrit un champ 'gathered' sur la grille 2D pour le passer
2304! au coupleur.
2305!
2306!
2307! input:         
2308!   champ_in     champ sur la grille gathere       
2309!   knon         nombre de points dans le domaine a traiter
2310!   knindex      index des points de la surface a traiter
2311!   klon         taille de la grille
2312!   iim,jjm      dimension de la grille 2D
2313!
2314! output:
2315!   champ_out    champ sur la grille 2D
2316!
2317! input
2318  integer                   :: klon, knon, iim, jjm
2319  real, dimension(iim,jjm+1)     :: champ_in
2320  integer, dimension(klon)  :: knindex
2321! output
2322  real, dimension(klon)  :: champ_out
2323! local
2324  integer                   :: i, ig, j
2325  real, dimension(klon)     :: tamp
2326  logical ,save                  :: check = .false.
2327
2328  ig = 1
2329  tamp(ig) = champ_in(1,1)
2330  do j = 2, jjm
2331    do i = 1, iim
2332      ig = ig + 1
2333      tamp(ig) = champ_in(i,j)
2334    enddo
2335  enddo
2336  ig = ig + 1
2337  tamp(ig) = champ_in(1,jjm+1)
2338
2339  do i = 1, knon
2340    ig = knindex(i)
2341    champ_out(i) = tamp(ig)
2342  enddo   
2343
2344  END SUBROUTINE cpl2gath
2345!
2346!#########################################################################
2347!
2348  SUBROUTINE albsno(klon, knon,dtime,agesno,alb_neig_grid, precip_snow)
2349  IMPLICIT none
2350 
2351  INTEGER :: klon, knon
2352  INTEGER, PARAMETER :: nvm = 8
2353  REAL   :: dtime
2354  REAL, dimension(klon,nvm) :: veget
2355  REAL, DIMENSION(klon) :: alb_neig_grid, agesno, precip_snow
2356 
2357  INTEGER :: i, nv
2358 
2359  REAL, DIMENSION(nvm),SAVE :: init, decay
2360  REAL :: as
2361  DATA init /0.55, 0.14, 0.18, 0.29, 0.15, 0.15, 0.14, 0./
2362  DATA decay/0.30, 0.67, 0.63, 0.45, 0.40, 0.14, 0.06, 1./
2363 
2364  veget = 0.
2365  veget(:,1) = 1.     ! desert partout
2366  DO i = 1, knon
2367    alb_neig_grid(i) = 0.0
2368  ENDDO
2369  DO nv = 1, nvm
2370    DO i = 1, knon
2371      as = init(nv)+decay(nv)*EXP(-agesno(i)/5.)
2372      alb_neig_grid(i) = alb_neig_grid(i) + veget(i,nv)*as
2373    ENDDO
2374  ENDDO
2375!
2376!! modilation en fonction de l'age de la neige
2377!
2378  DO i = 1, knon
2379    agesno(i)  = (agesno(i) + (1.-agesno(i)/50.)*dtime/86400.)&
2380            &             * EXP(-1.*MAX(0.0,precip_snow(i))*dtime/0.3)
2381    agesno(i) =  MAX(agesno(i),0.0)
2382  ENDDO
2383 
2384  END SUBROUTINE albsno
2385!
2386!#########################################################################
2387!
2388
2389  SUBROUTINE fonte_neige( klon, knon, nisurf, dtime, &
2390     & tsurf, p1lay, cal, beta, coef1lay, ps, &
2391     & precip_rain, precip_snow, snow, qsol, &
2392     & radsol, dif_grnd, t1lay, q1lay, u1lay, v1lay, &
2393     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
2394     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
2395
2396! Routine de traitement de la fonte de la neige dans le cas du traitement
2397! de sol simplifié
2398!
2399! LF 03/2001
2400! input:
2401!   knon         nombre de points a traiter
2402!   nisurf       surface a traiter
2403!   tsurf        temperature de surface
2404!   p1lay        pression 1er niveau (milieu de couche)
2405!   cal          capacite calorifique du sol
2406!   beta         evap reelle
2407!   coef1lay     coefficient d'echange
2408!   ps           pression au sol
2409!   precip_rain  precipitations liquides
2410!   precip_snow  precipitations solides
2411!   snow         champs hauteur de neige
2412!   qsol         humidite du sol
2413!   runoff       runoff en cas de trop plein
2414!   petAcoef     coeff. A de la resolution de la CL pour t
2415!   peqAcoef     coeff. A de la resolution de la CL pour q
2416!   petBcoef     coeff. B de la resolution de la CL pour t
2417!   peqBcoef     coeff. B de la resolution de la CL pour q
2418!   radsol       rayonnement net aus sol (LW + SW)
2419!   dif_grnd     coeff. diffusion vers le sol profond
2420!
2421! output:
2422!   tsurf_new    temperature au sol
2423!   fluxsens     flux de chaleur sensible
2424!   fluxlat      flux de chaleur latente
2425!   dflux_s      derivee du flux de chaleur sensible / Ts
2426!   dflux_l      derivee du flux de chaleur latente  / Ts
2427!
2428
2429#include "YOETHF.inc"
2430#include "FCTTRE.inc"
2431#include "indicesol.inc"
2432
2433! Parametres d'entree
2434  integer, intent(IN) :: knon, nisurf, klon
2435  real   , intent(IN) :: dtime
2436  real, dimension(klon), intent(IN) :: petAcoef, peqAcoef
2437  real, dimension(klon), intent(IN) :: petBcoef, peqBcoef
2438  real, dimension(klon), intent(IN) :: ps, q1lay
2439  real, dimension(klon), intent(IN) :: tsurf, p1lay, cal, beta, coef1lay
2440  real, dimension(klon), intent(IN) :: precip_rain, precip_snow
2441  real, dimension(klon), intent(IN) :: radsol, dif_grnd
2442  real, dimension(klon), intent(IN) :: t1lay, u1lay, v1lay
2443  real, dimension(klon), intent(INOUT) :: snow, qsol
2444
2445! Parametres sorties
2446  real, dimension(klon), intent(INOUT):: tsurf_new, evap, fluxsens, fluxlat
2447  real, dimension(klon), intent(INOUT):: dflux_s, dflux_l
2448
2449! Variables locales
2450  integer :: i
2451  real, dimension(klon) :: zx_mh, zx_nh, zx_oh
2452  real, dimension(klon) :: zx_mq, zx_nq, zx_oq
2453  real, dimension(klon) :: zx_pkh, zx_dq_s_dt, zx_qsat, zx_coef
2454  real, dimension(klon) :: zx_sl, zx_k1
2455  real, dimension(klon) :: zx_q_0 , d_ts
2456  real                  :: zdelta, zcvm5, zx_qs, zcor, zx_dq_s_dh
2457  real                  :: bilan_f, fq_fonte
2458  REAL                  :: subli, fsno
2459  real, parameter :: t_grnd = 271.35, t_coup = 273.15
2460!! PB temporaire en attendant mieux pour le modele de neige
2461  REAL, parameter :: chasno = 3.334E+05/(2.3867E+06*0.15)
2462!
2463  logical, save         :: check = .FALSE.
2464  character (len = 20)  :: modname = 'fonte_neige'
2465  logical, save         :: neige_fond = .false.
2466  real, save            :: max_eau_sol = 150.0
2467  character (len = 80) :: abort_message
2468  logical,save         :: first = .true.,second=.false.
2469
2470  if (check) write(*,*)'Entree ', modname,' surface = ',nisurf
2471
2472! Initialisations
2473  DO i = 1, knon
2474    zx_pkh(i) = (ps(i)/ps(i))**RKAPPA
2475  IF (thermcep) THEN
2476      zdelta=MAX(0.,SIGN(1.,rtt-tsurf(i)))
2477      zcvm5 = R5LES*RLVTT*(1.-zdelta) + R5IES*RLSTT*zdelta
2478      zcvm5 = zcvm5 / RCPD / (1.0+RVTMP2*q1lay(i))
2479      zx_qs= r2es * FOEEW(tsurf(i),zdelta)/ps(i)
2480      zx_qs=MIN(0.5,zx_qs)
2481      zcor=1./(1.-retv*zx_qs)
2482      zx_qs=zx_qs*zcor
2483      zx_dq_s_dh = FOEDE(tsurf(i),zdelta,zcvm5,zx_qs,zcor) &
2484     &                 /RLVTT / zx_pkh(i)
2485    ELSE
2486      IF (tsurf(i).LT.t_coup) THEN
2487        zx_qs = qsats(tsurf(i)) / ps(i)
2488        zx_dq_s_dh = dqsats(tsurf(i),zx_qs)/RLVTT &
2489     &                    / zx_pkh(i)
2490      ELSE
2491        zx_qs = qsatl(tsurf(i)) / ps(i)
2492        zx_dq_s_dh = dqsatl(tsurf(i),zx_qs)/RLVTT &
2493     &               / zx_pkh(i)
2494      ENDIF
2495    ENDIF
2496    zx_dq_s_dt(i) = RCPD * zx_pkh(i) * zx_dq_s_dh
2497    zx_qsat(i) = zx_qs
2498    zx_coef(i) = coef1lay(i) &
2499     & * (1.0+SQRT(u1lay(i)**2+v1lay(i)**2)) &
2500     & * p1lay(i)/(RD*t1lay(i))
2501  ENDDO
2502
2503
2504! === Calcul de la temperature de surface ===
2505!
2506! zx_sl = chaleur latente d'evaporation ou de sublimation
2507!
2508  do i = 1, knon
2509    zx_sl(i) = RLVTT
2510    if (tsurf(i) .LT. RTT) zx_sl(i) = RLSTT
2511    zx_k1(i) = zx_coef(i)
2512  enddo
2513
2514
2515  do i = 1, knon
2516! Q
2517    zx_oq(i) = 1. - (beta(i) * zx_k1(i) * peqBcoef(i) * dtime)
2518    zx_mq(i) = beta(i) * zx_k1(i) * &
2519     &             (peqAcoef(i) - zx_qsat(i) &
2520     &                          + zx_dq_s_dt(i) * tsurf(i)) &
2521     &             / zx_oq(i)
2522    zx_nq(i) = beta(i) * zx_k1(i) * (-1. * zx_dq_s_dt(i)) &
2523     &                              / zx_oq(i)
2524
2525! H
2526    zx_oh(i) = 1. - (zx_k1(i) * petBcoef(i) * dtime)
2527    zx_mh(i) = zx_k1(i) * petAcoef(i) / zx_oh(i)
2528    zx_nh(i) = - (zx_k1(i) * RCPD * zx_pkh(i))/ zx_oh(i)
2529  enddo
2530
2531
2532  WHERE (precip_snow > 0.) snow = snow + (precip_snow * dtime)
2533  WHERE (evap > 0 ) snow = MAX(0.0, snow - (evap * dtime))
2534  qsol = qsol + (precip_rain - evap) * dtime
2535!
2536! Y'a-t-il fonte de neige?
2537!
2538  do i = 1, knon
2539    neige_fond = ((snow(i) > epsfra .OR. nisurf == is_sic .OR. nisurf == is_lic) &
2540     & .AND. tsurf_new(i) >= RTT)
2541    if (neige_fond) then
2542      fq_fonte = MIN( MAX((tsurf_new(i)-RTT )/chasno,0.0),snow(i))
2543      snow(i) = max(0., snow(i) - fq_fonte)
2544      qsol(i) = qsol(i) + fq_fonte
2545      tsurf_new(i) = tsurf_new(i) - fq_fonte * chasno 
2546      IF (nisurf == is_sic .OR. nisurf == is_lic ) tsurf_new(i) = RTT -1.8
2547      d_ts(i) = tsurf_new(i) - tsurf(i)
2548!      zx_h_ts(i) = tsurf_new(i) * RCPD * zx_pkh(i)
2549!      zx_q_0(i) = zx_qsat(i) + zx_dq_s_dt(i) * d_ts(i)
2550!== flux_q est le flux de vapeur d'eau: kg/(m**2 s)  positive vers bas
2551!== flux_t est le flux de cpt (energie sensible): j/(m**2 s)
2552!!$      evap(i) = - zx_mq(i) - zx_nq(i) * tsurf_new(i)
2553!!$      fluxlat(i) = - evap(i) * zx_sl(i)
2554!!$      fluxsens(i) = zx_mh(i) + zx_nh(i) * tsurf_new(i)
2555! Derives des flux dF/dTs (W m-2 K-1):
2556!!$      dflux_s(i) = zx_nh(i)
2557!!$      dflux_l(i) = (zx_sl(i) * zx_nq(i))
2558!!$      bilan_f = radsol(i) + fluxsens(i) - (zx_sl(i) * evap (i)) - &
2559!!$     &          dif_grnd(i) * (tsurf_new(i) - t_grnd) - &
2560!!$     &          RCPD * (zx_pkh(i))/cal(i)/dtime * (tsurf_new(i) - tsurf(i))
2561!!$      bilan_f = max(0., bilan_f)
2562!!$      fq_fonte = bilan_f / zx_sl(i)
2563    endif
2564    IF (nisurf == is_ter)  &
2565       &  run_off(i) = run_off(i) + MAX(qsol(i) - max_eau_sol, 0.0)
2566    qsol(i) = MIN(qsol(i), max_eau_sol)
2567  enddo
2568
2569  END SUBROUTINE fonte_neige
2570!
2571!#########################################################################
2572!
2573  END MODULE interface_surf
Note: See TracBrowser for help on using the repository browser.