source: LMDZ6/branches/Ocean_skin/libf/phylmd/cpl_mod.F90 @ 3627

Last change on this file since 3627 was 3627, checked in by lguez, 4 years ago

If the ocean skin parameterization is working (passively or actively,
activate_ocean_skin >= 1) and we are coupled to the ocean then
receive bulk salinity of the surface layer of the ocean from the ocean
and feed it to procedure bulk_flux instead of the constant
value 35. If the ocean skin parameterization is working actively
(activate_ocean_skin == 2) and we are coupled to the ocean then send
ocean-air interface temperature to the ocean. We can only send
interface temperature from the previous time-step since communication
with the ocean is before the call to bulk_flux. In module cpl_mod,
define cpl_t_int with rank 1: no dimension for cpl_index because
t_int is only defined over ocean. New dummy argument sss of
procedures cpl_receive_ocean_fields and ocean_cpl_noice. New dummy
argument t_int of cpl_send_ocean_fields. In procedure
surf_ocean, rename local variable s1 to sss and give it the size
klon, which is required by the coupling machinery.

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 64.0 KB
Line 
1!
2MODULE cpl_mod
3!
4! This module excahanges and transforms all fields that should be recieved or sent to
5! coupler. The transformation of the fields are done from the grid 1D-array in phylmd
6! to the regular 2D grid accepted by the coupler. Cumulation of the fields for each
7! timestep is done in here.
8!
9! Each type of surface that recevie fields from the coupler have a subroutine named
10! cpl_receive_XXX_fields and each surface that have fields to be sent to the coupler
11! have a subroutine named cpl_send_XXX_fields.
12!
13!*************************************************************************************
14
15! Use statements
16!*************************************************************************************
17  USE dimphy, ONLY : klon
18  USE mod_phys_lmdz_para
19  USE ioipsl
20  USE iophy
21
22! The module oasis is always used. Without the cpp key CPP_COUPLE only the parameters
23! in the module are compiled and not the subroutines.
24  USE oasis
25  USE write_field_phy
26  USE time_phylmdz_mod, ONLY: day_step_phy
27 
28! Global attributes
29!*************************************************************************************
30  IMPLICIT NONE
31  PRIVATE
32
33  ! All subroutine are public except cpl_send_all
34  PUBLIC :: cpl_init, cpl_receive_frac, cpl_receive_ocean_fields, cpl_receive_seaice_fields, &
35       cpl_send_ocean_fields, cpl_send_seaice_fields, cpl_send_land_fields, &
36       cpl_send_landice_fields, gath2cpl
37 
38
39! Declaration of module variables
40!*************************************************************************************
41! variable for coupling period
42  INTEGER, SAVE :: nexca
43  !$OMP THREADPRIVATE(nexca)
44
45! variables for cumulating fields during a coupling periode :
46  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: cpl_sols, cpl_nsol, cpl_rain
47  !$OMP THREADPRIVATE(cpl_sols,cpl_nsol,cpl_rain)
48  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: cpl_snow, cpl_evap, cpl_tsol
49  !$OMP THREADPRIVATE(cpl_snow,cpl_evap,cpl_tsol)
50
51  REAL, ALLOCATABLE, SAVE:: cpl_t_int(:)
52  !$OMP THREADPRIVATE(cpl_t_int)
53 
54  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: cpl_fder, cpl_albe, cpl_taux, cpl_tauy
55  !$OMP THREADPRIVATE(cpl_fder,cpl_albe,cpl_taux,cpl_tauy)
56  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: cpl_windsp
57  !$OMP THREADPRIVATE(cpl_windsp)
58  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: cpl_sens_rain, cpl_sens_snow
59  !$OMP THREADPRIVATE(cpl_sens_rain, cpl_sens_snow)
60  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: cpl_taumod
61  !$OMP THREADPRIVATE(cpl_taumod)
62  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: cpl_atm_co2
63  !$OMP THREADPRIVATE(cpl_atm_co2)
64  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: cpl_rriv2D, cpl_rcoa2D, cpl_rlic2D
65  !$OMP THREADPRIVATE(cpl_rriv2D,cpl_rcoa2D,cpl_rlic2D)
66
67! variables read from coupler :
68  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: read_sst     ! sea surface temperature
69  !$OMP THREADPRIVATE(read_sst)
70  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: read_sit     ! sea ice temperature
71  !$OMP THREADPRIVATE(read_sit)
72
73  REAL, ALLOCATABLE, SAVE:: read_sss(:, :)
74  ! bulk salinity of the surface layer of the ocean, in ppt
75  !$OMP THREADPRIVATE(read_sss)
76
77  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: read_sic     ! sea ice fraction
78  !$OMP THREADPRIVATE(read_sic)
79  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: read_alb_sic ! albedo at sea ice
80  !$OMP THREADPRIVATE(read_alb_sic)
81  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: read_u0, read_v0 ! ocean surface current
82  !$OMP THREADPRIVATE(read_u0,read_v0)
83  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: read_co2     ! ocean co2 flux
84  !$OMP THREADPRIVATE(read_co2)
85  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: unity
86  !$OMP THREADPRIVATE(unity)
87  INTEGER, SAVE                             :: nidct, nidcs
88  !$OMP THREADPRIVATE(nidct,nidcs)
89
90! variables to be sent to the coupler
91  REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE :: cpl_sols2D, cpl_nsol2D, cpl_rain2D
92  !$OMP THREADPRIVATE(cpl_sols2D, cpl_nsol2D, cpl_rain2D)
93  REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE :: cpl_snow2D, cpl_evap2D, cpl_tsol2D
94  !$OMP THREADPRIVATE(cpl_snow2D, cpl_evap2D, cpl_tsol2D)
95
96  REAL, ALLOCATABLE, SAVE:: cpl_t_int_2D(:,:)
97  !$OMP THREADPRIVATE(cpl_t_int_2D)
98
99  REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE :: cpl_fder2D, cpl_albe2D
100  !$OMP THREADPRIVATE(cpl_fder2D, cpl_albe2D)
101  REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE :: cpl_taux2D, cpl_tauy2D
102  !$OMP THREADPRIVATE(cpl_taux2D, cpl_tauy2D)
103  REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE :: cpl_taumod2D
104  !$OMP THREADPRIVATE(cpl_taumod2D)
105  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: cpl_windsp2D
106  !$OMP THREADPRIVATE(cpl_windsp2D)
107  REAL, ALLOCATABLE, DIMENSION(:,:,:), SAVE   :: cpl_sens_rain2D, cpl_sens_snow2D
108  !$OMP THREADPRIVATE(cpl_sens_rain2D, cpl_sens_snow2D)
109  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: cpl_atm_co22D
110  !$OMP THREADPRIVATE(cpl_atm_co22D)
111
112!!!!!!!!!! variable for calving
113  INTEGER, PARAMETER :: nb_zone_calving = 3
114  REAL,ALLOCATABLE, DIMENSION(:,:,:),SAVE :: area_calving
115  !$OMP THREADPRIVATE(area_calving)
116  REAL,ALLOCATABLE, DIMENSION(:,:),SAVE :: cell_area2D
117  !$OMP THREADPRIVATE(cell_area2D)
118  INTEGER, SAVE :: ind_calving(nb_zone_calving)
119  !$OMP THREADPRIVATE(ind_calving)
120
121  LOGICAL,SAVE :: cpl_old_calving
122  !$OMP THREADPRIVATE(cpl_old_calving)
123 
124CONTAINS
125!
126!************************************************************************************
127!
128  SUBROUTINE cpl_init(dtime, rlon, rlat)
129    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, fco2_ocn_day
130    USE surface_data
131    USE indice_sol_mod
132    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid1dTo2d_glo, klon_glo, grid_type, unstructured, regular_lonlat
133    USE time_phylmdz_mod, ONLY: annee_ref, day_ini, itau_phy, itaufin_phy
134    USE print_control_mod, ONLY: lunout
135    USE geometry_mod, ONLY : longitude_deg, latitude_deg, ind_cell_glo, cell_area
136    USE ioipsl_getin_p_mod, ONLY: getin_p
137    use config_ocean_skin_m, only: activate_ocean_skin
138
139! Input arguments
140!*************************************************************************************
141    REAL, INTENT(IN)                  :: dtime
142    REAL, DIMENSION(klon), INTENT(IN) :: rlon, rlat
143
144! Local variables
145!*************************************************************************************
146    INTEGER                           :: error, sum_error, ig, i
147    INTEGER                           :: jf, nhoridct
148    INTEGER                           :: nhoridcs
149    INTEGER                           :: idtime
150    INTEGER                           :: idayref
151    INTEGER                           :: npas ! only for OASIS2
152    REAL                              :: zjulian
153    REAL, DIMENSION(nbp_lon,nbp_lat)  :: zx_lon, zx_lat
154    CHARACTER(len = 20)               :: modname = 'cpl_init'
155    CHARACTER(len = 80)               :: abort_message
156    CHARACTER(len=80)                 :: clintocplnam, clfromcplnam
157    REAL, DIMENSION(klon_mpi)         :: rlon_mpi, rlat_mpi, cell_area_mpi
158    INTEGER, DIMENSION(klon_mpi)           :: ind_cell_glo_mpi
159    REAL, DIMENSION(nbp_lon,jj_nb)         :: lon2D, lat2D
160    INTEGER :: mask_calving(nbp_lon,jj_nb,nb_zone_calving)
161    REAL :: pos
162
163!***************************************
164! Use old calving or not (default new calving method)
165! New calving method should be used with DYNAMICO and when using new coupling
166! weights.
167    cpl_old_calving=.FALSE.
168    CALL getin_p("cpl_old_calving",cpl_old_calving)
169
170
171!*************************************************************************************
172! Calculate coupling period
173!
174!*************************************************************************************
175     
176    npas = itaufin_phy
177!    nexca = 86400 / dtime
178    nexca = t_coupl / dtime
179    WRITE(lunout,*)' ##### Ocean couple #####'
180    WRITE(lunout,*)' Valeurs des pas de temps'
181    WRITE(lunout,*)' npas = ', npas
182    WRITE(lunout,*)' nexca = ', nexca
183   
184!*************************************************************************************
185! Allocate variables
186!
187!*************************************************************************************
188    error = 0
189    sum_error = 0
190
191    ALLOCATE(unity(klon), stat = error)
192    sum_error = sum_error + error
193    ALLOCATE(cpl_sols(klon,2), stat = error)
194    sum_error = sum_error + error
195    ALLOCATE(cpl_nsol(klon,2), stat = error)
196    sum_error = sum_error + error
197    ALLOCATE(cpl_rain(klon,2), stat = error)
198    sum_error = sum_error + error
199    ALLOCATE(cpl_snow(klon,2), stat = error)
200    sum_error = sum_error + error
201    ALLOCATE(cpl_evap(klon,2), stat = error)
202    sum_error = sum_error + error
203    ALLOCATE(cpl_tsol(klon,2), stat = error)
204    sum_error = sum_error + error
205    ALLOCATE(cpl_fder(klon,2), stat = error)
206    sum_error = sum_error + error
207    ALLOCATE(cpl_albe(klon,2), stat = error)
208    sum_error = sum_error + error
209    ALLOCATE(cpl_taux(klon,2), stat = error)
210    sum_error = sum_error + error
211    ALLOCATE(cpl_tauy(klon,2), stat = error)
212    sum_error = sum_error + error
213    ALLOCATE(cpl_windsp(klon,2), stat = error)
214    sum_error = sum_error + error
215    ALLOCATE(cpl_taumod(klon,2), stat = error)
216    sum_error = sum_error + error
217    ALLOCATE(cpl_sens_rain(klon,2), stat = error)
218    sum_error = sum_error + error
219    ALLOCATE(cpl_sens_snow(klon,2), stat = error)
220    sum_error = sum_error + error
221    ALLOCATE(cpl_rriv2D(nbp_lon,jj_nb), stat=error)
222    sum_error = sum_error + error
223    ALLOCATE(cpl_rcoa2D(nbp_lon,jj_nb), stat=error)
224    sum_error = sum_error + error
225    ALLOCATE(cpl_rlic2D(nbp_lon,jj_nb), stat=error)
226    sum_error = sum_error + error
227    ALLOCATE(read_sst(nbp_lon, jj_nb), stat = error)
228    sum_error = sum_error + error
229    ALLOCATE(read_sic(nbp_lon, jj_nb), stat = error)
230    sum_error = sum_error + error
231    ALLOCATE(read_sit(nbp_lon, jj_nb), stat = error)
232    sum_error = sum_error + error
233
234    if (activate_ocean_skin >= 1) then
235       ALLOCATE(read_sss(nbp_lon, jj_nb), stat = error)
236       sum_error = sum_error + error
237   
238       if (activate_ocean_skin == 2) then
239          ALLOCATE(cpl_t_int(klon), stat = error)
240          sum_error = sum_error + error
241       end if
242    end if
243
244    ALLOCATE(read_alb_sic(nbp_lon, jj_nb), stat = error)
245    sum_error = sum_error + error
246    ALLOCATE(read_u0(nbp_lon, jj_nb), stat = error)
247    sum_error = sum_error + error
248    ALLOCATE(read_v0(nbp_lon, jj_nb), stat = error)
249    sum_error = sum_error + error
250
251    IF (carbon_cycle_cpl) THEN
252       ALLOCATE(read_co2(nbp_lon, jj_nb), stat = error)
253       sum_error = sum_error + error
254       ALLOCATE(cpl_atm_co2(klon,2), stat = error)
255       sum_error = sum_error + error
256
257! Allocate variable in carbon_cycle_mod
258       IF (.NOT.ALLOCATED(fco2_ocn_day)) ALLOCATE(fco2_ocn_day(klon), stat = error)
259       sum_error = sum_error + error
260    ENDIF
261
262! calving initialization
263    ALLOCATE(area_calving(nbp_lon, jj_nb, nb_zone_calving), stat = error)
264    sum_error = sum_error + error
265    ALLOCATE(cell_area2D(nbp_lon, jj_nb), stat = error)   
266    sum_error = sum_error + error
267
268
269    CALL gather_omp(longitude_deg,rlon_mpi)
270    CALL gather_omp(latitude_deg,rlat_mpi)
271    CALL gather_omp(ind_cell_glo,ind_cell_glo_mpi)
272    CALL gather_omp(cell_area,cell_area_mpi)
273     
274    IF (is_omp_master) THEN
275      CALL Grid1DTo2D_mpi(rlon_mpi,lon2D)
276      CALL Grid1DTo2D_mpi(rlat_mpi,lat2D)
277      CALL Grid1DTo2D_mpi(cell_area_mpi,cell_area2D)
278      mask_calving(:,:,:) = 0
279      WHERE ( lat2D >= 40) mask_calving(:,:,1) = 1
280      WHERE ( lat2D < 40 .AND. lat2D > -50) mask_calving(:,:,2) = 1
281      WHERE ( lat2D <= -50) mask_calving(:,:,3) = 1
282   
283   
284      DO i=1,nb_zone_calving
285        area_calving(:,:,i)=mask_calving(:,:,i)*cell_area2D(:,:)
286        pos=1
287        IF (i>1) pos = 1 + ((nbp_lon*nbp_lat-1)*(i-1))/(nb_zone_calving-1)
288     
289        ind_calving(i)=0
290        IF (grid_type==unstructured) THEN
291
292          DO ig=1,klon_mpi
293            IF (ind_cell_glo_mpi(ig)==pos) ind_calving(i)=ig
294          ENDDO
295
296        ELSE IF (grid_type==regular_lonlat) THEN
297          IF ((ij_begin<=pos .AND. ij_end>=pos) .OR. (ij_begin<=pos .AND. is_south_pole_dyn )) THEN
298            ind_calving(i)=pos-(jj_begin-1)*nbp_lon
299          ENDIF
300        ENDIF
301     
302      ENDDO
303    ENDIF
304   
305           
306    IF (sum_error /= 0) THEN
307       abort_message='Pb allocation variables couplees'
308       CALL abort_physic(modname,abort_message,1)
309    ENDIF
310!*************************************************************************************
311! Initialize the allocated varaibles
312!
313!*************************************************************************************
314    DO ig = 1, klon
315       unity(ig) = ig
316    ENDDO
317
318!*************************************************************************************
319! Initialize coupling
320!
321!*************************************************************************************
322    idtime = INT(dtime)
323#ifdef CPP_COUPLE
324    CALL inicma
325#endif
326
327!*************************************************************************************
328! initialize NetCDF output
329!
330!*************************************************************************************
331    IF (is_sequential) THEN
332       idayref = day_ini
333       CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian)
334       CALL grid1dTo2d_glo(rlon,zx_lon)
335       DO i = 1, nbp_lon
336          zx_lon(i,1) = rlon(i+1)
337          zx_lon(i,nbp_lat) = rlon(i+1)
338       ENDDO
339       CALL grid1dTo2d_glo(rlat,zx_lat)
340       clintocplnam="cpl_atm_tauflx"
341       CALL histbeg(clintocplnam,nbp_lon,zx_lon(:,1),nbp_lat,zx_lat(1,:),&
342            1,nbp_lon,1,nbp_lat, itau_phy,zjulian,dtime,nhoridct,nidct)
343! no vertical axis
344       CALL histdef(nidct, 'tauxe','tauxe', &
345            "-",nbp_lon,nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
346       CALL histdef(nidct, 'tauyn','tauyn', &
347            "-",nbp_lon,nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
348       CALL histdef(nidct, 'tmp_lon','tmp_lon', &
349            "-",nbp_lon,nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
350       CALL histdef(nidct, 'tmp_lat','tmp_lat', &
351            "-",nbp_lon,nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)
352       DO jf=1,maxsend
353         IF (infosend(i)%action) THEN
354             CALL histdef(nidct, infosend(i)%name ,infosend(i)%name , &
355                "-",nbp_lon,nbp_lat,nhoridct,1,1,1,-99,32,"inst",dtime,dtime)
356         ENDIF
357       ENDDO
358       CALL histend(nidct)
359       CALL histsync(nidct)
360       
361       clfromcplnam="cpl_atm_sst"
362       CALL histbeg(clfromcplnam,nbp_lon,zx_lon(:,1),nbp_lat,zx_lat(1,:),1,nbp_lon,1,nbp_lat, &
363            0,zjulian,dtime,nhoridcs,nidcs)
364! no vertical axis
365       DO jf=1,maxrecv
366         IF (inforecv(i)%action) THEN
367             CALL histdef(nidcs,inforecv(i)%name ,inforecv(i)%name , &
368                "-",nbp_lon,nbp_lat,nhoridcs,1,1,1,-99,32,"inst",dtime,dtime)
369         ENDIF
370       ENDDO
371       CALL histend(nidcs)
372       CALL histsync(nidcs)
373
374    ENDIF    ! is_sequential
375   
376
377!*************************************************************************************
378! compatibility test
379!
380!*************************************************************************************
381    IF (carbon_cycle_cpl .AND. version_ocean=='opa8') THEN
382       abort_message='carbon_cycle_cpl does not work with opa8'
383       CALL abort_physic(modname,abort_message,1)
384    ENDIF
385
386  END SUBROUTINE cpl_init
387 
388!
389!*************************************************************************************
390!
391 
392  SUBROUTINE cpl_receive_frac(itime, dtime, pctsrf, is_modified)
393! This subroutine receives from coupler for both ocean and seaice
394! 4 fields : read_sst, read_sic, read_sit and read_alb_sic.
395! The new sea-ice-land-landice fraction is returned. The others fields
396! are stored in this module.
397    USE surface_data
398    USE geometry_mod, ONLY : longitude_deg, latitude_deg
399    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
400    USE indice_sol_mod
401    USE time_phylmdz_mod, ONLY: start_time, itau_phy
402    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
403    use config_ocean_skin_m, only: activate_ocean_skin
404
405    INCLUDE "YOMCST.h"
406
407! Arguments
408!************************************************************************************
409    INTEGER, INTENT(IN)                        :: itime
410    REAL, INTENT(IN)                           :: dtime
411    REAL, DIMENSION(klon,nbsrf), INTENT(INOUT) :: pctsrf
412    LOGICAL, INTENT(OUT)                       :: is_modified
413
414! Local variables
415!************************************************************************************
416    INTEGER                                 :: j, i, time_sec
417    INTEGER                                 :: itau_w
418    INTEGER, DIMENSION(nbp_lon*nbp_lat)     :: ndexcs
419    CHARACTER(len = 20)                     :: modname = 'cpl_receive_frac'
420    CHARACTER(len = 80)                     :: abort_message
421    REAL, DIMENSION(klon)                   :: read_sic1D
422    REAL, DIMENSION(nbp_lon,jj_nb,maxrecv)      :: tab_read_flds
423    REAL, DIMENSION(klon,nbsrf)             :: pctsrf_old
424    REAL, DIMENSION(klon_mpi)               :: rlon_mpi, rlat_mpi
425    REAL, DIMENSION(nbp_lon,jj_nb)             :: tmp_lon, tmp_lat
426    REAL, DIMENSION(nbp_lon,jj_nb)             :: tmp_r0
427
428!*************************************************************************************
429! Start calculation
430! Get fields from coupler
431!
432!*************************************************************************************
433
434    is_modified=.FALSE.
435
436! Check if right moment to receive from coupler
437    IF (MOD(itime, nexca) == 1) THEN
438       is_modified=.TRUE.
439 
440       time_sec=(itime-1)*dtime
441#ifdef CPP_COUPLE
442!$OMP MASTER
443    CALL fromcpl(time_sec, tab_read_flds)
444!$OMP END MASTER
445#endif
446   
447! NetCDF output of received fields
448       IF (is_sequential) THEN
449          ndexcs(:) = 0
450          itau_w = itau_phy + itime + start_time * day_step_phy
451          DO i = 1, maxrecv
452            IF (inforecv(i)%action) THEN
453                CALL histwrite(nidcs,inforecv(i)%name,itau_w,tab_read_flds(:,:,i),nbp_lon*(nbp_lat),ndexcs)
454            ENDIF
455          ENDDO
456       ENDIF
457
458
459! Save each field in a 2D array.
460!$OMP MASTER
461       read_sst(:,:)     = tab_read_flds(:,:,idr_sisutw)  ! Sea surface temperature
462       read_sic(:,:)     = tab_read_flds(:,:,idr_icecov)  ! Sea ice concentration
463       read_alb_sic(:,:) = tab_read_flds(:,:,idr_icealw)  ! Albedo at sea ice
464       read_sit(:,:)     = tab_read_flds(:,:,idr_icetem)  ! Sea ice temperature
465       if (activate_ocean_skin >= 1) read_sss(:,:) = tab_read_flds(:,:,idr_sss)
466!$OMP END MASTER
467
468       IF (cpl_current) THEN
469
470! Transform the longitudes and latitudes on 2D arrays
471          CALL gather_omp(longitude_deg,rlon_mpi)
472          CALL gather_omp(latitude_deg,rlat_mpi)
473!$OMP MASTER
474          CALL Grid1DTo2D_mpi(rlon_mpi,tmp_lon)
475          CALL Grid1DTo2D_mpi(rlat_mpi,tmp_lat)
476
477! Transform the currents from cartesian to spheric coordinates
478! tmp_r0 should be zero
479          CALL geo2atm(nbp_lon, jj_nb, tab_read_flds(:,:,idr_curenx), &
480             tab_read_flds(:,:,idr_cureny), tab_read_flds(:,:,idr_curenz), &
481               tmp_lon, tmp_lat, &
482               read_u0(:,:), read_v0(:,:), tmp_r0(:,:))
483!$OMP END MASTER
484
485      ELSE
486          read_u0(:,:) = 0.
487          read_v0(:,:) = 0.
488      ENDIF
489
490       IF (carbon_cycle_cpl) THEN
491!$OMP MASTER
492           read_co2(:,:) = tab_read_flds(:,:,idr_oceco2) ! CO2 flux
493!$OMP END MASTER
494       ENDIF
495
496!*************************************************************************************
497!  Transform seaice fraction (read_sic : ocean-seaice mask) into global
498!  fraction (pctsrf : ocean-seaice-land-landice mask)
499!
500!*************************************************************************************
501       CALL cpl2gath(read_sic, read_sic1D, klon, unity)
502
503       pctsrf_old(:,:) = pctsrf(:,:)
504       DO i = 1, klon
505          ! treatment only of points with ocean and/or seaice
506          ! old land-ocean mask can not be changed
507          IF (pctsrf_old(i,is_oce) + pctsrf_old(i,is_sic) > 0.) THEN
508             pctsrf(i,is_sic) = (pctsrf_old(i,is_oce) + pctsrf_old(i,is_sic)) &
509                  * read_sic1D(i)
510             pctsrf(i,is_oce) = (pctsrf_old(i,is_oce) + pctsrf_old(i,is_sic)) &
511                  - pctsrf(i,is_sic)
512          ENDIF
513       ENDDO
514
515    ENDIF ! if time to receive
516
517  END SUBROUTINE cpl_receive_frac
518
519!
520!*************************************************************************************
521!
522
523  SUBROUTINE cpl_receive_ocean_fields(knon, knindex, tsurf_new, u0_new, &
524       v0_new, sss)
525!
526! This routine returns the field for the ocean that has been read from the coupler
527! (done earlier with cpl_receive_frac). The field is the temperature.
528! The temperature is transformed into 1D array with valid points from index 1 to knon.
529!
530    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, fco2_ocn_day
531    USE indice_sol_mod
532    use config_ocean_skin_m, only: activate_ocean_skin
533
534! Input arguments
535!*************************************************************************************
536    INTEGER, INTENT(IN)                     :: knon
537    INTEGER, DIMENSION(klon), INTENT(IN)    :: knindex
538
539! Output arguments
540!*************************************************************************************
541    REAL, DIMENSION(klon), INTENT(OUT)      :: tsurf_new
542
543    REAL, INTENT(OUT):: sss(:) ! (klon)
544    ! bulk salinity of the surface layer of the ocean, in ppt
545
546    REAL, DIMENSION(klon), INTENT(OUT)      :: u0_new
547    REAL, DIMENSION(klon), INTENT(OUT)      :: v0_new
548
549! Local variables
550!*************************************************************************************
551    INTEGER                  :: i
552    INTEGER, DIMENSION(klon) :: index
553    REAL, DIMENSION(klon)    :: sic_new
554
555!*************************************************************************************
556! Transform read_sst into compressed 1D variable tsurf_new
557!
558!*************************************************************************************
559    CALL cpl2gath(read_sst, tsurf_new, knon, knindex)
560    if (activate_ocean_skin >= 1) CALL cpl2gath(read_sss, sss, knon, knindex)
561    CALL cpl2gath(read_sic, sic_new, knon, knindex)
562    CALL cpl2gath(read_u0, u0_new, knon, knindex)
563    CALL cpl2gath(read_v0, v0_new, knon, knindex)
564
565!*************************************************************************************
566! Transform read_co2 into uncompressed 1D variable fco2_ocn_day added directly in
567! the module carbon_cycle_mod
568!
569!*************************************************************************************
570    IF (carbon_cycle_cpl) THEN
571       DO i=1,klon
572          index(i)=i
573       ENDDO
574       CALL cpl2gath(read_co2, fco2_ocn_day, klon, index)
575    ENDIF
576
577!*************************************************************************************
578! The fields received from the coupler have to be weighted with the fraction of ocean
579! in relation to the total sea-ice+ocean
580!
581!*************************************************************************************
582    DO i=1, knon
583       tsurf_new(i) = tsurf_new(i)/(1. - sic_new(i))
584    ENDDO
585
586  END SUBROUTINE cpl_receive_ocean_fields
587
588!
589!*************************************************************************************
590!
591
592  SUBROUTINE cpl_receive_seaice_fields(knon, knindex, &
593       tsurf_new, alb_new, u0_new, v0_new)
594!
595! This routine returns the fields for the seaice that have been read from the coupler
596! (done earlier with cpl_receive_frac). These fields are the temperature and
597! albedo at sea ice surface and fraction of sea ice.
598! The fields are transformed into 1D arrays with valid points from index 1 to knon.
599!
600
601! Input arguments
602!*************************************************************************************
603    INTEGER, INTENT(IN)                     :: knon
604    INTEGER, DIMENSION(klon), INTENT(IN)    :: knindex
605
606! Output arguments
607!*************************************************************************************
608    REAL, DIMENSION(klon), INTENT(OUT)      :: tsurf_new
609    REAL, DIMENSION(klon), INTENT(OUT)      :: alb_new
610    REAL, DIMENSION(klon), INTENT(OUT)      :: u0_new
611    REAL, DIMENSION(klon), INTENT(OUT)      :: v0_new
612
613! Local variables
614!*************************************************************************************
615    INTEGER               :: i
616    REAL, DIMENSION(klon) :: sic_new
617
618!*************************************************************************************
619! Transform fields read from coupler from 2D into compressed 1D variables
620!
621!*************************************************************************************
622    CALL cpl2gath(read_sit, tsurf_new, knon, knindex)
623    CALL cpl2gath(read_alb_sic, alb_new, knon, knindex)
624    CALL cpl2gath(read_sic, sic_new, knon, knindex)
625    CALL cpl2gath(read_u0, u0_new, knon, knindex)
626    CALL cpl2gath(read_v0, v0_new, knon, knindex)
627
628!*************************************************************************************
629! The fields received from the coupler have to be weighted with the sea-ice
630! concentration (in relation to the total sea-ice + ocean).
631!
632!*************************************************************************************
633    DO i= 1, knon
634       tsurf_new(i) = tsurf_new(i) / sic_new(i)
635       alb_new(i)   = alb_new(i)   / sic_new(i)
636    ENDDO
637
638  END SUBROUTINE cpl_receive_seaice_fields
639
640!
641!*************************************************************************************
642!
643
644  SUBROUTINE cpl_send_ocean_fields(itime, knon, knindex, &
645       swdown, lwdown, fluxlat, fluxsens, &
646       precip_rain, precip_snow, evap, tsurf, fder, albsol, taux, tauy, windsp,&
647       sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol, t_int)
648
649    ! This subroutine cumulates some fields for each time-step during
650    ! a coupling period. At last time-step in a coupling period the
651    ! fields are transformed to the grid accepted by the coupler. No
652    ! sending to the coupler will be done from here (it is done in
653    ! cpl_send_seaice_fields). Crucial hypothesis is that the surface
654    ! fractions do not change between coupling time-steps.
655
656    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send
657    USE indice_sol_mod
658    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
659    use config_ocean_skin_m, only: activate_ocean_skin
660
661! Input arguments
662!*************************************************************************************
663    INTEGER, INTENT(IN)                     :: itime
664    INTEGER, INTENT(IN)                     :: knon
665    INTEGER, DIMENSION(klon), INTENT(IN)    :: knindex
666    REAL, DIMENSION(klon), INTENT(IN)       :: swdown, lwdown
667    REAL, DIMENSION(klon), INTENT(IN)       :: fluxlat, fluxsens
668    REAL, DIMENSION(klon), INTENT(IN)       :: precip_rain, precip_snow
669    REAL, DIMENSION(klon), INTENT(IN)       :: evap, tsurf, fder, albsol
670    REAL, DIMENSION(klon), INTENT(IN)       :: taux, tauy, windsp
671    REAL, DIMENSION(klon), INTENT(IN)       :: sens_prec_liq, sens_prec_sol
672    REAL, DIMENSION(klon), INTENT(IN)       :: lat_prec_liq, lat_prec_sol
673    real, intent(in):: t_int(:) ! (klon) ocean-air interface temperature, in K
674
675! Local variables
676!*************************************************************************************
677    INTEGER                                 :: cpl_index, ig
678    INTEGER                                 :: error, sum_error
679    CHARACTER(len = 25)                     :: modname = 'cpl_send_ocean_fields'
680    CHARACTER(len = 80)                     :: abort_message
681
682!*************************************************************************************
683! Start calculation
684! The ocean points are saved with second array index=1
685!
686!*************************************************************************************
687    cpl_index = 1
688
689!*************************************************************************************
690! Reset fields to zero in the beginning of a new coupling period
691!
692!*************************************************************************************
693    IF (MOD(itime, nexca) == 1) THEN
694       cpl_sols(1:knon,cpl_index) = 0.0
695       cpl_nsol(1:knon,cpl_index) = 0.0
696       cpl_rain(1:knon,cpl_index) = 0.0
697       cpl_snow(1:knon,cpl_index) = 0.0
698       cpl_evap(1:knon,cpl_index) = 0.0
699       cpl_tsol(1:knon,cpl_index) = 0.0
700       cpl_fder(1:knon,cpl_index) = 0.0
701       cpl_albe(1:knon,cpl_index) = 0.0
702       cpl_taux(1:knon,cpl_index) = 0.0
703       cpl_tauy(1:knon,cpl_index) = 0.0
704       cpl_windsp(1:knon,cpl_index) = 0.0
705       cpl_sens_rain(1:knon,cpl_index) = 0.0
706       cpl_sens_snow(1:knon,cpl_index) = 0.0
707       cpl_taumod(1:knon,cpl_index) = 0.0
708       IF (carbon_cycle_cpl) cpl_atm_co2(1:knon,cpl_index) = 0.0
709       if (activate_ocean_skin == 2) cpl_t_int(:knon) = 0.
710    ENDIF
711       
712!*************************************************************************************
713! Cumulate at each time-step
714!
715!*************************************************************************************   
716    DO ig = 1, knon
717       cpl_sols(ig,cpl_index) = cpl_sols(ig,cpl_index) + &
718            swdown(ig)      / REAL(nexca)
719       cpl_nsol(ig,cpl_index) = cpl_nsol(ig,cpl_index) + &
720            (lwdown(ig) + fluxlat(ig) +fluxsens(ig)) / REAL(nexca)
721       cpl_rain(ig,cpl_index) = cpl_rain(ig,cpl_index) + &
722            precip_rain(ig) / REAL(nexca)
723       cpl_snow(ig,cpl_index) = cpl_snow(ig,cpl_index) + &
724            precip_snow(ig) / REAL(nexca)
725       cpl_evap(ig,cpl_index) = cpl_evap(ig,cpl_index) + &
726            evap(ig)        / REAL(nexca)
727       cpl_tsol(ig,cpl_index) = cpl_tsol(ig,cpl_index) + &
728            tsurf(ig)       / REAL(nexca)
729       cpl_fder(ig,cpl_index) = cpl_fder(ig,cpl_index) + &
730            fder(ig)        / REAL(nexca)
731       cpl_albe(ig,cpl_index) = cpl_albe(ig,cpl_index) + &
732            albsol(ig)      / REAL(nexca)
733       cpl_taux(ig,cpl_index) = cpl_taux(ig,cpl_index) + &
734            taux(ig)        / REAL(nexca)
735       cpl_tauy(ig,cpl_index) = cpl_tauy(ig,cpl_index) + &
736            tauy(ig)        / REAL(nexca)     
737       cpl_windsp(ig,cpl_index) = cpl_windsp(ig,cpl_index) + &
738            windsp(ig)      / REAL(nexca)
739       cpl_sens_rain(ig,cpl_index) = cpl_sens_rain(ig,cpl_index) + &
740            sens_prec_liq(ig)      / REAL(nexca)
741       cpl_sens_snow(ig,cpl_index) = cpl_sens_snow(ig,cpl_index) + &
742            sens_prec_sol(ig)      / REAL(nexca)
743       cpl_taumod(ig,cpl_index) =   cpl_taumod(ig,cpl_index) + &
744          SQRT ( taux(ig)*taux(ig)+tauy(ig)*tauy(ig) ) / REAL (nexca)
745
746       IF (carbon_cycle_cpl) THEN
747          cpl_atm_co2(ig,cpl_index) = cpl_atm_co2(ig,cpl_index) + &
748               co2_send(knindex(ig))/ REAL(nexca)
749!!---OB: this is correct but why knindex ??
750       ENDIF
751
752       if (activate_ocean_skin == 2) &
753            cpl_t_int(ig) = cpl_t_int(ig) + t_int(ig) / REAL(nexca)
754     ENDDO
755
756!*************************************************************************************
757! If the time-step corresponds to the end of coupling period the
758! fields are transformed to the 2D grid.
759! No sending to the coupler (it is done from cpl_send_seaice_fields).
760!
761!*************************************************************************************
762    IF (MOD(itime, nexca) == 0) THEN
763
764       IF (.NOT. ALLOCATED(cpl_sols2D)) THEN
765          sum_error = 0
766          ALLOCATE(cpl_sols2D(nbp_lon,jj_nb,2), stat=error)
767          sum_error = sum_error + error
768          ALLOCATE(cpl_nsol2D(nbp_lon,jj_nb,2), stat=error)
769          sum_error = sum_error + error
770          ALLOCATE(cpl_rain2D(nbp_lon,jj_nb,2), stat=error)
771          sum_error = sum_error + error
772          ALLOCATE(cpl_snow2D(nbp_lon,jj_nb,2), stat=error)
773          sum_error = sum_error + error
774          ALLOCATE(cpl_evap2D(nbp_lon,jj_nb,2), stat=error)
775          sum_error = sum_error + error
776          ALLOCATE(cpl_tsol2D(nbp_lon,jj_nb,2), stat=error)
777          sum_error = sum_error + error
778          ALLOCATE(cpl_fder2D(nbp_lon,jj_nb,2), stat=error)
779          sum_error = sum_error + error
780          ALLOCATE(cpl_albe2D(nbp_lon,jj_nb,2), stat=error)
781          sum_error = sum_error + error
782          ALLOCATE(cpl_taux2D(nbp_lon,jj_nb,2), stat=error)
783          sum_error = sum_error + error
784          ALLOCATE(cpl_tauy2D(nbp_lon,jj_nb,2), stat=error)
785          sum_error = sum_error + error
786          ALLOCATE(cpl_windsp2D(nbp_lon,jj_nb), stat=error)
787          sum_error = sum_error + error
788          ALLOCATE(cpl_sens_rain2D(nbp_lon,jj_nb,2), stat=error)
789          sum_error = sum_error + error
790          ALLOCATE(cpl_sens_snow2D(nbp_lon,jj_nb,2), stat=error)
791          sum_error = sum_error + error
792          ALLOCATE(cpl_taumod2D(nbp_lon,jj_nb,2), stat=error)
793          sum_error = sum_error + error
794         
795          IF (carbon_cycle_cpl) THEN
796             ALLOCATE(cpl_atm_co22D(nbp_lon,jj_nb), stat=error)
797             sum_error = sum_error + error
798          ENDIF
799
800          if (activate_ocean_skin == 2) then
801             ALLOCATE(cpl_t_int_2D(nbp_lon, jj_nb), stat = error)
802             sum_error = sum_error + error
803          end if
804
805          IF (sum_error /= 0) THEN
806             abort_message='Pb allocation variables couplees pour l''ecriture'
807             CALL abort_physic(modname,abort_message,1)
808          ENDIF
809       ENDIF
810       
811
812       CALL gath2cpl(cpl_sols(:,cpl_index), cpl_sols2D(:,:,cpl_index), &
813            knon, knindex)
814
815       CALL gath2cpl(cpl_nsol(:,cpl_index), cpl_nsol2D(:,:,cpl_index), &
816            knon, knindex)
817
818       CALL gath2cpl(cpl_rain(:,cpl_index), cpl_rain2D(:,:,cpl_index), &
819            knon, knindex)
820
821       CALL gath2cpl(cpl_snow(:,cpl_index), cpl_snow2D(:,:,cpl_index), &
822            knon, knindex)
823
824       CALL gath2cpl(cpl_evap(:,cpl_index), cpl_evap2D(:,:,cpl_index), &
825            knon, knindex)
826
827! cpl_tsol2D(:,:,:) not used!
828       CALL gath2cpl(cpl_tsol(:,cpl_index), cpl_tsol2D(:,:, cpl_index), &
829            knon, knindex)
830
831! cpl_fder2D(:,:,1) not used, only cpl_fder(:,:,2)!
832       CALL gath2cpl(cpl_fder(:,cpl_index), cpl_fder2D(:,:,cpl_index), &
833            knon, knindex)
834
835! cpl_albe2D(:,:,:) not used!
836       CALL gath2cpl(cpl_albe(:,cpl_index), cpl_albe2D(:,:,cpl_index), &
837            knon, knindex)
838
839       CALL gath2cpl(cpl_taux(:,cpl_index), cpl_taux2D(:,:,cpl_index), &
840            knon, knindex)
841
842       CALL gath2cpl(cpl_tauy(:,cpl_index), cpl_tauy2D(:,:,cpl_index), &
843            knon, knindex)
844
845       CALL gath2cpl(cpl_windsp(:,cpl_index), cpl_windsp2D(:,:), &
846            knon, knindex)
847
848       CALL gath2cpl(cpl_sens_rain(:,cpl_index), cpl_sens_rain2D(:,:,cpl_index), &
849            knon, knindex)
850
851       CALL gath2cpl(cpl_sens_snow(:,cpl_index), cpl_sens_snow2D(:,:,cpl_index), &
852            knon, knindex)
853
854       CALL gath2cpl(cpl_taumod(:,cpl_index), cpl_taumod2D(:,:,cpl_index), &
855            knon, knindex)
856
857       IF (carbon_cycle_cpl) &
858            CALL gath2cpl(cpl_atm_co2(:,cpl_index), cpl_atm_co22D(:,:), knon, knindex)
859       if (activate_ocean_skin == 2) &
860            CALL gath2cpl(cpl_t_int, cpl_t_int_2D, knon, knindex)
861    ENDIF
862
863  END SUBROUTINE cpl_send_ocean_fields
864
865!
866!*************************************************************************************
867!
868
869  SUBROUTINE cpl_send_seaice_fields(itime, dtime, knon, knindex, &
870       pctsrf, lafin, rlon, rlat, &
871       swdown, lwdown, fluxlat, fluxsens, &
872       precip_rain, precip_snow, evap, tsurf, fder, albsol, taux, tauy,&
873       sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol)
874!
875! This subroutine cumulates some fields for each time-step during a coupling
876! period. At last time-step in a coupling period the fields are transformed to the
877! grid accepted by the coupler. All fields for all types of surfaces are sent to
878! the coupler.
879!
880    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
881    USE indice_sol_mod
882    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
883
884! Input arguments
885!*************************************************************************************
886    INTEGER, INTENT(IN)                     :: itime
887    INTEGER, INTENT(IN)                     :: knon
888    INTEGER, DIMENSION(klon), INTENT(IN)    :: knindex
889    REAL, INTENT(IN)                        :: dtime
890    REAL, DIMENSION(klon), INTENT(IN)       :: rlon, rlat
891    REAL, DIMENSION(klon), INTENT(IN)       :: swdown, lwdown
892    REAL, DIMENSION(klon), INTENT(IN)       :: fluxlat, fluxsens
893    REAL, DIMENSION(klon), INTENT(IN)       :: precip_rain, precip_snow
894    REAL, DIMENSION(klon), INTENT(IN)       :: evap, tsurf, fder
895    REAL, DIMENSION(klon), INTENT(IN)       :: albsol, taux, tauy
896    REAL, DIMENSION(klon,nbsrf), INTENT(IN) :: pctsrf
897    REAL, DIMENSION(klon), INTENT(IN)       :: sens_prec_liq, sens_prec_sol
898    REAL, DIMENSION(klon), INTENT(IN)       :: lat_prec_liq, lat_prec_sol
899    LOGICAL, INTENT(IN)                     :: lafin
900
901! Local variables
902!*************************************************************************************
903    INTEGER                                 :: cpl_index, ig
904    INTEGER                                 :: error, sum_error
905    CHARACTER(len = 25)                     :: modname = 'cpl_send_seaice_fields'
906    CHARACTER(len = 80)                     :: abort_message
907    REAL, DIMENSION(klon)                   :: cpl_fder_tmp
908
909!*************************************************************************************
910! Start calulation
911! The sea-ice points are saved with second array index=2
912!
913!*************************************************************************************
914    cpl_index = 2
915
916!*************************************************************************************
917! Reset fields to zero in the beginning of a new coupling period
918!
919!*************************************************************************************
920    IF (MOD(itime, nexca) == 1) THEN
921       cpl_sols(1:knon,cpl_index) = 0.0
922       cpl_nsol(1:knon,cpl_index) = 0.0
923       cpl_rain(1:knon,cpl_index) = 0.0
924       cpl_snow(1:knon,cpl_index) = 0.0
925       cpl_evap(1:knon,cpl_index) = 0.0
926       cpl_tsol(1:knon,cpl_index) = 0.0
927       cpl_fder(1:knon,cpl_index) = 0.0
928       cpl_albe(1:knon,cpl_index) = 0.0
929       cpl_taux(1:knon,cpl_index) = 0.0
930       cpl_tauy(1:knon,cpl_index) = 0.0
931       cpl_sens_rain(1:knon,cpl_index) = 0.0
932       cpl_sens_snow(1:knon,cpl_index) = 0.0
933       cpl_taumod(1:knon,cpl_index) = 0.0
934    ENDIF
935       
936!*************************************************************************************
937! Cumulate at each time-step
938!
939!*************************************************************************************   
940    DO ig = 1, knon
941       cpl_sols(ig,cpl_index) = cpl_sols(ig,cpl_index) + &
942            swdown(ig)      / REAL(nexca)
943       cpl_nsol(ig,cpl_index) = cpl_nsol(ig,cpl_index) + &
944            (lwdown(ig) + fluxlat(ig) +fluxsens(ig)) / REAL(nexca)
945       cpl_rain(ig,cpl_index) = cpl_rain(ig,cpl_index) + &
946            precip_rain(ig) / REAL(nexca)
947       cpl_snow(ig,cpl_index) = cpl_snow(ig,cpl_index) + &
948            precip_snow(ig) / REAL(nexca)
949       cpl_evap(ig,cpl_index) = cpl_evap(ig,cpl_index) + &
950            evap(ig)        / REAL(nexca)
951       cpl_tsol(ig,cpl_index) = cpl_tsol(ig,cpl_index) + &
952            tsurf(ig)       / REAL(nexca)
953       cpl_fder(ig,cpl_index) = cpl_fder(ig,cpl_index) + &
954            fder(ig)        / REAL(nexca)
955       cpl_albe(ig,cpl_index) = cpl_albe(ig,cpl_index) + &
956            albsol(ig)      / REAL(nexca)
957       cpl_taux(ig,cpl_index) = cpl_taux(ig,cpl_index) + &
958            taux(ig)        / REAL(nexca)
959       cpl_tauy(ig,cpl_index) = cpl_tauy(ig,cpl_index) + &
960            tauy(ig)        / REAL(nexca)     
961       cpl_sens_rain(ig,cpl_index) = cpl_sens_rain(ig,cpl_index) + &
962            sens_prec_liq(ig)      / REAL(nexca)
963       cpl_sens_snow(ig,cpl_index) = cpl_sens_snow(ig,cpl_index) + &
964            sens_prec_sol(ig)      / REAL(nexca)
965       cpl_taumod(ig,cpl_index) = cpl_taumod(ig,cpl_index) + &
966            SQRT ( taux(ig)*taux(ig)+tauy(ig)*tauy(ig) ) / REAL(nexca)
967    ENDDO
968
969!*************************************************************************************
970! If the time-step corresponds to the end of coupling period the
971! fields are transformed to the 2D grid and all fields are sent to coupler.
972!
973!*************************************************************************************
974    IF (MOD(itime, nexca) == 0) THEN
975       IF (.NOT. ALLOCATED(cpl_sols2D)) THEN
976          sum_error = 0
977          ALLOCATE(cpl_sols2D(nbp_lon,jj_nb,2), stat=error)
978          sum_error = sum_error + error
979          ALLOCATE(cpl_nsol2D(nbp_lon,jj_nb,2), stat=error)
980          sum_error = sum_error + error
981          ALLOCATE(cpl_rain2D(nbp_lon,jj_nb,2), stat=error)
982          sum_error = sum_error + error
983          ALLOCATE(cpl_snow2D(nbp_lon,jj_nb,2), stat=error)
984          sum_error = sum_error + error
985          ALLOCATE(cpl_evap2D(nbp_lon,jj_nb,2), stat=error)
986          sum_error = sum_error + error
987          ALLOCATE(cpl_tsol2D(nbp_lon,jj_nb,2), stat=error)
988          sum_error = sum_error + error
989          ALLOCATE(cpl_fder2D(nbp_lon,jj_nb,2), stat=error)
990          sum_error = sum_error + error
991          ALLOCATE(cpl_albe2D(nbp_lon,jj_nb,2), stat=error)
992          sum_error = sum_error + error
993          ALLOCATE(cpl_taux2D(nbp_lon,jj_nb,2), stat=error)
994          sum_error = sum_error + error
995          ALLOCATE(cpl_tauy2D(nbp_lon,jj_nb,2), stat=error)
996          sum_error = sum_error + error
997          ALLOCATE(cpl_windsp2D(nbp_lon,jj_nb), stat=error)
998          sum_error = sum_error + error
999          ALLOCATE(cpl_sens_rain2D(nbp_lon,jj_nb,2), stat=error)
1000          sum_error = sum_error + error
1001          ALLOCATE(cpl_sens_snow2D(nbp_lon,jj_nb,2), stat=error)
1002          sum_error = sum_error + error
1003          ALLOCATE(cpl_taumod2D(nbp_lon,jj_nb,2), stat=error)
1004          sum_error = sum_error + error
1005
1006          IF (carbon_cycle_cpl) THEN
1007             ALLOCATE(cpl_atm_co22D(nbp_lon,jj_nb), stat=error)
1008             sum_error = sum_error + error
1009          ENDIF
1010
1011          IF (sum_error /= 0) THEN
1012             abort_message='Pb allocation variables couplees pour l''ecriture'
1013             CALL abort_physic(modname,abort_message,1)
1014          ENDIF
1015       ENDIF
1016
1017       CALL gath2cpl(cpl_sols(:,cpl_index), cpl_sols2D(:,:,cpl_index), &
1018            knon, knindex)
1019
1020       CALL gath2cpl(cpl_nsol(:,cpl_index), cpl_nsol2D(:,:,cpl_index), &
1021            knon, knindex)
1022
1023       CALL gath2cpl(cpl_rain(:,cpl_index), cpl_rain2D(:,:,cpl_index), &
1024            knon, knindex)
1025
1026       CALL gath2cpl(cpl_snow(:,cpl_index), cpl_snow2D(:,:,cpl_index), &
1027            knon, knindex)
1028
1029       CALL gath2cpl(cpl_evap(:,cpl_index), cpl_evap2D(:,:,cpl_index), &
1030            knon, knindex)
1031
1032! cpl_tsol2D(:,:,:) not used!
1033       CALL gath2cpl(cpl_tsol(:,cpl_index), cpl_tsol2D(:,:, cpl_index), &
1034            knon, knindex)
1035
1036       ! Set default value and decompress before gath2cpl
1037       cpl_fder_tmp(:) = -20.
1038       DO ig = 1, knon
1039          cpl_fder_tmp(knindex(ig))=cpl_fder(ig,cpl_index)
1040       ENDDO
1041       CALL gath2cpl(cpl_fder_tmp(:), cpl_fder2D(:,:,cpl_index), &
1042            klon, unity)
1043
1044! cpl_albe2D(:,:,:) not used!
1045       CALL gath2cpl(cpl_albe(:,cpl_index), cpl_albe2D(:,:,cpl_index), &
1046            knon, knindex)
1047
1048       CALL gath2cpl(cpl_taux(:,cpl_index), cpl_taux2D(:,:,cpl_index), &
1049            knon, knindex)
1050
1051       CALL gath2cpl(cpl_tauy(:,cpl_index), cpl_tauy2D(:,:,cpl_index), &
1052            knon, knindex)
1053
1054       CALL gath2cpl(cpl_sens_rain(:,cpl_index), cpl_sens_rain2D(:,:,cpl_index), &
1055            knon, knindex)
1056
1057       CALL gath2cpl(cpl_sens_snow(:,cpl_index), cpl_sens_snow2D(:,:,cpl_index), &
1058            knon, knindex)
1059
1060       CALL gath2cpl(cpl_taumod(:,cpl_index), cpl_taumod2D(:,:,cpl_index), &
1061            knon, knindex)
1062
1063       ! Send all fields
1064       CALL cpl_send_all(itime, dtime, pctsrf, lafin, rlon, rlat)
1065    ENDIF
1066
1067  END SUBROUTINE cpl_send_seaice_fields
1068
1069!
1070!*************************************************************************************
1071!
1072
1073  SUBROUTINE cpl_send_land_fields(itime, knon, knindex, rriv_in, rcoa_in)
1074!
1075! This subroutine cumulates some fields for each time-step during a coupling
1076! period. At last time-step in a coupling period the fields are transformed to the
1077! grid accepted by the coupler. No sending to the coupler will be done from here
1078! (it is done in cpl_send_seaice_fields).
1079!
1080    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
1081
1082! Input arguments
1083!*************************************************************************************
1084    INTEGER, INTENT(IN)                       :: itime
1085    INTEGER, INTENT(IN)                       :: knon
1086    INTEGER, DIMENSION(klon), INTENT(IN)      :: knindex
1087    REAL, DIMENSION(klon), INTENT(IN)         :: rriv_in
1088    REAL, DIMENSION(klon), INTENT(IN)         :: rcoa_in
1089
1090! Local variables
1091!*************************************************************************************
1092    REAL, DIMENSION(nbp_lon,jj_nb)             :: rriv2D
1093    REAL, DIMENSION(nbp_lon,jj_nb)             :: rcoa2D
1094
1095!*************************************************************************************
1096! Rearrange fields in 2D variables
1097! First initialize to zero to avoid unvalid points causing problems
1098!
1099!*************************************************************************************
1100!$OMP MASTER
1101    rriv2D(:,:) = 0.0
1102    rcoa2D(:,:) = 0.0
1103!$OMP END MASTER
1104    CALL gath2cpl(rriv_in, rriv2D, knon, knindex)
1105    CALL gath2cpl(rcoa_in, rcoa2D, knon, knindex)
1106
1107!*************************************************************************************
1108! Reset cumulated fields to zero in the beginning of a new coupling period
1109!
1110!*************************************************************************************
1111    IF (MOD(itime, nexca) == 1) THEN
1112!$OMP MASTER
1113       cpl_rriv2D(:,:) = 0.0
1114       cpl_rcoa2D(:,:) = 0.0
1115!$OMP END MASTER
1116    ENDIF
1117
1118!*************************************************************************************
1119! Cumulate : Following fields should be cumulated at each time-step
1120!
1121!*************************************************************************************   
1122!$OMP MASTER
1123    cpl_rriv2D(:,:) = cpl_rriv2D(:,:) + rriv2D(:,:) / REAL(nexca)
1124    cpl_rcoa2D(:,:) = cpl_rcoa2D(:,:) + rcoa2D(:,:) / REAL(nexca)
1125!$OMP END MASTER
1126
1127  END SUBROUTINE cpl_send_land_fields
1128
1129!
1130!*************************************************************************************
1131!
1132
1133  SUBROUTINE cpl_send_landice_fields(itime, knon, knindex, rlic_in)
1134! This subroutine cumulates the field for melting ice for each time-step
1135! during a coupling period. This routine will not send to coupler. Sending
1136! will be done in cpl_send_seaice_fields.
1137!
1138
1139    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
1140
1141! Input varibales
1142!*************************************************************************************
1143    INTEGER, INTENT(IN)                       :: itime
1144    INTEGER, INTENT(IN)                       :: knon
1145    INTEGER, DIMENSION(klon), INTENT(IN)      :: knindex
1146    REAL, DIMENSION(klon), INTENT(IN)         :: rlic_in
1147
1148! Local varibales
1149!*************************************************************************************
1150    REAL, DIMENSION(nbp_lon,jj_nb)             :: rlic2D
1151
1152!*************************************************************************************
1153! Rearrange field in a 2D variable
1154! First initialize to zero to avoid unvalid points causing problems
1155!
1156!*************************************************************************************
1157!$OMP MASTER
1158    rlic2D(:,:) = 0.0
1159!$OMP END MASTER
1160    CALL gath2cpl(rlic_in, rlic2D, knon, knindex)
1161
1162!*************************************************************************************
1163! Reset field to zero in the beginning of a new coupling period
1164!
1165!*************************************************************************************
1166    IF (MOD(itime, nexca) == 1) THEN
1167!$OMP MASTER
1168       cpl_rlic2D(:,:) = 0.0
1169!$OMP END MASTER
1170    ENDIF
1171
1172!*************************************************************************************
1173! Cumulate : Melting ice should be cumulated at each time-step
1174!
1175!*************************************************************************************   
1176!$OMP MASTER
1177    cpl_rlic2D(:,:) = cpl_rlic2D(:,:) + rlic2D(:,:) / REAL(nexca)
1178!$OMP END MASTER
1179
1180  END SUBROUTINE cpl_send_landice_fields
1181
1182!
1183!*************************************************************************************
1184!
1185
1186  SUBROUTINE cpl_send_all(itime, dtime, pctsrf, lafin, rlon, rlat)
1187! This routine will send fields for all different surfaces to the coupler.
1188! This subroutine should be executed after calculations by the last surface(sea-ice),
1189! all calculations at the different surfaces have to be done before.
1190!   
1191    USE surface_data
1192    USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
1193    USE indice_sol_mod
1194    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
1195    USE time_phylmdz_mod, ONLY: start_time, itau_phy
1196    use config_ocean_skin_m, only: activate_ocean_skin
1197! Some includes
1198!   
1199! Input arguments
1200!*************************************************************************************
1201    INTEGER, INTENT(IN)                                  :: itime
1202    REAL, INTENT(IN)                                     :: dtime
1203    REAL, DIMENSION(klon), INTENT(IN)                    :: rlon, rlat
1204    REAL, DIMENSION(klon,nbsrf), INTENT(IN)              :: pctsrf
1205    LOGICAL, INTENT(IN)                                  :: lafin
1206   
1207! Local variables
1208!*************************************************************************************
1209    INTEGER                                              :: error, sum_error, i,j,k
1210    INTEGER                                              :: itau_w
1211    INTEGER                                              :: time_sec
1212    INTEGER, DIMENSION(nbp_lon*(nbp_lat))                      :: ndexct
1213    REAL                                                 :: Up, Down
1214    REAL, DIMENSION(nbp_lon, jj_nb)                          :: tmp_lon, tmp_lat
1215    REAL, DIMENSION(nbp_lon, jj_nb, 4)                       :: pctsrf2D
1216    REAL, DIMENSION(nbp_lon, jj_nb)                          :: deno
1217    CHARACTER(len = 20)                                  :: modname = 'cpl_send_all'
1218    CHARACTER(len = 80)                                  :: abort_message
1219   
1220! Variables with fields to coupler
1221    REAL, DIMENSION(nbp_lon, jj_nb)                          :: tmp_taux
1222    REAL, DIMENSION(nbp_lon, jj_nb)                          :: tmp_tauy
1223    REAL, DIMENSION(nbp_lon, jj_nb)                          :: tmp_calv
1224! Table with all fields to send to coupler
1225    REAL, DIMENSION(nbp_lon, jj_nb, maxsend)                 :: tab_flds
1226    REAL, DIMENSION(klon_mpi)                                :: rlon_mpi, rlat_mpi
1227    REAL  :: calving(nb_zone_calving)
1228    REAL  :: calving_glo(nb_zone_calving)
1229   
1230#ifdef CPP_MPI
1231    INCLUDE 'mpif.h'
1232    INTEGER, DIMENSION(MPI_STATUS_SIZE)                  :: status
1233#endif
1234
1235! End definitions
1236!*************************************************************************************
1237   
1238
1239
1240!*************************************************************************************
1241! All fields are stored in a table tab_flds(:,:,:)
1242! First store the fields which are already on the right format
1243!
1244!*************************************************************************************
1245!$OMP MASTER
1246    tab_flds(:,:,ids_windsp) = cpl_windsp2D(:,:)
1247    tab_flds(:,:,ids_shfice) = cpl_sols2D(:,:,2)
1248    tab_flds(:,:,ids_nsfice) = cpl_nsol2D(:,:,2)
1249    tab_flds(:,:,ids_dflxdt) = cpl_fder2D(:,:,2)
1250    tab_flds(:,:,ids_qraioc) = cpl_sens_rain2D(:,:,1)
1251    tab_flds(:,:,ids_qsnooc) = cpl_sens_snow2D(:,:,1)
1252    tab_flds(:,:,ids_qraiic) = cpl_sens_rain2D(:,:,2)
1253    tab_flds(:,:,ids_qsnoic) = cpl_sens_snow2D(:,:,2)
1254    if (activate_ocean_skin == 2) tab_flds(:, :, ids_t_int) = cpl_t_int_2D
1255   
1256    IF (version_ocean=='nemo') THEN
1257       tab_flds(:,:,ids_liqrun) = (cpl_rriv2D(:,:) + cpl_rcoa2D(:,:))
1258       IF (carbon_cycle_cpl) tab_flds(:,:,ids_atmco2)=cpl_atm_co22D(:,:)
1259    ELSE IF (version_ocean=='opa8') THEN
1260       tab_flds(:,:,ids_shfoce) = cpl_sols2D(:,:,1)
1261       tab_flds(:,:,ids_nsfoce) = cpl_nsol2D(:,:,1)
1262       tab_flds(:,:,ids_icevap) = cpl_evap2D(:,:,2)
1263       tab_flds(:,:,ids_ocevap) = cpl_evap2D(:,:,1)
1264       tab_flds(:,:,ids_runcoa) = cpl_rcoa2D(:,:)
1265       tab_flds(:,:,ids_rivflu) = cpl_rriv2D(:,:)
1266    ENDIF
1267
1268!*************************************************************************************
1269! Transform the fraction of sub-surfaces from 1D to 2D array
1270!
1271!*************************************************************************************
1272    pctsrf2D(:,:,:) = 0.
1273!$OMP END MASTER
1274    CALL gath2cpl(pctsrf(:,is_oce), pctsrf2D(:,:,is_oce), klon, unity)
1275    CALL gath2cpl(pctsrf(:,is_sic), pctsrf2D(:,:,is_sic), klon, unity)
1276    CALL gath2cpl(pctsrf(:,is_lic), pctsrf2D(:,:,is_lic), klon, unity)
1277
1278!*************************************************************************************
1279! Calculate the average calving per latitude
1280! Store calving in tab_flds(:,:,19)
1281!
1282!*************************************************************************************     
1283    IF (is_omp_root) THEN
1284
1285      IF (cpl_old_calving) THEN   ! use old calving
1286
1287        DO j = 1, jj_nb
1288           tmp_calv(:,j) = DOT_PRODUCT (cpl_rlic2D(1:nbp_lon,j), &
1289                pctsrf2D(1:nbp_lon,j,is_lic)) / REAL(nbp_lon)
1290        ENDDO
1291   
1292   
1293        IF (is_parallel) THEN
1294           IF (.NOT. is_north_pole_dyn) THEN
1295#ifdef CPP_MPI
1296              CALL MPI_RECV(Up,1,MPI_REAL_LMDZ,mpi_rank-1,1234,COMM_LMDZ_PHY,status,error)
1297              CALL MPI_SEND(tmp_calv(1,1),1,MPI_REAL_LMDZ,mpi_rank-1,1234,COMM_LMDZ_PHY,error)
1298#endif
1299           ENDIF
1300       
1301           IF (.NOT. is_south_pole_dyn) THEN
1302#ifdef CPP_MPI
1303              CALL MPI_SEND(tmp_calv(1,jj_nb),1,MPI_REAL_LMDZ,mpi_rank+1,1234,COMM_LMDZ_PHY,error)
1304              CALL MPI_RECV(down,1,MPI_REAL_LMDZ,mpi_rank+1,1234,COMM_LMDZ_PHY,status,error)
1305#endif
1306           ENDIF
1307         
1308           IF (.NOT. is_north_pole_dyn .AND. ii_begin /=1) THEN
1309              Up=Up+tmp_calv(nbp_lon,1)
1310              tmp_calv(:,1)=Up
1311           ENDIF
1312           
1313           IF (.NOT. is_south_pole_dyn .AND. ii_end /= nbp_lon) THEN
1314              Down=Down+tmp_calv(1,jj_nb)
1315              tmp_calv(:,jj_nb)=Down
1316           ENDIF
1317        ENDIF
1318        tab_flds(:,:,ids_calvin) = tmp_calv(:,:)
1319
1320      ELSE
1321         ! cpl_old_calving=FALSE
1322         ! To be used with new method for calculation of coupling weights
1323         DO k=1,nb_zone_calving
1324            calving(k)=0
1325            DO j = 1, jj_nb
1326               calving(k)= calving(k)+DOT_PRODUCT(cpl_rlic2D(:,j)*area_calving(:,j,k),pctsrf2D(:,j,is_lic))
1327            ENDDO
1328         ENDDO
1329         
1330#ifdef CPP_MPI
1331         CALL MPI_ALLREDUCE(calving, calving_glo, nb_zone_calving, MPI_REAL_LMDZ, MPI_SUM, COMM_LMDZ_PHY, error)
1332#endif
1333         
1334         tab_flds(:,:,ids_calvin) = 0
1335         DO k=1,nb_zone_calving
1336            IF (ind_calving(k)>0 ) THEN
1337               j=(ind_calving(k)-1)/nbp_lon + 1
1338               i=MOD(ind_calving(k)-1,nbp_lon)+1
1339               tab_flds(i,j,ids_calvin) = calving_glo(k)
1340            ENDIF
1341         ENDDO
1342         
1343      ENDIF
1344     
1345!*************************************************************************************
1346! Calculate total flux for snow, rain and wind with weighted addition using the
1347! fractions of ocean and seaice.
1348!
1349!*************************************************************************************   
1350       ! fraction oce+seaice
1351       deno =  pctsrf2D(:,:,is_oce) + pctsrf2D(:,:,is_sic)
1352
1353       IF (version_ocean=='nemo') THEN
1354          tab_flds(:,:,ids_shftot)  = 0.0
1355          tab_flds(:,:,ids_nsftot) = 0.0
1356          tab_flds(:,:,ids_totrai) = 0.0
1357          tab_flds(:,:,ids_totsno) = 0.0
1358          tab_flds(:,:,ids_toteva) = 0.0
1359          tab_flds(:,:,ids_taumod) = 0.0
1360 
1361          tmp_taux(:,:)    = 0.0
1362          tmp_tauy(:,:)    = 0.0
1363          ! For all valid grid cells containing some fraction of ocean or sea-ice
1364          WHERE ( deno(:,:) /= 0 )
1365             tmp_taux = cpl_taux2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
1366                  cpl_taux2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
1367             tmp_tauy = cpl_tauy2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
1368                  cpl_tauy2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
1369
1370             tab_flds(:,:,ids_shftot) = cpl_sols2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
1371                  cpl_sols2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
1372             tab_flds(:,:,ids_nsftot) = cpl_nsol2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
1373                  cpl_nsol2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
1374             tab_flds(:,:,ids_totrai) = cpl_rain2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
1375                  cpl_rain2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
1376             tab_flds(:,:,ids_totsno) = cpl_snow2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
1377                  cpl_snow2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
1378             tab_flds(:,:,ids_toteva) = cpl_evap2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
1379                  cpl_evap2D(:,:,2)  * pctsrf2D(:,:,is_sic) / deno(:,:)
1380             tab_flds(:,:,ids_taumod) = cpl_taumod2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
1381                  cpl_taumod2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
1382             
1383         ENDWHERE
1384
1385          tab_flds(:,:,ids_icevap) = cpl_evap2D(:,:,2)
1386         
1387       ELSE IF (version_ocean=='opa8') THEN
1388          ! Store fields for rain and snow in tab_flds(:,:,15) and tab_flds(:,:,16)
1389          tab_flds(:,:,ids_totrai) = 0.0
1390          tab_flds(:,:,ids_totsno) = 0.0
1391          tmp_taux(:,:)    = 0.0
1392          tmp_tauy(:,:)    = 0.0
1393          ! For all valid grid cells containing some fraction of ocean or sea-ice
1394          WHERE ( deno(:,:) /= 0 )
1395             tab_flds(:,:,ids_totrai) = cpl_rain2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
1396                  cpl_rain2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
1397             tab_flds(:,:,ids_totsno) = cpl_snow2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
1398                  cpl_snow2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
1399             
1400             tmp_taux = cpl_taux2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
1401                  cpl_taux2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
1402             tmp_tauy = cpl_tauy2D(:,:,1) * pctsrf2D(:,:,is_oce) / deno(:,:) +    &
1403                  cpl_tauy2D(:,:,2) * pctsrf2D(:,:,is_sic) / deno(:,:)
1404          ENDWHERE
1405       ENDIF
1406
1407    ENDIF ! is_omp_root
1408 
1409!*************************************************************************************
1410! Transform the wind components from local atmospheric 2D coordinates to geocentric
1411! 3D coordinates.
1412! Store the resulting wind components in tab_flds(:,:,1:6)
1413!*************************************************************************************
1414
1415! Transform the longitudes and latitudes on 2D arrays
1416   
1417    CALL gather_omp(rlon,rlon_mpi)
1418    CALL gather_omp(rlat,rlat_mpi)
1419!$OMP MASTER
1420    CALL Grid1DTo2D_mpi(rlon_mpi,tmp_lon)
1421    CALL Grid1DTo2D_mpi(rlat_mpi,tmp_lat)
1422!$OMP END MASTER   
1423
1424    IF (is_sequential) THEN
1425       IF (is_north_pole_dyn) tmp_lon(:,1)     = tmp_lon(:,2)
1426       IF (is_south_pole_dyn) tmp_lon(:,nbp_lat) = tmp_lon(:,nbp_lat-1)
1427    ENDIF
1428     
1429! NetCDF output of the wind before transformation of coordinate system
1430    IF (is_sequential) THEN
1431       ndexct(:) = 0
1432       itau_w = itau_phy + itime + start_time * day_step_phy
1433       CALL histwrite(nidct,'tauxe',itau_w,tmp_taux,nbp_lon*(nbp_lat),ndexct)
1434       CALL histwrite(nidct,'tauyn',itau_w,tmp_tauy,nbp_lon*(nbp_lat),ndexct)
1435       CALL histwrite(nidct,'tmp_lon',itau_w,tmp_lon,nbp_lon*(nbp_lat),ndexct)
1436       CALL histwrite(nidct,'tmp_lat',itau_w,tmp_lat,nbp_lon*(nbp_lat),ndexct)
1437    ENDIF
1438
1439! Transform the wind from spherical atmospheric 2D coordinates to geocentric
1440! cartesian 3D coordinates
1441!$OMP MASTER
1442    CALL atm2geo (nbp_lon, jj_nb, tmp_taux, tmp_tauy, tmp_lon, tmp_lat, &
1443         tab_flds(:,:,ids_tauxxu), tab_flds(:,:,ids_tauyyu), tab_flds(:,:,ids_tauzzu) )
1444   
1445    tab_flds(:,:,ids_tauxxv)  = tab_flds(:,:,ids_tauxxu)
1446    tab_flds(:,:,ids_tauyyv)  = tab_flds(:,:,ids_tauyyu)
1447    tab_flds(:,:,ids_tauzzv)  = tab_flds(:,:,ids_tauzzu)
1448!$OMP END MASTER
1449
1450!*************************************************************************************
1451! NetCDF output of all fields just before sending to coupler.
1452!
1453!*************************************************************************************
1454    IF (is_sequential) THEN
1455        DO j=1,maxsend
1456          IF (infosend(j)%action) CALL histwrite(nidct,infosend(j)%name, itau_w, &
1457             tab_flds(:,:,j),nbp_lon*(nbp_lat),ndexct)
1458        ENDDO
1459    ENDIF
1460!*************************************************************************************
1461! Send the table of all fields
1462!
1463!*************************************************************************************
1464    time_sec=(itime-1)*dtime
1465#ifdef CPP_COUPLE
1466!$OMP MASTER
1467    CALL intocpl(time_sec, lafin, tab_flds(:,:,:))
1468!$OMP END MASTER
1469#endif
1470
1471!*************************************************************************************
1472! Finish with some dellocate
1473!
1474!************************************************************************************* 
1475    sum_error=0
1476    DEALLOCATE(cpl_sols2D, cpl_nsol2D, cpl_rain2D, cpl_snow2D, stat=error )
1477    sum_error = sum_error + error
1478    DEALLOCATE(cpl_evap2D, cpl_tsol2D, cpl_fder2D, cpl_albe2D, stat=error )
1479    sum_error = sum_error + error
1480    DEALLOCATE(cpl_taux2D, cpl_tauy2D, cpl_windsp2D, cpl_taumod2D, stat=error )
1481    sum_error = sum_error + error
1482    DEALLOCATE(cpl_sens_rain2D, cpl_sens_snow2D, stat=error)
1483    sum_error = sum_error + error
1484
1485   
1486    IF (carbon_cycle_cpl) THEN
1487       DEALLOCATE(cpl_atm_co22D, stat=error )
1488       sum_error = sum_error + error
1489    ENDIF
1490
1491    if (activate_ocean_skin == 2) deallocate(cpl_t_int_2d)
1492
1493    IF (sum_error /= 0) THEN
1494       abort_message='Pb in deallocation of cpl_xxxx2D coupling variables'
1495       CALL abort_physic(modname,abort_message,1)
1496    ENDIF
1497   
1498  END SUBROUTINE cpl_send_all
1499!
1500!*************************************************************************************
1501!
1502  SUBROUTINE cpl2gath(champ_in, champ_out, knon, knindex)
1503  USE mod_phys_lmdz_para
1504! Cette routine transforme un champs de la grille 2D recu du coupleur sur la grille
1505! 'gathered' (la grille physiq comprime).
1506!
1507!
1508! input:         
1509!   champ_in     champ sur la grille 2D
1510!   knon         nombre de points dans le domaine a traiter
1511!   knindex      index des points de la surface a traiter
1512!
1513! output:
1514!   champ_out    champ sur la grille 'gatherd'
1515!
1516    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
1517
1518! Input
1519    INTEGER, INTENT(IN)                       :: knon
1520    REAL, DIMENSION(nbp_lon,jj_nb), INTENT(IN)    :: champ_in
1521    INTEGER, DIMENSION(klon), INTENT(IN)      :: knindex
1522
1523! Output
1524    REAL, DIMENSION(klon_mpi), INTENT(OUT)        :: champ_out
1525
1526! Local
1527    INTEGER                                   :: i, ig
1528    REAL, DIMENSION(klon_mpi)                 :: temp_mpi
1529    REAL, DIMENSION(klon)                     :: temp_omp
1530
1531!*************************************************************************************
1532!
1533   
1534
1535! Transform from 2 dimensions (nbp_lon,jj_nb) to 1 dimension (klon)
1536!$OMP MASTER
1537    CALL Grid2Dto1D_mpi(champ_in,temp_mpi)
1538!$OMP END MASTER
1539
1540    CALL scatter_omp(temp_mpi,temp_omp)
1541   
1542! Compress from klon to knon
1543    DO i = 1, knon
1544       ig = knindex(i)
1545       champ_out(i) = temp_omp(ig)
1546    ENDDO
1547
1548  END SUBROUTINE cpl2gath
1549!
1550!*************************************************************************************
1551!
1552  SUBROUTINE gath2cpl(champ_in, champ_out, knon, knindex)
1553  USE mod_phys_lmdz_para
1554! Cette routine ecrit un champ 'gathered' sur la grille 2D pour le passer
1555! au coupleur.
1556!
1557! input:         
1558!   champ_in     champ sur la grille gathere       
1559!   knon         nombre de points dans le domaine a traiter
1560!   knindex      index des points de la surface a traiter
1561!
1562! output:
1563!   champ_out    champ sur la grille 2D
1564!
1565    USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat
1566   
1567! Input arguments
1568!*************************************************************************************
1569    INTEGER, INTENT(IN)                    :: knon
1570    REAL, DIMENSION(klon), INTENT(IN)      :: champ_in
1571    INTEGER, DIMENSION(klon), INTENT(IN)   :: knindex
1572
1573! Output arguments
1574!*************************************************************************************
1575    REAL, DIMENSION(nbp_lon,jj_nb), INTENT(OUT) :: champ_out
1576
1577! Local variables
1578!*************************************************************************************
1579    INTEGER                                :: i, ig
1580    REAL, DIMENSION(klon)                  :: temp_omp
1581    REAL, DIMENSION(klon_mpi)              :: temp_mpi
1582!*************************************************************************************
1583
1584! Decompress from knon to klon
1585    temp_omp = 0.
1586    DO i = 1, knon
1587       ig = knindex(i)
1588       temp_omp(ig) = champ_in(i)
1589    ENDDO
1590
1591! Transform from 1 dimension (klon) to 2 dimensions (nbp_lon,jj_nb)
1592    CALL gather_omp(temp_omp,temp_mpi)
1593
1594!$OMP MASTER   
1595    CALL Grid1Dto2D_mpi(temp_mpi,champ_out)
1596   
1597    IF (is_north_pole_dyn) champ_out(:,1)=temp_mpi(1)
1598    IF (is_south_pole_dyn) champ_out(:,jj_nb)=temp_mpi(klon)
1599!$OMP END MASTER
1600   
1601  END SUBROUTINE gath2cpl
1602!
1603!*************************************************************************************
1604!
1605END MODULE cpl_mod
1606
Note: See TracBrowser for help on using the repository browser.