source: LMDZ4/tags/Merge_v3_Yann/libf/phylmd/interface_surf.F90 @ 1405

Last change on this file since 1405 was 776, checked in by Laurent Fairhead, 17 years ago

Suite du merge entre la version et la HEAD: quelques modifications
de Yann sur le

LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 121.6 KB
Line 
1!
2! $Header$
3!
4
5  MODULE interface_surf
6
7! Ce module regroupe toutes les routines gerant l'interface entre le modele
8! atmospherique et les modeles de surface (sols continentaux, oceans, glaces)
9! Les routines sont les suivantes:
10!
11!   interfsurf_*: routines d'aiguillage vers les interfaces avec les
12!                 differents modeles de surface
13!   interfsol\
14!             > routines d'interface proprement dite
15!   interfoce/
16!
17!   interfstart: routine d'initialisation et de lecture de l'etat initial
18!                "interface"
19!   interffin  : routine d'ecriture de l'etat de redemmarage de l'interface
20!
21!
22! L. Fairhead, LMD, 02/2000
23
24!ym  USE ioipsl
25
26  IMPLICIT none
27
28  PRIVATE
29  PUBLIC :: interfsurf,interfsurf_hq, gath2cpl
30
31  INTERFACE interfsurf
32    module procedure interfsurf_hq, interfsurf_vent
33  END INTERFACE
34
35  INTERFACE interfoce
36    module procedure interfoce_cpl, interfoce_slab, interfoce_lim
37  END INTERFACE
38
39#include "YOMCST.inc"
40#include "indicesol.inc"
41!IM
42#include "clesphys.inc"
43
44! run_off      ruissellement total
45  REAL, ALLOCATABLE, DIMENSION(:),SAVE    :: run_off, run_off_lic
46!$OMP THREADPRIVATE(run_off, run_off_lic)
47  real, allocatable, dimension(:),save    :: coastalflow, riverflow
48!$OMP THREADPRIVATE(coastalflow, riverflow)
49!!$PB
50  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: tmp_rriv, tmp_rcoa,tmp_rlic
51!$OMP THREADPRIVATE(tmp_rriv, tmp_rcoa,tmp_rlic)
52!! pour simuler la fonte des glaciers antarctiques
53  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: coeff_iceberg
54!$OMP THREADPRIVATE(coeff_iceberg)
55  real, save                              :: surf_maille
56!$OMP THREADPRIVATE(surf_maille)
57  real, save                              :: cte_flux_iceberg = 6.3e7
58!$OMP THREADPRIVATE(cte_flux_iceberg) 
59  integer, save                           :: num_antarctic = 1
60!$OMP THREADPRIVATE(num_antarctic)
61  REAL, save                              :: tau_calv
62!$OMP THREADPRIVATE(tau_calv)
63!!$
64  CONTAINS
65!
66!############################################################################
67!
68  SUBROUTINE interfsurf_hq(itime, dtime, date0, jour, rmu0, &
69      & klon, iim, jjm, nisurf, knon, knindex, pctsrf, &
70      & rlon, rlat, cufi, cvfi,&
71      & debut, lafin, ok_veget, soil_model, nsoilmx, tsoil, qsol,&
72      & zlev,  u1_lay, v1_lay, temp_air, spechum, epot_air, ccanopy, &
73      & tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
74      & precip_rain, precip_snow, sollw, sollwdown, swnet, swdown, &
75      & fder, taux, tauy, &
76! -- LOOP
77      & windsp, &
78! -- LOOP
79      & rugos, rugoro, &
80      & albedo, snow, qsurf, &
81      & tsurf, p1lay, ps, radsol, &
82      & ocean, npas, nexca, zmasq, &
83      & evap, fluxsens, fluxlat, dflux_l, dflux_s, &             
84      & tsol_rad, tsurf_new, alb_new, alblw, emis_new, &
85      & z0_new, pctsrf_new, agesno,fqcalving,fqfonte,ffonte, run_off_lic_0,&
86!IM "slab" ocean
87      & flux_o, flux_g, tslab, seaice)
88
89
90   USE mod_phys_lmdz_para
91! Cette routine sert d'aiguillage entre l'atmosphere et la surface en general
92! (sols continentaux, oceans, glaces) pour les fluxs de chaleur et d'humidite.
93! En pratique l'interface se fait entre la couche limite du modele
94! atmospherique (clmain.F) et les routines de surface (sechiba, oasis, ...)
95!
96!
97! L.Fairhead 02/2000
98!
99! input:
100!   itime        numero du pas de temps
101!   klon         nombre total de points de grille
102!   iim, jjm     nbres de pts de grille
103!   dtime        pas de temps de la physique (en s)
104!   date0        jour initial
105!   jour         jour dans l'annee en cours,
106!   rmu0         cosinus de l'angle solaire zenithal
107!   nexca        pas de temps couplage
108!   nisurf       index de la surface a traiter (1 = sol continental)
109!   knon         nombre de points de la surface a traiter
110!   knindex      index des points de la surface a traiter
111!   pctsrf       tableau des pourcentages de surface de chaque maille
112!   rlon         longitudes
113!   rlat         latitudes
114!   cufi,cvfi    resolution des mailles en x et y (m)
115!   debut        logical: 1er appel a la physique
116!   lafin        logical: dernier appel a la physique
117!   ok_veget     logical: appel ou non au schema de surface continental
118!                     (si false calcul simplifie des fluxs sur les continents)
119!   zlev         hauteur de la premiere couche
120!   u1_lay       vitesse u 1ere couche
121!   v1_lay       vitesse v 1ere couche
122!   temp_air     temperature de l'air 1ere couche
123!   spechum      humidite specifique 1ere couche
124!   epot_air     temp potentielle de l'air
125!   ccanopy      concentration CO2 canopee
126!   tq_cdrag     cdrag
127!   petAcoef     coeff. A de la resolution de la CL pour t
128!   peqAcoef     coeff. A de la resolution de la CL pour q
129!   petBcoef     coeff. B de la resolution de la CL pour t
130!   peqBcoef     coeff. B de la resolution de la CL pour q
131!   precip_rain  precipitation liquide
132!   precip_snow  precipitation solide
133!   sollw        flux IR net a la surface
134!   sollwdown    flux IR descendant a la surface
135!   swnet        flux solaire net
136!   swdown       flux solaire entrant a la surface
137!   albedo       albedo de la surface
138!   tsurf        temperature de surface
139!   tslab        temperature slab ocean
140!   pctsrf_slab  pourcentages (0-1) des sous-surfaces dans le slab
141!   tmp_pctsrf_slab = pctsrf_slab
142!   p1lay        pression 1er niveau (milieu de couche)
143!   ps           pression au sol
144!   radsol       rayonnement net aus sol (LW + SW)
145!   ocean        type d'ocean utilise (force, slab, couple)
146!   fder         derivee des flux (pour le couplage)
147!   taux, tauy   tension de vents
148! -- LOOP
149!   windsp       module du vent a 10m
150! -- LOOP
151!   rugos        rugosite
152!   zmasq        masque terre/ocean
153!   rugoro       rugosite orographique
154!   run_off_lic_0 runoff glacier du pas de temps precedent
155!
156! output:
157!   evap         evaporation totale
158!   fluxsens     flux de chaleur sensible
159!   fluxlat      flux de chaleur latente
160!   tsol_rad     
161!   tsurf_new    temperature au sol
162!   alb_new      albedo
163!   emis_new     emissivite
164!   z0_new       surface roughness
165!   pctsrf_new   nouvelle repartition des surfaces
166
167#include "iniprint.h"
168
169
170! Parametres d'entree
171  integer, intent(IN) :: itime
172  integer, intent(IN) :: iim, jjm
173  integer, intent(IN) :: klon
174  real, intent(IN) :: dtime
175  real, intent(IN) :: date0
176  integer, intent(IN) :: jour
177  real, intent(IN)    :: rmu0(klon)
178  integer, intent(IN) :: nisurf
179  integer, intent(IN) :: knon
180  integer, dimension(klon), intent(in) :: knindex
181  real, dimension(klon,nbsrf), intent(IN) :: pctsrf
182  logical, intent(IN) :: debut, lafin, ok_veget
183  real, dimension(klon), intent(IN) :: rlon, rlat
184  real, dimension(klon), intent(IN) :: cufi, cvfi
185  real, dimension(klon), intent(INOUT) :: tq_cdrag
186  real, dimension(klon), intent(IN) :: zlev
187  real, dimension(klon), intent(IN) :: u1_lay, v1_lay
188  real, dimension(klon), intent(IN) :: temp_air, spechum
189  real, dimension(klon), intent(IN) :: epot_air, ccanopy
190  real, dimension(klon), intent(IN) :: petAcoef, peqAcoef
191  real, dimension(klon), intent(IN) :: petBcoef, peqBcoef
192  real, dimension(klon), intent(IN) :: precip_rain, precip_snow
193  real, dimension(klon), intent(IN) :: sollw, sollwdown, swnet, swdown
194  real, dimension(klon), intent(IN) :: ps, albedo
195  real, dimension(klon), intent(IN) :: tsurf, p1lay
196!IM: "slab" ocean
197  real :: amn, amx
198  real, dimension(klon), intent(INOUT) :: tslab
199  real, allocatable, dimension(:), save :: tmp_tslab
200!$OMP THREADPRIVATE(tmp_tslab)
201  real, dimension(klon), intent(OUT) :: flux_o, flux_g
202  real, dimension(klon), intent(INOUT)        :: seaice ! glace de mer (kg/m2)
203  real, dimension(klon)                       :: siceh  ! hauteur glace de mer (m)
204  REAL, DIMENSION(klon), INTENT(INOUT) :: radsol,fder
205 
206!  real, dimension(klon), intent(IN) :: zmasq
207  real, dimension(klon), intent(IN) :: zmasq
208  real, dimension(klon), intent(IN) :: taux, tauy, rugos, rugoro
209! -- LOOP
210  real, dimension(klon), intent(IN) :: windsp
211! -- LOOP
212  character (len = 6)  :: ocean
213  integer              :: npas, nexca ! nombre et pas de temps couplage
214  real, dimension(klon), intent(INOUT) :: evap, snow, qsurf
215!! PB ajout pour soil
216  logical          :: soil_model
217  integer          :: nsoilmx
218  REAL, DIMENSION(klon, nsoilmx) :: tsoil
219  REAL, dimension(klon), intent(INOUT) :: qsol
220  REAL, dimension(klon)          :: soilcap
221  REAL, dimension(klon)          :: soilflux
222! Parametres de sortie
223  real, dimension(klon), intent(OUT):: fluxsens, fluxlat
224  real, dimension(klon), intent(OUT):: tsol_rad, tsurf_new, alb_new
225  real, dimension(klon), intent(OUT):: alblw
226  real, dimension(klon), intent(OUT):: emis_new, z0_new
227  real, dimension(klon), intent(OUT):: dflux_l, dflux_s
228  real, dimension(klon,nbsrf), intent(OUT) :: pctsrf_new
229  real, dimension(klon), intent(INOUT):: agesno
230  real, dimension(klon), intent(INOUT):: run_off_lic_0
231
232! Flux thermique utiliser pour fondre la neige
233!jld a rajouter   real, dimension(klon), intent(INOUT):: ffonte
234  real, dimension(klon), intent(INOUT):: ffonte
235! Flux d'eau "perdue" par la surface et necessaire pour que limiter la
236! hauteur de neige, en kg/m2/s. Et quantite d'eau de fonte de la calotte.
237!jld a rajouter   real, dimension(klon), intent(INOUT):: fqcalving, fqfonte
238  REAL, DIMENSION(klon), INTENT(INOUT):: fqcalving, fqfonte
239!IM: "slab" ocean
240  real, dimension(klon) :: new_dif_grnd
241!IM: "slab" ocean - Local
242  real, parameter :: t_grnd=271.35
243  real, dimension(klon) :: zx_sl
244  integer i
245  real, allocatable, dimension(:), save :: tmp_flux_o, tmp_flux_g
246!$OMP THREADPRIVATE(tmp_flux_o, tmp_flux_g) 
247  real, allocatable, dimension(:), save :: tmp_radsol
248!$OMP THREADPRIVATE(tmp_radsol)
249  real, allocatable, dimension(:,:), save :: tmp_pctsrf_slab
250!$OMP THREADPRIVATE(tmp_pctsrf_slab)
251  real, allocatable, dimension(:), save :: tmp_seaice
252!$OMP THREADPRIVATE(tmp_seaice)
253! Local
254  character (len = 20),save :: modname = 'interfsurf_hq'
255!$OMP THREADPRIVATE(modname)
256  character (len = 80) :: abort_message
257  logical, save        :: first_call = .true.
258!$OMP THREADPRIVATE(first_call) 
259  integer, save        :: error
260!$OMP THREADPRIVATE(error) 
261  integer              :: ii, index
262  logical,save              :: check = .true.
263!$OMP THREADPRIVATE(check) 
264  real, dimension(klon):: cal, beta, dif_grnd, capsol
265!!$PB  real, parameter      :: calice=1.0/(5.1444e+06*0.15), tau_gl=86400.*5.
266  real, parameter      :: calice=1.0/(5.1444e+06*0.15), tau_gl=86400.*5.
267  real, parameter      :: calsno=1./(2.3867e+06*.15)
268  real, dimension(klon):: alb_ice
269  real, dimension(klon):: tsurf_temp
270  real, dimension(klon):: qsurf_new
271!!  real, allocatable, dimension(:), save :: alb_neig_grid
272  real, dimension(klon):: alb_neig, alb_eau
273  real, DIMENSION(klon):: zfra
274  logical              :: cumul = .false.
275  INTEGER,dimension(1) :: iloc
276  INTEGER                 :: isize
277  real, dimension(klon):: fder_prev
278  REAL, dimension(klon) :: bidule
279  real, dimension(klon) :: ps_tmp,p1lay_tmp
280  INTEGER :: j
281!
282!IM ?? quelques variables pour netcdf
283#include "netcdf.inc"
284
285  if (check) write(*,*) 'Entree ', modname
286!
287! On doit commencer par appeler les schemas de surfaces continentales
288! car l'ocean a besoin du ruissellement qui est y calcule
289!
290  if (first_call) then
291    call conf_interface(tau_calv)
292    if (nisurf /= is_ter .and. klon > 1) then
293      write(*,*)' *** Warning ***'
294      write(*,*)' nisurf = ',nisurf,' /= is_ter = ',is_ter
295      write(*,*)'or on doit commencer par les surfaces continentales'
296      abort_message='voir ci-dessus'
297      call abort_gcm(modname,abort_message,1)
298    endif
299    if (ocean /= 'slab  ' .and. ocean /= 'force ' .and. ocean /= 'couple') then
300      write(*,*)' *** Warning ***'
301      write(*,*)'Option couplage pour l''ocean = ', ocean
302      abort_message='option pour l''ocean non valable'
303      call abort_gcm(modname,abort_message,1)
304    endif
305    if ( is_oce > is_sic ) then
306      write(*,*)' *** Warning ***'
307      write(*,*)' Pour des raisons de sequencement dans le code'
308      write(*,*)' l''ocean doit etre traite avant la banquise'
309      write(*,*)' or is_oce = ',is_oce, '> is_sic = ',is_sic
310      abort_message='voir ci-dessus'
311      call abort_gcm(modname,abort_message,1)
312    endif
313!    allocate(alb_neig_grid(klon), stat = error)
314!    if (error /= 0) then
315!      abort_message='Pb allocation alb_neig_grid'
316!      call abort_gcm(modname,abort_message,1)
317!    endif
318  endif
319  first_call = .false.
320 
321! Initialisations diverses
322!
323!!$  cal=0.; beta=1.; dif_grnd=0.; capsol=0.
324!!$  alb_new = 0.; z0_new = 0.; alb_neig = 0.0
325!!$! PB
326!!$  tsurf_new = 0.
327
328!IM cf JLD
329  ffonte(1:knon)=0.
330  fqcalving(1:knon)=0.
331  fqfonte  (1:knon)=0.
332
333
334  cal = 999999. ; beta = 999999. ; dif_grnd = 999999. ; capsol = 999999.
335  alb_new = 999999. ; z0_new = 999999. ; alb_neig = 999999.
336  tsurf_new = 999999.
337  alblw = 999999.
338
339!IM: "slab" ocean; initialisations
340  flux_o = 0.
341  flux_g = 0.
342!
343    if (.not. allocated(tmp_flux_o)) then
344      allocate(tmp_flux_o(klon), stat = error)
345      DO i=1, knon
346       tmp_flux_o(knindex(i))=flux_o(i)
347      ENDDO
348      if (error /= 0) then
349        abort_message='Pb allocation tmp_flux_o'
350        call abort_gcm(modname,abort_message,1)
351      endif
352    endif
353    if (.not. allocated(tmp_flux_g)) then 
354      allocate(tmp_flux_g(klon), stat = error)
355      DO i=1, knon
356       tmp_flux_g(knindex(i))=flux_g(i)
357      ENDDO
358      if (error /= 0) then
359        abort_message='Pb allocation tmp_flux_g'
360        call abort_gcm(modname,abort_message,1)
361      endif
362    endif
363    if (.not. allocated(tmp_radsol)) then 
364      allocate(tmp_radsol(klon), stat = error)
365      if (error /= 0) then
366        abort_message='Pb allocation tmp_radsol'
367        call abort_gcm(modname,abort_message,1)
368      endif
369    endif
370    if (.not. allocated(tmp_pctsrf_slab)) then
371      allocate(tmp_pctsrf_slab(klon,nbsrf), stat = error)
372      if (error /= 0) then
373        abort_message='Pb allocation tmp_pctsrf_slab'
374        call abort_gcm(modname,abort_message,1)
375      endif
376    DO i=1, klon
377     tmp_pctsrf_slab(i,1:nbsrf)=pctsrf(i,1:nbsrf)
378    ENDDO
379    endif
380!
381    if (.not. allocated(tmp_seaice)) then
382      allocate(tmp_seaice(klon), stat = error)
383      if (error /= 0) then
384        abort_message='Pb allocation tmp_seaice'
385        call abort_gcm(modname,abort_message,1)
386      endif
387    IF(check) THEN
388     PRINT*,'allocation tmp_seaice nisurf itime',nisurf, itime
389    ENDIF
390    endif
391!
392    if (.not. allocated(tmp_tslab)) then
393      allocate(tmp_tslab(klon), stat = error)
394      if (error /= 0) then
395        abort_message='Pb allocation tmp_tslab'
396        call abort_gcm(modname,abort_message,1)
397      endif
398    endif
399    DO i=1, klon
400     tmp_tslab(i)=tslab(i)
401    ENDDO
402!
403! Aiguillage vers les differents schemas de surface
404
405  if (nisurf == is_ter) then
406!
407! Surface "terre" appel a l'interface avec les sols continentaux
408!
409! allocation du run-off
410    if (.not. allocated(coastalflow)) then
411      allocate(coastalflow(knon), stat = error)
412      if (error /= 0) then
413        abort_message='Pb allocation coastalflow'
414        call abort_gcm(modname,abort_message,1)
415      endif
416      allocate(riverflow(knon), stat = error)
417      if (error /= 0) then
418        abort_message='Pb allocation riverflow'
419        call abort_gcm(modname,abort_message,1)
420      endif
421      allocate(run_off(knon), stat = error)
422      if (error /= 0) then
423        abort_message='Pb allocation run_off'
424        call abort_gcm(modname,abort_message,1)
425      endif
426!cym     
427      run_off=0.0
428!cym
429
430!!$PB
431      ALLOCATE (tmp_rriv(iim,jj_nb), stat=error)
432      if (error /= 0) then
433        abort_message='Pb allocation tmp_rriv'
434        call abort_gcm(modname,abort_message,1)
435      endif
436      tmp_rriv=0.
437      ALLOCATE (tmp_rcoa(iim,jj_nb), stat=error)
438      if (error /= 0) then
439        abort_message='Pb allocation tmp_rcoa'
440        call abort_gcm(modname,abort_message,1)
441      endif
442      tmp_rcoa=0.
443!ym      ALLOCATE (tmp_rlic(iim,jjm+1), stat=error)
444      ALLOCATE (tmp_rlic(iim,jj_nb), stat=error)
445      if (error /= 0) then
446        abort_message='Pb allocation tmp_rlic'
447        call abort_gcm(modname,abort_message,1)
448      endif
449      tmp_rlic=0.
450!!$
451    else if (size(coastalflow) /= knon) then
452      write(*,*)'Bizarre, le nombre de points continentaux'
453      write(*,*)'a change entre deux appels. J''arrete ...'
454      abort_message='voir ci-dessus'
455      call abort_gcm(modname,abort_message,1)
456    endif
457    coastalflow = 0.
458    riverflow = 0.
459!
460! Calcul age de la neige
461!
462!!$ PB ATTENTION changement ordre des appels
463!!$    CALL albsno(klon,agesno,alb_neig_grid) 
464
465    if (.not. ok_veget) then
466!
467! calcul albedo: lecture albedo fichier CL puis ajout albedo neige
468!
469       call interfsur_lim(itime, dtime, jour, &
470     & klon, nisurf, knon, knindex, debut,  &
471     & alb_new, z0_new)
472
473! calcul snow et qsurf, hydrol adapte !
474       CALL calbeta(dtime, nisurf, knon, snow, qsol, beta, capsol, dif_grnd)
475
476       IF (soil_model) THEN
477           CALL soil(dtime, nisurf, knon,snow, tsurf, tsoil,soilcap, soilflux)
478           cal(1:knon) = RCPD / soilcap(1:knon)
479           radsol(1:knon) = radsol(1:knon)  + soilflux(1:knon)
480       ELSE
481           cal = RCPD * capsol
482!!$      cal = capsol
483       ENDIF
484       CALL calcul_fluxs( klon, knon, nisurf, dtime, &
485     &   tsurf, p1lay, cal, beta, tq_cdrag, ps, &
486     &   precip_rain, precip_snow, snow, qsurf,  &
487     &   radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
488     &   petAcoef, peqAcoef, petBcoef, peqBcoef, &
489     &   tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
490
491       CALL fonte_neige( klon, knon, nisurf, dtime, &
492     &   tsurf, p1lay, cal, beta, tq_cdrag, ps, &
493     &   precip_rain, precip_snow, snow, qsol,  &
494     &   radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
495     &   petAcoef, peqAcoef, petBcoef, peqBcoef, &
496     &   tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
497     &   fqcalving,fqfonte,ffonte, run_off_lic_0)
498
499
500     call albsno(klon,knon,dtime,agesno(:),alb_neig(:), precip_snow(:)) 
501     where (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
502     zfra(1:knon) = max(0.0,min(1.0,snow(1:knon)/(snow(1:knon)+10.0)))
503     alb_new(1 : knon)  = alb_neig(1 : knon) *zfra(1:knon) + &
504    &                     alb_new(1 : knon)*(1.0-zfra(1:knon))
505     z0_new = sqrt(z0_new**2+rugoro**2)
506     alblw(1 : knon) = alb_new(1 : knon)
507
508    else
509!!      CALL albsno(klon,agesno,alb_neig_grid) 
510!
511!  appel a sechiba
512!
513#ifdef CPP_VEGET
514      p1lay_tmp(1:knon)=p1lay(1:knon)/100.
515      ps_tmp(1:knon)=ps(1:knon)/100.
516 
517       call interfsol(itime, klon, dtime, date0, nisurf, knon, &
518     &  knindex, rlon, rlat, cufi, cvfi, iim, jjm, pctsrf, &
519     &  debut, lafin, ok_veget, &
520     &  zlev,  u1_lay, v1_lay, temp_air, spechum, epot_air, ccanopy, &
521     &  tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
522     &  precip_rain, precip_snow, sollwdown, swnet, swdown, &
523     &  tsurf, p1lay_tmp, ps_tmp, radsol, &
524     &  evap, fluxsens, fluxlat, &             
525     &  tsol_rad, tsurf_new, alb_new, alblw, &
526     &  emis_new, z0_new, dflux_l, dflux_s, qsurf_new)
527
528
529! ajout de la contribution du relief
530
531      z0_new = SQRT(z0_new**2+rugoro**2)
532!
533! mise a jour de l'humidite saturante calculee par ORCHIDEE
534      qsurf(1:knon) = qsurf_new(1:knon)
535#else
536      abort_message='Pb de coherence: ok_veget = .t. mais CPP_VEGET = .f.'
537      call abort_gcm(modname,abort_message,1)
538#endif
539
540    endif   
541!
542! Remplissage des pourcentages de surface
543!
544    pctsrf_new(:,nisurf) = pctsrf(:,nisurf)
545
546  else if (nisurf == is_oce) then
547
548    if (check) write(*,*)'ocean, nisurf = ',nisurf,'knon=',knon
549!
550! Surface "ocean" appel a l'interface avec l'ocean
551!
552    if (ocean == 'couple') then
553      if (nexca == 0) then
554        abort_message='nexca = 0 dans interfoce_cpl'
555        call abort_gcm(modname,abort_message,1)
556      endif
557
558      cumul = .false.
559
560      iloc = maxloc(fder(1:klon))
561      if (check) then
562        if (fder(iloc(1))> 0.) then
563          WRITE(*,*)'**** Debug fder ****'
564          WRITE(*,*)'max fder(',iloc(1),') = ',fder(iloc(1))
565        endif
566      endif
567!!$
568!!$      where(fder.gt.0.)
569!!$        fder = 0.
570!!$      endwhere
571
572      call interfoce(itime, dtime, cumul, &
573      & klon, iim, jjm, nisurf, pctsrf, knon, knindex, rlon, rlat, &
574      & ocean, npas, nexca, debut, lafin, &
575      & swdown, sollw, precip_rain, precip_snow, evap, tsurf, &
576      & fluxlat, fluxsens, fder, albedo, taux, tauy, &
577! -- LOOP
578      & windsp, &
579! -- LOOP
580      & zmasq, &
581      & tsurf_new, alb_new, &
582      & pctsrf_new)
583
584!IM: "slab" ocean
585     else if (ocean == 'slab  ') then
586      DO i=1, knon
587       tsurf_new(i) = tmp_tslab(knindex(i))
588      ENDDO
589      pctsrf_new = tmp_pctsrf_slab
590!
591    else                              ! lecture conditions limites
592      call interfoce(itime, dtime, jour, &
593     &  klon, nisurf, knon, knindex, &
594     &  debut, &
595     &  tsurf_new, pctsrf_new)
596
597    endif
598
599    tsurf_temp = tsurf_new
600    cal = 0.
601    beta = 1.
602    dif_grnd = 0.
603    alb_neig(:) = 0.
604    agesno(:) = 0.
605
606    call calcul_fluxs( klon, knon, nisurf, dtime, &
607     &   tsurf_temp, p1lay, cal, beta, tq_cdrag, ps, &
608     &   precip_rain, precip_snow, snow, qsurf,  &
609     &   radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
610     &   petAcoef, peqAcoef, petBcoef, peqBcoef, &
611     &   tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
612
613    fder_prev = fder   
614    fder = fder_prev + dflux_s + dflux_l
615
616      iloc = maxloc(fder(1:klon))
617        if (check.and.fder(iloc(1))> 0.) then
618          WRITE(*,*)'**** Debug fder****'
619          WRITE(*,*)'max fder(',iloc(1),') = ',fder(iloc(1))
620          WRITE(*,*)'fder_prev, dflux_s, dflux_l',fder_prev(iloc(1)), &
621     &                        dflux_s(iloc(1)), dflux_l(iloc(1))
622        endif
623!!$
624!!$      where(fder.gt.0.)
625!!$        fder = 0.
626!!$      endwhere
627
628!IM: flux ocean-atmosphere utile pour le "slab" ocean
629    DO i=1, knon
630     zx_sl(i) = RLVTT
631     if (tsurf_new(i) .LT. RTT) zx_sl(i) = RLSTT
632!IM     flux_o(i) = fluxsens(i)-evap(i)*zx_sl(i)
633     flux_o(i) = fluxsens(i) + fluxlat(i)
634     tmp_flux_o(knindex(i)) = flux_o(i)
635     tmp_radsol(knindex(i))=radsol(i)
636    ENDDO
637!
638! 2eme appel a interfoce pour le cumul des champs (en particulier
639! fluxsens et fluxlat calcules dans calcul_fluxs)
640!
641    if (ocean == 'couple') then
642
643      cumul = .true.
644
645      call interfoce(itime, dtime, cumul, &
646      & klon, iim, jjm, nisurf, pctsrf, knon, knindex, rlon, rlat, &
647      & ocean, npas, nexca, debut, lafin, &
648      & swdown, sollw, precip_rain, precip_snow, evap, tsurf, &
649      & fluxlat, fluxsens, fder, albedo, taux, tauy, &
650! -- LOOP
651      & windsp, &
652! -- LOOP
653      & zmasq, &
654      & tsurf_new, alb_new, &
655      & pctsrf_new)
656
657    endif
658
659!
660! calcul albedo
661!
662
663    if ( minval(rmu0) == maxval(rmu0) .and. minval(rmu0) == -999.999 ) then
664      CALL alboc(FLOAT(jour),rlat,alb_eau)
665    else  ! cycle diurne
666      CALL alboc_cd(rmu0,alb_eau)
667    endif
668    DO ii =1, knon
669      alb_new(ii) = alb_eau(knindex(ii))
670    enddo
671
672    z0_new = sqrt(rugos**2 + rugoro**2)
673    alblw(1:knon) = alb_new(1:knon)
674
675!
676  else if (nisurf == is_sic) then
677
678    if (check) write(*,*)'sea ice, nisurf = ',nisurf,'knon=',knon
679!
680! Surface "glace de mer" appel a l'interface avec l'ocean
681!
682!
683    if (ocean == 'couple') then
684
685      cumul =.false.
686
687      iloc = maxloc(fder(1:klon))
688      if (check.and.fder(iloc(1))> 0.) then
689        WRITE(*,*)'**** Debug fder ****'
690        WRITE(*,*)'max fder(',iloc(1),') = ',fder(iloc(1))
691      endif
692!!$
693!!$      where(fder.gt.0.)
694!!$        fder = 0.
695!!$      endwhere
696
697      call interfoce(itime, dtime, cumul, &
698      & klon, iim, jjm, nisurf, pctsrf, knon, knindex, rlon, rlat, &
699      & ocean, npas, nexca, debut, lafin, &
700      & swdown, sollw, precip_rain, precip_snow, evap, tsurf, &
701      & fluxlat, fluxsens, fder, albedo, taux, tauy, &
702! -- LOOP
703      & windsp, &
704! -- LOOP
705      & zmasq, &
706      & tsurf_new, alb_new, &
707      & pctsrf_new)
708
709      tsurf_temp = tsurf_new
710      cal = 0.
711      dif_grnd = 0.
712      beta = 1.0
713
714!IM: "slab" ocean
715    else if (ocean == 'slab  ') then
716!IM ajout sicOBSERVE BEG
717   IF ( ok_slab_sicOBS) THEN
718!                              ! lecture conditions limites
719      CALL interfoce(itime, dtime, jour, &
720             &  klon, nisurf, knon, knindex, &
721             &  debut, &
722             &  tsurf_new, pctsrf_new)
723!
724    tmp_pctsrf_slab=pctsrf_new
725    print*,'jour lecture pctsrf_new sic =',jour
726!
727   ELSE !ok_slab_sicOBS
728     pctsrf_new=tmp_pctsrf_slab
729   ENDIF
730!IM ajout sicOBSERVE END
731!
732     DO ii = 1, knon
733      tsurf_new(ii) = tsurf(ii)
734      IF (pctsrf_new(knindex(ii),nisurf) < EPSFRA) then
735       snow(ii) = 0.0
736       tsurf_new(ii) = RTT - 1.8
737       IF (soil_model) tsoil(ii,:) = RTT -1.8
738      ENDIF
739     ENDDO
740
741     CALL calbeta(dtime, nisurf, knon, snow, qsol, beta, capsol, dif_grnd)
742     
743     IF (soil_model) THEN
744      CALL soil(dtime, nisurf, knon,snow, tsurf_new, tsoil,soilcap, soilflux)
745      cal(1:knon) = RCPD / soilcap(1:knon)
746      radsol(1:knon) = radsol(1:knon)  + soilflux(1:knon)
747     ELSE
748      dif_grnd = 1.0 / tau_gl
749      cal = RCPD * calice
750      WHERE (snow > 0.0) cal = RCPD * calsno
751     ENDIF
752     tsurf_temp = tsurf_new
753     beta = 1.0
754!
755    ELSE
756!                              ! lecture conditions limites
757      CALL interfoce(itime, dtime, jour, &
758             &  klon, nisurf, knon, knindex, &
759             &  debut, &
760             &  tsurf_new, pctsrf_new)
761
762!IM cf LF
763      DO ii = 1, knon
764       tsurf_new(ii) = tsurf(ii)
765       IF (pctsrf_new(knindex(ii),nisurf) < EPSFRA) then
766          snow(ii) = 0.0
767!IM cf LF/JLD         tsurf(ii) = RTT - 1.8
768          tsurf_new(ii) = RTT - 1.8
769          IF (soil_model) tsoil(ii,:) = RTT -1.8
770        endif
771      enddo
772
773      CALL calbeta(dtime, nisurf, knon, snow, qsol, beta, capsol, dif_grnd)
774     
775      IF (soil_model) THEN
776!IM cf LF/JLD        CALL soil(dtime, nisurf, knon,snow, tsurf, tsoil,soilcap, soilflux)
777         CALL soil(dtime, nisurf, knon,snow, tsurf_new, tsoil,soilcap, soilflux)
778         cal(1:knon) = RCPD / soilcap(1:knon)
779         radsol(1:knon) = radsol(1:knon)  + soilflux(1:knon)
780         dif_grnd = 1.0 / tau_gl
781      ELSE
782         dif_grnd = 1.0 / tau_gl
783         cal = RCPD * calice
784         WHERE (snow > 0.0) cal = RCPD * calsno
785      ENDIF
786!IMbadtsurf_temp = tsurf
787      tsurf_temp = tsurf_new
788      beta = 1.0
789    ENDIF !ocean ==
790
791    CALL calcul_fluxs( klon, knon, nisurf, dtime, &
792         &   tsurf_temp, p1lay, cal, beta, tq_cdrag, ps, &
793         &   precip_rain, precip_snow, snow, qsurf,  &
794         &   radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
795         &   petAcoef, peqAcoef, petBcoef, peqBcoef, &
796         &   tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
797!
798    IF (ocean /= 'couple') THEN
799      CALL fonte_neige( klon, knon, nisurf, dtime, &
800             &   tsurf_temp, p1lay, cal, beta, tq_cdrag, ps, &
801             &   precip_rain, precip_snow, snow, qsol,  &
802             &   radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
803             &   petAcoef, peqAcoef, petBcoef, peqBcoef, &
804             &   tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
805             &   fqcalving,fqfonte,ffonte, run_off_lic_0)
806
807!     calcul albedo
808
809      CALL albsno(klon,knon,dtime,agesno(:),alb_neig(:), precip_snow(:)) 
810      WHERE (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
811      zfra(1:knon) = MAX(0.0,MIN(1.0,snow(1:knon)/(snow(1:knon)+10.0)))
812      alb_new(1 : knon) = alb_neig(1 : knon) *zfra(1:knon) + &
813     &                    0.6 * (1.0-zfra(1:knon))
814!!      alb_new(1 : knon) = 0.6
815    ENDIF
816!
817!IM: flux entre l'ocean et la glace de mer pour le "slab" ocean
818!
819    DO i = 1, knon
820!
821!IM: faire dependre le coefficient de conduction de la glace de mer
822!    de l'epaisseur de la glace de mer, dans l'hypothese ou le coeff.
823!    actuel correspond a 3m de glace de mer, cf. L.Li
824!
825       IF(1.EQ.0) THEN
826        IF(siceh(i).GT.0.) THEN
827         new_dif_grnd(i) = dif_grnd(i)*3./siceh(i)
828        ELSE
829         new_dif_grnd(i) = 0.
830        ENDIF
831       ENDIF !(1.EQ.0) THEN
832!
833     IF (cal(i).GT.1.0e-15) THEN
834       flux_g(i)=(tsurf_new(i)-t_grnd) &
835    &                          * dif_grnd(i) *RCPD/cal(i)
836!   &                          * new_dif_grnd(i) *RCPD/cal(i)
837     ENDIF
838     tmp_flux_g(knindex(i))=flux_g(i)
839!
840!IM: Attention: ne pas initialiser le tmp_radsol puisque c'est deja fait sur is_oce;
841!IM:            tmp_radsol doit etre le flux solaire qui arrive sur l'ocean
842!IM:            et non pas celui qui arrive sur la glace de mer
843!
844    ENDDO
845
846    fder_prev = fder   
847    fder = fder_prev + dflux_s + dflux_l
848
849      iloc = maxloc(fder(1:klon))
850      if (check.and.fder(iloc(1))> 0.) then
851        WRITE(*,*)'**** Debug fder ****'
852        WRITE(*,*)'max fder(',iloc(1),') = ',fder(iloc(1))
853        WRITE(*,*)'fder_prev, dflux_s, dflux_l',fder_prev(iloc(1)), &
854     &                        dflux_s(iloc(1)), dflux_l(iloc(1))
855      endif
856!!$      where(fder.gt.0.)
857!!$        fder = 0.
858!!$      endwhere
859
860!
861! 2eme appel a interfoce pour le cumul et le passage des flux a l'ocean
862!
863    if (ocean == 'couple') then
864
865      cumul =.true.
866
867      call interfoce(itime, dtime, cumul, &
868      & klon, iim, jjm, nisurf, pctsrf, knon, knindex, rlon, rlat, &
869      & ocean, npas, nexca, debut, lafin, &
870      & swdown, sollw, precip_rain, precip_snow, evap, tsurf, &
871      & fluxlat, fluxsens, fder, albedo, taux, tauy, &
872! -- LOOP
873      & windsp, &
874! -- LOOP
875      & zmasq, &
876      & tsurf_new, alb_new, &
877      & pctsrf_new)
878
879!IM: "slab" ocean
880    else if (ocean == 'slab  ') then
881!
882   IF (check) THEN
883    amn=MIN(tmp_tslab(1),1000.)
884    amx=MAX(tmp_tslab(1),-1000.)
885    DO i=2, klon
886     amn=MIN(tmp_tslab(i),amn)
887     amx=MAX(tmp_tslab(i),amx)
888    ENDDO
889!
890    PRINT*,' debut avant interfoce_slab min max tmp_tslab',amn,amx
891   ENDIF !(check) THEN
892!
893       cumul = .true.
894       tslab = tmp_tslab   
895       call interfoce(klon, debut, itime, dtime, jour, &
896     & tmp_radsol, tmp_flux_o, tmp_flux_g, tmp_pctsrf_slab, &
897     & tslab, seaice, pctsrf_new)
898!
899       tmp_seaice=seaice
900       tmp_pctsrf_slab=pctsrf_new
901       DO i=1, knon
902         tmp_tslab(knindex(i))=tslab(knindex(i))
903       ENDDO !i
904!
905
906    endif
907
908     
909    z0_new = 0.002
910    z0_new = SQRT(z0_new**2+rugoro**2)
911    alblw(1:knon) = alb_new(1:knon)
912
913
914  else if (nisurf == is_lic) then
915
916    if (check) write(*,*)'glacier, nisurf = ',nisurf
917
918    if (.not. allocated(run_off_lic)) then
919      allocate(run_off_lic(klon), stat = error)
920      if (error /= 0) then
921        abort_message='Pb allocation run_off_lic'
922        call abort_gcm(modname,abort_message,1)
923      endif
924      run_off_lic = 0.
925    endif
926!
927! Surface "glacier continentaux" appel a l'interface avec le sol
928!
929!    call interfsol(nisurf)
930    IF (soil_model) THEN
931        CALL soil(dtime, nisurf, knon, snow, tsurf, tsoil,soilcap, soilflux)
932        cal(1:knon) = RCPD / soilcap(1:knon)
933        radsol(1:knon)  = radsol(1:knon) + soilflux(1:knon)
934    ELSE
935        cal = RCPD * calice
936        WHERE (snow > 0.0) cal = RCPD * calsno
937    ENDIF
938    beta = 1.0
939    dif_grnd = 0.0
940
941    call calcul_fluxs( klon, knon, nisurf, dtime, &
942     &   tsurf, p1lay, cal, beta, tq_cdrag, ps, &
943     &   precip_rain, precip_snow, snow, qsurf,  &
944     &   radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
945     &   petAcoef, peqAcoef, petBcoef, peqBcoef, &
946     &   tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
947
948    call fonte_neige( klon, knon, nisurf, dtime, &
949     &   tsurf, p1lay, cal, beta, tq_cdrag, ps, &
950     &   precip_rain, precip_snow, snow, qsol,  &
951     &   radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, &
952     &   petAcoef, peqAcoef, petBcoef, peqBcoef, &
953     &   tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
954     &   fqcalving,fqfonte,ffonte, run_off_lic_0)
955
956! passage du run-off des glaciers calcule dans fonte_neige au coupleur
957    bidule=0.
958    bidule(1:knon)= run_off_lic(1:knon)   
959    call gath2cpl(bidule, tmp_rlic, klon, knon,iim,jjm,knindex)
960!
961! calcul albedo
962!
963     CALL albsno(klon,knon,dtime,agesno(:),alb_neig(:), precip_snow(:)) 
964     WHERE (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
965     zfra(1:knon) = MAX(0.0,MIN(1.0,snow(1:knon)/(snow(1:knon)+10.0)))
966     alb_new(1 : knon)  = alb_neig(1 : knon)*zfra(1:knon) + &
967    &                     0.6 * (1.0-zfra(1:knon))
968!
969!IM: plusieurs choix/tests sur l'albedo des "glaciers continentaux"
970!       alb_new(1 : knon)  = 0.6 !IM cf FH/GK
971!       alb_new(1 : knon)  = 0.82
972!       alb_new(1 : knon)  = 0.77 !211003 Ksta0.77
973!       alb_new(1 : knon)  = 0.8 !KstaTER0.8 & LMD_ARMIP5
974!IM: KstaTER0.77 & LMD_ARMIP6   
975        alb_new(1 : knon)  = 0.77
976
977!
978! Rugosite
979!
980    z0_new = rugoro
981!
982! Remplissage des pourcentages de surface
983!
984    pctsrf_new(:,nisurf) = pctsrf(:,nisurf)
985
986    alblw(1:knon) = alb_new(1:knon)
987  else
988    write(*,*)'Index surface = ',nisurf
989    abort_message = 'Index surface non valable'
990    call abort_gcm(modname,abort_message,1)
991  endif
992
993  END SUBROUTINE interfsurf_hq
994
995!
996!#########################################################################
997!
998  SUBROUTINE interfsurf_vent(nisurf, knon   &         
999  &                     )
1000!
1001! Cette routine sert d'aiguillage entre l'atmosphere et la surface en general
1002! (sols continentaux, oceans, glaces) pour les tensions de vents.
1003! En pratique l'interface se fait entre la couche limite du modele
1004! atmospherique (clmain.F) et les routines de surface (sechiba, oasis, ...)
1005!
1006!
1007! L.Fairhead 02/2000
1008!
1009! input:
1010!   nisurf       index de la surface a traiter (1 = sol continental)
1011!   knon         nombre de points de la surface a traiter
1012
1013! Parametres d'entree
1014  integer, intent(IN) :: nisurf
1015  integer, intent(IN) :: knon
1016
1017
1018  return
1019  END SUBROUTINE interfsurf_vent
1020!
1021!#########################################################################
1022!
1023#ifdef CPP_VEGET
1024  SUBROUTINE interfsol(itime, klon, dtime, date0, nisurf, knon, &
1025     & knindex, rlon, rlat, cufi, cvfi, iim, jjm, pctsrf, &
1026     & debut, lafin, ok_veget, &
1027     & plev,  u1_lay, v1_lay, temp_air, spechum, epot_air, ccanopy, &
1028     & tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
1029     & precip_rain, precip_snow, lwdown, swnet, swdown, &
1030     & tsurf, p1lay, ps, radsol, &
1031     & evap, fluxsens, fluxlat, &             
1032     & tsol_rad, tsurf_new, alb_new, alblw, &
1033     & emis_new, z0_new, dflux_l, dflux_s, qsurf)
1034
1035  USE intersurf
1036  USE mod_grid_phy_lmdz
1037  USE mod_phys_lmdz_para
1038  IMPLICIT NONE
1039! Cette routine sert d'interface entre le modele atmospherique et le
1040! modele de sol continental. Appel a sechiba
1041!
1042! L. Fairhead 02/2000
1043!
1044! input:
1045!   itime        numero du pas de temps
1046!   klon         nombre total de points de grille
1047!   dtime        pas de temps de la physique (en s)
1048!   nisurf       index de la surface a traiter (1 = sol continental)
1049!   knon         nombre de points de la surface a traiter
1050!   knindex      index des points de la surface a traiter
1051!   rlon         longitudes de la grille entiere
1052!   rlat         latitudes de la grille entiere
1053!   pctsrf       tableau des fractions de surface de chaque maille
1054!   debut        logical: 1er appel a la physique (lire les restart)
1055!   lafin        logical: dernier appel a la physique (ecrire les restart)
1056!   ok_veget     logical: appel ou non au schema de surface continental
1057!                     (si false calcul simplifie des fluxs sur les continents)
1058!   plev         hauteur de la premiere couche (Pa)     
1059!   u1_lay       vitesse u 1ere couche
1060!   v1_lay       vitesse v 1ere couche
1061!   temp_air     temperature de l'air 1ere couche
1062!   spechum      humidite specifique 1ere couche
1063!   epot_air     temp pot de l'air
1064!   ccanopy      concentration CO2 canopee
1065!   tq_cdrag     cdrag
1066!   petAcoef     coeff. A de la resolution de la CL pour t
1067!   peqAcoef     coeff. A de la resolution de la CL pour q
1068!   petBcoef     coeff. B de la resolution de la CL pour t
1069!   peqBcoef     coeff. B de la resolution de la CL pour q
1070!   precip_rain  precipitation liquide
1071!   precip_snow  precipitation solide
1072!   lwdown       flux IR descendant a la surface
1073!   swnet        flux solaire net
1074!   swdown       flux solaire entrant a la surface
1075!   tsurf        temperature de surface
1076!   p1lay        pression 1er niveau (milieu de couche)
1077!   ps           pression au sol
1078!   radsol       rayonnement net aus sol (LW + SW)
1079!   
1080!
1081! input/output
1082!   run_off      ruissellement total
1083!
1084! output:
1085!   evap         evaporation totale
1086!   fluxsens     flux de chaleur sensible
1087!   fluxlat      flux de chaleur latente
1088!   tsol_rad     
1089!   tsurf_new    temperature au sol
1090!   alb_new      albedo
1091!   emis_new     emissivite
1092!   z0_new       surface roughness
1093!   qsurf        air moisture at surface
1094
1095! Parametres d'entree
1096  integer, intent(IN) :: itime
1097  integer, intent(IN) :: klon
1098  real, intent(IN)    :: dtime
1099  real, intent(IN)    :: date0
1100  integer, intent(IN) :: nisurf
1101  integer, intent(IN) :: knon
1102  integer, intent(IN) :: iim, jjm
1103  integer, dimension(klon), intent(IN) :: knindex
1104  logical, intent(IN) :: debut, lafin, ok_veget
1105  real, dimension(klon,nbsrf), intent(IN) :: pctsrf
1106  real, dimension(klon), intent(IN) :: rlon, rlat
1107  real, dimension(klon), intent(IN) :: cufi, cvfi
1108  real, dimension(klon), intent(IN) :: plev
1109  real, dimension(klon), intent(IN) :: u1_lay, v1_lay
1110  real, dimension(klon), intent(IN) :: temp_air, spechum
1111  real, dimension(klon), intent(IN) :: epot_air, ccanopy
1112  real, dimension(klon), intent(INOUT) :: tq_cdrag
1113  real, dimension(klon), intent(IN) :: petAcoef, peqAcoef
1114  real, dimension(klon), intent(IN) :: petBcoef, peqBcoef
1115  real, dimension(klon), intent(IN) :: precip_rain, precip_snow
1116  real, dimension(klon), intent(IN) :: lwdown, swnet, swdown, ps
1117!IM cf. JP +++
1118  real, dimension(klon) :: swdown_vrai
1119!IM cf. JP ---
1120  real, dimension(klon), intent(IN) :: tsurf, p1lay
1121  real, dimension(klon), intent(IN) :: radsol
1122! Parametres de sortie
1123  real, dimension(klon), intent(OUT):: evap, fluxsens, fluxlat, qsurf
1124  real, dimension(klon), intent(OUT):: tsol_rad, tsurf_new, alb_new, alblw
1125  real, dimension(klon), intent(OUT):: emis_new, z0_new
1126  real, dimension(klon), intent(OUT):: dflux_s, dflux_l
1127
1128! Local
1129!
1130  integer              :: ii, ij, jj, igrid, ireal, i, index, iglob
1131  integer              :: error
1132  character (len = 20) :: modname = 'interfsol'
1133  character (len = 80) :: abort_message
1134  logical,save              :: check = .FALSE.
1135  real, dimension(klon) :: cal, beta, dif_grnd, capsol
1136! type de couplage dans sechiba
1137!  character (len=10)   :: coupling = 'implicit'
1138! drapeaux controlant les appels dans SECHIBA
1139!  type(control_type), save   :: control_in
1140! Preserved albedo
1141!IM cf. JP +++
1142  real, allocatable, dimension(:), save :: albedo_keep, zlev
1143!IM cf. JP ---
1144! coordonnees geographiques
1145  real, allocatable, dimension(:,:), save :: lalo
1146! pts voisins
1147  integer,allocatable, dimension(:,:), save :: neighbours
1148! fractions continents
1149  real,allocatable, dimension(:), save :: contfrac
1150! resolution de la grille
1151  real, allocatable, dimension (:,:), save :: resolution
1152! correspondance point n -> indices (i,j)
1153  integer, allocatable, dimension(:,:), save :: correspond
1154! offset pour calculer les point voisins
1155  integer, dimension(8,3), save :: off_ini
1156 ! Identifieurs des fichiers restart et histoire
1157  integer, save          :: rest_id, hist_id
1158  integer, save          :: rest_id_stom, hist_id_stom
1159!
1160  real, allocatable, dimension (:,:), save :: lon_scat, lat_scat 
1161
1162  logical, save          :: lrestart_read = .true. , lrestart_write = .false.
1163
1164  real, dimension(klon):: snow
1165  real, dimension(knon,2) :: albedo_out
1166! Pb de nomenclature
1167  real, dimension(klon) :: petA_orc, peqA_orc
1168  real, dimension(klon) :: petB_orc, peqB_orc
1169! Pb de correspondances de grilles
1170  integer, dimension(:), save, allocatable :: ig, jg
1171  integer :: indi, indj
1172  integer, save, allocatable,dimension(:) :: ktindex
1173  REAL, dimension(klon) :: bidule
1174! Essai cdrag
1175  real, dimension(klon) :: cdrag
1176  integer :: jjb,jje,ijb,ije
1177  INTEGER,SAVE :: offset
1178  REAL, dimension(klon_glo) :: rlon_g,rlat_g
1179  INTEGER, SAVE          :: orch_comm
1180#include "temps.inc"
1181#include "YOMCST.inc"
1182#include "iniprint.h"
1183
1184  if (check) write(lunout,*)'Entree ', modname
1185  if (check) write(lunout,*)'ok_veget = ',ok_veget
1186
1187
1188 
1189! initialisation
1190 
1191  if (debut) then
1192    ALLOCATE(ktindex(klon))
1193  IF ( .NOT. allocated(albedo_keep)) THEN
1194     ALLOCATE(albedo_keep(klon))
1195     ALLOCATE(zlev(klon))
1196  ENDIF
1197! Pb de correspondances de grilles
1198   allocate(ig(klon))
1199   allocate(jg(klon))
1200   ig(1) = 1
1201   jg(1) = 1
1202   indi = 0
1203   indj = 2
1204   do igrid = 2, klon - 1
1205     indi = indi + 1
1206     if ( indi > iim) then
1207       indi = 1
1208       indj = indj + 1
1209     endif
1210     ig(igrid) = indi
1211     jg(igrid) = indj
1212   enddo
1213   ig(klon) = 1
1214   jg(klon) = jjm + 1
1215
1216    if ((.not. allocated(lalo))) then
1217      allocate(lalo(knon,2), stat = error)
1218      if (error /= 0) then
1219        abort_message='Pb allocation lalo'
1220        call abort_gcm(modname,abort_message,1)
1221      endif     
1222    endif
1223    if ((.not. allocated(lon_scat))) then
1224      allocate(lon_scat(iim,jjm+1), stat = error)
1225      if (error /= 0) then
1226        abort_message='Pb allocation lon_scat'
1227        call abort_gcm(modname,abort_message,1)
1228      endif     
1229    endif
1230    if ((.not. allocated(lat_scat))) then
1231      allocate(lat_scat(iim,jjm+1), stat = error)
1232      if (error /= 0) then
1233        abort_message='Pb allocation lat_scat'
1234        call abort_gcm(modname,abort_message,1)
1235      endif     
1236    endif
1237    lon_scat = 0.
1238    lat_scat = 0.
1239    do igrid = 1, knon
1240      index = knindex(igrid)
1241      lalo(igrid,2) = rlon(index)
1242      lalo(igrid,1) = rlat(index)
1243
1244    enddo
1245   
1246
1247   
1248    CALL Gather(rlon,rlon_g)
1249    CALL Gather(rlat,rlat_g)
1250
1251    IF (is_mpi_root) THEN
1252      index = 1
1253      do jj = 2, jjm
1254        do ij = 1, iim
1255          index = index + 1
1256          lon_scat(ij,jj) = rlon_g(index)
1257          lat_scat(ij,jj) = rlat_g(index)
1258        enddo
1259      enddo
1260     lon_scat(:,1) = lon_scat(:,2)
1261     lat_scat(:,1) = rlat_g(1)
1262     lon_scat(:,jjm+1) = lon_scat(:,2)
1263     lat_scat(:,jjm+1) = rlat_g(klon_glo)
1264   ENDIF
1265   
1266
1267!
1268! Allouer et initialiser le tableau des voisins et des fraction de continents
1269!
1270    if ( (.not.allocated(neighbours))) THEN
1271      allocate(neighbours(knon,8), stat = error)
1272      if (error /= 0) then
1273        abort_message='Pb allocation neighbours'
1274        call abort_gcm(modname,abort_message,1)
1275      endif
1276    endif
1277    neighbours = -1.
1278    if (( .not. allocated(contfrac))) then
1279      allocate(contfrac(knon), stat = error)
1280      if (error /= 0) then
1281        abort_message='Pb allocation contfrac'
1282        call abort_gcm(modname,abort_message,1)
1283      endif     
1284    endif
1285
1286    do igrid = 1, knon
1287      ireal = knindex(igrid)
1288      contfrac(igrid) = pctsrf(ireal,is_ter)
1289    enddo
1290
1291
1292   CALL Init_neighbours(iim,jjm,knon,neighbours,knindex,pctsrf(:,is_ter))
1293
1294!
1295!  Allocation et calcul resolutions
1296    IF ( (.NOT.ALLOCATED(resolution))) THEN
1297      ALLOCATE(resolution(knon,2), stat = error)
1298      if (error /= 0) then
1299        abort_message='Pb allocation resolution'
1300        call abort_gcm(modname,abort_message,1)
1301      endif
1302    ENDIF
1303    do igrid = 1, knon
1304      ij = knindex(igrid)
1305      resolution(igrid,1) = cufi(ij)
1306      resolution(igrid,2) = cvfi(ij)
1307    enddo 
1308
1309  endif                          ! (fin debut)
1310
1311!
1312! Appel a la routine sols continentaux
1313!
1314  if (lafin) lrestart_write = .true.
1315  if (check) write(lunout,*)'lafin ',lafin,lrestart_write
1316
1317  petA_orc = petBcoef * dtime
1318  petB_orc = petAcoef
1319  peqA_orc = peqBcoef * dtime
1320  peqB_orc = peqAcoef
1321
1322  cdrag = 0.
1323  cdrag(1:knon) = tq_cdrag(1:knon)
1324
1325!IM cf. JP +++
1326! zlev(1:knon) = (100.*plev(1:knon))/((ps(1:knon)/287.05*temp_air(1:knon))*9.80665)
1327  zlev(1:knon) = (100.*plev(1:knon))/((ps(1:knon)/RD*temp_air(1:knon))*RG)
1328!IM cf. JP ---
1329
1330
1331! PF et PASB
1332!   where(cdrag > 0.01)
1333!     cdrag = 0.01
1334!   endwhere
1335!  write(*,*)'Cdrag = ',minval(cdrag),maxval(cdrag)
1336
1337!
1338! Init Orchidee
1339!
1340!  if (pole_nord) then
1341!    offset=0
1342!    ktindex(:)=ktindex(:)+iim-1
1343!  else
1344!    offset = klon_begin-1+iim-1
1345!    ktindex(:)=ktindex(:)+MOD(offset,iim)
1346!    offset=offset-MOD(offset,iim)
1347!  endif
1348 
1349   
1350  if (debut) then
1351    CALL Get_orchidee_communicator(knon,orch_comm)
1352    IF (knon /=0) THEN
1353      CALL Init_orchidee_index(iim,knon,orch_comm,knindex,offset,ktindex)
1354   
1355      call intersurf_main (itime+itau_phy-1, iim, jjm+1,offset, knon, ktindex, &
1356       & orch_comm,dtime, lrestart_read, lrestart_write, lalo, &
1357       & contfrac, neighbours, resolution, date0, &
1358       & zlev,  u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, &
1359       & cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, &
1360       & precip_rain, precip_snow, lwdown, swnet, swdown, ps, &
1361       & evap, fluxsens, fluxlat, coastalflow, riverflow, &
1362       & tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, &
1363       & lon_scat, lat_scat)
1364
1365     ENDIF
1366!IM cf. JP +++
1367    albedo_keep(1:knon) = (albedo_out(1:knon,1)+albedo_out(1:knon,2))/2.
1368!IM cf. JP ---
1369
1370  endif
1371
1372!IM cf. JP +++
1373!  swdown_vrai(1:knon) = swnet(1:knon)/(1. - albedo_keep(1:knon))
1374  swdown_vrai(1:knon) = swdown(1:knon)
1375
1376!IM cf. JP ---
1377    IF (knon /=0) THEN
1378   
1379      call intersurf_main (itime+itau_phy, iim, jjm+1,offset, knon, ktindex, &
1380       & orch_comm,dtime, lrestart_read, lrestart_write, lalo, &
1381       & contfrac, neighbours, resolution, date0, &
1382       & zlev,  u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, &
1383       & cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, &
1384       & precip_rain, precip_snow, lwdown, swnet, swdown_vrai, ps, &
1385       & evap, fluxsens, fluxlat, coastalflow, riverflow, &
1386       & tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, &
1387       & lon_scat, lat_scat)
1388
1389    ENDIF
1390!IM cf. JP +++
1391    albedo_keep(1:knon) = (albedo_out(1:knon,1)+albedo_out(1:knon,2))/2.
1392!IM cf. JP ---
1393
1394    bidule=0.
1395    bidule(1:knon)=riverflow(1:knon)
1396    call gath2cpl(bidule, tmp_rriv, klon, knon,iim,jj_nb,knindex)
1397    bidule=0.
1398    bidule(1:knon)=coastalflow(1:knon)
1399    call gath2cpl(bidule, tmp_rcoa, klon, knon,iim,jj_nb,knindex)
1400    alb_new(1:knon) = albedo_out(1:knon,1)
1401    alblw(1:knon) = albedo_out(1:knon,2)
1402
1403
1404! Convention orchidee: positif vers le haut
1405  fluxsens(1:knon) = -1. * fluxsens(1:knon)
1406  fluxlat(1:knon)  = -1. * fluxlat(1:knon)
1407
1408!  evap     = -1. * evap
1409
1410  if (debut) lrestart_read = .false.
1411
1412  END SUBROUTINE interfsol
1413 
1414  SUBROUTINE Init_orchidee_index(iim,knon,orch_comm,knindex,offset,ktindex)
1415  USE mod_phys_lmdz_para, ONLY : is_parallel
1416 
1417  IMPLICIT NONE
1418    INTEGER,INTENT(IN)  :: iim
1419    INTEGER,INTENT(IN)  :: knon
1420    INTEGER,INTENT(IN)  :: orch_comm
1421    INTEGER,INTENT(IN)  :: knindex(knon)
1422    INTEGER,INTENT(OUT) :: offset
1423    INTEGER,INTENT(OUT) :: ktindex(knon)
1424
1425#ifdef CPP_PARA
1426    INCLUDE 'mpif.h'
1427    INTEGER :: status(MPI_STATUS_SIZE)
1428#endif
1429    INTEGER :: MyLastPoint
1430    INTEGER :: LastPoint
1431    INTEGER :: mpi_rank
1432    INTEGER :: mpi_size
1433    INTEGER :: ierr   
1434   
1435    MyLastPoint=klon_begin-1+knindex(knon)+iim-1
1436
1437    IF (is_parallel) THEN
1438#ifdef CPP_PARA   
1439      call MPI_COMM_SIZE(orch_comm,mpi_size,ierr)
1440      call MPI_COMM_RANK(orch_comm,mpi_rank,ierr)
1441#endif
1442    ELSE
1443      mpi_rank=0
1444      mpi_size=1
1445    ENDIF
1446   
1447    IF (is_parallel) THEN
1448      IF (mpi_rank /= 0) then
1449#ifdef CPP_PARA
1450        CALL MPI_RECV(LastPoint,1,MPI_INTEGER,mpi_rank-1,1234,orch_comm,status,ierr)
1451#endif
1452      ENDIF
1453       
1454      IF (mpi_rank /= mpi_size-1) THEN
1455#ifdef CPP_PARA
1456        CALL MPI_SEND(MyLastPoint,1,MPI_INTEGER,mpi_rank+1,1234,orch_comm,ierr) 
1457#endif
1458      ENDIF
1459    ENDIF
1460   
1461    IF (mpi_rank==0) THEN
1462      offset=0
1463    ELSE
1464     offset=LastPoint-MOD(LastPoint,iim)
1465    ENDIF
1466     
1467    ktindex(:)=knindex(:)+(klon_begin+iim-1)-offset-1   
1468   
1469
1470   END SUBROUTINE  Init_orchidee_index
1471
1472 
1473  SUBROUTINE Get_orchidee_communicator(knon,orch_comm)
1474  USE mod_phys_lmdz_para, ONLY: mpi_rank, COMM_LMDZ_PHY
1475
1476  IMPLICIT NONE
1477#ifdef CPP_PARA
1478    include 'mpif.h'
1479#endif   
1480    INTEGER,INTENT(IN)  :: knon
1481    INTEGER,INTENT(OUT) :: orch_comm
1482   
1483    INTEGER :: color
1484    INTEGER :: ierr
1485   
1486    IF (knon==0) THEN
1487      color = 0
1488    ELSE
1489      color = 1
1490    ENDIF
1491
1492#ifdef CPP_PARA   
1493    CALL MPI_COMM_SPLIT(COMM_LMDZ_PHY,color,mpi_rank,orch_comm,ierr)
1494#endif
1495   
1496  END SUBROUTINE Get_orchidee_communicator
1497   
1498   
1499  SUBROUTINE Init_neighbours(iim,jjm,knon,neighbours,ktindex,pctsrf)
1500  USE mod_phys_lmdz_para, not_use_mpi_root=>mpi_root
1501  USE dimphy
1502  IMPLICIT NONE
1503
1504#ifdef CPP_PARA
1505  include 'mpif.h'
1506#endif
1507  INTEGER :: iim,jjm
1508  INTEGER :: knon
1509  INTEGER :: neighbours(knon,8)
1510  INTEGER :: ktindex(knon)
1511  REAL :: pctsrf(klon)
1512 
1513  INTEGER :: knon_nb(0:mpi_size-1)
1514  INTEGER,DIMENSION(0:mpi_size-1) :: displs,sendcount
1515  INTEGER,ALLOCATABLE :: ktindex_g(:)
1516  REAL*8  :: pctsrf_g(klon2)
1517  INTEGER,ALLOCATABLE ::neighbours_g(:,:)
1518  INTEGER :: knon_g
1519  REAL*8 :: correspond(iim,jjm+1)
1520  INTEGER :: i,igrid,jj,ij,iglob,ierr,ireal,index
1521  integer, dimension(8,3) :: off_ini
1522  integer, dimension(8)   :: offset 
1523  INTEGER :: ktindex_p(knon)
1524
1525  IF (is_sequential) THEN
1526    knon_nb(:)=knon
1527  ELSE 
1528
1529#ifdef CPP_PARA 
1530    CALL MPI_GATHER(knon,1,MPI_INTEGER,knon_nb,1,MPI_INTEGER,0,COMM_LMDZ_PHY,ierr)
1531#endif
1532 
1533  ENDIF
1534   
1535  IF (is_mpi_root) THEN
1536    knon_g=sum(knon_nb(:))
1537    ALLOCATE(ktindex_g(knon_g))
1538    ALLOCATE(neighbours_g(knon_g,8))
1539    neighbours_g(:,:)=-1
1540    displs(0)=0
1541    DO i=1,mpi_size-1
1542      displs(i)=displs(i-1)+knon_nb(i-1)
1543    ENDDO 
1544  ENDIF
1545 
1546  ktindex_p(:)=ktindex(:)+klon_begin-1+iim-1
1547
1548  IF (is_sequential) THEN
1549    ktindex_g(:)=ktindex_p(:)
1550  ELSE
1551
1552#ifdef CPP_PARA 
1553    CALL MPI_GATHERV(ktindex_p,knon,MPI_INTEGER,ktindex_g,knon_nb,displs,MPI_INTEGER,0,COMM_LMDZ_PHY,ierr)
1554#endif
1555
1556  ENDIF
1557     
1558  CALL Gather(pctsrf,pctsrf_g)
1559 
1560  IF (is_mpi_root) THEN
1561!  Initialisation des offset   
1562!
1563! offset bord ouest
1564   off_ini(1,1) = - iim  ; off_ini(2,1) = - iim + 1; off_ini(3,1) = 1
1565   off_ini(4,1) = iim + 1; off_ini(5,1) = iim      ; off_ini(6,1) = 2 * iim - 1
1566   off_ini(7,1) = iim -1 ; off_ini(8,1) = - 1
1567! offset point normal
1568   off_ini(1,2) = - iim  ; off_ini(2,2) = - iim + 1; off_ini(3,2) = 1
1569   off_ini(4,2) = iim + 1; off_ini(5,2) = iim      ; off_ini(6,2) = iim - 1
1570   off_ini(7,2) = -1     ; off_ini(8,2) = - iim - 1
1571! offset bord   est
1572   off_ini(1,3) = - iim; off_ini(2,3) = - 2 * iim + 1; off_ini(3,3) = - iim + 1
1573   off_ini(4,3) =  1   ; off_ini(5,3) = iim          ; off_ini(6,3) = iim - 1
1574   off_ini(7,3) = -1   ; off_ini(8,3) = - iim - 1
1575!
1576!
1577! Attention aux poles
1578!
1579    do igrid = 1, knon_g
1580      index = ktindex_g(igrid)
1581          jj = int((index - 1)/iim) + 1
1582          ij = index - (jj - 1) * iim
1583      correspond(ij,jj) = igrid
1584    enddo
1585
1586    do igrid = 1, knon_g
1587      iglob = ktindex_g(igrid)
1588      if (mod(iglob, iim) == 1) then
1589        offset = off_ini(:,1)
1590      else if(mod(iglob, iim) == 0) then
1591        offset = off_ini(:,3)
1592      else
1593        offset = off_ini(:,2)
1594      endif
1595      do i = 1, 8
1596        index = iglob + offset(i)
1597        ireal = (min(max(1, index - iim + 1), klon2))
1598        if (pctsrf_g(ireal) > EPSFRA) then
1599          jj = int((index - 1)/iim) + 1
1600          ij = index - (jj - 1) * iim
1601            neighbours_g(igrid, i) = correspond(ij, jj)
1602        endif
1603      enddo
1604    enddo
1605
1606!    DO i=0,phy_size-1
1607!      displs(i)=displs(i)*8
1608!      sendcount(i)=knon_nb(i)*8
1609!    ENDDO
1610 
1611  ENDIF
1612 
1613  DO i=1,8
1614    IF (is_sequential) THEN
1615      neighbours(:,i)=neighbours_g(:,i)
1616    ELSE
1617#ifdef CPP_PARA
1618    CALL MPI_SCATTERV(neighbours_g(:,i),knon_nb,displs,MPI_INTEGER,neighbours(:,i),knon,MPI_INTEGER,0,COMM_LMDZ_PHY,ierr)
1619#endif
1620    ENDIF
1621  ENDDO
1622 
1623  END SUBROUTINE Init_neighbours
1624#endif
1625!
1626!#########################################################################
1627!
1628  SUBROUTINE interfoce_cpl(itime, dtime, cumul, &
1629      & klon, iim, jjm, nisurf, pctsrf, knon, knindex, rlon, rlat, &
1630      & ocean, npas, nexca, debut, lafin, &
1631      & swdown, lwdown, precip_rain, precip_snow, evap, tsurf, &
1632      & fluxlat, fluxsens, fder, albsol, taux, tauy, &
1633! -- LOOP
1634      & windsp, &
1635! -- LOOP
1636      & zmasq, &
1637      & tsurf_new, alb_new, &
1638      & pctsrf_new)
1639
1640   USE ioipsl
1641   USE mod_phys_lmdz_para, not_use_mpi_root=>mpi_root
1642   
1643   USE iophy
1644
1645#ifdef CPP_PSMILE
1646   USE oasis
1647#endif
1648   USE write_field_phy
1649   implicit none
1650#include "indicesol.inc"
1651#include "YOMCST.inc"
1652! Cette routine sert d'interface entre le modele atmospherique et un
1653! coupleur avec un modele d'ocean 'complet' derriere
1654!
1655! Le modele de glace qu'il est prevu d'utiliser etant couple directement a
1656! l'ocean presentement, on va passer deux fois dans cette routine par pas de
1657! temps physique, une fois avec les points oceans et l'autre avec les points
1658! glace. A chaque pas de temps de couplage, la lecture des champs provenant
1659! du coupleur se fera "dans" l'ocean et l'ecriture des champs a envoyer
1660! au coupleur "dans" la glace. Il faut donc des tableaux de travail "tampons"
1661! dimensionnes sur toute la grille qui remplissent les champs sur les
1662! domaines ocean/glace quand il le faut. Il est aussi necessaire que l'index
1663! ocean soit traiter avant l'index glace (sinon tout intervertir)
1664!
1665!
1666! L. Fairhead 02/2000
1667!
1668! input:
1669!   itime        numero du pas de temps
1670!   iim, jjm     nbres de pts de grille
1671!   dtime        pas de temps de la physique
1672!   klon         nombre total de points de grille
1673!   nisurf       index de la surface a traiter (1 = sol continental)
1674!   pctsrf       tableau des fractions de surface de chaque maille
1675!   knon         nombre de points de la surface a traiter
1676!   knindex      index des points de la surface a traiter
1677!   rlon         longitudes
1678!   rlat         latitudes
1679!   debut        logical: 1er appel a la physique
1680!   lafin        logical: dernier appel a la physique
1681!   ocean        type d'ocean
1682!   nexca        frequence de couplage
1683!   swdown       flux solaire entrant a la surface
1684!   lwdown       flux IR net a la surface
1685!   precip_rain  precipitation liquide
1686!   precip_snow  precipitation solide
1687!   evap         evaporation
1688!   tsurf        temperature de surface
1689!   fder         derivee dF/dT
1690!   albsol       albedo du sol (coherent avec swdown)
1691!   taux         tension de vent en x
1692!   tauy         tension de vent en y
1693! -- LOOP
1694!    windsp       module du vent a 10m
1695! -- LOOP
1696!   nexca        frequence de couplage
1697!   zmasq        masque terre/ocean
1698!
1699!
1700! output:
1701!   tsurf_new    temperature au sol
1702!   alb_new      albedo
1703!   pctsrf_new   nouvelle repartition des surfaces
1704!   alb_ice      albedo de la glace
1705!
1706
1707
1708! Parametres d'entree
1709  integer, intent(IN) :: itime
1710  integer, intent(IN) :: iim, jjm
1711  real, intent(IN) :: dtime
1712  integer, intent(IN) :: klon
1713  integer, intent(IN) :: nisurf
1714  integer, intent(IN) :: knon
1715  real, dimension(klon,nbsrf), intent(IN) :: pctsrf
1716  integer, dimension(klon), intent(in) :: knindex
1717  logical, intent(IN) :: debut, lafin
1718  real, dimension(klon), intent(IN) :: rlon, rlat
1719  character (len = 6)  :: ocean
1720  real, dimension(klon), intent(IN) :: lwdown, swdown
1721  real, dimension(klon), intent(IN) :: precip_rain, precip_snow
1722  real, dimension(klon), intent(IN) :: tsurf, fder, albsol, taux, tauy
1723! -- LOOP
1724   real, dimension(klon), intent(IN) :: windsp
1725! -- LOOP
1726  INTEGER              :: nexca, npas, kstep
1727  real, dimension(klon), intent(IN) :: zmasq
1728  real, dimension(klon), intent(IN) :: fluxlat, fluxsens
1729  logical, intent(IN)               :: cumul
1730  real, dimension(klon), intent(INOUT) :: evap
1731
1732! Parametres de sortie
1733  real, dimension(klon), intent(OUT):: tsurf_new, alb_new
1734  real, dimension(klon,nbsrf), intent(OUT) :: pctsrf_new
1735
1736! Variables locales
1737  integer                    :: j, error, sum_error, ig, cpl_index,i
1738! -- LOOP
1739  INTEGER :: nsrf
1740! -- LOOP
1741  character (len = 20) :: modname = 'interfoce_cpl'
1742  character (len = 80) :: abort_message
1743  logical,save              :: check = .FALSE.
1744! variables pour moyenner les variables de couplage
1745  real, allocatable, dimension(:,:),save :: cpl_sols, cpl_nsol, cpl_rain
1746  real, allocatable, dimension(:,:),save :: cpl_snow, cpl_evap, cpl_tsol
1747  real, allocatable, dimension(:,:),save :: cpl_fder, cpl_albe, cpl_taux
1748! -- LOOP
1749  real, allocatable, dimension(:,:),save :: cpl_windsp
1750! -- LOOP
1751  real, allocatable, dimension(:,:),save :: cpl_tauy
1752  REAL, ALLOCATABLE, DIMENSION(:,:),SAVE :: cpl_rriv, cpl_rcoa, cpl_rlic
1753!!$
1754! variables tampons avant le passage au coupleur
1755  real, allocatable, dimension(:,:,:),save :: tmp_sols, tmp_nsol, tmp_rain
1756  real, allocatable, dimension(:,:,:),save :: tmp_snow, tmp_evap, tmp_tsol
1757  real, allocatable, dimension(:,:,:),save :: tmp_fder, tmp_albe, tmp_taux
1758! -- LOOP
1759  real, allocatable, dimension(:,:,:),save :: tmp_windsp
1760! -- LOOP
1761!!$  real, allocatable, dimension(:,:,:),save :: tmp_tauy, tmp_rriv, tmp_rcoa
1762  REAL, ALLOCATABLE, DIMENSION(:,:,:),SAVE :: tmp_tauy
1763! variables a passer au coupleur
1764!ym  real, dimension(iim, jjm+1) :: wri_sol_ice, wri_sol_sea, wri_nsol_ice
1765!ym  real, dimension(iim, jjm+1) :: wri_nsol_sea, wri_fder_ice, wri_evap_ice
1766!ym  REAL, DIMENSION(iim, jjm+1) :: wri_evap_sea, wri_rcoa, wri_rriv
1767!ym  REAL, DIMENSION(iim, jjm+1) :: wri_rain, wri_snow, wri_taux, wri_tauy
1768!ym  REAL, DIMENSION(iim, jjm+1) :: wri_calv
1769!ym  REAL, DIMENSION(iim, jjm+1) :: wri_tauxx, wri_tauyy, wri_tauzz
1770!ym  REAL, DIMENSION(iim, jjm+1) :: tmp_lon, tmp_lat
1771
1772  real, dimension(iim, jj_nb) :: wri_sol_ice, wri_sol_sea, wri_nsol_ice
1773  real, dimension(iim, jj_nb) :: wri_nsol_sea, wri_fder_ice, wri_evap_ice
1774  REAL, DIMENSION(iim, jj_nb) :: wri_evap_sea, wri_rcoa, wri_rriv
1775  REAL, DIMENSION(iim, jj_nb) :: wri_rain, wri_snow, wri_taux, wri_tauy
1776  REAL, DIMENSION(iim, jj_nb) :: wri_calv
1777  REAL, DIMENSION(iim, jj_nb) :: wri_tauxx, wri_tauyy, wri_tauzz
1778  REAL, DIMENSION(iim, jj_nb) :: tmp_lon, tmp_lat
1779  REAL, DIMENSION(iim, jj_nb) :: wri_windsp
1780
1781! variables relues par le coupleur
1782! read_sic = fraction de glace
1783! read_sit = temperature de glace
1784  real, allocatable, dimension(:,:),save :: read_sst, read_sic, read_sit
1785  real, allocatable, dimension(:,:),save :: read_alb_sic
1786! variable tampon
1787  real, dimension(klon)       :: tamp_sic
1788! sauvegarde des fractions de surface d'un pas de temps a l'autre apres
1789! l'avoir lu
1790  real, allocatable,dimension(:,:),save :: pctsrf_sav
1791  real, dimension(iim, jj_nb, 3) :: tamp_srf
1792  integer, allocatable, dimension(:), save :: tamp_ind
1793  real, allocatable, dimension(:,:),save :: tamp_zmasq
1794  real, dimension(iim, jj_nb) :: deno
1795  integer                     :: idtime
1796  integer, allocatable,dimension(:),save :: unity
1797!
1798  logical, save    :: first_appel = .true.
1799  logical,save          :: print
1800!maf
1801! variables pour avoir une sortie IOIPSL des champs echanges
1802  CHARACTER*80,SAVE :: clintocplnam, clfromcplnam
1803  INTEGER, SAVE :: jf,nhoridct,nidct
1804  INTEGER, SAVE :: nhoridcs,nidcs
1805  INTEGER :: ndexct(iim*(jjm+1)),ndexcs(iim*(jjm+1))
1806  REAL :: zx_lon(iim,jjm+1), zx_lat(iim,jjm+1), zjulian
1807  INTEGER,save :: idayref
1808!med  integer :: itau_w
1809  integer,save :: itau_w
1810! -- LOOP
1811  integer :: nb_interf_cpl
1812! -- LOOP
1813
1814  real :: Up,Down
1815  integer :: ierr
1816  integer :: il_time_secs
1817  real :: tmp_field(klon)
1818 
1819#include "param_cou.h"
1820#include "inc_cpl.h"
1821#include "temps.inc"
1822#include "iniprint.h"
1823
1824#ifdef CPP_PARA
1825  include 'mpif.h'
1826  integer :: status(MPI_STATUS_SIZE)
1827#endif
1828
1829!
1830! Initialisation
1831!
1832  if (check) write(*,*)'Entree ',modname,'nisurf = ',nisurf
1833 
1834  if (first_appel) then
1835    error = 0
1836    allocate(unity(klon), stat = error)
1837    if ( error  /=0) then
1838      abort_message='Pb allocation variable unity'
1839      call abort_gcm(modname,abort_message,1)
1840    endif
1841    allocate(pctsrf_sav(klon,nbsrf), stat = error)
1842    if ( error  /=0) then
1843      abort_message='Pb allocation variable pctsrf_sav'
1844      call abort_gcm(modname,abort_message,1)
1845    endif
1846    pctsrf_sav = 0.
1847
1848    do ig = 1, klon
1849      unity(ig) = ig
1850    enddo
1851    sum_error = 0
1852    allocate(cpl_sols(klon,2), stat = error); sum_error = sum_error + error
1853    allocate(cpl_nsol(klon,2), stat = error); sum_error = sum_error + error
1854    allocate(cpl_rain(klon,2), stat = error); sum_error = sum_error + error
1855    allocate(cpl_snow(klon,2), stat = error); sum_error = sum_error + error
1856    allocate(cpl_evap(klon,2), stat = error); sum_error = sum_error + error
1857    allocate(cpl_tsol(klon,2), stat = error); sum_error = sum_error + error
1858    allocate(cpl_fder(klon,2), stat = error); sum_error = sum_error + error
1859    allocate(cpl_albe(klon,2), stat = error); sum_error = sum_error + error
1860    allocate(cpl_taux(klon,2), stat = error); sum_error = sum_error + error
1861! -- LOOP
1862     allocate(cpl_windsp(klon,2), stat = error); sum_error = sum_error + error
1863! -- LOOP
1864    allocate(cpl_tauy(klon,2), stat = error); sum_error = sum_error + error
1865!ym    ALLOCATE(cpl_rriv(iim,jjm+1), stat=error); sum_error = sum_error + error
1866!ym    ALLOCATE(cpl_rcoa(iim,jjm+1), stat=error); sum_error = sum_error + error
1867!ym    ALLOCATE(cpl_rlic(iim,jjm+1), stat=error); sum_error = sum_error + error
1868    ALLOCATE(cpl_rriv(iim,jj_nb), stat=error); sum_error = sum_error + error
1869    ALLOCATE(cpl_rcoa(iim,jj_nb), stat=error); sum_error = sum_error + error
1870    ALLOCATE(cpl_rlic(iim,jj_nb), stat=error); sum_error = sum_error + error
1871
1872
1873!!
1874!ym    allocate(read_sst(iim, jjm+1), stat = error); sum_error = sum_error + error
1875!ym    allocate(read_sic(iim, jjm+1), stat = error); sum_error = sum_error + error
1876!ym    allocate(read_sit(iim, jjm+1), stat = error); sum_error = sum_error + error
1877!ym    allocate(read_alb_sic(iim, jjm+1), stat = error); sum_error = sum_error + error
1878    allocate(read_sst(iim, jj_nb), stat = error); sum_error = sum_error + error
1879    allocate(read_sic(iim, jj_nb), stat = error); sum_error = sum_error + error
1880    allocate(read_sit(iim, jj_nb), stat = error); sum_error = sum_error + error
1881    allocate(read_alb_sic(iim, jj_nb), stat = error); sum_error = sum_error + error
1882    read_sst=0.
1883    read_sic=0.
1884    read_sit=0.
1885    read_alb_sic=0.
1886    if (sum_error /= 0) then
1887      abort_message='Pb allocation variables couplees'
1888      call abort_gcm(modname,abort_message,1)
1889    endif
1890    cpl_sols = 0.; cpl_nsol = 0.; cpl_rain = 0.; cpl_snow = 0.
1891    cpl_evap = 0.; cpl_tsol = 0.; cpl_fder = 0.; cpl_albe = 0.
1892    cpl_taux = 0.; cpl_tauy = 0.; cpl_rriv = 0.; cpl_rcoa = 0.; cpl_rlic = 0.
1893! -- LOOP
1894     cpl_windsp = 0.
1895! -- LOOP
1896
1897    sum_error = 0
1898    allocate(tamp_ind(klon), stat = error); sum_error = sum_error + error
1899!ym    allocate(tamp_zmasq(iim, jjm+1), stat = error); sum_error = sum_error + error   
1900    allocate(tamp_zmasq(iim, jj_nb), stat = error); sum_error = sum_error + error   
1901    tamp_zmasq=1.
1902   
1903    do ig = 1, klon
1904      tamp_ind(ig) = ig
1905    enddo
1906    call gath2cpl(zmasq, tamp_zmasq, klon, klon, iim, jj_nb, tamp_ind)
1907!
1908! initialisation couplage
1909!
1910    idtime = int(dtime)
1911#ifdef CPP_COUPLE
1912#ifdef CPP_PSMILE
1913   CALL inicma(iim, (jjm+1))
1914#else
1915   if (is_parallel) then
1916      abort_message='coupleur parallele uniquement avec PSMILE'
1917      call abort_gcm(modname,abort_message,1)
1918   endif
1919   call inicma(npas , nexca, idtime,(jjm+1)*iim)
1920#endif
1921#endif
1922!
1923! initialisation sorties netcdf
1924!
1925 !ym  IO de check deconnecte pour le moment en //
1926    IF (is_sequential) THEN
1927    idayref = day_ini
1928    CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
1929    CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlon,zx_lon)
1930    DO i = 1, iim
1931      zx_lon(i,1) = rlon(i+1)
1932      zx_lon(i,jjm+1) = rlon(i+1)
1933    ENDDO
1934    CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlat,zx_lat)
1935    clintocplnam="cpl_atm_tauflx"
1936    CALL histbeg(clintocplnam, iim,zx_lon(:,1),jjm+1,zx_lat(1,:),1,iim,1,jjm+1, &
1937       & itau_phy,zjulian,dtime,nhoridct,nidct)
1938! no vertical axis
1939    CALL histdef(nidct, 'tauxe','tauxe', &
1940         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1941    CALL histdef(nidct, 'tauyn','tauyn', &
1942         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1943    CALL histdef(nidct, 'tmp_lon','tmp_lon', &
1944         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1945    CALL histdef(nidct, 'tmp_lat','tmp_lat', &
1946         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1947    DO jf=1,jpflda2o1 + jpflda2o2
1948      CALL histdef(nidct, cl_writ(jf),cl_writ(jf), &
1949         & "-",iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1950    END DO
1951    CALL histend(nidct)
1952    CALL histsync(nidct)
1953
1954    clfromcplnam="cpl_atm_sst"
1955    CALL histbeg(clfromcplnam, iim,zx_lon(:,1),jjm+1,zx_lat(1,:),1,iim,1,jjm+1, &
1956       & 0,zjulian,dtime,nhoridcs,nidcs)
1957! no vertical axis
1958    DO jf=1,jpfldo2a
1959      CALL histdef(nidcs, cl_read(jf),cl_read(jf), &
1960         & "-",iim, jjm+1, nhoridcs, 1, 1, 1, -99, 32, "inst", dtime,dtime)
1961    END DO
1962    CALL histend(nidcs)
1963    CALL histsync(nidcs)
1964
1965    ENDIF    ! monocpu
1966   
1967! pour simuler la fonte des glaciers antarctiques
1968!
1969!ym => pour le moment, c'est en commentaire, donc je squizze
1970
1971!ym    surf_maille = (4. * rpi * ra**2) / (iim * (jjm +1))
1972!ym    ALLOCATE(coeff_iceberg(iim,jjm+1), stat=error)
1973!ym    if (error /= 0) then
1974!ym      abort_message='Pb allocation variable coeff_iceberg'
1975!ym      call abort_gcm(modname,abort_message,1)
1976!ym    endif
1977!ym    open (12,file='flux_iceberg',form='formatted',status='old')
1978!ym    read (12,*) coeff_iceberg
1979!ym    close (12)
1980!ym    num_antarctic = max(1, count(coeff_iceberg > 0))
1981   
1982    first_appel = .false.
1983  endif ! fin if (first_appel)
1984
1985! Initialisations
1986
1987! calcul des fluxs a passer
1988! -- LOOP
1989  nb_interf_cpl = nb_interf_cpl + 1 
1990  if (check) write(lunout,*)'passage dans interface_surf.F90 :  ',nb_interf_cpl
1991! -- LOOP
1992  cpl_index = 1
1993  if (nisurf == is_sic) cpl_index = 2
1994  if (cumul) then
1995! -- LOOP
1996      if (check) write(lunout,*)'passage dans cumul '
1997      if (check) write(lunout,*)'valeur de cpl_index ', cpl_index
1998! -- LOOP 
1999    if (check) write(*,*) modname, 'cumul des champs'
2000    do ig = 1, knon
2001      cpl_sols(ig,cpl_index) = cpl_sols(ig,cpl_index) &
2002       &                          + swdown(ig)      / FLOAT(nexca)
2003      cpl_nsol(ig,cpl_index) = cpl_nsol(ig,cpl_index) &
2004       &                          + (lwdown(ig) + fluxlat(ig) +fluxsens(ig))&
2005       &                                / FLOAT(nexca)
2006      cpl_rain(ig,cpl_index) = cpl_rain(ig,cpl_index) &
2007       &                          + precip_rain(ig) / FLOAT(nexca)
2008      cpl_snow(ig,cpl_index) = cpl_snow(ig,cpl_index) &
2009       &                          + precip_snow(ig) / FLOAT(nexca)
2010      cpl_evap(ig,cpl_index) = cpl_evap(ig,cpl_index) &
2011       &                          + evap(ig)        / FLOAT(nexca)
2012      cpl_tsol(ig,cpl_index) = cpl_tsol(ig,cpl_index) &
2013       &                          + tsurf(ig)       / FLOAT(nexca)
2014      cpl_fder(ig,cpl_index) = cpl_fder(ig,cpl_index) &
2015       &                          + fder(ig)        / FLOAT(nexca)
2016      cpl_albe(ig,cpl_index) = cpl_albe(ig,cpl_index) &
2017       &                          + albsol(ig)      / FLOAT(nexca)
2018      cpl_taux(ig,cpl_index) = cpl_taux(ig,cpl_index) &
2019       &                          + taux(ig)        / FLOAT(nexca)
2020      cpl_tauy(ig,cpl_index) = cpl_tauy(ig,cpl_index) &
2021       &                          + tauy(ig)        / FLOAT(nexca)
2022! -- LOOP
2023      IF (cpl_index .EQ. 1) THEN
2024      cpl_windsp(ig,cpl_index) = cpl_windsp(ig,cpl_index) &
2025       &                          + windsp(ig)      / FLOAT(nexca)
2026      ENDIF
2027! -- LOOP
2028    enddo
2029    IF (cpl_index .EQ. 1) THEN
2030        cpl_rriv(:,:) = cpl_rriv(:,:) + tmp_rriv(:,:) / FLOAT(nexca)
2031        cpl_rcoa(:,:) = cpl_rcoa(:,:) + tmp_rcoa(:,:) / FLOAT(nexca)
2032        cpl_rlic(:,:) = cpl_rlic(:,:) + tmp_rlic(:,:) / FLOAT(nexca)
2033    ENDIF
2034  endif
2035
2036  if (mod(itime, nexca) == 1) then
2037!
2038! Demande des champs au coupleur
2039!
2040! Si le domaine considere est l'ocean, on lit les champs venant du coupleur
2041!
2042    if (nisurf == is_oce .and. .not. cumul) then
2043      if (check) write(*,*)'rentree fromcpl, itime-1 = ',itime-1
2044#ifdef CPP_COUPLE
2045#ifdef CPP_PSMILE
2046      il_time_secs=(itime-1)*dtime
2047      CALL fromcpl(il_time_secs, iim, jj_nb,                           &
2048     &        read_sst, read_sic, read_sit, read_alb_sic)
2049#else
2050     if (is_parallel) then
2051        abort_message='coupleur parallele uniquement avec PSMILE'
2052        call abort_gcm(modname,abort_message,1)
2053     endif
2054
2055      call fromcpl(itime-1,(jjm+1)*iim,                                  &
2056     &        read_sst, read_sic, read_sit, read_alb_sic)
2057#endif
2058#endif
2059!
2060! sorties NETCDF des champs recus
2061!
2062     if (is_sequential) THEN
2063       ndexcs(:)=0
2064       itau_w = itau_phy + itime
2065       CALL histwrite(nidcs,cl_read(1),itau_w,read_sst,iim*(jjm+1),ndexcs)
2066       CALL histwrite(nidcs,cl_read(2),itau_w,read_sic,iim*(jjm+1),ndexcs)
2067       CALL histwrite(nidcs,cl_read(3),itau_w,read_alb_sic,iim*(jjm+1),ndexcs)
2068       CALL histwrite(nidcs,cl_read(4),itau_w,read_sit,iim*(jjm+1),ndexcs)
2069       CALL histsync(nidcs)
2070     endif
2071! pas utile      IF (npas-itime.LT.nexca )CALL histclo(nidcs)
2072
2073!ym      do j = 1, jjm + 1
2074       do j = 1, jj_nb
2075         do ig = 1, iim
2076          if (abs(1. - read_sic(ig,j)) < 0.00001) then
2077            read_sst(ig,j) = RTT - 1.8
2078            read_sit(ig,j) = read_sit(ig,j) / read_sic(ig,j)
2079            read_alb_sic(ig,j) = read_alb_sic(ig,j) / read_sic(ig,j)
2080          else if (abs(read_sic(ig,j)) < 0.00001) then
2081            read_sst(ig,j) = read_sst(ig,j) / (1. - read_sic(ig,j))
2082            read_sit(ig,j) = read_sst(ig,j)
2083            read_alb_sic(ig,j) =  0.6
2084          else
2085            read_sst(ig,j) = read_sst(ig,j) / (1. - read_sic(ig,j))
2086            read_sit(ig,j) = read_sit(ig,j) / read_sic(ig,j)
2087            read_alb_sic(ig,j) = read_alb_sic(ig,j) / read_sic(ig,j)
2088          endif
2089        enddo
2090      enddo
2091!
2092! transformer read_sic en pctsrf_sav
2093!
2094      call cpl2gath(read_sic, tamp_sic , klon, klon,iim,jj_nb, unity)
2095      do ig = 1, klon
2096        IF (pctsrf(ig,is_oce) > epsfra .OR.            &
2097     &             pctsrf(ig,is_sic) > epsfra) THEN
2098          pctsrf_sav(ig,is_sic) = (pctsrf(ig,is_oce) + pctsrf(ig,is_sic)) &
2099     &                               * tamp_sic(ig)
2100          pctsrf_sav(ig,is_oce) = (pctsrf(ig,is_oce) + pctsrf(ig,is_sic)) &
2101     &                        - pctsrf_sav(ig,is_sic)
2102        endif
2103      enddo
2104!
2105! Pour rattraper des erreurs d'arrondis
2106!
2107      where (abs(pctsrf_sav(:,is_sic)) .le. 2.*epsilon(pctsrf_sav(1,is_sic)))
2108        pctsrf_sav(:,is_sic) = 0.
2109        pctsrf_sav(:,is_oce) = pctsrf(:,is_oce) + pctsrf(:,is_sic)
2110      endwhere
2111      where (abs(pctsrf_sav(:,is_oce)) .le. 2.*epsilon(pctsrf_sav(1,is_oce)))
2112        pctsrf_sav(:,is_sic) = pctsrf(:,is_oce) + pctsrf(:,is_sic)
2113        pctsrf_sav(:,is_oce) = 0.
2114      endwhere
2115      if (minval(pctsrf_sav(:,is_oce)) < 0.) then
2116        write(*,*)'Pb fraction ocean inferieure a 0'
2117        write(*,*)'au point ',minloc(pctsrf_sav(:,is_oce))
2118        write(*,*)'valeur = ',minval(pctsrf_sav(:,is_oce))
2119        abort_message = 'voir ci-dessus'
2120        call abort_gcm(modname,abort_message,1)
2121      endif
2122      if (minval(pctsrf_sav(:,is_sic)) < 0.) then
2123        write(*,*)'Pb fraction glace inferieure a 0'
2124        write(*,*)'au point ',minloc(pctsrf_sav(:,is_sic))
2125        write(*,*)'valeur = ',minval(pctsrf_sav(:,is_sic))
2126        abort_message = 'voir ci-dessus'
2127        call abort_gcm(modname,abort_message,1)
2128      endif
2129    endif
2130  endif                         ! fin mod(itime, nexca) == 1
2131
2132  if (mod(itime, nexca) == 0) then
2133!
2134! allocation memoire
2135    if (nisurf == is_oce .and. (.not. cumul) ) then
2136      sum_error = 0
2137      allocate(tmp_sols(iim,jj_nb,2), stat=error); sum_error = sum_error + error
2138      allocate(tmp_nsol(iim,jj_nb,2), stat=error); sum_error = sum_error + error
2139      allocate(tmp_rain(iim,jj_nb,2), stat=error); sum_error = sum_error + error
2140      allocate(tmp_snow(iim,jj_nb,2), stat=error); sum_error = sum_error + error
2141      allocate(tmp_evap(iim,jj_nb,2), stat=error); sum_error = sum_error + error
2142      allocate(tmp_tsol(iim,jj_nb,2), stat=error); sum_error = sum_error + error
2143      allocate(tmp_fder(iim,jj_nb,2), stat=error); sum_error = sum_error + error
2144      allocate(tmp_albe(iim,jj_nb,2), stat=error); sum_error = sum_error + error
2145      allocate(tmp_taux(iim,jj_nb,2), stat=error); sum_error = sum_error + error
2146      allocate(tmp_tauy(iim,jj_nb,2), stat=error); sum_error = sum_error + error
2147! -- LOOP
2148       allocate(tmp_windsp(iim,jj_nb,2), stat=error); sum_error = sum_error + error
2149! -- LOOP
2150!!$      allocate(tmp_rriv(iim,jjm+1,2), stat=error); sum_error = sum_error + error
2151!!$      allocate(tmp_rcoa(iim,jjm+1,2), stat=error); sum_error = sum_error + error
2152      if (sum_error /= 0) then
2153        abort_message='Pb allocation variables couplees pour l''ecriture'
2154        call abort_gcm(modname,abort_message,1)
2155      endif
2156    endif
2157
2158!
2159! Mise sur la bonne grille des champs a passer au coupleur
2160!
2161    cpl_index = 1
2162    if (nisurf == is_sic) cpl_index = 2
2163    call gath2cpl(cpl_sols(1,cpl_index), tmp_sols(1,1,cpl_index), klon, knon,iim,jj_nb,                  knindex)
2164    call gath2cpl(cpl_nsol(1,cpl_index), tmp_nsol(1,1,cpl_index), klon, knon,iim,jj_nb,                  knindex)
2165    call gath2cpl(cpl_rain(1,cpl_index), tmp_rain(1,1,cpl_index), klon, knon,iim,jj_nb,                  knindex)
2166    call gath2cpl(cpl_snow(1,cpl_index), tmp_snow(1,1,cpl_index), klon, knon,iim,jj_nb,                  knindex)
2167    call gath2cpl(cpl_evap(1,cpl_index), tmp_evap(1,1,cpl_index), klon, knon,iim,jj_nb,                  knindex)
2168    call gath2cpl(cpl_tsol(1,cpl_index), tmp_tsol(1,1,cpl_index), klon, knon,iim,jj_nb,                  knindex)
2169    call gath2cpl(cpl_fder(1,cpl_index), tmp_fder(1,1,cpl_index), klon, knon,iim,jj_nb,                  knindex)
2170    call gath2cpl(cpl_albe(1,cpl_index), tmp_albe(1,1,cpl_index), klon, knon,iim,jj_nb,                  knindex)
2171    call gath2cpl(cpl_taux(1,cpl_index), tmp_taux(1,1,cpl_index), klon, knon,iim,jj_nb,                  knindex)
2172    call gath2cpl(cpl_tauy(1,cpl_index), tmp_tauy(1,1,cpl_index), klon, knon,iim,jj_nb,                  knindex)
2173! -- LOOP
2174     call gath2cpl(cpl_windsp(1,cpl_index), tmp_windsp(1,1,cpl_index), klon, knon,iim,jj_nb,            knindex)
2175! -- LOOP
2176
2177!
2178! Si le domaine considere est la banquise, on envoie les champs au coupleur
2179!
2180    if (nisurf == is_sic .and. cumul) then
2181      wri_rain = 0.; wri_snow = 0.; wri_rcoa = 0.; wri_rriv = 0.
2182      wri_taux = 0.; wri_tauy = 0.
2183! -- LOOP
2184       wri_windsp = 0.
2185! -- LOOP     
2186      call gath2cpl(pctsrf(1,is_oce), tamp_srf(1,1,1), klon, klon, iim, jj_nb, tamp_ind)
2187      call gath2cpl(pctsrf(1,is_sic), tamp_srf(1,1,2), klon, klon, iim, jj_nb, tamp_ind)
2188
2189      wri_sol_ice = tmp_sols(:,:,2)
2190      wri_sol_sea = tmp_sols(:,:,1)
2191      wri_nsol_ice = tmp_nsol(:,:,2)
2192      wri_nsol_sea = tmp_nsol(:,:,1)
2193      wri_fder_ice = tmp_fder(:,:,2)
2194      wri_evap_ice = tmp_evap(:,:,2)
2195      wri_evap_sea = tmp_evap(:,:,1)
2196! -- LOOP
2197       wri_windsp = tmp_windsp(:,:,1)
2198! -- LOOP
2199
2200!!$PB
2201      wri_rriv = cpl_rriv(:,:)
2202      wri_rcoa = cpl_rcoa(:,:)
2203
2204!ym  !! ATTENTION ICI
2205     
2206!ym      DO j = 1, jjm + 1
2207!ym        wri_calv(:,j) = sum(cpl_rlic(:,j)) / iim
2208!ym      enddo
2209
2210!Essai OM+JLD : ca marche !!!! (17 mars 2006)
2211      tamp_srf(:,:,3)=0.
2212      CALL gath2cpl( pctsrf(1,is_lic), tamp_srf(1,1,3), klon, klon, iim, jj_nb, tamp_ind)
2213
2214!YM pour retrouver resultat avant tamp_srf(:,3)=1.
2215     
2216      DO j = 1, jj_nb
2217         wri_calv(:,j) = DOT_PRODUCT (cpl_rlic(1:iim,j), tamp_srf(1:iim,j,3)) / REAL(iim)
2218      ENDDO
2219
2220!ym      wri_calv(:,:)=0.
2221!ym      DO j = 1, jjphy_nb
2222!ym        wri_calv(:,j) = sum(cpl_rlic(:,j))/iim
2223!ym      enddo
2224
2225      IF (is_parallel) THEN
2226        if (.NOT.is_north_pole) then
2227#ifdef CPP_PARA
2228          call MPI_RECV(Up,1,MPI_REAL_LMDZ,mpi_rank-1,1234,COMM_LMDZ_PHY,status,ierr)
2229          call MPI_SEND(wri_calv(1,1),1,MPI_REAL_LMDZ,mpi_rank-1,1234,COMM_LMDZ_PHY,ierr)
2230#endif
2231        endif
2232       
2233        if (.NOT.is_south_pole) then
2234#ifdef CPP_PARA
2235          call MPI_SEND(wri_calv(1,jj_nb),1,MPI_REAL_LMDZ,mpi_rank+1,1234,COMM_LMDZ_PHY,ierr) 
2236          call MPI_RECV(down,1,MPI_REAL_LMDZ,mpi_rank+1,1234,COMM_LMDZ_PHY,status,ierr)
2237#endif
2238        endif
2239       
2240        if (mpi_rank /=0 .and. ii_begin /=1) then
2241          Up=Up+wri_calv(iim,1)
2242          wri_calv(:,1)=Up
2243        endif
2244     
2245        if (mpi_rank /=mpi_size-1 .and. ii_end /= iim) then
2246          Down=Down+wri_calv(1,jj_nb)
2247          wri_calv(:,jj_nb)=Down         
2248        endif
2249      ENDIF
2250     
2251      where (tamp_zmasq /= 1.)
2252        deno =  tamp_srf(:,:,1) + tamp_srf(:,:,2)
2253        wri_rain = tmp_rain(:,:,1) * tamp_srf(:,:,1) / deno +    &
2254      &            tmp_rain(:,:,2) * tamp_srf(:,:,2) / deno
2255        wri_snow = tmp_snow(:,:,1) * tamp_srf(:,:,1) / deno +    &
2256      &            tmp_snow(:,:,2) * tamp_srf(:,:,2) / deno
2257        wri_taux = tmp_taux(:,:,1) * tamp_srf(:,:,1) / deno +    &
2258      &            tmp_taux(:,:,2) * tamp_srf(:,:,2) / deno
2259        wri_tauy = tmp_tauy(:,:,1) * tamp_srf(:,:,1) / deno +    &
2260      &            tmp_tauy(:,:,2) * tamp_srf(:,:,2) / deno
2261      endwhere
2262!
2263! pour simuler la fonte des glaciers antarctiques
2264!
2265!$$$        wri_rain = wri_rain      &
2266!$$$      &     + coeff_iceberg * cte_flux_iceberg / (num_antarctic * surf_maille)
2267!      wri_calv = coeff_iceberg * cte_flux_iceberg / (num_antarctic * surf_maille)
2268!
2269! on passe les coordonnees de la grille
2270!
2271
2272!ym      CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlon,tmp_lon)
2273!ym      CALL gr_fi_ecrit(1,klon,iim,jjm+1,rlat,tmp_lat)
2274
2275!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2276!!! ATENTION A NE PAS OUBLIER
2277!!! REMPLACER phy2dyn par grid1DTo2D_mpi
2278!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2279
2280       CALL Grid1DTo2D_mpi(rlon,tmp_lon)
2281       CALL Grid1DTo2D_mpi(rlat,tmp_lat)
2282
2283
2284!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2285     IF (is_sequential) THEN
2286       IF (is_north_pole) tmp_lon(:,1) = tmp_lon(:,2)
2287       IF (is_south_pole) tmp_lon(:,jjm + 1) = tmp_lon(:,jjm)
2288     ENDIF
2289!
2290! sortie netcdf des champs pour le changement de repere
2291!
2292      IF (is_sequential) THEN
2293        ndexct(:)=0
2294        CALL histwrite(nidct,'tauxe',itau_w,wri_taux,iim*(jjm+1),ndexct)
2295        CALL histwrite(nidct,'tauyn',itau_w,wri_tauy,iim*(jjm+1),ndexct)
2296        CALL histwrite(nidct,'tmp_lon',itau_w,tmp_lon,iim*(jjm+1),ndexct)
2297        CALL histwrite(nidct,'tmp_lat',itau_w,tmp_lat,iim*(jjm+1),ndexct)
2298      ENDIF 
2299!
2300! calcul 3 coordonnees du vent
2301!
2302      CALL atm2geo (iim , jj_nb, wri_taux, wri_tauy, tmp_lon, tmp_lat, &
2303         & wri_tauxx, wri_tauyy, wri_tauzz )
2304!
2305! sortie netcdf des champs apres changement de repere et juste avant
2306! envoi au coupleur
2307!
2308    IF (is_sequential) THEN
2309      CALL histwrite(nidct,cl_writ(8),itau_w,wri_sol_ice,iim*(jjm+1),ndexct)
2310      CALL histwrite(nidct,cl_writ(9),itau_w,wri_sol_sea,iim*(jjm+1),ndexct)
2311      CALL histwrite(nidct,cl_writ(10),itau_w,wri_nsol_ice,iim*(jjm+1),ndexct)
2312      CALL histwrite(nidct,cl_writ(11),itau_w,wri_nsol_sea,iim*(jjm+1),ndexct)
2313      CALL histwrite(nidct,cl_writ(12),itau_w,wri_fder_ice,iim*(jjm+1),ndexct)
2314      CALL histwrite(nidct,cl_writ(13),itau_w,wri_evap_ice,iim*(jjm+1),ndexct)
2315      CALL histwrite(nidct,cl_writ(14),itau_w,wri_evap_sea,iim*(jjm+1),ndexct)
2316      CALL histwrite(nidct,cl_writ(15),itau_w,wri_rain,iim*(jjm+1),ndexct)
2317      CALL histwrite(nidct,cl_writ(16),itau_w,wri_snow,iim*(jjm+1),ndexct)
2318      CALL histwrite(nidct,cl_writ(17),itau_w,wri_rcoa,iim*(jjm+1),ndexct)
2319      CALL histwrite(nidct,cl_writ(18),itau_w,wri_rriv,iim*(jjm+1),ndexct)
2320      CALL histwrite(nidct,cl_writ(19),itau_w,wri_calv,iim*(jjm+1),ndexct)
2321      CALL histwrite(nidct,cl_writ(1),itau_w,wri_tauxx,iim*(jjm+1),ndexct)
2322      CALL histwrite(nidct,cl_writ(2),itau_w,wri_tauyy,iim*(jjm+1),ndexct)
2323      CALL histwrite(nidct,cl_writ(3),itau_w,wri_tauzz,iim*(jjm+1),ndexct)
2324      CALL histwrite(nidct,cl_writ(4),itau_w,wri_tauxx,iim*(jjm+1),ndexct)
2325      CALL histwrite(nidct,cl_writ(5),itau_w,wri_tauyy,iim*(jjm+1),ndexct)
2326      CALL histwrite(nidct,cl_writ(6),itau_w,wri_tauzz,iim*(jjm+1),ndexct)
2327! -- LOOP
2328      CALL histwrite(nidct,cl_writ(7),itau_w,wri_windsp,iim*(jjm+1),ndexct)
2329! -- LOOP
2330      CALL histsync(nidct)
2331    ENDIF
2332! pas utile      IF (lafin) CALL histclo(nidct)
2333#ifdef CPP_COUPLE
2334#ifdef CPP_PSMILE
2335      il_time_secs=(itime-1)*dtime
2336     
2337      CALL intocpl(il_time_secs, iim, jjm+1, wri_sol_ice, wri_sol_sea, wri_nsol_ice,&
2338      & wri_nsol_sea, wri_fder_ice, wri_evap_ice, wri_evap_sea, wri_rain, &
2339      & wri_snow, wri_rcoa, wri_rriv, wri_calv, wri_tauxx, wri_tauyy,     &
2340      & wri_tauzz, wri_tauxx, wri_tauyy, wri_tauzz,                       &
2341! -- LOOP
2342      & wri_windsp,lafin)
2343! -- LOOP
2344#else
2345      call intocpl(itime, (jjm+1)*iim, wri_sol_ice, wri_sol_sea, wri_nsol_ice,&
2346      & wri_nsol_sea, wri_fder_ice, wri_evap_ice, wri_evap_sea, wri_rain, &
2347      & wri_snow, wri_rcoa, wri_rriv, wri_calv, wri_tauxx, wri_tauyy,     &
2348      & wri_tauzz, wri_tauxx, wri_tauyy, wri_tauzz,                       &
2349! -- LOOP
2350      & wri_windsp,lafin)
2351! -- LOOP
2352#endif
2353#endif
2354!
2355      cpl_sols = 0.; cpl_nsol = 0.; cpl_rain = 0.; cpl_snow = 0.
2356      cpl_evap = 0.; cpl_tsol = 0.; cpl_fder = 0.; cpl_albe = 0.
2357      cpl_taux = 0.; cpl_tauy = 0.; cpl_rriv = 0.; cpl_rcoa = 0.; cpl_rlic = 0.
2358! -- LOOP
2359      cpl_windsp = 0.
2360! -- LOOP
2361!
2362! deallocation memoire variables temporaires
2363!
2364      sum_error = 0
2365      deallocate(tmp_sols, stat=error); sum_error = sum_error + error
2366      deallocate(tmp_nsol, stat=error); sum_error = sum_error + error
2367      deallocate(tmp_rain, stat=error); sum_error = sum_error + error
2368      deallocate(tmp_snow, stat=error); sum_error = sum_error + error
2369      deallocate(tmp_evap, stat=error); sum_error = sum_error + error
2370      deallocate(tmp_fder, stat=error); sum_error = sum_error + error
2371      deallocate(tmp_tsol, stat=error); sum_error = sum_error + error
2372      deallocate(tmp_albe, stat=error); sum_error = sum_error + error
2373      deallocate(tmp_taux, stat=error); sum_error = sum_error + error
2374      deallocate(tmp_tauy, stat=error); sum_error = sum_error + error
2375! -- LOOP
2376      deallocate(tmp_windsp, stat=error); sum_error = sum_error + error
2377! -- LOOP
2378!!$PB
2379!!$      deallocate(tmp_rriv, stat=error); sum_error = sum_error + error
2380!!$      deallocate(tmp_rcoa, stat=error); sum_error = sum_error + error
2381      if (sum_error /= 0) then
2382        abort_message='Pb deallocation variables couplees'
2383        call abort_gcm(modname,abort_message,1)
2384      endif
2385
2386    endif
2387
2388  endif            ! fin (mod(itime, nexca) == 0)
2389!
2390! on range les variables lues/sauvegardees dans les bonnes variables de sortie
2391!
2392  if (nisurf == is_oce) then
2393    call cpl2gath(read_sst, tsurf_new, klon, knon,iim,jj_nb, knindex)
2394  else if (nisurf == is_sic) then
2395    call cpl2gath(read_sit, tsurf_new, klon, knon,iim,jj_nb, knindex)
2396    call cpl2gath(read_alb_sic, alb_new, klon, knon,iim,jj_nb, knindex)
2397  endif
2398  pctsrf_new(:,nisurf) = pctsrf_sav(:,nisurf)
2399 
2400  if (mod(itime, nexca) == -1) then
2401    tmp_field=0.
2402    do i = 1, knon
2403      ig = knindex(i)
2404      tmp_field(ig) = 1.
2405    enddo   
2406!ym    call WriteField_phy('knindex',tmp_field,1)
2407   
2408    tmp_field=0.
2409    do i = 1, knon
2410      ig = knindex(i)
2411      tmp_field(ig) = tsurf_new(i)
2412    enddo   
2413!ym    call WriteField_phy('tsurf_new',tmp_field,1)
2414   
2415    tmp_field=0.
2416    do i = 1, knon
2417      ig = knindex(i)
2418      tmp_field(ig) = alb_new(i)
2419    enddo   
2420!ym    call WriteField_phy('alb_new',tmp_field,1)
2421   
2422!    tmp_field=0.
2423!   do i = 1, knon
2424!      ig = knindex(i)
2425!      tmp_field(ig) = pctsrf_new(i,nisurf)
2426 !   enddo   
2427!ym    call WriteField_phy('pctsrf_new', pctsrf_new(:,nisurf),1)
2428  endif
2429!ym  do j=1,jjphy_nb
2430!ym    do i=1,iim
2431!ym      print *,phy_rank,'read_sst(',i,',',j,')=',read_sst(i,j)
2432!ym    enddo
2433!ym  enddo
2434 
2435!ym  do i=1,knon
2436!ym    print *,phy_rank,'tsurf_new(',i,')=',tsurf_new(i)
2437!ym  enddo
2438!  if (lafin) call quitcpl
2439
2440  END SUBROUTINE interfoce_cpl
2441!
2442!#########################################################################
2443!
2444   SUBROUTINE interfoce_slab(klon, debut, itap, dtime, ijour, &
2445 & radsol, fluxo, fluxg, pctsrf, &
2446 & tslab, seaice, pctsrf_slab)
2447!
2448! Cette routine calcule la temperature d'un slab ocean, la glace de mer
2449! et les pourcentages de la maille couverte par l'ocean libre et/ou
2450! la glace de mer pour un "slab" ocean de 50m
2451!
2452! Conception: Laurent Li
2453! Re-ecriture + adaptation LMDZ4: I. Musat
2454!
2455! input:
2456!   klon         nombre total de points de grille
2457!   debut        logical: 1er appel a la physique
2458!   itap         numero du pas de temps
2459!   dtime        pas de temps de la physique (en s)
2460!   ijour        jour dans l'annee en cours
2461!   radsol       rayonnement net au sol (LW + SW)
2462!   fluxo        flux turbulent (sensible + latent) sur les mailles oceaniques
2463!   fluxg        flux de conduction entre la surface de la glace de mer et l'ocean
2464!   pctsrf       tableau des pourcentages de surface de chaque maille
2465! output:
2466!   tslab        temperature de l'ocean libre
2467!   seaice       glace de mer (kg/m2)
2468!   pctsrf_slab  "pourcentages" (valeurs entre 0. et 1.) surfaces issus du slab
2469!
2470#include "indicesol.inc"
2471#include "clesphys.inc"
2472! Parametres d'entree
2473  integer, intent(IN) :: klon
2474  logical, intent(IN) :: debut
2475  INTEGER, intent(IN) :: itap
2476  REAL, intent(IN) :: dtime
2477  INTEGER, intent(IN) :: ijour
2478  REAL, dimension(klon), intent(IN) :: radsol
2479  REAL, dimension(klon), intent(IN) :: fluxo
2480  REAL, dimension(klon), intent(IN) :: fluxg
2481  real, dimension(klon, nbsrf), intent(IN) :: pctsrf
2482! Parametres de sortie
2483  real, dimension(klon), intent(INOUT) :: tslab
2484  real, dimension(klon), intent(INOUT)        :: seaice ! glace de mer (kg/m2)
2485  real, dimension(klon, nbsrf), intent(OUT) :: pctsrf_slab
2486!
2487! Variables locales :
2488  REAL :: amn, amx
2489  INTEGER, save :: lmt_pas, julien, idayvrai
2490!$OMP THREADPRIVATE(lmt_pas, julien, idayvrai)
2491  REAL, parameter :: unjour=86400.
2492  real, allocatable, dimension(:), save :: tmp_tslab, tmp_seaice
2493  REAL, allocatable, dimension(:), save :: slab_bils
2494  REAL, allocatable, dimension(:), save :: lmt_bils
2495!$OMP THREADPRIVATE(tmp_tslab, tmp_seaice,slab_bils,lmt_bils)
2496  logical,save              :: check = .false.
2497!$OMP THREADPRIVATE(check)
2498
2499!
2500  REAL, parameter :: cyang=50.0 * 4.228e+06 ! capacite calorifique volumetrique de l'eau J/(m2 K)
2501  REAL, parameter :: cbing=0.334e+05        ! J/kg
2502  real, dimension(klon)                 :: siceh !hauteur de la glace de mer (m)
2503  INTEGER :: i
2504  integer :: sum_error, error
2505  REAL :: zz, za, zb
2506!
2507  character (len = 80) :: abort_message
2508  character (len = 20) :: modname = 'interfoce_slab'
2509!
2510  julien = MOD(ijour,360)
2511  sum_error = 0
2512  IF (debut) THEN
2513   allocate(slab_bils(klon), stat = error); sum_error = sum_error + error
2514   allocate(lmt_bils(klon), stat = error); sum_error = sum_error + error
2515   allocate(tmp_tslab(klon), stat = error); sum_error = sum_error + error
2516   allocate(tmp_seaice(klon), stat = error); sum_error = sum_error + error
2517   if (sum_error /= 0) then
2518    abort_message='Pb allocation var. slab_bils,lmt_bils,tmp_tslab,tmp_seaice'
2519    call abort_gcm(modname,abort_message,1)
2520   endif
2521   tmp_tslab=tslab
2522   tmp_seaice=seaice
2523   lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour
2524!
2525   IF (check) THEN
2526    PRINT*,'interfoce_slab klon, debut, itap, dtime, ijour, &
2527 &          lmt_pas ', klon, debut, itap, dtime, ijour, &
2528 &          lmt_pas
2529   ENDIF !check
2530!
2531   PRINT*, '************************'
2532   PRINT*, 'SLAB OCEAN est actif, prenez precautions !'
2533   PRINT*, '************************'
2534!
2535! a mettre un slab_bils aussi en force !!!
2536!
2537    DO i = 1, klon
2538     slab_bils(i) = 0.0
2539    ENDDO
2540!
2541   ENDIF !debut
2542!
2543   IF (check ) THEN
2544    amn=MIN(tmp_tslab(1),1000.)
2545    amx=MAX(tmp_tslab(1),-1000.)
2546    DO i=2, klon
2547     amn=MIN(tmp_tslab(i),amn)
2548     amx=MAX(tmp_tslab(i),amx)
2549    ENDDO
2550!
2551    PRINT*,' debut min max tslab',amn,amx
2552!
2553!!
2554    PRINT*,' itap,lmt_pas unjour',itap,lmt_pas,unjour
2555   ENDIF
2556!!
2557!
2558   pctsrf_slab(1:klon,1:nbsrf) = pctsrf(1:klon,1:nbsrf)
2559!
2560! lecture du bilan au sol lmt_bils issu d'une simulation forcee en debut de journee
2561!
2562   IF (MOD(itap,lmt_pas) .EQ. 1) THEN !1er pas de temps de la journee
2563    idayvrai = ijour
2564    CALL condsurf(julien,idayvrai, lmt_bils)
2565   ENDIF !(MOD(itap-1,lmt_pas) .EQ. 0) THEN
2566
2567   DO i = 1, klon
2568     IF((pctsrf_slab(i,is_oce).GT.epsfra).OR. &
2569     &  (pctsrf_slab(i,is_sic).GT.epsfra)) THEN
2570!
2571! fabriquer de la glace si congelation atteinte:
2572!
2573      IF (tmp_tslab(i).LT.(RTT-1.8)) THEN
2574       zz =  (RTT-1.8)-tmp_tslab(i)
2575       tmp_seaice(i) = tmp_seaice(i) + cyang/cbing * zz
2576       seaice(i) = tmp_seaice(i)
2577       tmp_tslab(i) = RTT-1.8
2578      ENDIF
2579!
2580! faire fondre de la glace si temperature est superieure a 0:
2581!
2582      IF ((tmp_tslab(i).GT.RTT) .AND. (tmp_seaice(i).GT.0.0)) THEN
2583       zz = cyang/cbing * (tmp_tslab(i)-RTT)
2584       zz = MIN(zz,tmp_seaice(i))
2585       tmp_seaice(i) = tmp_seaice(i) - zz
2586       seaice(i) = tmp_seaice(i)
2587       tmp_tslab(i) = tmp_tslab(i) - zz*cbing/cyang
2588      ENDIF
2589!
2590! limiter la glace de mer a 10 metres (10000 kg/m2)
2591!
2592      IF(tmp_seaice(i).GT.45.) THEN
2593       tmp_seaice(i) = MIN(tmp_seaice(i),10000.0)
2594      ELSE
2595       tmp_seaice(i) = 0.
2596      ENDIF
2597      seaice(i) = tmp_seaice(i)
2598      siceh(i)=tmp_seaice(i)/1000. !en metres
2599!
2600! determiner la nature du sol (glace de mer ou ocean libre):
2601!
2602! on fait dependre la fraction de seaice "pctsrf(i,is_sic)"
2603! de l'epaisseur de seaice :
2604! pctsrf(i,is_sic)=1. si l'epaisseur de la glace de mer est >= a 20cm
2605! et pctsrf(i,is_sic) croit lineairement avec seaice de 0. a 20cm d'epaisseur
2606!
2607
2608     IF(.NOT.ok_slab_sicOBS) then
2609      pctsrf_slab(i,is_sic)=MIN(siceh(i)/0.20, &
2610     &                      1.-(pctsrf_slab(i,is_ter)+pctsrf_slab(i,is_lic)))
2611      pctsrf_slab(i,is_oce)=1.0 - &
2612     &      (pctsrf_slab(i,is_ter)+pctsrf_slab(i,is_lic)+pctsrf_slab(i,is_sic))
2613     ELSE
2614      IF (i.EQ.1) print*,'cas ok_slab_sicOBS TRUE : passe sur la modif.'
2615     ENDIF !(.NOT.ok_slab_sicOBS) then
2616     ENDIF !pctsrf
2617   ENDDO
2618!
2619! Calculer le bilan du flux de chaleur au sol :
2620!
2621   DO i = 1, klon
2622    za = radsol(i) + fluxo(i)
2623    zb = fluxg(i)
2624    IF((pctsrf_slab(i,is_oce).GT.epsfra).OR. &
2625   &   (pctsrf_slab(i,is_sic).GT.epsfra)) THEN
2626     slab_bils(i)=slab_bils(i)+(za*pctsrf_slab(i,is_oce) &
2627   &             +zb*pctsrf_slab(i,is_sic))/ FLOAT(lmt_pas)
2628    ENDIF
2629   ENDDO !klon
2630!
2631! calcul tslab
2632!
2633   IF (MOD(itap,lmt_pas).EQ.0) THEN !fin de journee
2634!
2635! calcul tslab
2636    amn=MIN(tmp_tslab(1),1000.)
2637    amx=MAX(tmp_tslab(1),-1000.)
2638    DO i = 1, klon
2639      IF ((pctsrf_slab(i,is_oce).GT.epsfra).OR. &
2640     &    (pctsrf_slab(i,is_sic).GT.epsfra)) THEN
2641       tmp_tslab(i) = tmp_tslab(i) + &
2642     & (slab_bils(i)-lmt_bils(i)) &
2643     &                         /cyang*unjour
2644! on remet l'accumulation a 0
2645       slab_bils(i) = 0.
2646      ENDIF !pctsrf
2647!
2648      IF (check) THEN
2649       IF(i.EQ.1) THEN 
2650        PRINT*,'i tmp_tslab MOD(itap,lmt_pas).EQ.0 sicINTER',i,itap, &
2651      & tmp_tslab(i), tmp_seaice(i)
2652       ENDIF
2653!
2654       amn=MIN(tmp_tslab(i),amn)
2655       amx=MAX(tmp_tslab(i),amx)
2656      ENDIF
2657    ENDDO !klon
2658   ENDIF !(MOD(itap,lmt_pas).EQ.0) THEN
2659!
2660   IF ( check ) THEN
2661    PRINT*,'fin min max tslab',amn,amx
2662   ENDIF
2663!
2664   tslab = tmp_tslab
2665   seaice = tmp_seaice
2666  END SUBROUTINE interfoce_slab
2667!
2668!#########################################################################
2669!
2670  SUBROUTINE interfoce_lim(itime, dtime, jour, &
2671     & klon, nisurf, knon, knindex, &
2672     & debut,  &
2673     & lmt_sst_p, pctsrf_new_p)
2674     
2675     USE mod_grid_phy_lmdz
2676     USE mod_phys_lmdz_para
2677#include "indicesol.inc"
2678
2679! Cette routine sert d'interface entre le modele atmospherique et un fichier
2680! de conditions aux limites
2681!
2682! L. Fairhead 02/2000
2683!
2684! input:
2685!   itime        numero du pas de temps courant
2686!   dtime        pas de temps de la physique (en s)
2687!   jour         jour a lire dans l'annee
2688!   nisurf       index de la surface a traiter (1 = sol continental)
2689!   knon         nombre de points dans le domaine a traiter
2690!   knindex      index des points de la surface a traiter
2691!   klon         taille de la grille
2692!   debut        logical: 1er appel a la physique (initialisation)
2693!
2694! output:
2695!   lmt_sst      SST lues dans le fichier de CL
2696!   pctsrf_new   sous-maille fractionnelle
2697!
2698
2699
2700! Parametres d'entree
2701  integer, intent(IN) :: itime
2702  real   , intent(IN) :: dtime
2703  integer, intent(IN) :: jour
2704  integer, intent(in) :: klon
2705  integer, intent(IN) :: nisurf
2706  integer, intent(IN) :: knon
2707  integer, dimension(klon_loc), intent(in) :: knindex
2708  logical, intent(IN) :: debut
2709
2710! Parametres de sortie
2711  real, intent(out), dimension(klon_loc) :: lmt_sst_p
2712  real, intent(out), dimension(klon_loc,nbsrf) :: pctsrf_new_p
2713
2714!  real, dimension(klon) :: lmt_sst
2715  real, dimension(klon_glo,nbsrf) :: pctsrf_new
2716
2717! Variables locales
2718  integer     :: ii
2719  INTEGER,save :: lmt_pas     ! frequence de lecture des conditions limites
2720                             ! (en pas de physique)
2721!$OMP THREADPRIVATE(lmt_pas)
2722  logical,save :: deja_lu    ! pour indiquer que le jour a lire a deja
2723                             ! lu pour une surface precedente
2724!$OMP THREADPRIVATE(deja_lu)
2725  integer,save :: jour_lu
2726!$OMP THREADPRIVATE(jour_lu)
2727  integer      :: ierr
2728  character (len = 20) :: modname = 'interfoce_lim'
2729  character (len = 80) :: abort_message
2730  character (len = 20),save :: fich ='limit.nc'
2731!$OMP THREADPRIVATE(fich)
2732  logical, save     :: newlmt = .TRUE.
2733!$OMP THREADPRIVATE(newlmt)
2734  logical, save     :: check = .FALSE.
2735!$OMP THREADPRIVATE(check)
2736! Champs lus dans le fichier de CL
2737  real, allocatable , save, dimension(:) :: sst_lu_p
2738!$OMP THREADPRIVATE(sst_lu_p)
2739
2740  real, allocatable , save, dimension(:,:) :: pct_tmp_p
2741!$OMP THREADPRIVATE(pct_tmp_p)
2742  real, dimension(klon_glo,nbsrf) :: pct_tmp
2743  real, dimension(klon_glo) :: sst_lu
2744  real, dimension(klon_glo) :: nat_lu
2745!
2746! quelques variables pour netcdf
2747!
2748#include "netcdf.inc"
2749  integer              :: nid, nvarid
2750  integer, dimension(2) :: start, epais
2751!
2752! Fin declaration
2753!
2754 
2755  if (debut .and. .not. allocated(sst_lu_p)) then
2756    lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour
2757    jour_lu = jour - 1
2758    allocate(sst_lu_p(klon_loc))
2759    allocate(pct_tmp_p(klon_loc,nbsrf))
2760  endif
2761
2762  if ((jour - jour_lu) /= 0) deja_lu = .false.
2763 
2764  if (check) write(*,*)modname,' :: jour, jour_lu, deja_lu', jour, jour_lu, deja_lu
2765  if (check) write(*,*)modname,' :: itime, lmt_pas ', itime, lmt_pas,dtime
2766
2767! Tester d'abord si c'est le moment de lire le fichier
2768  if (mod(itime-1, lmt_pas) == 0 .and. .not. deja_lu) then
2769!
2770! Ouverture du fichier
2771!
2772!$OMP MASTER
2773    if (is_mpi_root) then
2774   
2775    fich = trim(fich)
2776    ierr = NF_OPEN (fich, NF_NOWRITE,nid)
2777    if (ierr.NE.NF_NOERR) then
2778      abort_message = 'Pb d''ouverture du fichier de conditions aux limites'
2779      call abort_gcm(modname,abort_message,1)
2780    endif
2781!
2782! La tranche de donnees a lire:
2783!
2784    start(1) = 1
2785    start(2) = jour
2786    epais(1) = klon_glo
2787    epais(2) = 1
2788!
2789    if (newlmt) then
2790!
2791! Fraction "ocean"
2792!
2793      ierr = NF_INQ_VARID(nid, 'FOCE', nvarid)
2794      if (ierr /= NF_NOERR) then
2795        abort_message = 'Le champ <FOCE> est absent'
2796        call abort_gcm(modname,abort_message,1)
2797      endif
2798#ifdef NC_DOUBLE
2799      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pct_tmp(1,is_oce))
2800#else
2801      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pct_tmp(1,is_oce))
2802#endif
2803      if (ierr /= NF_NOERR) then
2804        abort_message = 'Lecture echouee pour <FOCE>'
2805        call abort_gcm(modname,abort_message,1)
2806      endif
2807!
2808! Fraction "glace de mer"
2809!
2810      ierr = NF_INQ_VARID(nid, 'FSIC', nvarid)
2811      if (ierr /= NF_NOERR) then
2812        abort_message = 'Le champ <FSIC> est absent'
2813        call abort_gcm(modname,abort_message,1)
2814      endif
2815#ifdef NC_DOUBLE
2816      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pct_tmp(1,is_sic))
2817#else
2818      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pct_tmp(1,is_sic))
2819#endif
2820      if (ierr /= NF_NOERR) then
2821        abort_message = 'Lecture echouee pour <FSIC>'
2822        call abort_gcm(modname,abort_message,1)
2823      endif
2824!
2825! Fraction "terre"
2826!
2827      ierr = NF_INQ_VARID(nid, 'FTER', nvarid)
2828      if (ierr /= NF_NOERR) then
2829        abort_message = 'Le champ <FTER> est absent'
2830        call abort_gcm(modname,abort_message,1)
2831      endif
2832#ifdef NC_DOUBLE
2833      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pct_tmp(1,is_ter))
2834#else
2835      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pct_tmp(1,is_ter))
2836#endif
2837      if (ierr /= NF_NOERR) then
2838        abort_message = 'Lecture echouee pour <FTER>'
2839        call abort_gcm(modname,abort_message,1)
2840      endif
2841!
2842! Fraction "glacier terre"
2843!
2844      ierr = NF_INQ_VARID(nid, 'FLIC', nvarid)
2845      if (ierr /= NF_NOERR) then
2846        abort_message = 'Le champ <FLIC> est absent'
2847        call abort_gcm(modname,abort_message,1)
2848      endif
2849#ifdef NC_DOUBLE
2850      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais,pct_tmp(1,is_lic))
2851#else
2852      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais,pct_tmp(1,is_lic))
2853#endif
2854      if (ierr /= NF_NOERR) then
2855        abort_message = 'Lecture echouee pour <FLIC>'
2856        call abort_gcm(modname,abort_message,1)
2857      endif
2858!
2859    else  ! on en est toujours a rnatur
2860!
2861      ierr = NF_INQ_VARID(nid, 'NAT', nvarid)
2862      if (ierr /= NF_NOERR) then
2863        abort_message = 'Le champ <NAT> est absent'
2864        call abort_gcm(modname,abort_message,1)
2865      endif
2866#ifdef NC_DOUBLE
2867      ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, nat_lu)
2868#else
2869      ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, nat_lu)
2870#endif
2871      if (ierr /= NF_NOERR) then
2872        abort_message = 'Lecture echouee pour <NAT>'
2873        call abort_gcm(modname,abort_message,1)
2874      endif
2875!
2876! Remplissage des fractions de surface
2877! nat = 0, 1, 2, 3 pour ocean, terre, glacier, seaice
2878!
2879      pct_tmp = 0.0
2880      do ii = 1, klon_glo
2881        pct_tmp(ii,nint(nat_lu(ii)) + 1) = 1.
2882      enddo
2883
2884!
2885!  On se retrouve avec ocean en 1 et terre en 2 alors qu'on veut le contraire
2886!
2887      pctsrf_new = pct_tmp
2888      pctsrf_new (:,2)= pct_tmp (:,1)
2889      pctsrf_new (:,1)= pct_tmp (:,2)
2890      pct_tmp = pctsrf_new
2891    endif ! fin test sur newlmt
2892!
2893! Lecture SST
2894!
2895    ierr = NF_INQ_VARID(nid, 'SST', nvarid)
2896    if (ierr /= NF_NOERR) then
2897      abort_message = 'Le champ <SST> est absent'
2898      call abort_gcm(modname,abort_message,1)
2899    endif
2900#ifdef NC_DOUBLE
2901    ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, sst_lu)
2902#else
2903    ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, sst_lu)
2904#endif
2905    if (ierr /= NF_NOERR) then
2906      abort_message = 'Lecture echouee pour <SST>'
2907      call abort_gcm(modname,abort_message,1)
2908    endif   
2909
2910!
2911! Fin de lecture
2912!
2913    ierr = NF_CLOSE(nid)
2914   endif ! is_mpi_root
2915
2916!$OMP END MASTER
2917!$OMP BARRIER
2918  call Scatter(sst_lu,sst_lu_p)
2919  call Scatter(pct_tmp(:,is_oce),pct_tmp_p(:,is_oce))
2920  call Scatter(pct_tmp(:,is_sic),pct_tmp_p(:,is_sic))
2921   deja_lu = .true.
2922   jour_lu = jour
2923  endif   
2924
2925!
2926! Recopie des variables dans les champs de sortie
2927!
2928 
2929  lmt_sst_p = 999999999.
2930 
2931  do ii = 1, knon
2932    lmt_sst_p(ii) = sst_lu_p(knindex(ii))
2933  enddo
2934
2935  do ii=1,klon_loc
2936    pctsrf_new_p(ii,is_oce)=pct_tmp_p(ii,is_oce)
2937    pctsrf_new_p(ii,is_sic)=pct_tmp_p(ii,is_sic)
2938  enddo
2939 
2940
2941  END SUBROUTINE interfoce_lim
2942
2943!
2944!#########################################################################
2945!
2946  SUBROUTINE interfsur_lim(itime, dtime, jour, &
2947     & klon, nisurf, knon, knindex, &
2948     & debut,  &
2949     & lmt_alb_p, lmt_rug_p)
2950
2951     USE mod_grid_phy_lmdz
2952     USE mod_phys_lmdz_para
2953     
2954! Cette routine sert d'interface entre le modele atmospherique et un fichier
2955! de conditions aux limites
2956!
2957! L. Fairhead 02/2000
2958!
2959! input:
2960!   itime        numero du pas de temps courant
2961!   dtime        pas de temps de la physique (en s)
2962!   jour         jour a lire dans l'annee
2963!   nisurf       index de la surface a traiter (1 = sol continental)
2964!   knon         nombre de points dans le domaine a traiter
2965!   knindex      index des points de la surface a traiter
2966!   klon         taille de la grille
2967!   debut        logical: 1er appel a la physique (initialisation)
2968!
2969! output:
2970!   lmt_sst      SST lues dans le fichier de CL
2971!   lmt_alb      Albedo lu
2972!   lmt_rug      longueur de rugosite lue
2973!   pctsrf_new   sous-maille fractionnelle
2974!
2975
2976
2977! Parametres d'entree
2978  integer, intent(IN) :: itime
2979  real   , intent(IN) :: dtime
2980  integer, intent(IN) :: jour
2981  integer, intent(IN) :: nisurf
2982  integer, intent(IN) :: knon
2983  integer, intent(IN) :: klon
2984  integer, dimension(klon_loc), intent(in) :: knindex
2985  logical, intent(IN) :: debut
2986
2987! Parametres de sortie
2988  real, intent(out), dimension(klon_loc) :: lmt_alb_p
2989  real, intent(out), dimension(klon_loc) :: lmt_rug_p
2990
2991!  real,  dimension(klon) :: lmt_alb
2992!  real,  dimension(klon) :: lmt_rug
2993
2994! Variables locales
2995  integer     :: ii
2996  integer,save :: lmt_pas     ! frequence de lecture des conditions limites
2997                             ! (en pas de physique)
2998!$OMP THREADPRIVATE(lmt_pas)
2999  logical,save :: deja_lu_sur! pour indiquer que le jour a lire a deja
3000                             ! lu pour une surface precedente
3001!$OMP THREADPRIVATE(deja_lu_sur)
3002  integer,save :: jour_lu_sur
3003!$OMP THREADPRIVATE(jour_lu_sur)
3004  integer      :: ierr
3005  character (len = 20) :: modname = 'interfsur_lim'
3006  character (len = 80) :: abort_message
3007  character (len = 20),save :: fich ='limit.nc'
3008!$OMP THREADPRIVATE(fich)
3009  logical,save     :: newlmt = .false.
3010!$OMP THREADPRIVATE(newlmt)
3011  logical,save     :: check = .false.
3012!$OMP THREADPRIVATE(check)
3013! Champs lus dans le fichier de CL
3014  real, allocatable , save, dimension(:) :: alb_lu_p, rug_lu_p
3015!$OMP THREADPRIVATE(alb_lu_p, rug_lu_p)
3016  real, dimension(klon_glo) :: alb_lu, rug_lu
3017!
3018! quelques variables pour netcdf
3019!
3020#include "netcdf.inc"
3021  integer ,save             :: nid, nvarid
3022!$OMP THREADPRIVATE(nid, nvarid)
3023  integer, dimension(2),save :: start, epais
3024!$OMP THREADPRIVATE(start, epais)
3025!
3026! Fin declaration
3027!
3028 
3029  if (debut) then
3030    lmt_pas = nint(86400./dtime * 1.0) ! pour une lecture une fois par jour
3031    jour_lu_sur = jour - 1
3032    allocate(alb_lu_p(klon_loc))
3033    allocate(rug_lu_p(klon_loc))
3034  endif
3035
3036  if ((jour - jour_lu_sur) /= 0) deja_lu_sur = .false.
3037 
3038  if (check) write(*,*)modname,':: jour_lu_sur, deja_lu_sur', jour_lu_sur, deja_lu_sur
3039  if (check) write(*,*)modname,':: itime, lmt_pas', itime, lmt_pas
3040  if (check) call flush(6)
3041
3042! Tester d'abord si c'est le moment de lire le fichier
3043  if (mod(itime-1, lmt_pas) == 0 .and. .not. deja_lu_sur) then
3044
3045!$OMP MASTER
3046   if (is_mpi_root) then
3047!
3048! Ouverture du fichier
3049!
3050    fich = trim(fich)
3051    IF (check) WRITE(*,*)modname,' ouverture fichier ',fich
3052    if (check) CALL flush(6)
3053    ierr = NF_OPEN (fich, NF_NOWRITE,nid)
3054    if (ierr.NE.NF_NOERR) then
3055      abort_message = 'Pb d''ouverture du fichier de conditions aux limites'
3056      call abort_gcm(modname,abort_message,1)
3057    endif
3058!
3059! La tranche de donnees a lire:
3060 
3061    start(1) = 1
3062    start(2) = jour
3063    epais(1) = klon_glo
3064    epais(2) = 1
3065!
3066! Lecture Albedo
3067!
3068    ierr = NF_INQ_VARID(nid, 'ALB', nvarid)
3069    if (ierr /= NF_NOERR) then
3070      abort_message = 'Le champ <ALB> est absent'
3071      call abort_gcm(modname,abort_message,1)
3072    endif
3073#ifdef NC_DOUBLE
3074    ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, alb_lu)
3075#else
3076    ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, alb_lu)
3077#endif
3078    if (ierr /= NF_NOERR) then
3079      abort_message = 'Lecture echouee pour <ALB>'
3080      call abort_gcm(modname,abort_message,1)
3081    endif
3082!
3083! Lecture rugosite !
3084    ierr = NF_INQ_VARID(nid, 'RUG', nvarid)
3085    if (ierr /= NF_NOERR) then
3086      abort_message = 'Le champ <RUG> est absent'
3087      call abort_gcm(modname,abort_message,1)
3088    endif
3089#ifdef NC_DOUBLE
3090    ierr = NF_GET_VARA_DOUBLE(nid,nvarid,start,epais, rug_lu)
3091#else
3092    ierr = NF_GET_VARA_REAL(nid,nvarid,start,epais, rug_lu)
3093#endif
3094    if (ierr /= NF_NOERR) then
3095      abort_message = 'Lecture echouee pour <RUG>'
3096      call abort_gcm(modname,abort_message,1)
3097    endif
3098
3099!
3100! Fin de lecture
3101!
3102    ierr = NF_CLOSE(nid)
3103
3104
3105  endif  !! is_mpi_root
3106!$OMP END MASTER
3107
3108    call Scatter(alb_lu,alb_lu_p)
3109    call Scatter(rug_lu,rug_lu_p)
3110   
3111    deja_lu_sur = .true.
3112    jour_lu_sur = jour
3113
3114
3115  endif
3116 
3117!
3118! Recopie des variables dans les champs de sortie
3119!
3120!!$  lmt_alb(:) = 0.0
3121!!$  lmt_rug(:) = 0.0
3122 
3123  lmt_alb_p(:) = 999999.
3124  lmt_rug_p(:) = 999999.
3125  DO ii = 1, knon
3126    lmt_alb_p(ii) = alb_lu_p(knindex(ii))
3127    lmt_rug_p(ii) = rug_lu_p(knindex(ii))
3128  enddo
3129
3130
3131  END SUBROUTINE interfsur_lim
3132
3133!
3134!#########################################################################
3135!
3136
3137  SUBROUTINE calcul_fluxs( klon, knon, nisurf, dtime, &
3138     & tsurf, p1lay, cal, beta, coef1lay, ps, &
3139     & precip_rain, precip_snow, snow, qsurf, &
3140     & radsol, dif_grnd, t1lay, q1lay, u1lay, v1lay, &
3141     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
3142     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l)
3143
3144! Cette routine calcule les fluxs en h et q a l'interface et eventuellement
3145! une temperature de surface (au cas ou ok_veget = false)
3146!
3147! L. Fairhead 4/2000
3148!
3149! input:
3150!   knon         nombre de points a traiter
3151!   nisurf       surface a traiter
3152!   tsurf        temperature de surface
3153!   p1lay        pression 1er niveau (milieu de couche)
3154!   cal          capacite calorifique du sol
3155!   beta         evap reelle
3156!   coef1lay     coefficient d'echange
3157!   ps           pression au sol
3158!   precip_rain  precipitations liquides
3159!   precip_snow  precipitations solides
3160!   snow         champs hauteur de neige
3161!   runoff       runoff en cas de trop plein
3162!   petAcoef     coeff. A de la resolution de la CL pour t
3163!   peqAcoef     coeff. A de la resolution de la CL pour q
3164!   petBcoef     coeff. B de la resolution de la CL pour t
3165!   peqBcoef     coeff. B de la resolution de la CL pour q
3166!   radsol       rayonnement net aus sol (LW + SW)
3167!   dif_grnd     coeff. diffusion vers le sol profond
3168!
3169! output:
3170!   tsurf_new    temperature au sol
3171!   qsurf        humidite de l'air au dessus du sol
3172!   fluxsens     flux de chaleur sensible
3173!   fluxlat      flux de chaleur latente
3174!   dflux_s      derivee du flux de chaleur sensible / Ts
3175!   dflux_l      derivee du flux de chaleur latente  / Ts
3176!
3177
3178#include "YOETHF.inc"
3179#include "FCTTRE.inc"
3180#include "indicesol.inc"
3181#include "YOMCST.inc"
3182
3183! Parametres d'entree
3184  integer, intent(IN) :: knon, nisurf, klon
3185  real   , intent(IN) :: dtime
3186  real, dimension(klon), intent(IN) :: petAcoef, peqAcoef
3187  real, dimension(klon), intent(IN) :: petBcoef, peqBcoef
3188  real, dimension(klon), intent(IN) :: ps, q1lay
3189  real, dimension(klon), intent(IN) :: tsurf, p1lay, cal, beta, coef1lay
3190  real, dimension(klon), intent(IN) :: precip_rain, precip_snow
3191  real, dimension(klon), intent(IN) :: radsol, dif_grnd
3192  real, dimension(klon), intent(IN) :: t1lay, u1lay, v1lay
3193  real, dimension(klon), intent(INOUT) :: snow, qsurf
3194
3195! Parametres sorties
3196  real, dimension(klon), intent(OUT):: tsurf_new, evap, fluxsens, fluxlat
3197  real, dimension(klon), intent(OUT):: dflux_s, dflux_l
3198
3199! Variables locales
3200  integer :: i
3201  real, dimension(klon) :: zx_mh, zx_nh, zx_oh
3202  real, dimension(klon) :: zx_mq, zx_nq, zx_oq
3203  real, dimension(klon) :: zx_pkh, zx_dq_s_dt, zx_qsat, zx_coef
3204  real, dimension(klon) :: zx_sl, zx_k1
3205  real, dimension(klon) :: zx_q_0 , d_ts
3206  real                  :: zdelta, zcvm5, zx_qs, zcor, zx_dq_s_dh
3207  real                  :: bilan_f, fq_fonte
3208  REAL                  :: subli, fsno
3209  REAL                  :: qsat_new, q1_new
3210  real, parameter :: t_grnd = 271.35, t_coup = 273.15
3211!! PB temporaire en attendant mieux pour le modele de neige
3212  REAL, parameter :: chasno = 3.334E+05/(2.3867E+06*0.15)
3213!
3214  logical, save         :: check = .false.
3215!$OMP THREADPRIVATE(check)
3216  character (len = 20)  :: modname = 'calcul_fluxs'
3217  logical, save         :: fonte_neige = .false.
3218!$OMP THREADPRIVATE(fonte_neige)
3219  real, save            :: max_eau_sol = 150.0
3220!$OMP THREADPRIVATE(max_eau_sol)
3221  character (len = 80) :: abort_message
3222  logical,save         :: first = .true.,second=.false.
3223!$OMP THREADPRIVATE(first,second)
3224
3225  if (check) write(*,*)'Entree ', modname,' surface = ',nisurf
3226
3227  IF (check) THEN
3228      WRITE(*,*)' radsol (min, max)' &
3229         &     , MINVAL(radsol(1:knon)), MAXVAL(radsol(1:knon))
3230      CALL flush(6)
3231  ENDIF
3232
3233  if (size(coastalflow) /= knon .AND. nisurf == is_ter) then
3234    write(*,*)'Bizarre, le nombre de points continentaux'
3235    write(*,*)'a change entre deux appels. J''arrete ...'
3236    abort_message='Pb run_off'
3237    call abort_gcm(modname,abort_message,1)
3238  endif
3239!
3240! Traitement neige et humidite du sol
3241!
3242!!$  WRITE(*,*)'test calcul_flux, surface ', nisurf
3243!!PB test
3244!!$    if (nisurf == is_oce) then
3245!!$      snow = 0.
3246!!$      qsol = max_eau_sol
3247!!$    else
3248!!$      where (precip_snow > 0.) snow = snow + (precip_snow * dtime)
3249!!$      where (snow > epsilon(snow)) snow = max(0.0, snow - (evap * dtime))
3250!!$!      snow = max(0.0, snow + (precip_snow - evap) * dtime)
3251!!$      where (precip_rain > 0.) qsol = qsol + (precip_rain - evap) * dtime
3252!!$    endif
3253!!$    IF (nisurf /= is_ter) qsol = max_eau_sol
3254
3255
3256!
3257! Initialisation
3258!
3259  evap = 0.
3260  fluxsens=0.
3261  fluxlat=0.
3262  dflux_s = 0.
3263  dflux_l = 0. 
3264!
3265! zx_qs = qsat en kg/kg
3266!
3267  DO i = 1, knon
3268    zx_pkh(i) = (ps(i)/ps(i))**RKAPPA
3269  IF (thermcep) THEN
3270      zdelta=MAX(0.,SIGN(1.,rtt-tsurf(i)))
3271      zcvm5 = R5LES*RLVTT*(1.-zdelta) + R5IES*RLSTT*zdelta
3272      zcvm5 = zcvm5 / RCPD / (1.0+RVTMP2*q1lay(i))
3273      zx_qs= r2es * FOEEW(tsurf(i),zdelta)/ps(i)
3274      zx_qs=MIN(0.5,zx_qs)
3275      zcor=1./(1.-retv*zx_qs)
3276      zx_qs=zx_qs*zcor
3277      zx_dq_s_dh = FOEDE(tsurf(i),zdelta,zcvm5,zx_qs,zcor) &
3278     &                 /RLVTT / zx_pkh(i)
3279    ELSE
3280      IF (tsurf(i).LT.t_coup) THEN
3281        zx_qs = qsats(tsurf(i)) / ps(i)
3282        zx_dq_s_dh = dqsats(tsurf(i),zx_qs)/RLVTT &
3283     &                    / zx_pkh(i)
3284      ELSE
3285        zx_qs = qsatl(tsurf(i)) / ps(i)
3286        zx_dq_s_dh = dqsatl(tsurf(i),zx_qs)/RLVTT &
3287     &               / zx_pkh(i)
3288      ENDIF
3289    ENDIF
3290    zx_dq_s_dt(i) = RCPD * zx_pkh(i) * zx_dq_s_dh
3291    zx_qsat(i) = zx_qs
3292    zx_coef(i) = coef1lay(i) &
3293     & * (1.0+SQRT(u1lay(i)**2+v1lay(i)**2)) &
3294     & * p1lay(i)/(RD*t1lay(i))
3295
3296  ENDDO
3297
3298
3299! === Calcul de la temperature de surface ===
3300!
3301! zx_sl = chaleur latente d'evaporation ou de sublimation
3302!
3303  do i = 1, knon
3304    zx_sl(i) = RLVTT
3305    if (tsurf(i) .LT. RTT) zx_sl(i) = RLSTT
3306    zx_k1(i) = zx_coef(i)
3307  enddo
3308
3309
3310  do i = 1, knon
3311! Q
3312    zx_oq(i) = 1. - (beta(i) * zx_k1(i) * peqBcoef(i) * dtime)
3313    zx_mq(i) = beta(i) * zx_k1(i) * &
3314     &             (peqAcoef(i) - zx_qsat(i) &
3315     &                          + zx_dq_s_dt(i) * tsurf(i)) &
3316     &             / zx_oq(i)
3317    zx_nq(i) = beta(i) * zx_k1(i) * (-1. * zx_dq_s_dt(i)) &
3318     &                              / zx_oq(i)
3319
3320! H
3321    zx_oh(i) = 1. - (zx_k1(i) * petBcoef(i) * dtime)
3322    zx_mh(i) = zx_k1(i) * petAcoef(i) / zx_oh(i)
3323    zx_nh(i) = - (zx_k1(i) * RCPD * zx_pkh(i))/ zx_oh(i)
3324
3325! Tsurface
3326    tsurf_new(i) = (tsurf(i) + cal(i)/(RCPD * zx_pkh(i)) * dtime * &
3327     &             (radsol(i) + zx_mh(i) + zx_sl(i) * zx_mq(i)) &
3328     &                 + dif_grnd(i) * t_grnd * dtime)/ &
3329     &          ( 1. - dtime * cal(i)/(RCPD * zx_pkh(i)) * ( &
3330     &                       zx_nh(i) + zx_sl(i) * zx_nq(i)) & 
3331     &                     + dtime * dif_grnd(i))
3332
3333!
3334! Y'a-t-il fonte de neige?
3335!
3336!    fonte_neige = (nisurf /= is_oce) .AND. &
3337!     & (snow(i) > epsfra .OR. nisurf == is_sic .OR. nisurf == is_lic) &
3338!     & .AND. (tsurf_new(i) >= RTT)
3339!    if (fonte_neige) tsurf_new(i) = RTT 
3340    d_ts(i) = tsurf_new(i) - tsurf(i)
3341!    zx_h_ts(i) = tsurf_new(i) * RCPD * zx_pkh(i)
3342!    zx_q_0(i) = zx_qsat(i) + zx_dq_s_dt(i) * d_ts(i)
3343!== flux_q est le flux de vapeur d'eau: kg/(m**2 s)  positive vers bas
3344!== flux_t est le flux de cpt (energie sensible): j/(m**2 s)
3345    evap(i) = - zx_mq(i) - zx_nq(i) * tsurf_new(i)
3346    fluxlat(i) = - evap(i) * zx_sl(i)
3347    fluxsens(i) = zx_mh(i) + zx_nh(i) * tsurf_new(i)
3348! Derives des flux dF/dTs (W m-2 K-1):
3349    dflux_s(i) = zx_nh(i)
3350    dflux_l(i) = (zx_sl(i) * zx_nq(i))
3351! Nouvelle valeure de l'humidite au dessus du sol
3352    qsat_new=zx_qsat(i) + zx_dq_s_dt(i) * d_ts(i)
3353    q1_new = peqAcoef(i) - peqBcoef(i)*evap(i)*dtime
3354    qsurf(i)=q1_new*(1.-beta(i)) + beta(i)*qsat_new
3355!
3356! en cas de fonte de neige
3357!
3358!    if (fonte_neige) then
3359!      bilan_f = radsol(i) + fluxsens(i) - (zx_sl(i) * evap (i)) - &
3360!     &          dif_grnd(i) * (tsurf_new(i) - t_grnd) - &
3361!     &          RCPD * (zx_pkh(i))/cal(i)/dtime * (tsurf_new(i) - tsurf(i))
3362!      bilan_f = max(0., bilan_f)
3363!      fq_fonte = bilan_f / zx_sl(i)
3364!      snow(i) = max(0., snow(i) - fq_fonte * dtime)
3365!      qsol(i) = qsol(i) + (fq_fonte * dtime)
3366!    endif
3367!!$    if (nisurf == is_ter)  &
3368!!$     &  run_off(i) = run_off(i) + max(qsol(i) - max_eau_sol, 0.0)
3369!!$    qsol(i) = min(qsol(i), max_eau_sol)
3370  ENDDO
3371
3372  END SUBROUTINE calcul_fluxs
3373!
3374!#########################################################################
3375!
3376  SUBROUTINE gath2cpl(champ_in, champ_out, klon, knon, iim, jmp1, knindex)
3377  USE mod_phys_lmdz_para
3378  implicit none
3379 
3380! Cette routine ecrit un champ 'gathered' sur la grille 2D pour le passer
3381! au coupleur.
3382!
3383!
3384! input:         
3385!   champ_in     champ sur la grille gathere       
3386!   knon         nombre de points dans le domaine a traiter
3387!   knindex      index des points de la surface a traiter
3388!   klon         taille de la grille
3389!   iim,jjm      dimension de la grille 2D
3390!
3391! output:
3392!   champ_out    champ sur la grille 2D
3393!
3394! input
3395  integer                   :: klon, knon, iim, jmp1
3396  real, dimension(klon_loc)     :: champ_in
3397  integer, dimension(klon_loc)  :: knindex
3398! output
3399  real, dimension(iim,jmp1)  :: champ_out
3400! local
3401  integer                   :: i, ig, j
3402  real, dimension(klon_loc)     :: tamp
3403
3404  tamp = 0.
3405  do i = 1, knon
3406    ig = knindex(i)
3407    tamp(ig) = champ_in(i)
3408  enddo   
3409
3410
3411  CALL Grid1Dto2D_mpi(tamp,champ_out)
3412
3413  END SUBROUTINE gath2cpl
3414!
3415!#########################################################################
3416!
3417  SUBROUTINE cpl2gath(champ_in, champ_out, klon, knon, iim, jmp1, knindex)
3418  USE mod_phys_lmdz_para
3419  implicit none
3420! Cette routine ecrit un champ 'gathered' sur la grille 2D pour le passer
3421! au coupleur.
3422!
3423!
3424! input:         
3425!   champ_in     champ sur la grille gathere       
3426!   knon         nombre de points dans le domaine a traiter
3427!   knindex      index des points de la surface a traiter
3428!   klon         taille de la grille
3429!   iim,jjm      dimension de la grille 2D
3430!
3431! output:
3432!   champ_out    champ sur la grille 2D
3433!
3434! input
3435  integer                   :: klon, knon, iim, jmp1
3436  real, dimension(iim,jmp1)     :: champ_in
3437  integer, dimension(klon_loc)  :: knindex
3438! output
3439  real, dimension(klon_loc)  :: champ_out
3440! local
3441  integer                   :: i, ig, j
3442  real, dimension(klon_loc)     :: tamp
3443  logical ,save                  :: check = .false.
3444!$OMP THREADPRIVATE(check)
3445
3446  CALL Grid2Dto1D_mpi(champ_in,tamp)
3447 
3448  do i = 1, knon
3449    ig = knindex(i)
3450    champ_out(i) = tamp(ig)
3451  enddo   
3452
3453  END SUBROUTINE cpl2gath
3454!
3455!#########################################################################
3456!
3457  SUBROUTINE albsno(klon, knon,dtime,agesno,alb_neig_grid, precip_snow)
3458  IMPLICIT none
3459 
3460  INTEGER :: klon, knon
3461  INTEGER, PARAMETER :: nvm = 8
3462  REAL   :: dtime
3463  REAL, dimension(klon,nvm) :: veget
3464  REAL, DIMENSION(klon) :: alb_neig_grid, agesno, precip_snow
3465 
3466  INTEGER :: i, nv
3467 
3468  REAL, DIMENSION(nvm),SAVE :: init, decay
3469!$OMP THREADPRIVATE(init, decay)
3470  REAL :: as
3471  DATA init /0.55, 0.14, 0.18, 0.29, 0.15, 0.15, 0.14, 0./
3472  DATA decay/0.30, 0.67, 0.63, 0.45, 0.40, 0.14, 0.06, 1./
3473 
3474  veget = 0.
3475  veget(:,1) = 1.     ! desert partout
3476  DO i = 1, knon
3477    alb_neig_grid(i) = 0.0
3478  ENDDO
3479  DO nv = 1, nvm
3480    DO i = 1, knon
3481      as = init(nv)+decay(nv)*EXP(-agesno(i)/5.)
3482      alb_neig_grid(i) = alb_neig_grid(i) + veget(i,nv)*as
3483    ENDDO
3484  ENDDO
3485!
3486!! modilation en fonction de l'age de la neige
3487!
3488  DO i = 1, knon
3489    agesno(i)  = (agesno(i) + (1.-agesno(i)/50.)*dtime/86400.)&
3490            &             * EXP(-1.*MAX(0.0,precip_snow(i))*dtime/0.3)
3491    agesno(i) =  MAX(agesno(i),0.0)
3492  ENDDO
3493 
3494  END SUBROUTINE albsno
3495!
3496!#########################################################################
3497!
3498
3499  SUBROUTINE fonte_neige( klon, knon, nisurf, dtime, &
3500     & tsurf, p1lay, cal, beta, coef1lay, ps, &
3501     & precip_rain, precip_snow, snow, qsol, &
3502     & radsol, dif_grnd, t1lay, q1lay, u1lay, v1lay, &
3503     & petAcoef, peqAcoef, petBcoef, peqBcoef, &
3504     & tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
3505     & fqcalving,fqfonte,ffonte,run_off_lic_0)
3506
3507! Routine de traitement de la fonte de la neige dans le cas du traitement
3508! de sol simplifie !
3509! LF 03/2001
3510! input:
3511!   knon         nombre de points a traiter
3512!   nisurf       surface a traiter
3513!   tsurf        temperature de surface
3514!   p1lay        pression 1er niveau (milieu de couche)
3515!   cal          capacite calorifique du sol
3516!   beta         evap reelle
3517!   coef1lay     coefficient d'echange
3518!   ps           pression au sol
3519!   precip_rain  precipitations liquides
3520!   precip_snow  precipitations solides
3521!   snow         champs hauteur de neige
3522!   qsol         hauteur d'eau contenu dans le sol
3523!   runoff       runoff en cas de trop plein
3524!   petAcoef     coeff. A de la resolution de la CL pour t
3525!   peqAcoef     coeff. A de la resolution de la CL pour q
3526!   petBcoef     coeff. B de la resolution de la CL pour t
3527!   peqBcoef     coeff. B de la resolution de la CL pour q
3528!   radsol       rayonnement net aus sol (LW + SW)
3529!   dif_grnd     coeff. diffusion vers le sol profond
3530!
3531! output:
3532!   tsurf_new    temperature au sol
3533!   fluxsens     flux de chaleur sensible
3534!   fluxlat      flux de chaleur latente
3535!   dflux_s      derivee du flux de chaleur sensible / Ts
3536!   dflux_l      derivee du flux de chaleur latente  / Ts
3537! in/out:
3538!   run_off_lic_0 run off glacier du pas de temps precedent
3539!
3540
3541#include "YOETHF.inc"
3542!rv#include "FCTTRE.inc"
3543#include "indicesol.inc"
3544!IM cf JLD
3545#include "YOMCST.inc"
3546
3547! Parametres d'entree
3548  integer, intent(IN) :: knon, nisurf, klon
3549  real   , intent(IN) :: dtime
3550  real, dimension(klon), intent(IN) :: petAcoef, peqAcoef
3551  real, dimension(klon), intent(IN) :: petBcoef, peqBcoef
3552  real, dimension(klon), intent(IN) :: ps, q1lay
3553  real, dimension(klon), intent(IN) :: tsurf, p1lay, cal, beta, coef1lay
3554  real, dimension(klon), intent(IN) :: precip_rain, precip_snow
3555  real, dimension(klon), intent(IN) :: radsol, dif_grnd
3556  real, dimension(klon), intent(IN) :: t1lay, u1lay, v1lay
3557  real, dimension(klon), intent(INOUT) :: snow, qsol
3558
3559! Parametres sorties
3560  real, dimension(klon), intent(INOUT):: tsurf_new, evap, fluxsens, fluxlat
3561  real, dimension(klon), intent(INOUT):: dflux_s, dflux_l
3562! Flux thermique utiliser pour fondre la neige
3563  real, dimension(klon), intent(INOUT):: ffonte
3564! Flux d'eau "perdu" par la surface et necessaire pour que limiter la
3565! hauteur de neige, en kg/m2/s. Et flux d'eau de fonte de la calotte.
3566  REAL, DIMENSION(klon), INTENT(INOUT):: fqcalving, fqfonte
3567  real, dimension(klon), intent(INOUT):: run_off_lic_0
3568! Variables locales
3569! Masse maximum de neige (kg/m2). Au dessus de ce seuil, la neige
3570! en exces "s'ecoule" (calving)
3571!  real, parameter :: snow_max=1.
3572!IM cf JLD/GK
3573  real, parameter :: snow_max=3000.
3574  integer :: i
3575  real, dimension(klon) :: zx_mh, zx_nh, zx_oh
3576  real, dimension(klon) :: zx_mq, zx_nq, zx_oq
3577  real, dimension(klon) :: zx_pkh, zx_dq_s_dt, zx_qsat, zx_coef
3578  real, dimension(klon) :: zx_sl, zx_k1
3579  real, dimension(klon) :: zx_q_0 , d_ts
3580  real                  :: zdelta, zcvm5, zx_qs, zcor, zx_dq_s_dh
3581  real                  :: bilan_f, fq_fonte
3582  REAL                  :: subli, fsno
3583  REAL, DIMENSION(klon) :: bil_eau_s, snow_evap
3584  real, parameter :: t_grnd = 271.35, t_coup = 273.15
3585!! PB temporaire en attendant mieux pour le modele de neige
3586! REAL, parameter :: chasno = RLMLT/(2.3867E+06*0.15)
3587  REAL, parameter :: chasno = 3.334E+05/(2.3867E+06*0.15)
3588!IM cf JLD/ GKtest
3589  REAL, parameter :: chaice = 3.334E+05/(2.3867E+06*0.15)
3590! fin GKtest
3591!
3592  logical, save         :: check = .FALSE.
3593!$OMP THREADPRIVATE(check)
3594  character (len = 20)  :: modname = 'fonte_neige'
3595  logical, save         :: neige_fond = .false.
3596!$OMP THREADPRIVATE(neige_fond)
3597  real, save            :: max_eau_sol = 150.0
3598!$OMP THREADPRIVATE(max_eau_sol)
3599  character (len = 80) :: abort_message
3600  logical,save         :: first = .true.,second=.false.
3601!$OMP THREADPRIVATE(first,second)
3602  real                 :: coeff_rel
3603#include "FCTTRE.inc"
3604
3605
3606  if (check) write(*,*)'Entree ', modname,' surface = ',nisurf
3607
3608! Initialisations
3609  coeff_rel = dtime/(tau_calv * rday)
3610  bil_eau_s(:) = 0.
3611  DO i = 1, knon
3612    zx_pkh(i) = (ps(i)/ps(i))**RKAPPA
3613  IF (thermcep) THEN
3614      zdelta=MAX(0.,SIGN(1.,rtt-tsurf(i)))
3615      zcvm5 = R5LES*RLVTT*(1.-zdelta) + R5IES*RLSTT*zdelta
3616      zcvm5 = zcvm5 / RCPD / (1.0+RVTMP2*q1lay(i))
3617      zx_qs= r2es * FOEEW(tsurf(i),zdelta)/ps(i)
3618      zx_qs=MIN(0.5,zx_qs)
3619      zcor=1./(1.-retv*zx_qs)
3620      zx_qs=zx_qs*zcor
3621      zx_dq_s_dh = FOEDE(tsurf(i),zdelta,zcvm5,zx_qs,zcor) &
3622     &                 /RLVTT / zx_pkh(i)
3623    ELSE
3624      IF (tsurf(i).LT.t_coup) THEN
3625        zx_qs = qsats(tsurf(i)) / ps(i)
3626        zx_dq_s_dh = dqsats(tsurf(i),zx_qs)/RLVTT &
3627     &                    / zx_pkh(i)
3628      ELSE
3629        zx_qs = qsatl(tsurf(i)) / ps(i)
3630        zx_dq_s_dh = dqsatl(tsurf(i),zx_qs)/RLVTT &
3631     &               / zx_pkh(i)
3632      ENDIF
3633    ENDIF
3634    zx_dq_s_dt(i) = RCPD * zx_pkh(i) * zx_dq_s_dh
3635    zx_qsat(i) = zx_qs
3636    zx_coef(i) = coef1lay(i) &
3637     & * (1.0+SQRT(u1lay(i)**2+v1lay(i)**2)) &
3638     & * p1lay(i)/(RD*t1lay(i))
3639  ENDDO
3640
3641
3642! === Calcul de la temperature de surface ===
3643!
3644! zx_sl = chaleur latente d'evaporation ou de sublimation
3645!
3646  do i = 1, knon
3647    zx_sl(i) = RLVTT
3648    if (tsurf(i) .LT. RTT) zx_sl(i) = RLSTT
3649    zx_k1(i) = zx_coef(i)
3650  enddo
3651
3652
3653  do i = 1, knon
3654! Q
3655    zx_oq(i) = 1. - (beta(i) * zx_k1(i) * peqBcoef(i) * dtime)
3656    zx_mq(i) = beta(i) * zx_k1(i) * &
3657     &             (peqAcoef(i) - zx_qsat(i) &
3658     &                          + zx_dq_s_dt(i) * tsurf(i)) &
3659     &             / zx_oq(i)
3660    zx_nq(i) = beta(i) * zx_k1(i) * (-1. * zx_dq_s_dt(i)) &
3661     &                              / zx_oq(i)
3662
3663! H
3664    zx_oh(i) = 1. - (zx_k1(i) * petBcoef(i) * dtime)
3665    zx_mh(i) = zx_k1(i) * petAcoef(i) / zx_oh(i)
3666    zx_nh(i) = - (zx_k1(i) * RCPD * zx_pkh(i))/ zx_oh(i)
3667  enddo
3668
3669
3670  WHERE (precip_snow > 0.) snow = snow + (precip_snow * dtime)
3671  snow_evap = 0.
3672  WHERE (evap > 0. )
3673    snow_evap = MIN (snow / dtime, evap)
3674    snow = snow - snow_evap * dtime
3675    snow = MAX(0.0, snow)
3676  end where
3677 
3678!  bil_eau_s = bil_eau_s + (precip_rain * dtime) - (evap - snow_evap) * dtime
3679  bil_eau_s = (precip_rain * dtime) - (evap - snow_evap) * dtime
3680
3681!
3682! Y'a-t-il fonte de neige?
3683!
3684  ffonte=0.
3685  do i = 1, knon
3686    neige_fond = ((snow(i) > epsfra .OR. nisurf == is_sic .OR. nisurf == is_lic) &
3687     & .AND. tsurf_new(i) >= RTT)
3688    if (neige_fond) then
3689      fq_fonte = MIN( MAX((tsurf_new(i)-RTT )/chasno,0.0),snow(i))
3690      ffonte(i) = fq_fonte * RLMLT/dtime
3691      fqfonte(i) = fq_fonte/dtime
3692      snow(i) = max(0., snow(i) - fq_fonte)
3693      bil_eau_s(i) = bil_eau_s(i) + fq_fonte
3694      tsurf_new(i) = tsurf_new(i) - fq_fonte * chasno 
3695!IM cf JLD OK     
3696!IM cf JLD/ GKtest fonte aussi pour la glace
3697      IF (nisurf == is_sic .OR. nisurf == is_lic ) THEN
3698        fq_fonte = MAX((tsurf_new(i)-RTT )/chaice,0.0)
3699        ffonte(i) = ffonte(i) + fq_fonte * RLMLT/dtime
3700        IF ( ok_lic_melt ) THEN
3701           fqfonte(i) = fqfonte(i) + fq_fonte/dtime
3702           bil_eau_s(i) = bil_eau_s(i) + fq_fonte
3703        ENDIF
3704        tsurf_new(i) = RTT
3705      ENDIF
3706      d_ts(i) = tsurf_new(i) - tsurf(i)
3707    endif
3708!
3709!   s'il y a une hauteur trop importante de neige, elle s'coule
3710    fqcalving(i) = max(0., snow(i) - snow_max)/dtime
3711    snow(i)=min(snow(i),snow_max)
3712!
3713    IF (nisurf == is_ter) then
3714      qsol(i) = qsol(i) + bil_eau_s(i)
3715      run_off(i) = run_off(i) + MAX(qsol(i) - max_eau_sol, 0.0)
3716      qsol(i) = MIN(qsol(i), max_eau_sol)
3717    else if (nisurf == is_lic) then
3718      run_off_lic(i) = (coeff_rel *  fqcalving(i)) + &
3719 &                        (1. - coeff_rel) * run_off_lic_0(i)
3720      run_off_lic_0(i) = run_off_lic(i)
3721      run_off_lic(i) = run_off_lic(i) + fqfonte(i)/dtime
3722    endif
3723  enddo
3724
3725  END SUBROUTINE fonte_neige
3726!
3727!#########################################################################
3728!
3729  END MODULE interface_surf
Note: See TracBrowser for help on using the repository browser.