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

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

Orchidee utilise psol plutot que p1lay (commentaire erroné dans intersurf)
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  if (check) write(*,*)'Entree ', modname
793  if (check) write(*,*)'ok_veget = ',ok_veget
794
795  ktindex(:) = knindex(:) + iim - 1
796
797! initialisation
798  if (debut) then
799
800! Pb de correspondances de grilles
801   allocate(ig(klon))
802   allocate(jg(klon))
803   ig(1) = 1
804   jg(1) = 1
805   indi = 0
806   indj = 2
807   do igrid = 2, klon - 1
808     indi = indi + 1
809     if ( indi > iim) then
810       indi = 1
811       indj = indj + 1
812     endif
813     ig(igrid) = indi
814     jg(igrid) = indj
815   enddo
816   ig(klon) = 1
817   jg(klon) = jjm + 1
818!
819!  Initialisation des offset   
820!
821! offset bord ouest
822   off_ini(1,1) = - iim  ; off_ini(2,1) = - iim + 1; off_ini(3,1) = 1
823   off_ini(4,1) = iim + 1; off_ini(5,1) = iim      ; off_ini(6,1) = 2 * iim - 1
824   off_ini(7,1) = iim -1 ; off_ini(8,1) = - 1
825! offset point normal
826   off_ini(1,2) = - iim  ; off_ini(2,2) = - iim + 1; off_ini(3,2) = 1
827   off_ini(4,2) = iim + 1; off_ini(5,2) = iim      ; off_ini(6,2) = iim - 1
828   off_ini(7,2) = -1     ; off_ini(8,2) = - iim - 1
829! offset bord   est
830   off_ini(1,3) = - iim; off_ini(2,3) = - 2 * iim + 1; off_ini(3,3) = - iim + 1
831   off_ini(4,3) =  1   ; off_ini(5,3) = iim          ; off_ini(6,3) = iim - 1
832   off_ini(7,3) = -1   ; off_ini(8,3) = - iim - 1
833!
834! Initialisation des correspondances point -> indices i,j
835!
836    if (( .not. allocated(correspond))) then
837      allocate(correspond(iim,jjm+1), stat = error)
838      if (error /= 0) then
839        abort_message='Pb allocation correspond'
840        call abort_gcm(modname,abort_message,1)
841      endif     
842    endif
843!
844! Attention aux poles
845!
846    do igrid = 1, knon
847      index = ktindex(igrid)
848          jj = int((index - 1)/iim) + 1
849          ij = index - (jj - 1) * iim
850      correspond(ij,jj) = igrid
851    enddo
852
853! Allouer et initialiser le tableau de coordonnees du sol
854!
855    if ((.not. allocated(lalo))) then
856      allocate(lalo(knon,2), stat = error)
857      if (error /= 0) then
858        abort_message='Pb allocation lalo'
859        call abort_gcm(modname,abort_message,1)
860      endif     
861    endif
862    if ((.not. allocated(lon_scat))) then
863      allocate(lon_scat(iim,jjm+1), stat = error)
864      if (error /= 0) then
865        abort_message='Pb allocation lon_scat'
866        call abort_gcm(modname,abort_message,1)
867      endif     
868    endif
869    if ((.not. allocated(lat_scat))) then
870      allocate(lat_scat(iim,jjm+1), stat = error)
871      if (error /= 0) then
872        abort_message='Pb allocation lat_scat'
873        call abort_gcm(modname,abort_message,1)
874      endif     
875    endif
876    lon_scat = 0.
877    lat_scat = 0.
878    do igrid = 1, knon
879      index = knindex(igrid)
880      lalo(igrid,2) = rlon(index)
881      lalo(igrid,1) = rlat(index)
882      ij = index - int((index-1)/iim)*iim - 1
883      jj = 2 + int((index-1)/iim)
884      if (mod(index,iim) == 1 ) then
885        jj = 1 + int((index-1)/iim)
886        ij = iim
887      endif
888!      lon_scat(ij,jj) = rlon(index)
889!      lat_scat(ij,jj) = rlat(index)
890    enddo
891    index = 1
892    do jj = 2, jjm
893      do ij = 1, iim
894        index = index + 1
895        lon_scat(ij,jj) = rlon(index)
896        lat_scat(ij,jj) = rlat(index)
897      enddo
898    enddo
899    lon_scat(:,1) = lon_scat(:,2)
900    lat_scat(:,1) = rlat(1)
901    lon_scat(:,jjm+1) = lon_scat(:,2)
902    lat_scat(:,jjm+1) = rlat(klon)
903! Pb de correspondances de grilles!
904!    do igrid = 1, knon
905!      index = ktindex(igrid)
906!      ij = ig(index)
907!      jj = jg(index)
908!      lon_scat(ij,jj) = rlon(index)
909!      lat_scat(ij,jj) = rlat(index)
910!    enddo
911
912!
913! Allouer et initialiser le tableau des voisins et des fraction de continents
914!
915    if ( (.not.allocated(neighbours))) THEN
916      allocate(neighbours(knon,8), stat = error)
917      if (error /= 0) then
918        abort_message='Pb allocation neighbours'
919        call abort_gcm(modname,abort_message,1)
920      endif
921    endif
922    neighbours = -1.
923    if (( .not. allocated(contfrac))) then
924      allocate(contfrac(knon), stat = error)
925      if (error /= 0) then
926        abort_message='Pb allocation contfrac'
927        call abort_gcm(modname,abort_message,1)
928      endif     
929    endif
930
931    do igrid = 1, knon
932      ireal = knindex(igrid)
933      contfrac(igrid) = pctsrf(ireal,is_ter)
934    enddo
935
936    do igrid = 1, knon
937      iglob = ktindex(igrid)
938      if (mod(iglob, iim) == 1) then
939        offset = off_ini(:,1)
940      else if(mod(iglob, iim) == 0) then
941        offset = off_ini(:,3)
942      else
943        offset = off_ini(:,2)
944      endif
945      do i = 1, 8
946        index = iglob + offset(i)
947        ireal = (min(max(1, index - iim + 1), klon))
948        if (pctsrf(ireal, is_ter) > EPSFRA) then
949          jj = int((index - 1)/iim) + 1
950          ij = index - (jj - 1) * iim
951            neighbours(igrid, i) = correspond(ij, jj)
952        endif
953      enddo
954    enddo
955
956!
957!  Allocation et calcul resolutions
958    IF ( (.NOT.ALLOCATED(resolution))) THEN
959      ALLOCATE(resolution(knon,2), stat = error)
960      if (error /= 0) then
961        abort_message='Pb allocation resolution'
962        call abort_gcm(modname,abort_message,1)
963      endif
964    ENDIF
965    do igrid = 1, knon
966      ij = knindex(igrid)
967      resolution(igrid,1) = cufi(ij)
968      resolution(igrid,2) = cvfi(ij)
969    enddo 
970
971  endif                          ! (fin debut)
972
973!
974! Appel a la routine sols continentaux
975!
976  if (lafin) lrestart_write = .true.
977  if (check) write(*,*)'lafin ',lafin,lrestart_write
978
979  petA_orc = petBcoef * dtime
980  petB_orc = petAcoef
981  peqA_orc = peqBcoef * dtime
982  peqB_orc = peqAcoef
983
984  cdrag = 0.
985  cdrag(1:knon) = tq_cdrag(1:knon)
986
987   where(cdrag > 0.01)
988     cdrag = 0.01
989   endwhere
990!  write(*,*)'Cdrag = ',minval(cdrag),maxval(cdrag)
991
992!
993! Init Orchidee
994!
995  if (debut) then
996    call intersurf_main (itime-1, iim, jjm+1, knon, ktindex, dtime, &
997     & lrestart_read, lrestart_write, lalo, &
998     & contfrac, neighbours, resolution, date0, &
999     & zlev,  u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, &
1000     & cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, &
1001     & precip_rain, precip_snow, lwdown, swnet, swdown, ps, &
1002     & evap, fluxsens, fluxlat, coastalflow, riverflow, &
1003     & tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, &
1004     & lon_scat, lat_scat)
1005  endif
1006
1007  call intersurf_main (itime, iim, jjm+1, knon, ktindex, dtime, &
1008     & lrestart_read, lrestart_write, lalo, &
1009     & contfrac, neighbours, resolution, date0, &
1010     & zlev,  u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, &
1011     & cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, &
1012     & precip_rain, precip_snow, lwdown, swnet, swdown, ps, &
1013     & evap, fluxsens, fluxlat, coastalflow, riverflow, &
1014     & tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, &
1015     & lon_scat, lat_scat)
1016
1017    bidule=0.
1018    bidule(1:knon)=riverflow(1:knon)
1019    call gath2cpl(bidule, tmp_rriv, klon, knon,iim,jjm,ktindex)
1020    bidule=0.
1021    bidule(1:knon)=coastalflow(1:knon)
1022    call gath2cpl(bidule, tmp_rcoa, klon, knon,iim,jjm,ktindex)
1023    alb_new(1:knon) = albedo_out(1:knon,1)
1024    alblw(1:knon) = albedo_out(1:knon,2)
1025
1026
1027! Convention orchidee: positif vers le haut
1028  fluxsens(1:knon) = -1. * fluxsens(1:knon)
1029  fluxlat(1:knon)  = -1. * fluxlat(1:knon)
1030
1031!  evap     = -1. * evap
1032
1033  if (debut) lrestart_read = .false.
1034
1035  END SUBROUTINE interfsol
1036!
1037!#########################################################################
1038!
1039  SUBROUTINE interfoce_cpl(itime, dtime, cumul, &
1040      & klon, iim, jjm, nisurf, pctsrf, knon, knindex, rlon, rlat, &
1041      & ocean, npas, nexca, debut, lafin, &
1042      & swdown, lwdown, precip_rain, precip_snow, evap, tsurf, &
1043      & fluxlat, fluxsens, fder, albsol, taux, tauy, zmasq, &
1044      & tsurf_new, alb_new, pctsrf_new)
1045
1046! Cette routine sert d'interface entre le modele atmospherique et un
1047! coupleur avec un modele d'ocean 'complet' derriere
1048!
1049! Le modele de glace qu'il est prevu d'utiliser etant couple directement a
1050! l'ocean presentement, on va passer deux fois dans cette routine par pas de
1051! temps physique, une fois avec les points oceans et l'autre avec les points
1052! glace. A chaque pas de temps de couplage, la lecture des champs provenant
1053! du coupleur se fera "dans" l'ocean et l'ecriture des champs a envoyer
1054! au coupleur "dans" la glace. Il faut donc des tableaux de travail "tampons"
1055! dimensionnes sur toute la grille qui remplissent les champs sur les
1056! domaines ocean/glace quand il le faut. Il est aussi necessaire que l'index
1057! ocean soit traiter avant l'index glace (sinon tout intervertir)
1058!
1059!
1060! L. Fairhead 02/2000
1061!
1062! input:
1063!   itime        numero du pas de temps
1064!   iim, jjm     nbres de pts de grille
1065!   dtime        pas de temps de la physique
1066!   klon         nombre total de points de grille
1067!   nisurf       index de la surface a traiter (1 = sol continental)
1068!   pctsrf       tableau des fractions de surface de chaque maille
1069!   knon         nombre de points de la surface a traiter
1070!   knindex      index des points de la surface a traiter
1071!   rlon         longitudes
1072!   rlat         latitudes
1073!   debut        logical: 1er appel a la physique
1074!   lafin        logical: dernier appel a la physique
1075!   ocean        type d'ocean
1076!   nexca        frequence de couplage
1077!   swdown       flux solaire entrant a la surface
1078!   lwdown       flux IR net a la surface
1079!   precip_rain  precipitation liquide
1080!   precip_snow  precipitation solide
1081!   evap         evaporation
1082!   tsurf        temperature de surface
1083!   fder         derivee dF/dT
1084!   albsol       albedo du sol (coherent avec swdown)
1085!   taux         tension de vent en x
1086!   tauy         tension de vent en y
1087!   nexca        frequence de couplage
1088!   zmasq        masque terre/ocean
1089!
1090!
1091! output:
1092!   tsurf_new    temperature au sol
1093!   alb_new      albedo
1094!   pctsrf_new   nouvelle repartition des surfaces
1095!   alb_ice      albedo de la glace
1096!
1097
1098
1099! Parametres d'entree
1100  integer, intent(IN) :: itime
1101  integer, intent(IN) :: iim, jjm
1102  real, intent(IN) :: dtime
1103  integer, intent(IN) :: klon
1104  integer, intent(IN) :: nisurf
1105  integer, intent(IN) :: knon
1106  real, dimension(klon,nbsrf), intent(IN) :: pctsrf
1107  integer, dimension(klon), intent(in) :: knindex
1108  logical, intent(IN) :: debut, lafin
1109  real, dimension(klon), intent(IN) :: rlon, rlat
1110  character (len = 6)  :: ocean
1111  real, dimension(klon), intent(IN) :: lwdown, swdown
1112  real, dimension(klon), intent(IN) :: precip_rain, precip_snow
1113  real, dimension(klon), intent(IN) :: tsurf, fder, albsol, taux, tauy
1114  INTEGER              :: nexca, npas, kstep
1115  real, dimension(klon), intent(IN) :: zmasq
1116  real, dimension(klon), intent(IN) :: fluxlat, fluxsens
1117  logical, intent(IN)               :: cumul
1118  real, dimension(klon), intent(INOUT) :: evap
1119
1120! Parametres de sortie
1121  real, dimension(klon), intent(OUT):: tsurf_new, alb_new
1122  real, dimension(klon,nbsrf), intent(OUT) :: pctsrf_new
1123
1124! Variables locales
1125  integer                    :: j, error, sum_error, ig, cpl_index,i
1126  character (len = 20) :: modname = 'interfoce_cpl'
1127  character (len = 80) :: abort_message
1128  logical,save              :: check = .FALSE.
1129! variables pour moyenner les variables de couplage
1130  real, allocatable, dimension(:,:),save :: cpl_sols, cpl_nsol, cpl_rain
1131  real, allocatable, dimension(:,:),save :: cpl_snow, cpl_evap, cpl_tsol
1132  real, allocatable, dimension(:,:),save :: cpl_fder, cpl_albe, cpl_taux
1133!!$PB  real, allocatable, dimension(:,:),save :: cpl_tauy, cpl_rriv, cpl_rcoa
1134  real, allocatable, dimension(:,:),save :: cpl_tauy
1135  real, allocatable, dimension(:,:),save :: cpl_rriv, cpl_rcoa
1136!!$
1137! variables tampons avant le passage au coupleur
1138  real, allocatable, dimension(:,:,:),save :: tmp_sols, tmp_nsol, tmp_rain
1139  real, allocatable, dimension(:,:,:),save :: tmp_snow, tmp_evap, tmp_tsol
1140  real, allocatable, dimension(:,:,:),save :: tmp_fder, tmp_albe, tmp_taux
1141!!$  real, allocatable, dimension(:,:,:),save :: tmp_tauy, tmp_rriv, tmp_rcoa
1142  REAL, ALLOCATABLE, DIMENSION(:,:,:),SAVE :: tmp_tauy
1143! variables a passer au coupleur
1144  real, dimension(iim, jjm+1) :: wri_sol_ice, wri_sol_sea, wri_nsol_ice
1145  real, dimension(iim, jjm+1) :: wri_nsol_sea, wri_fder_ice, wri_evap_ice
1146  REAL, DIMENSION(iim, jjm+1) :: wri_evap_sea, wri_rcoa, wri_rriv
1147  REAL, DIMENSION(iim, jjm+1) :: wri_rain, wri_snow, wri_taux, wri_tauy
1148  REAL, DIMENSION(iim, jjm+1) :: wri_tauxx, wri_tauyy, wri_tauzz
1149  REAL, DIMENSION(iim, jjm+1) :: tmp_lon, tmp_lat
1150! variables relues par le coupleur
1151! read_sic = fraction de glace
1152! read_sit = temperature de glace
1153  real, allocatable, dimension(:,:),save :: read_sst, read_sic, read_sit
1154  real, allocatable, dimension(:,:),save :: read_alb_sic
1155! variable tampon
1156  real, dimension(klon)       :: tamp_sic
1157! sauvegarde des fractions de surface d'un pas de temps a l'autre apres
1158! l'avoir lu
1159  real, allocatable,dimension(:,:),save :: pctsrf_sav
1160  real, dimension(iim, jjm+1, 2) :: tamp_srf
1161  integer, allocatable, dimension(:), save :: tamp_ind
1162  real, allocatable, dimension(:,:),save :: tamp_zmasq
1163  real, dimension(iim, jjm+1) :: deno
1164  integer                     :: idtime
1165  integer, allocatable,dimension(:),save :: unity
1166!
1167  logical, save    :: first_appel = .true.
1168  logical,save          :: print
1169!maf
1170! variables pour avoir une sortie IOIPSL des champs echanges
1171  CHARACTER*80,SAVE :: clintocplnam, clfromcplnam
1172  INTEGER, SAVE :: jf,nhoridct,nidct
1173  INTEGER, SAVE :: nhoridcs,nidcs
1174  INTEGER :: ndexct(iim*(jjm+1)),ndexcs(iim*(jjm+1))
1175  REAL :: zx_lon(iim,jjm+1), zx_lat(iim,jjm+1), zjulian
1176  integer :: idayref, itau_w
1177  include 'param_cou.h'
1178  include 'inc_cpl.h'
1179  include 'temps.inc'
1180!
1181! Initialisation
1182!
1183  if (check) write(*,*)'Entree ',modname,'nisurf = ',nisurf
1184 
1185  if (first_appel) then
1186    error = 0
1187    allocate(unity(klon), stat = error)
1188    if ( error  /=0) then
1189      abort_message='Pb allocation variable unity'
1190      call abort_gcm(modname,abort_message,1)
1191    endif
1192    allocate(pctsrf_sav(klon,nbsrf), stat = error)
1193    if ( error  /=0) then
1194      abort_message='Pb allocation variable pctsrf_sav'
1195      call abort_gcm(modname,abort_message,1)
1196    endif
1197    pctsrf_sav = 0.
1198
1199    do ig = 1, klon
1200      unity(ig) = ig
1201    enddo
1202    sum_error = 0
1203    allocate(cpl_sols(klon,2), stat = error); sum_error = sum_error + error
1204    allocate(cpl_nsol(klon,2), stat = error); sum_error = sum_error + error
1205    allocate(cpl_rain(klon,2), stat = error); sum_error = sum_error + error
1206    allocate(cpl_snow(klon,2), stat = error); sum_error = sum_error + error
1207    allocate(cpl_evap(klon,2), stat = error); sum_error = sum_error + error
1208    allocate(cpl_tsol(klon,2), stat = error); sum_error = sum_error + error
1209    allocate(cpl_fder(klon,2), stat = error); sum_error = sum_error + error
1210    allocate(cpl_albe(klon,2), stat = error); sum_error = sum_error + error
1211    allocate(cpl_taux(klon,2), stat = error); sum_error = sum_error + error
1212    allocate(cpl_tauy(klon,2), stat = error); sum_error = sum_error + error
1213!!$PB
1214!!$    allocate(cpl_rcoa(klon,2), stat = error); sum_error = sum_error + error
1215!!$    allocate(cpl_rriv(klon,2), stat = error); sum_error = sum_error + error
1216    ALLOCATE(cpl_rriv(iim,jjm+1), stat=error); sum_error = sum_error + error
1217    ALLOCATE(cpl_rcoa(iim,jjm+1), stat=error); sum_error = sum_error + error
1218!!
1219    allocate(read_sst(iim, jjm+1), stat = error); sum_error = sum_error + error
1220    allocate(read_sic(iim, jjm+1), stat = error); sum_error = sum_error + error
1221    allocate(read_sit(iim, jjm+1), stat = error); sum_error = sum_error + error
1222    allocate(read_alb_sic(iim, jjm+1), stat = error); sum_error = sum_error + error
1223
1224    if (sum_error /= 0) then
1225      abort_message='Pb allocation variables couplees'
1226      call abort_gcm(modname,abort_message,1)
1227    endif
1228    cpl_sols = 0.; cpl_nsol = 0.; cpl_rain = 0.; cpl_snow = 0.
1229    cpl_evap = 0.; cpl_tsol = 0.; cpl_fder = 0.; cpl_albe = 0.
1230    cpl_taux = 0.; cpl_tauy = 0.; cpl_rriv = 0.; cpl_rcoa = 0.
1231
1232    sum_error = 0
1233    allocate(tamp_ind(klon), stat = error); sum_error = sum_error + error
1234    allocate(tamp_zmasq(iim, jjm+1), stat = error); sum_error = sum_error + error   
1235    do ig = 1, klon
1236      tamp_ind(ig) = ig
1237    enddo
1238    call gath2cpl(zmasq, tamp_zmasq, klon, klon, iim, jjm, tamp_ind)
1239!
1240! initialisation couplage
1241!
1242    idtime = int(dtime)
1243    call inicma(npas , nexca, idtime,(jjm+1)*iim)
1244
1245!
1246! initialisation sorties netcdf
1247!
1248    idayref = day_ini
1249    CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
1250    CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlon,zx_lon)
1251    DO i = 1, iim
1252      zx_lon(i,1) = rlon(i+1)
1253      zx_lon(i,jjm+1) = rlon(i+1)
1254    ENDDO
1255    CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlat,zx_lat)
1256    clintocplnam="cpl_atm_tauflx"
1257    CALL histbeg(clintocplnam, iim,zx_lon(:,1),jjm+1,zx_lat(1,:),1,iim,1,jjm+1, &
1258       & itau_phy,zjulian,dtime,nhoridct,nidct)
1259! no vertical axis
1260    CALL histdef(nidct, 'tauxe','tauxe', &
1261         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1262    CALL histdef(nidct, 'tauyn','tauyn', &
1263         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1264    CALL histdef(nidct, 'tmp_lon','tmp_lon', &
1265         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1266    CALL histdef(nidct, 'tmp_lat','tmp_lat', &
1267         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1268    DO jf=1,jpflda2o1 + jpflda2o2
1269      CALL histdef(nidct, cl_writ(jf),cl_writ(jf), &
1270         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1271    END DO
1272    CALL histend(nidct)
1273    CALL histsync(nidct)
1274
1275    clfromcplnam="cpl_atm_sst"
1276    CALL histbeg(clfromcplnam, iim,zx_lon(:,1),jjm+1,zx_lat(1,:),1,iim,1,jjm+1, &
1277       & 0,zjulian,dtime,nhoridcs,nidcs)
1278! no vertical axis
1279    DO jf=1,jpfldo2a
1280      CALL histdef(nidcs, cl_read(jf),cl_read(jf), &
1281         & "-",iim, jjm+1, nhoridcs, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1282    END DO
1283    CALL histend(nidcs)
1284    CALL histsync(nidcs)
1285
1286! pour simuler la fonte des glaciers antarctiques
1287!
1288    surf_maille = (4. * rpi * ra**2) / (iim * (jjm +1))
1289    ALLOCATE(coeff_iceberg(iim,jjm+1), stat=error)
1290    if (error /= 0) then
1291      abort_message='Pb allocation variable coeff_iceberg'
1292      call abort_gcm(modname,abort_message,1)
1293    endif
1294    open (12,file='flux_iceberg',form='formatted',status='old')
1295    read (12,*) coeff_iceberg
1296    close (12)
1297    num_antarctic = max(1, count(coeff_iceberg > 0))
1298   
1299    first_appel = .false.
1300  endif ! fin if (first_appel)
1301
1302! Initialisations
1303
1304! calcul des fluxs a passer
1305
1306  cpl_index = 1
1307  if (nisurf == is_sic) cpl_index = 2
1308  if (cumul) then
1309    if (check) write(*,*) modname, 'cumul des champs'
1310    do ig = 1, knon
1311      cpl_sols(ig,cpl_index) = cpl_sols(ig,cpl_index) &
1312       &                          + swdown(ig)      / FLOAT(nexca)
1313      cpl_nsol(ig,cpl_index) = cpl_nsol(ig,cpl_index) &
1314       &                          + (lwdown(ig) + fluxlat(ig) +fluxsens(ig))&
1315       &                                / FLOAT(nexca)
1316      cpl_rain(ig,cpl_index) = cpl_rain(ig,cpl_index) &
1317       &                          + precip_rain(ig) / FLOAT(nexca)
1318      cpl_snow(ig,cpl_index) = cpl_snow(ig,cpl_index) &
1319       &                          + precip_snow(ig) / FLOAT(nexca)
1320      cpl_evap(ig,cpl_index) = cpl_evap(ig,cpl_index) &
1321       &                          + evap(ig)        / FLOAT(nexca)
1322      cpl_tsol(ig,cpl_index) = cpl_tsol(ig,cpl_index) &
1323       &                          + tsurf(ig)       / FLOAT(nexca)
1324      cpl_fder(ig,cpl_index) = cpl_fder(ig,cpl_index) &
1325       &                          + fder(ig)        / FLOAT(nexca)
1326      cpl_albe(ig,cpl_index) = cpl_albe(ig,cpl_index) &
1327       &                          + albsol(ig)      / FLOAT(nexca)
1328      cpl_taux(ig,cpl_index) = cpl_taux(ig,cpl_index) &
1329       &                          + taux(ig)        / FLOAT(nexca)
1330      cpl_tauy(ig,cpl_index) = cpl_tauy(ig,cpl_index) &
1331       &                          + tauy(ig)        / FLOAT(nexca)
1332!!$      cpl_rriv(ig,cpl_index) = cpl_rriv(ig,cpl_index) &
1333!!$       &                          + riverflow(ig)   / FLOAT(nexca)/dtime
1334!!$      cpl_rcoa(ig,cpl_index) = cpl_rcoa(ig,cpl_index) &
1335!!$       &                          + coastalflow(ig) / FLOAT(nexca)/dtime
1336    enddo
1337    IF (cpl_index .EQ. 1) THEN
1338        cpl_rriv(:,:) = cpl_rriv(:,:) + tmp_rriv(:,:) / FLOAT(nexca)
1339        cpl_rcoa(:,:) = cpl_rcoa(:,:) + tmp_rcoa(:,:) / FLOAT(nexca)
1340    ENDIF
1341  endif
1342
1343  if (mod(itime, nexca) == 1) then
1344!
1345! Demande des champs au coupleur
1346!
1347! Si le domaine considere est l'ocean, on lit les champs venant du coupleur
1348!
1349    if (nisurf == is_oce .and. .not. cumul) then
1350      if (check) write(*,*)'rentree fromcpl, itime-1 = ',itime-1
1351      call fromcpl(itime-1,(jjm+1)*iim,                                  &
1352     &        read_sst, read_sic, read_sit, read_alb_sic)
1353!
1354! sorties NETCDF des champs recus
1355!
1356      ndexcs(:)=0
1357      itau_w = itau_phy + itime
1358      CALL histwrite(nidcs,cl_read(1),itau_w,read_sst,iim*(jjm+1),ndexcs)
1359      CALL histwrite(nidcs,cl_read(2),itau_w,read_sic,iim*(jjm+1),ndexcs)
1360      CALL histwrite(nidcs,cl_read(3),itau_w,read_alb_sic,iim*(jjm+1),ndexcs)
1361      CALL histwrite(nidcs,cl_read(4),itau_w,read_sit,iim*(jjm+1),ndexcs)
1362      CALL histsync(nidcs)
1363! pas utile      IF (npas-itime.LT.nexca )CALL histclo(nidcs)
1364
1365      do j = 1, jjm + 1
1366        do ig = 1, iim
1367          if (abs(1. - read_sic(ig,j)) < 0.00001) then
1368            read_sst(ig,j) = RTT - 1.8
1369            read_sit(ig,j) = read_sit(ig,j) / read_sic(ig,j)
1370            read_alb_sic(ig,j) = read_alb_sic(ig,j) / read_sic(ig,j)
1371          else if (abs(read_sic(ig,j)) < 0.00001) then
1372            read_sst(ig,j) = read_sst(ig,j) / (1. - read_sic(ig,j))
1373            read_sit(ig,j) = read_sst(ig,j)
1374            read_alb_sic(ig,j) =  0.6
1375          else
1376            read_sst(ig,j) = read_sst(ig,j) / (1. - read_sic(ig,j))
1377            read_sit(ig,j) = read_sit(ig,j) / read_sic(ig,j)
1378            read_alb_sic(ig,j) = read_alb_sic(ig,j) / read_sic(ig,j)
1379          endif
1380        enddo
1381      enddo
1382!
1383! transformer read_sic en pctsrf_sav
1384!
1385      call cpl2gath(read_sic, tamp_sic , klon, klon,iim,jjm, unity)
1386      do ig = 1, klon
1387        IF (pctsrf(ig,is_oce) > epsfra .OR.            &
1388     &             pctsrf(ig,is_sic) > epsfra) THEN
1389          pctsrf_sav(ig,is_sic) = (pctsrf(ig,is_oce) + pctsrf(ig,is_sic)) &
1390     &                               * tamp_sic(ig)
1391          pctsrf_sav(ig,is_oce) = (pctsrf(ig,is_oce) + pctsrf(ig,is_sic)) &
1392     &                        - pctsrf_sav(ig,is_sic)
1393        endif
1394      enddo
1395!
1396! Pour rattraper des erreurs d'arrondis
1397!
1398      where (abs(pctsrf_sav(:,is_sic)) .le. 2.*epsilon(pctsrf_sav(1,is_sic)))
1399        pctsrf_sav(:,is_sic) = 0.
1400        pctsrf_sav(:,is_oce) = pctsrf(:,is_oce) + pctsrf(:,is_sic)
1401      endwhere
1402      where (abs(pctsrf_sav(:,is_oce)) .le. 2.*epsilon(pctsrf_sav(1,is_oce)))
1403        pctsrf_sav(:,is_sic) = pctsrf(:,is_oce) + pctsrf(:,is_sic)
1404        pctsrf_sav(:,is_oce) = 0.
1405      endwhere
1406      if (minval(pctsrf_sav(:,is_oce)) < 0.) then
1407        write(*,*)'Pb fraction ocean inferieure a 0'
1408        write(*,*)'au point ',minloc(pctsrf_sav(:,is_oce))
1409        write(*,*)'valeur = ',minval(pctsrf_sav(:,is_oce))
1410        abort_message = 'voir ci-dessus'
1411        call abort_gcm(modname,abort_message,1)
1412      endif
1413      if (minval(pctsrf_sav(:,is_sic)) < 0.) then
1414        write(*,*)'Pb fraction glace inferieure a 0'
1415        write(*,*)'au point ',minloc(pctsrf_sav(:,is_sic))
1416        write(*,*)'valeur = ',minval(pctsrf_sav(:,is_sic))
1417        abort_message = 'voir ci-dessus'
1418        call abort_gcm(modname,abort_message,1)
1419      endif
1420    endif
1421  endif                         ! fin mod(itime, nexca) == 1
1422
1423  if (mod(itime, nexca) == 0) then
1424!
1425! allocation memoire
1426    if (nisurf == is_oce .and. (.not. cumul) ) then
1427      sum_error = 0
1428      allocate(tmp_sols(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1429      allocate(tmp_nsol(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1430      allocate(tmp_rain(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1431      allocate(tmp_snow(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1432      allocate(tmp_evap(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1433      allocate(tmp_tsol(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1434      allocate(tmp_fder(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1435      allocate(tmp_albe(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1436      allocate(tmp_taux(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1437      allocate(tmp_tauy(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1438!!$      allocate(tmp_rriv(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1439!!$      allocate(tmp_rcoa(iim,jjm+1,2), stat=error); sum_error = sum_error + error
1440      if (sum_error /= 0) then
1441        abort_message='Pb allocation variables couplees pour l''ecriture'
1442        call abort_gcm(modname,abort_message,1)
1443      endif
1444    endif
1445
1446!
1447! Mise sur la bonne grille des champs a passer au coupleur
1448!
1449    cpl_index = 1
1450    if (nisurf == is_sic) cpl_index = 2
1451    call gath2cpl(cpl_sols(1,cpl_index), tmp_sols(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1452    call gath2cpl(cpl_nsol(1,cpl_index), tmp_nsol(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1453    call gath2cpl(cpl_rain(1,cpl_index), tmp_rain(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1454    call gath2cpl(cpl_snow(1,cpl_index), tmp_snow(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1455    call gath2cpl(cpl_evap(1,cpl_index), tmp_evap(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1456    call gath2cpl(cpl_tsol(1,cpl_index), tmp_tsol(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1457    call gath2cpl(cpl_fder(1,cpl_index), tmp_fder(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1458    call gath2cpl(cpl_albe(1,cpl_index), tmp_albe(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1459    call gath2cpl(cpl_taux(1,cpl_index), tmp_taux(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1460    call gath2cpl(cpl_tauy(1,cpl_index), tmp_tauy(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1461!!$    call gath2cpl(cpl_rriv(1,cpl_index), tmp_rriv(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1462!!$    call gath2cpl(cpl_rcoa(1,cpl_index), tmp_rcoa(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
1463
1464!
1465! Si le domaine considere est la banquise, on envoie les champs au coupleur
1466!
1467    if (nisurf == is_sic .and. cumul) then
1468      wri_rain = 0.; wri_snow = 0.; wri_rcoa = 0.; wri_rriv = 0.
1469      wri_taux = 0.; wri_tauy = 0.
1470      call gath2cpl(pctsrf(1,is_oce), tamp_srf(1,1,1), klon, klon, iim, jjm, tamp_ind)
1471      call gath2cpl(pctsrf(1,is_sic), tamp_srf(1,1,2), klon, klon, iim, jjm, tamp_ind)
1472
1473      wri_sol_ice = tmp_sols(:,:,2)
1474      wri_sol_sea = tmp_sols(:,:,1)
1475      wri_nsol_ice = tmp_nsol(:,:,2)
1476      wri_nsol_sea = tmp_nsol(:,:,1)
1477      wri_fder_ice = tmp_fder(:,:,2)
1478      wri_evap_ice = tmp_evap(:,:,2)
1479      wri_evap_sea = tmp_evap(:,:,1)
1480!!$PB
1481      wri_rriv = cpl_rriv(:,:)
1482      wri_rcoa = cpl_rcoa(:,:)
1483
1484      where (tamp_zmasq /= 1.)
1485        deno =  tamp_srf(:,:,1) + tamp_srf(:,:,2)
1486        wri_rain = tmp_rain(:,:,1) * tamp_srf(:,:,1) / deno +    &
1487      &            tmp_rain(:,:,2) * tamp_srf(:,:,2) / deno
1488        wri_snow = tmp_snow(:,:,1) * tamp_srf(:,:,1) / deno +    &
1489      &            tmp_snow(:,:,2) * tamp_srf(:,:,2) / deno
1490!!$PB
1491!!$        wri_rriv = tmp_rriv(:,:,1) * tamp_srf(:,:,1) / deno +    &
1492!!$      &            tmp_rriv(:,:,2) * tamp_srf(:,:,2) / deno
1493!!$        wri_rcoa = tmp_rcoa(:,:,1) * tamp_srf(:,:,1) / deno +    &
1494!!$      &            tmp_rcoa(:,:,2) * tamp_srf(:,:,2) / deno
1495        wri_taux = tmp_taux(:,:,1) * tamp_srf(:,:,1) / deno +    &
1496      &            tmp_taux(:,:,2) * tamp_srf(:,:,2) / deno
1497        wri_tauy = tmp_tauy(:,:,1) * tamp_srf(:,:,1) / deno +    &
1498      &            tmp_tauy(:,:,2) * tamp_srf(:,:,2) / deno
1499      endwhere
1500!
1501! pour simuler la fonte des glaciers antarctiques
1502!
1503        wri_rain = wri_rain      &
1504      &     + coeff_iceberg * cte_flux_iceberg / (num_antarctic * surf_maille)
1505
1506!
1507! on passe les coordonnées de la grille
1508!
1509
1510      CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlon,tmp_lon)
1511      CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlat,tmp_lat)
1512
1513      DO i = 1, iim
1514        tmp_lon(i,1) = rlon(i+1)
1515        tmp_lon(i,jjm + 1) = rlon(i+1)
1516      ENDDO
1517!
1518! sortie netcdf des champs pour le changement de repere
1519!
1520      ndexct(:)=0
1521      CALL histwrite(nidct,'tauxe',itau_w,wri_taux,iim*(jjm+1),ndexct)
1522      CALL histwrite(nidct,'tauyn',itau_w,wri_tauy,iim*(jjm+1),ndexct)
1523      CALL histwrite(nidct,'tmp_lon',itau_w,tmp_lon,iim*(jjm+1),ndexct)
1524      CALL histwrite(nidct,'tmp_lat',itau_w,tmp_lat,iim*(jjm+1),ndexct)
1525
1526!
1527! calcul 3 coordonnées du vent
1528!
1529      CALL atm2geo (iim , jjm + 1, wri_taux, wri_tauy, tmp_lon, tmp_lat, &
1530         & wri_tauxx, wri_tauyy, wri_tauzz )
1531!
1532! sortie netcdf des champs apres changement de repere et juste avant
1533! envoi au coupleur
1534!
1535      CALL histwrite(nidct,cl_writ(1),itau_w,wri_sol_ice,iim*(jjm+1),ndexct)
1536      CALL histwrite(nidct,cl_writ(2),itau_w,wri_sol_sea,iim*(jjm+1),ndexct)
1537      CALL histwrite(nidct,cl_writ(3),itau_w,wri_nsol_ice,iim*(jjm+1),ndexct)
1538      CALL histwrite(nidct,cl_writ(4),itau_w,wri_nsol_sea,iim*(jjm+1),ndexct)
1539      CALL histwrite(nidct,cl_writ(5),itau_w,wri_fder_ice,iim*(jjm+1),ndexct)
1540      CALL histwrite(nidct,cl_writ(6),itau_w,wri_evap_ice,iim*(jjm+1),ndexct)
1541      CALL histwrite(nidct,cl_writ(7),itau_w,wri_evap_sea,iim*(jjm+1),ndexct)
1542      CALL histwrite(nidct,cl_writ(8),itau_w,wri_rain,iim*(jjm+1),ndexct)
1543      CALL histwrite(nidct,cl_writ(9),itau_w,wri_snow,iim*(jjm+1),ndexct)
1544      CALL histwrite(nidct,cl_writ(10),itau_w,wri_rcoa,iim*(jjm+1),ndexct)
1545      CALL histwrite(nidct,cl_writ(11),itau_w,wri_rriv,iim*(jjm+1),ndexct)
1546      CALL histwrite(nidct,cl_writ(12),itau_w,wri_tauxx,iim*(jjm+1),ndexct)
1547      CALL histwrite(nidct,cl_writ(13),itau_w,wri_tauyy,iim*(jjm+1),ndexct)
1548      CALL histwrite(nidct,cl_writ(14),itau_w,wri_tauzz,iim*(jjm+1),ndexct)
1549      CALL histwrite(nidct,cl_writ(15),itau_w,wri_tauxx,iim*(jjm+1),ndexct)
1550      CALL histwrite(nidct,cl_writ(16),itau_w,wri_tauyy,iim*(jjm+1),ndexct)
1551      CALL histwrite(nidct,cl_writ(17),itau_w,wri_tauzz,iim*(jjm+1),ndexct)
1552      CALL histsync(nidct)
1553! pas utile      IF (lafin) CALL histclo(nidct)
1554
1555      call intocpl(itime, (jjm+1)*iim, wri_sol_ice, wri_sol_sea, wri_nsol_ice,&
1556      & wri_nsol_sea, wri_fder_ice, wri_evap_ice, wri_evap_sea, wri_rain, &
1557      & wri_snow, wri_rcoa, wri_rriv, wri_tauxx, wri_tauyy, wri_tauzz, &
1558      & wri_tauxx, wri_tauyy, wri_tauzz,lafin )
1559!
1560      cpl_sols = 0.; cpl_nsol = 0.; cpl_rain = 0.; cpl_snow = 0.
1561      cpl_evap = 0.; cpl_tsol = 0.; cpl_fder = 0.; cpl_albe = 0.
1562      cpl_taux = 0.; cpl_tauy = 0.; cpl_rriv = 0.; cpl_rcoa = 0.
1563!
1564! deallocation memoire variables temporaires
1565!
1566      sum_error = 0
1567      deallocate(tmp_sols, stat=error); sum_error = sum_error + error
1568      deallocate(tmp_nsol, stat=error); sum_error = sum_error + error
1569      deallocate(tmp_rain, stat=error); sum_error = sum_error + error
1570      deallocate(tmp_snow, stat=error); sum_error = sum_error + error
1571      deallocate(tmp_evap, stat=error); sum_error = sum_error + error
1572      deallocate(tmp_fder, stat=error); sum_error = sum_error + error
1573      deallocate(tmp_tsol, stat=error); sum_error = sum_error + error
1574      deallocate(tmp_albe, stat=error); sum_error = sum_error + error
1575      deallocate(tmp_taux, stat=error); sum_error = sum_error + error
1576      deallocate(tmp_tauy, stat=error); sum_error = sum_error + error
1577!!$PB
1578!!$      deallocate(tmp_rriv, stat=error); sum_error = sum_error + error
1579!!$      deallocate(tmp_rcoa, stat=error); sum_error = sum_error + error
1580      if (sum_error /= 0) then
1581        abort_message='Pb deallocation variables couplees'
1582        call abort_gcm(modname,abort_message,1)
1583      endif
1584
1585    endif
1586
1587  endif            ! fin (mod(itime, nexca) == 0)
1588!
1589! on range les variables lues/sauvegardees dans les bonnes variables de sortie
1590!
1591  if (nisurf == is_oce) then
1592    call cpl2gath(read_sst, tsurf_new, klon, knon,iim,jjm, knindex)
1593  else if (nisurf == is_sic) then
1594    call cpl2gath(read_sit, tsurf_new, klon, knon,iim,jjm, knindex)
1595    call cpl2gath(read_alb_sic, alb_new, klon, knon,iim,jjm, knindex)
1596  endif
1597  pctsrf_new(:,nisurf) = pctsrf_sav(:,nisurf)
1598 
1599!  if (lafin) call quitcpl
1600
1601  END SUBROUTINE interfoce_cpl
1602!
1603!#########################################################################
1604!
1605
1606  SUBROUTINE interfoce_slab(nisurf)
1607
1608! Cette routine sert d'interface entre le modele atmospherique et un
1609! modele de 'slab' ocean
1610!
1611! L. Fairhead 02/2000
1612!
1613! input:
1614!   nisurf       index de la surface a traiter (1 = sol continental)
1615!
1616! output:
1617!
1618
1619! Parametres d'entree
1620  integer, intent(IN) :: nisurf
1621
1622  END SUBROUTINE interfoce_slab
1623!
1624!#########################################################################
1625!
1626  SUBROUTINE interfoce_lim(itime, dtime, jour, &
1627     & klon, nisurf, knon, knindex, &
1628     & debut,  &
1629     & lmt_sst, pctsrf_new)
1630
1631! Cette routine sert d'interface entre le modele atmospherique et un fichier
1632! de conditions aux limites
1633!
1634! L. Fairhead 02/2000
1635!
1636! input:
1637!   itime        numero du pas de temps courant
1638!   dtime        pas de temps de la physique (en s)
1639!   jour         jour a lire dans l'annee
1640!   nisurf       index de la surface a traiter (1 = sol continental)
1641!   knon         nombre de points dans le domaine a traiter
1642!   knindex      index des points de la surface a traiter
1643!   klon         taille de la grille
1644!   debut        logical: 1er appel a la physique (initialisation)
1645!
1646! output:
1647!   lmt_sst      SST lues dans le fichier de CL
1648!   pctsrf_new   sous-maille fractionnelle
1649!
1650
1651
1652! Parametres d'entree
1653  integer, intent(IN) :: itime
1654  real   , intent(IN) :: dtime
1655  integer, intent(IN) :: jour
1656  integer, intent(IN) :: nisurf
1657  integer, intent(IN) :: knon
1658  integer, intent(IN) :: klon
1659  integer, dimension(klon), intent(in) :: knindex
1660  logical, intent(IN) :: debut
1661
1662! Parametres de sortie
1663  real, intent(out), dimension(klon) :: lmt_sst
1664  real, intent(out), dimension(klon,nbsrf) :: pctsrf_new
1665
1666! Variables locales
1667  integer     :: ii
1668  INTEGER,save :: lmt_pas     ! frequence de lecture des conditions limites
1669                             ! (en pas de physique)
1670  logical,save :: deja_lu    ! pour indiquer que le jour a lire a deja
1671                             ! lu pour une surface precedente
1672  integer,save :: jour_lu
1673  integer      :: ierr
1674  character (len = 20) :: modname = 'interfoce_lim'
1675  character (len = 80) :: abort_message
1676  character (len = 20),save :: fich ='limit.nc'
1677  logical, save     :: newlmt = .TRUE.
1678  logical, save     :: check = .FALSE.
1679! Champs lus dans le fichier de CL
1680  real, allocatable , save, dimension(:) :: sst_lu, rug_lu, nat_lu
1681  real, allocatable , save, dimension(:,:) :: pct_tmp
1682!
1683! quelques variables pour netcdf
1684!
1685#include "netcdf.inc"
1686  integer              :: nid, nvarid
1687  integer, dimension(2) :: start, epais
1688!
1689! Fin déclaration
1690!
1691   
1692  if (debut .and. .not. allocated(sst_lu)) then
1693    lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour
1694    jour_lu = jour - 1
1695    allocate(sst_lu(klon))
1696    allocate(nat_lu(klon))
1697    allocate(pct_tmp(klon,nbsrf))
1698  endif
1699
1700  if ((jour - jour_lu) /= 0) deja_lu = .false.
1701 
1702  if (check) write(*,*)modname,' :: jour, jour_lu, deja_lu', jour, jour_lu, deja_lu
1703  if (check) write(*,*)modname,' :: itime, lmt_pas ', itime, lmt_pas,dtime
1704
1705! Tester d'abord si c'est le moment de lire le fichier
1706  if (mod(itime-1, lmt_pas) == 0 .and. .not. deja_lu) then
1707!
1708! Ouverture du fichier
1709!
1710    fich = trim(fich)
1711    ierr = NF_OPEN (fich, NF_NOWRITE,nid)
1712    if (ierr.NE.NF_NOERR) then
1713      abort_message = 'Pb d''ouverture du fichier de conditions aux limites'
1714      call abort_gcm(modname,abort_message,1)
1715    endif
1716!
1717! La tranche de donnees a lire:
1718!
1719    start(1) = 1
1720    start(2) = jour + 1
1721    epais(1) = klon
1722    epais(2) = 1
1723!
1724    if (newlmt) then
1725!
1726! Fraction "ocean"
1727!
1728      ierr = NF_INQ_VARID(nid, 'FOCE', nvarid)
1729      if (ierr /= NF_NOERR) then
1730        abort_message = 'Le champ <FOCE> est absent'
1731        call abort_gcm(modname,abort_message,1)
1732      endif
1733#ifdef NC_DOUBLE
1734      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pct_tmp(1,is_oce))
1735#else
1736      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pct_tmp(1,is_oce))
1737#endif
1738      if (ierr /= NF_NOERR) then
1739        abort_message = 'Lecture echouee pour <FOCE>'
1740        call abort_gcm(modname,abort_message,1)
1741      endif
1742!
1743! Fraction "glace de mer"
1744!
1745      ierr = NF_INQ_VARID(nid, 'FSIC', nvarid)
1746      if (ierr /= NF_NOERR) then
1747        abort_message = 'Le champ <FSIC> est absent'
1748        call abort_gcm(modname,abort_message,1)
1749      endif
1750#ifdef NC_DOUBLE
1751      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pct_tmp(1,is_sic))
1752#else
1753      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pct_tmp(1,is_sic))
1754#endif
1755      if (ierr /= NF_NOERR) then
1756        abort_message = 'Lecture echouee pour <FSIC>'
1757        call abort_gcm(modname,abort_message,1)
1758      endif
1759!
1760! Fraction "terre"
1761!
1762      ierr = NF_INQ_VARID(nid, 'FTER', nvarid)
1763      if (ierr /= NF_NOERR) then
1764        abort_message = 'Le champ <FTER> est absent'
1765        call abort_gcm(modname,abort_message,1)
1766      endif
1767#ifdef NC_DOUBLE
1768      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pct_tmp(1,is_ter))
1769#else
1770      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pct_tmp(1,is_ter))
1771#endif
1772      if (ierr /= NF_NOERR) then
1773        abort_message = 'Lecture echouee pour <FTER>'
1774        call abort_gcm(modname,abort_message,1)
1775      endif
1776!
1777! Fraction "glacier terre"
1778!
1779      ierr = NF_INQ_VARID(nid, 'FLIC', nvarid)
1780      if (ierr /= NF_NOERR) then
1781        abort_message = 'Le champ <FLIC> est absent'
1782        call abort_gcm(modname,abort_message,1)
1783      endif
1784#ifdef NC_DOUBLE
1785      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pct_tmp(1,is_lic))
1786#else
1787      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pct_tmp(1,is_lic))
1788#endif
1789      if (ierr /= NF_NOERR) then
1790        abort_message = 'Lecture echouee pour <FLIC>'
1791        call abort_gcm(modname,abort_message,1)
1792      endif
1793!
1794    else  ! on en est toujours a rnatur
1795!
1796      ierr = NF_INQ_VARID(nid, 'NAT', nvarid)
1797      if (ierr /= NF_NOERR) then
1798        abort_message = 'Le champ <NAT> est absent'
1799        call abort_gcm(modname,abort_message,1)
1800      endif
1801#ifdef NC_DOUBLE
1802      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, nat_lu)
1803#else
1804      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, nat_lu)
1805#endif
1806      if (ierr /= NF_NOERR) then
1807        abort_message = 'Lecture echouee pour <NAT>'
1808        call abort_gcm(modname,abort_message,1)
1809      endif
1810!
1811! Remplissage des fractions de surface
1812! nat = 0, 1, 2, 3 pour ocean, terre, glacier, seaice
1813!
1814      pct_tmp = 0.0
1815      do ii = 1, klon
1816        pct_tmp(ii,nint(nat_lu(ii)) + 1) = 1.
1817      enddo
1818
1819!
1820!  On se retrouve avec ocean en 1 et terre en 2 alors qu'on veut le contraire
1821!
1822      pctsrf_new = pct_tmp
1823      pctsrf_new (:,2)= pct_tmp (:,1)
1824      pctsrf_new (:,1)= pct_tmp (:,2)
1825      pct_tmp = pctsrf_new
1826    endif ! fin test sur newlmt
1827!
1828! Lecture SST
1829!
1830    ierr = NF_INQ_VARID(nid, 'SST', nvarid)
1831    if (ierr /= NF_NOERR) then
1832      abort_message = 'Le champ <SST> est absent'
1833      call abort_gcm(modname,abort_message,1)
1834    endif
1835#ifdef NC_DOUBLE
1836    ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, sst_lu)
1837#else
1838    ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, sst_lu)
1839#endif
1840    if (ierr /= NF_NOERR) then
1841      abort_message = 'Lecture echouee pour <SST>'
1842      call abort_gcm(modname,abort_message,1)
1843    endif   
1844
1845!
1846! Fin de lecture
1847!
1848    ierr = NF_CLOSE(nid)
1849    deja_lu = .true.
1850    jour_lu = jour
1851  endif
1852!
1853! Recopie des variables dans les champs de sortie
1854!
1855  lmt_sst = 999999999.
1856  do ii = 1, knon
1857    lmt_sst(ii) = sst_lu(knindex(ii))
1858  enddo
1859
1860  pctsrf_new(:,is_oce) = pct_tmp(:,is_oce)
1861  pctsrf_new(:,is_sic) = pct_tmp(:,is_sic)
1862
1863  END SUBROUTINE interfoce_lim
1864
1865!
1866!#########################################################################
1867!
1868  SUBROUTINE interfsur_lim(itime, dtime, jour, &
1869     & klon, nisurf, knon, knindex, &
1870     & debut,  &
1871     & lmt_alb, lmt_rug)
1872
1873! Cette routine sert d'interface entre le modele atmospherique et un fichier
1874! de conditions aux limites
1875!
1876! L. Fairhead 02/2000
1877!
1878! input:
1879!   itime        numero du pas de temps courant
1880!   dtime        pas de temps de la physique (en s)
1881!   jour         jour a lire dans l'annee
1882!   nisurf       index de la surface a traiter (1 = sol continental)
1883!   knon         nombre de points dans le domaine a traiter
1884!   knindex      index des points de la surface a traiter
1885!   klon         taille de la grille
1886!   debut        logical: 1er appel a la physique (initialisation)
1887!
1888! output:
1889!   lmt_sst      SST lues dans le fichier de CL
1890!   lmt_alb      Albedo lu
1891!   lmt_rug      longueur de rugosité lue
1892!   pctsrf_new   sous-maille fractionnelle
1893!
1894
1895
1896! Parametres d'entree
1897  integer, intent(IN) :: itime
1898  real   , intent(IN) :: dtime
1899  integer, intent(IN) :: jour
1900  integer, intent(IN) :: nisurf
1901  integer, intent(IN) :: knon
1902  integer, intent(IN) :: klon
1903  integer, dimension(klon), intent(in) :: knindex
1904  logical, intent(IN) :: debut
1905
1906! Parametres de sortie
1907  real, intent(out), dimension(klon) :: lmt_alb
1908  real, intent(out), dimension(klon) :: lmt_rug
1909
1910! Variables locales
1911  integer     :: ii
1912  integer,save :: lmt_pas     ! frequence de lecture des conditions limites
1913                             ! (en pas de physique)
1914  logical,save :: deja_lu_sur! pour indiquer que le jour a lire a deja
1915                             ! lu pour une surface precedente
1916  integer,save :: jour_lu_sur
1917  integer      :: ierr
1918  character (len = 20) :: modname = 'interfsur_lim'
1919  character (len = 80) :: abort_message
1920  character (len = 20),save :: fich ='limit.nc'
1921  logical,save     :: newlmt = .false.
1922  logical,save     :: check = .FALSE.
1923! Champs lus dans le fichier de CL
1924  real, allocatable , save, dimension(:) :: alb_lu, rug_lu
1925!
1926! quelques variables pour netcdf
1927!
1928#include "netcdf.inc"
1929  integer ,save             :: nid, nvarid
1930  integer, dimension(2),save :: start, epais
1931!
1932! Fin déclaration
1933!
1934   
1935  if (debut) then
1936    lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour
1937    jour_lu_sur = jour - 1
1938    allocate(alb_lu(klon))
1939    allocate(rug_lu(klon))
1940  endif
1941
1942  if ((jour - jour_lu_sur) /= 0) deja_lu_sur = .false.
1943 
1944  if (check) write(*,*)modname,':: jour_lu_sur, deja_lu_sur', jour_lu_sur, deja_lu_sur
1945  if (check) write(*,*)modname,':: itime, lmt_pas', itime, lmt_pas
1946  call flush(6)
1947
1948! Tester d'abord si c'est le moment de lire le fichier
1949  if (mod(itime-1, lmt_pas) == 0 .and. .not. deja_lu_sur) then
1950!
1951! Ouverture du fichier
1952!
1953    fich = trim(fich)
1954    ierr = NF_OPEN (fich, NF_NOWRITE,nid)
1955    if (ierr.NE.NF_NOERR) then
1956      abort_message = 'Pb d''ouverture du fichier de conditions aux limites'
1957      call abort_gcm(modname,abort_message,1)
1958    endif
1959!
1960! La tranche de donnees a lire:
1961 
1962    start(1) = 1
1963    start(2) = jour + 1
1964    epais(1) = klon
1965    epais(2) = 1
1966!
1967! Lecture Albedo
1968!
1969    ierr = NF_INQ_VARID(nid, 'ALB', nvarid)
1970    if (ierr /= NF_NOERR) then
1971      abort_message = 'Le champ <ALB> est absent'
1972      call abort_gcm(modname,abort_message,1)
1973    endif
1974#ifdef NC_DOUBLE
1975    ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, alb_lu)
1976#else
1977    ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, alb_lu)
1978#endif
1979    if (ierr /= NF_NOERR) then
1980      abort_message = 'Lecture echouee pour <ALB>'
1981      call abort_gcm(modname,abort_message,1)
1982    endif
1983!
1984! Lecture rugosité
1985!
1986    ierr = NF_INQ_VARID(nid, 'RUG', nvarid)
1987    if (ierr /= NF_NOERR) then
1988      abort_message = 'Le champ <RUG> est absent'
1989      call abort_gcm(modname,abort_message,1)
1990    endif
1991#ifdef NC_DOUBLE
1992    ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, rug_lu)
1993#else
1994    ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, rug_lu)
1995#endif
1996    if (ierr /= NF_NOERR) then
1997      abort_message = 'Lecture echouee pour <RUG>'
1998      call abort_gcm(modname,abort_message,1)
1999    endif
2000
2001!
2002! Fin de lecture
2003!
2004    ierr = NF_CLOSE(nid)
2005    deja_lu_sur = .true.
2006    jour_lu_sur = jour
2007  endif
2008!
2009! Recopie des variables dans les champs de sortie
2010!
2011!!$  lmt_alb(:) = 0.0
2012!!$  lmt_rug(:) = 0.0
2013  lmt_alb(:) = 999999.
2014  lmt_rug(:) = 999999.
2015  DO ii = 1, knon
2016    lmt_alb(ii) = alb_lu(knindex(ii))
2017    lmt_rug(ii) = rug_lu(knindex(ii))
2018  enddo
2019
2020  END SUBROUTINE interfsur_lim
2021
2022!
2023!#########################################################################
2024!
2025
2026  SUBROUTINE calcul_fluxs( klon, knon, nisurf, dtime, &
2027     & tsurf, p1lay, cal, beta, coef1lay, ps, &
2028     & precip_rain, precip_snow, snow, qsol, &
2029     & radsol, dif_grnd, t1lay, q1lay, u1lay, v1lay, &
2030     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
2031     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
2032
2033! Cette routine calcule les fluxs en h et q a l'interface et eventuellement
2034! une temperature de surface (au cas ou ok_veget = false)
2035!
2036! L. Fairhead 4/2000
2037!
2038! input:
2039!   knon         nombre de points a traiter
2040!   nisurf       surface a traiter
2041!   tsurf        temperature de surface
2042!   p1lay        pression 1er niveau (milieu de couche)
2043!   cal          capacite calorifique du sol
2044!   beta         evap reelle
2045!   coef1lay     coefficient d'echange
2046!   ps           pression au sol
2047!   precip_rain  precipitations liquides
2048!   precip_snow  precipitations solides
2049!   snow         champs hauteur de neige
2050!   qsol         humidite du sol
2051!   runoff       runoff en cas de trop plein
2052!   petAcoef     coeff. A de la resolution de la CL pour t
2053!   peqAcoef     coeff. A de la resolution de la CL pour q
2054!   petBcoef     coeff. B de la resolution de la CL pour t
2055!   peqBcoef     coeff. B de la resolution de la CL pour q
2056!   radsol       rayonnement net aus sol (LW + SW)
2057!   dif_grnd     coeff. diffusion vers le sol profond
2058!
2059! output:
2060!   tsurf_new    temperature au sol
2061!   fluxsens     flux de chaleur sensible
2062!   fluxlat      flux de chaleur latente
2063!   dflux_s      derivee du flux de chaleur sensible / Ts
2064!   dflux_l      derivee du flux de chaleur latente  / Ts
2065!
2066
2067#include "YOETHF.inc"
2068#include "FCTTRE.inc"
2069#include "indicesol.inc"
2070
2071! Parametres d'entree
2072  integer, intent(IN) :: knon, nisurf, klon
2073  real   , intent(IN) :: dtime
2074  real, dimension(klon), intent(IN) :: petAcoef, peqAcoef
2075  real, dimension(klon), intent(IN) :: petBcoef, peqBcoef
2076  real, dimension(klon), intent(IN) :: ps, q1lay
2077  real, dimension(klon), intent(IN) :: tsurf, p1lay, cal, beta, coef1lay
2078  real, dimension(klon), intent(IN) :: precip_rain, precip_snow
2079  real, dimension(klon), intent(IN) :: radsol, dif_grnd
2080  real, dimension(klon), intent(IN) :: t1lay, u1lay, v1lay
2081  real, dimension(klon), intent(INOUT) :: snow, qsol
2082
2083! Parametres sorties
2084  real, dimension(klon), intent(OUT):: tsurf_new, evap, fluxsens, fluxlat
2085  real, dimension(klon), intent(OUT):: dflux_s, dflux_l
2086
2087! Variables locales
2088  integer :: i
2089  real, dimension(klon) :: zx_mh, zx_nh, zx_oh
2090  real, dimension(klon) :: zx_mq, zx_nq, zx_oq
2091  real, dimension(klon) :: zx_pkh, zx_dq_s_dt, zx_qsat, zx_coef
2092  real, dimension(klon) :: zx_sl, zx_k1
2093  real, dimension(klon) :: zx_q_0 , d_ts
2094  real                  :: zdelta, zcvm5, zx_qs, zcor, zx_dq_s_dh
2095  real                  :: bilan_f, fq_fonte
2096  REAL                  :: subli, fsno
2097  real, parameter :: t_grnd = 271.35, t_coup = 273.15
2098!! PB temporaire en attendant mieux pour le modele de neige
2099  REAL, parameter :: chasno = 3.334E+05/(2.3867E+06*0.15)
2100!
2101  logical, save         :: check = .FALSE.
2102  character (len = 20)  :: modname = 'calcul_fluxs'
2103  logical, save         :: fonte_neige = .false.
2104  real, save            :: max_eau_sol = 150.0
2105  character (len = 80) :: abort_message
2106  logical,save         :: first = .true.,second=.false.
2107
2108  if (check) write(*,*)'Entree ', modname,' surface = ',nisurf
2109
2110  if (size(coastalflow) /= knon .AND. nisurf == is_ter) then
2111    write(*,*)'Bizarre, le nombre de points continentaux'
2112    write(*,*)'a change entre deux appels. J''arrete ...'
2113    abort_message='Pb run_off'
2114    call abort_gcm(modname,abort_message,1)
2115  endif
2116!
2117! Traitement neige et humidite du sol
2118!
2119!!$  WRITE(*,*)'test calcul_flux, surface ', nisurf
2120!!PB test
2121!!$    if (nisurf == is_oce) then
2122!!$      snow = 0.
2123!!$      qsol = max_eau_sol
2124!!$    else
2125!!$      where (precip_snow > 0.) snow = snow + (precip_snow * dtime)
2126!!$      where (snow > epsilon(snow)) snow = max(0.0, snow - (evap * dtime))
2127!!$!      snow = max(0.0, snow + (precip_snow - evap) * dtime)
2128!!$      where (precip_rain > 0.) qsol = qsol + (precip_rain - evap) * dtime
2129!!$    endif
2130    IF (nisurf /= is_ter) qsol = max_eau_sol
2131
2132
2133!
2134! Initialisation
2135!
2136  evap = 0.
2137  fluxsens=0.
2138  fluxlat=0.
2139  dflux_s = 0.
2140  dflux_l = 0. 
2141!
2142! zx_qs = qsat en kg/kg
2143!
2144  DO i = 1, knon
2145    zx_pkh(i) = (ps(i)/ps(i))**RKAPPA
2146  IF (thermcep) THEN
2147      zdelta=MAX(0.,SIGN(1.,rtt-tsurf(i)))
2148      zcvm5 = R5LES*RLVTT*(1.-zdelta) + R5IES*RLSTT*zdelta
2149      zcvm5 = zcvm5 / RCPD / (1.0+RVTMP2*q1lay(i))
2150      zx_qs= r2es * FOEEW(tsurf(i),zdelta)/ps(i)
2151      zx_qs=MIN(0.5,zx_qs)
2152      zcor=1./(1.-retv*zx_qs)
2153      zx_qs=zx_qs*zcor
2154      zx_dq_s_dh = FOEDE(tsurf(i),zdelta,zcvm5,zx_qs,zcor) &
2155     &                 /RLVTT / zx_pkh(i)
2156    ELSE
2157      IF (tsurf(i).LT.t_coup) THEN
2158        zx_qs = qsats(tsurf(i)) / ps(i)
2159        zx_dq_s_dh = dqsats(tsurf(i),zx_qs)/RLVTT &
2160     &                    / zx_pkh(i)
2161      ELSE
2162        zx_qs = qsatl(tsurf(i)) / ps(i)
2163        zx_dq_s_dh = dqsatl(tsurf(i),zx_qs)/RLVTT &
2164     &               / zx_pkh(i)
2165      ENDIF
2166    ENDIF
2167    zx_dq_s_dt(i) = RCPD * zx_pkh(i) * zx_dq_s_dh
2168    zx_qsat(i) = zx_qs
2169    zx_coef(i) = coef1lay(i) &
2170     & * (1.0+SQRT(u1lay(i)**2+v1lay(i)**2)) &
2171     & * p1lay(i)/(RD*t1lay(i))
2172
2173  ENDDO
2174
2175
2176! === Calcul de la temperature de surface ===
2177!
2178! zx_sl = chaleur latente d'evaporation ou de sublimation
2179!
2180  do i = 1, knon
2181    zx_sl(i) = RLVTT
2182    if (tsurf(i) .LT. RTT) zx_sl(i) = RLSTT
2183    zx_k1(i) = zx_coef(i)
2184  enddo
2185
2186
2187  do i = 1, knon
2188! Q
2189    zx_oq(i) = 1. - (beta(i) * zx_k1(i) * peqBcoef(i) * dtime)
2190    zx_mq(i) = beta(i) * zx_k1(i) * &
2191     &             (peqAcoef(i) - zx_qsat(i) &
2192     &                          + zx_dq_s_dt(i) * tsurf(i)) &
2193     &             / zx_oq(i)
2194    zx_nq(i) = beta(i) * zx_k1(i) * (-1. * zx_dq_s_dt(i)) &
2195     &                              / zx_oq(i)
2196
2197! H
2198    zx_oh(i) = 1. - (zx_k1(i) * petBcoef(i) * dtime)
2199    zx_mh(i) = zx_k1(i) * petAcoef(i) / zx_oh(i)
2200    zx_nh(i) = - (zx_k1(i) * RCPD * zx_pkh(i))/ zx_oh(i)
2201
2202! Tsurface
2203    tsurf_new(i) = (tsurf(i) + cal(i)/(RCPD * zx_pkh(i)) * dtime * &
2204     &             (radsol(i) + zx_mh(i) + zx_sl(i) * zx_mq(i)) &
2205     &                 + dif_grnd(i) * t_grnd * dtime)/ &
2206     &          ( 1. - dtime * cal(i)/(RCPD * zx_pkh(i)) * ( &
2207     &                       zx_nh(i) + zx_sl(i) * zx_nq(i)) & 
2208     &                     + dtime * dif_grnd(i))
2209
2210!
2211! Y'a-t-il fonte de neige?
2212!
2213!    fonte_neige = (nisurf /= is_oce) .AND. &
2214!     & (snow(i) > epsfra .OR. nisurf == is_sic .OR. nisurf == is_lic) &
2215!     & .AND. (tsurf_new(i) >= RTT)
2216!    if (fonte_neige) tsurf_new(i) = RTT 
2217    d_ts(i) = tsurf_new(i) - tsurf(i)
2218!    zx_h_ts(i) = tsurf_new(i) * RCPD * zx_pkh(i)
2219!    zx_q_0(i) = zx_qsat(i) + zx_dq_s_dt(i) * d_ts(i)
2220!== flux_q est le flux de vapeur d'eau: kg/(m**2 s)  positive vers bas
2221!== flux_t est le flux de cpt (energie sensible): j/(m**2 s)
2222    evap(i) = - zx_mq(i) - zx_nq(i) * tsurf_new(i)
2223    fluxlat(i) = - evap(i) * zx_sl(i)
2224    fluxsens(i) = zx_mh(i) + zx_nh(i) * tsurf_new(i)
2225! Derives des flux dF/dTs (W m-2 K-1):
2226    dflux_s(i) = zx_nh(i)
2227    dflux_l(i) = (zx_sl(i) * zx_nq(i))
2228
2229!
2230! en cas de fonte de neige
2231!
2232!    if (fonte_neige) then
2233!      bilan_f = radsol(i) + fluxsens(i) - (zx_sl(i) * evap (i)) - &
2234!     &          dif_grnd(i) * (tsurf_new(i) - t_grnd) - &
2235!     &          RCPD * (zx_pkh(i))/cal(i)/dtime * (tsurf_new(i) - tsurf(i))
2236!      bilan_f = max(0., bilan_f)
2237!      fq_fonte = bilan_f / zx_sl(i)
2238!      snow(i) = max(0., snow(i) - fq_fonte * dtime)
2239!      qsol(i) = qsol(i) + (fq_fonte * dtime)
2240!    endif
2241!!$    if (nisurf == is_ter)  &
2242!!$     &  run_off(i) = run_off(i) + max(qsol(i) - max_eau_sol, 0.0)
2243!!$    qsol(i) = min(qsol(i), max_eau_sol)
2244  ENDDO
2245
2246  END SUBROUTINE calcul_fluxs
2247!
2248!#########################################################################
2249!
2250  SUBROUTINE gath2cpl(champ_in, champ_out, klon, knon, iim, jjm, knindex)
2251
2252! Cette routine ecrit un champ 'gathered' sur la grille 2D pour le passer
2253! au coupleur.
2254!
2255!
2256! input:         
2257!   champ_in     champ sur la grille gathere       
2258!   knon         nombre de points dans le domaine a traiter
2259!   knindex      index des points de la surface a traiter
2260!   klon         taille de la grille
2261!   iim,jjm      dimension de la grille 2D
2262!
2263! output:
2264!   champ_out    champ sur la grille 2D
2265!
2266! input
2267  integer                   :: klon, knon, iim, jjm
2268  real, dimension(klon)     :: champ_in
2269  integer, dimension(klon)  :: knindex
2270! output
2271  real, dimension(iim,jjm+1)  :: champ_out
2272! local
2273  integer                   :: i, ig, j
2274  real, dimension(klon)     :: tamp
2275
2276  tamp = 0.
2277  do i = 1, knon
2278    ig = knindex(i)
2279    tamp(ig) = champ_in(i)
2280  enddo   
2281  ig = 1
2282  champ_out(:,1) = tamp(ig)
2283  do j = 2, jjm
2284    do i = 1, iim
2285      ig = ig + 1
2286      champ_out(i,j) = tamp(ig)
2287    enddo
2288  enddo
2289  ig = ig + 1
2290  champ_out(:,jjm+1) = tamp(ig)
2291
2292  END SUBROUTINE gath2cpl
2293!
2294!#########################################################################
2295!
2296  SUBROUTINE cpl2gath(champ_in, champ_out, klon, knon, iim, jjm, knindex)
2297
2298! Cette routine ecrit un champ 'gathered' sur la grille 2D pour le passer
2299! au coupleur.
2300!
2301!
2302! input:         
2303!   champ_in     champ sur la grille gathere       
2304!   knon         nombre de points dans le domaine a traiter
2305!   knindex      index des points de la surface a traiter
2306!   klon         taille de la grille
2307!   iim,jjm      dimension de la grille 2D
2308!
2309! output:
2310!   champ_out    champ sur la grille 2D
2311!
2312! input
2313  integer                   :: klon, knon, iim, jjm
2314  real, dimension(iim,jjm+1)     :: champ_in
2315  integer, dimension(klon)  :: knindex
2316! output
2317  real, dimension(klon)  :: champ_out
2318! local
2319  integer                   :: i, ig, j
2320  real, dimension(klon)     :: tamp
2321  logical ,save                  :: check = .false.
2322
2323  ig = 1
2324  tamp(ig) = champ_in(1,1)
2325  do j = 2, jjm
2326    do i = 1, iim
2327      ig = ig + 1
2328      tamp(ig) = champ_in(i,j)
2329    enddo
2330  enddo
2331  ig = ig + 1
2332  tamp(ig) = champ_in(1,jjm+1)
2333
2334  do i = 1, knon
2335    ig = knindex(i)
2336    champ_out(i) = tamp(ig)
2337  enddo   
2338
2339  END SUBROUTINE cpl2gath
2340!
2341!#########################################################################
2342!
2343  SUBROUTINE albsno(klon, knon,dtime,agesno,alb_neig_grid, precip_snow)
2344  IMPLICIT none
2345 
2346  INTEGER :: klon, knon
2347  INTEGER, PARAMETER :: nvm = 8
2348  REAL   :: dtime
2349  REAL, dimension(klon,nvm) :: veget
2350  REAL, DIMENSION(klon) :: alb_neig_grid, agesno, precip_snow
2351 
2352  INTEGER :: i, nv
2353 
2354  REAL, DIMENSION(nvm),SAVE :: init, decay
2355  REAL :: as
2356  DATA init /0.55, 0.14, 0.18, 0.29, 0.15, 0.15, 0.14, 0./
2357  DATA decay/0.30, 0.67, 0.63, 0.45, 0.40, 0.14, 0.06, 1./
2358 
2359  veget = 0.
2360  veget(:,1) = 1.     ! desert partout
2361  DO i = 1, knon
2362    alb_neig_grid(i) = 0.0
2363  ENDDO
2364  DO nv = 1, nvm
2365    DO i = 1, knon
2366      as = init(nv)+decay(nv)*EXP(-agesno(i)/5.)
2367      alb_neig_grid(i) = alb_neig_grid(i) + veget(i,nv)*as
2368    ENDDO
2369  ENDDO
2370!
2371!! modilation en fonction de l'age de la neige
2372!
2373  DO i = 1, knon
2374    agesno(i)  = (agesno(i) + (1.-agesno(i)/50.)*dtime/86400.)&
2375            &             * EXP(-1.*MAX(0.0,precip_snow(i))*dtime/0.3)
2376    agesno(i) =  MAX(agesno(i),0.0)
2377  ENDDO
2378 
2379  END SUBROUTINE albsno
2380!
2381!#########################################################################
2382!
2383
2384  SUBROUTINE fonte_neige( klon, knon, nisurf, dtime, &
2385     & tsurf, p1lay, cal, beta, coef1lay, ps, &
2386     & precip_rain, precip_snow, snow, qsol, &
2387     & radsol, dif_grnd, t1lay, q1lay, u1lay, v1lay, &
2388     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
2389     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
2390
2391! Routine de traitement de la fonte de la neige dans le cas du traitement
2392! de sol simplifié
2393!
2394! LF 03/2001
2395! input:
2396!   knon         nombre de points a traiter
2397!   nisurf       surface a traiter
2398!   tsurf        temperature de surface
2399!   p1lay        pression 1er niveau (milieu de couche)
2400!   cal          capacite calorifique du sol
2401!   beta         evap reelle
2402!   coef1lay     coefficient d'echange
2403!   ps           pression au sol
2404!   precip_rain  precipitations liquides
2405!   precip_snow  precipitations solides
2406!   snow         champs hauteur de neige
2407!   qsol         humidite du sol
2408!   runoff       runoff en cas de trop plein
2409!   petAcoef     coeff. A de la resolution de la CL pour t
2410!   peqAcoef     coeff. A de la resolution de la CL pour q
2411!   petBcoef     coeff. B de la resolution de la CL pour t
2412!   peqBcoef     coeff. B de la resolution de la CL pour q
2413!   radsol       rayonnement net aus sol (LW + SW)
2414!   dif_grnd     coeff. diffusion vers le sol profond
2415!
2416! output:
2417!   tsurf_new    temperature au sol
2418!   fluxsens     flux de chaleur sensible
2419!   fluxlat      flux de chaleur latente
2420!   dflux_s      derivee du flux de chaleur sensible / Ts
2421!   dflux_l      derivee du flux de chaleur latente  / Ts
2422!
2423
2424#include "YOETHF.inc"
2425#include "FCTTRE.inc"
2426#include "indicesol.inc"
2427
2428! Parametres d'entree
2429  integer, intent(IN) :: knon, nisurf, klon
2430  real   , intent(IN) :: dtime
2431  real, dimension(klon), intent(IN) :: petAcoef, peqAcoef
2432  real, dimension(klon), intent(IN) :: petBcoef, peqBcoef
2433  real, dimension(klon), intent(IN) :: ps, q1lay
2434  real, dimension(klon), intent(IN) :: tsurf, p1lay, cal, beta, coef1lay
2435  real, dimension(klon), intent(IN) :: precip_rain, precip_snow
2436  real, dimension(klon), intent(IN) :: radsol, dif_grnd
2437  real, dimension(klon), intent(IN) :: t1lay, u1lay, v1lay
2438  real, dimension(klon), intent(INOUT) :: snow, qsol
2439
2440! Parametres sorties
2441  real, dimension(klon), intent(INOUT):: tsurf_new, evap, fluxsens, fluxlat
2442  real, dimension(klon), intent(INOUT):: dflux_s, dflux_l
2443
2444! Variables locales
2445  integer :: i
2446  real, dimension(klon) :: zx_mh, zx_nh, zx_oh
2447  real, dimension(klon) :: zx_mq, zx_nq, zx_oq
2448  real, dimension(klon) :: zx_pkh, zx_dq_s_dt, zx_qsat, zx_coef
2449  real, dimension(klon) :: zx_sl, zx_k1
2450  real, dimension(klon) :: zx_q_0 , d_ts
2451  real                  :: zdelta, zcvm5, zx_qs, zcor, zx_dq_s_dh
2452  real                  :: bilan_f, fq_fonte
2453  REAL                  :: subli, fsno
2454  real, parameter :: t_grnd = 271.35, t_coup = 273.15
2455!! PB temporaire en attendant mieux pour le modele de neige
2456  REAL, parameter :: chasno = 3.334E+05/(2.3867E+06*0.15)
2457!
2458  logical, save         :: check = .FALSE.
2459  character (len = 20)  :: modname = 'fonte_neige'
2460  logical, save         :: neige_fond = .false.
2461  real, save            :: max_eau_sol = 150.0
2462  character (len = 80) :: abort_message
2463  logical,save         :: first = .true.,second=.false.
2464
2465  if (check) write(*,*)'Entree ', modname,' surface = ',nisurf
2466
2467! Initialisations
2468  DO i = 1, knon
2469    zx_pkh(i) = (ps(i)/ps(i))**RKAPPA
2470  IF (thermcep) THEN
2471      zdelta=MAX(0.,SIGN(1.,rtt-tsurf(i)))
2472      zcvm5 = R5LES*RLVTT*(1.-zdelta) + R5IES*RLSTT*zdelta
2473      zcvm5 = zcvm5 / RCPD / (1.0+RVTMP2*q1lay(i))
2474      zx_qs= r2es * FOEEW(tsurf(i),zdelta)/ps(i)
2475      zx_qs=MIN(0.5,zx_qs)
2476      zcor=1./(1.-retv*zx_qs)
2477      zx_qs=zx_qs*zcor
2478      zx_dq_s_dh = FOEDE(tsurf(i),zdelta,zcvm5,zx_qs,zcor) &
2479     &                 /RLVTT / zx_pkh(i)
2480    ELSE
2481      IF (tsurf(i).LT.t_coup) THEN
2482        zx_qs = qsats(tsurf(i)) / ps(i)
2483        zx_dq_s_dh = dqsats(tsurf(i),zx_qs)/RLVTT &
2484     &                    / zx_pkh(i)
2485      ELSE
2486        zx_qs = qsatl(tsurf(i)) / ps(i)
2487        zx_dq_s_dh = dqsatl(tsurf(i),zx_qs)/RLVTT &
2488     &               / zx_pkh(i)
2489      ENDIF
2490    ENDIF
2491    zx_dq_s_dt(i) = RCPD * zx_pkh(i) * zx_dq_s_dh
2492    zx_qsat(i) = zx_qs
2493    zx_coef(i) = coef1lay(i) &
2494     & * (1.0+SQRT(u1lay(i)**2+v1lay(i)**2)) &
2495     & * p1lay(i)/(RD*t1lay(i))
2496  ENDDO
2497
2498
2499! === Calcul de la temperature de surface ===
2500!
2501! zx_sl = chaleur latente d'evaporation ou de sublimation
2502!
2503  do i = 1, knon
2504    zx_sl(i) = RLVTT
2505    if (tsurf(i) .LT. RTT) zx_sl(i) = RLSTT
2506    zx_k1(i) = zx_coef(i)
2507  enddo
2508
2509
2510  do i = 1, knon
2511! Q
2512    zx_oq(i) = 1. - (beta(i) * zx_k1(i) * peqBcoef(i) * dtime)
2513    zx_mq(i) = beta(i) * zx_k1(i) * &
2514     &             (peqAcoef(i) - zx_qsat(i) &
2515     &                          + zx_dq_s_dt(i) * tsurf(i)) &
2516     &             / zx_oq(i)
2517    zx_nq(i) = beta(i) * zx_k1(i) * (-1. * zx_dq_s_dt(i)) &
2518     &                              / zx_oq(i)
2519
2520! H
2521    zx_oh(i) = 1. - (zx_k1(i) * petBcoef(i) * dtime)
2522    zx_mh(i) = zx_k1(i) * petAcoef(i) / zx_oh(i)
2523    zx_nh(i) = - (zx_k1(i) * RCPD * zx_pkh(i))/ zx_oh(i)
2524  enddo
2525
2526
2527  WHERE (precip_snow > 0.) snow = snow + (precip_snow * dtime)
2528  WHERE (evap > 0 ) snow = MAX(0.0, snow - (evap * dtime))
2529  qsol = qsol + (precip_rain - evap) * dtime
2530!
2531! Y'a-t-il fonte de neige?
2532!
2533  do i = 1, knon
2534    neige_fond = ((snow(i) > epsfra .OR. nisurf == is_sic .OR. nisurf == is_lic) &
2535     & .AND. tsurf_new(i) >= RTT)
2536    if (neige_fond) then
2537      fq_fonte = MIN( MAX((tsurf_new(i)-RTT )/chasno,0.0),snow(i))
2538      snow(i) = max(0., snow(i) - fq_fonte)
2539      qsol(i) = qsol(i) + fq_fonte
2540      tsurf_new(i) = tsurf_new(i) - fq_fonte * chasno 
2541      IF (nisurf == is_sic .OR. nisurf == is_lic ) tsurf_new(i) = RTT -1.8
2542      d_ts(i) = tsurf_new(i) - tsurf(i)
2543!      zx_h_ts(i) = tsurf_new(i) * RCPD * zx_pkh(i)
2544!      zx_q_0(i) = zx_qsat(i) + zx_dq_s_dt(i) * d_ts(i)
2545!== flux_q est le flux de vapeur d'eau: kg/(m**2 s)  positive vers bas
2546!== flux_t est le flux de cpt (energie sensible): j/(m**2 s)
2547!!$      evap(i) = - zx_mq(i) - zx_nq(i) * tsurf_new(i)
2548!!$      fluxlat(i) = - evap(i) * zx_sl(i)
2549!!$      fluxsens(i) = zx_mh(i) + zx_nh(i) * tsurf_new(i)
2550! Derives des flux dF/dTs (W m-2 K-1):
2551!!$      dflux_s(i) = zx_nh(i)
2552!!$      dflux_l(i) = (zx_sl(i) * zx_nq(i))
2553!!$      bilan_f = radsol(i) + fluxsens(i) - (zx_sl(i) * evap (i)) - &
2554!!$     &          dif_grnd(i) * (tsurf_new(i) - t_grnd) - &
2555!!$     &          RCPD * (zx_pkh(i))/cal(i)/dtime * (tsurf_new(i) - tsurf(i))
2556!!$      bilan_f = max(0., bilan_f)
2557!!$      fq_fonte = bilan_f / zx_sl(i)
2558    endif
2559    IF (nisurf == is_ter)  &
2560       &  run_off(i) = run_off(i) + MAX(qsol(i) - max_eau_sol, 0.0)
2561    qsol(i) = MIN(qsol(i), max_eau_sol)
2562  enddo
2563
2564  END SUBROUTINE fonte_neige
2565!
2566!#########################################################################
2567!
2568  END MODULE interface_surf
Note: See TracBrowser for help on using the repository browser.