source: LMDZ.3.3/branches/rel-LF/libf/phylmd/interface_surf.F90 @ 364

Last change on this file since 364 was 364, checked in by lmdzadmin, 23 years ago

Differentes modifs d'ajustement et de reglages du calendrier
LF

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