source: LMDZ6/branches/Amaury_dev/libf/phylmd/cpl_mod.F90 @ 5157

Last change on this file since 5157 was 5144, checked in by abarral, 7 weeks ago

Put YOMCST.h into modules

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