New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
sbccpl.F90 in branches/UKMO/dev_r5518_GSI7_GSI8_landice_bitcomp_medusa/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_r5518_GSI7_GSI8_landice_bitcomp_medusa/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 @ 6738

Last change on this file since 6738 was 6738, checked in by frrh, 8 years ago

Remove temporary array declarations used only in testing

File size: 141.1 KB
Line 
1MODULE sbccpl
2   !!======================================================================
3   !!                       ***  MODULE  sbccpl  ***
4   !! Surface Boundary Condition :  momentum, heat and freshwater fluxes in coupled mode
5   !!======================================================================
6   !! History :  2.0  ! 2007-06  (R. Redler, N. Keenlyside, W. Park) Original code split into flxmod & taumod
7   !!            3.0  ! 2008-02  (G. Madec, C Talandier)  surface module
8   !!            3.1  ! 2009_02  (G. Madec, S. Masson, E. Maisonave, A. Caubel) generic coupled interface
9   !!            3.4  ! 2011_11  (C. Harris) more flexibility + multi-category fields
10   !!----------------------------------------------------------------------
11   !!----------------------------------------------------------------------
12   !!   namsbc_cpl      : coupled formulation namlist
13   !!   sbc_cpl_init    : initialisation of the coupled exchanges
14   !!   sbc_cpl_rcv     : receive fields from the atmosphere over the ocean (ocean only)
15   !!                     receive stress from the atmosphere over the ocean (ocean-ice case)
16   !!   sbc_cpl_ice_tau : receive stress from the atmosphere over ice
17   !!   sbc_cpl_ice_flx : receive fluxes from the atmosphere over ice
18   !!   sbc_cpl_snd     : send     fields to the atmosphere
19   !!----------------------------------------------------------------------
20   USE dom_oce         ! ocean space and time domain
21   USE sbc_oce         ! Surface boundary condition: ocean fields
22   USE sbc_ice         ! Surface boundary condition: ice fields
23   USE sbcapr
24   USE sbcdcy          ! surface boundary condition: diurnal cycle
25   USE phycst          ! physical constants
26#if defined key_lim3
27   USE ice             ! ice variables
28#endif
29#if defined key_lim2
30   USE par_ice_2       ! ice parameters
31   USE ice_2           ! ice variables
32#endif
33   USE cpl_oasis3      ! OASIS3 coupling
34   USE geo2ocean       !
35   USE oce   , ONLY : tsn, un, vn, sshn, ub, vb, sshb, fraqsr_1lev,            &
36                      CO2Flux_out_cpl, DMS_out_cpl, PCO2a_in_cpl, Dust_in_cpl, &
37                      ln_medusa
38   USE albedo          !
39   USE in_out_manager  ! I/O manager
40   USE iom             ! NetCDF library
41   USE lib_mpp         ! distribued memory computing library
42   USE wrk_nemo        ! work arrays
43   USE timing          ! Timing
44   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
45   USE eosbn2
46   USE sbcrnf   , ONLY : l_rnfcpl
47#if defined key_cpl_carbon_cycle
48   USE p4zflx, ONLY : oce_co2
49#endif
50#if defined key_lim3
51   USE limthd_dh       ! for CALL lim_thd_snwblow
52#endif
53   USE lib_fortran, ONLY: glob_sum
54
55   IMPLICIT NONE
56   PRIVATE
57
58   PUBLIC   sbc_cpl_init       ! routine called by sbcmod.F90
59   PUBLIC   sbc_cpl_rcv        ! routine called by sbc_ice_lim(_2).F90
60   PUBLIC   sbc_cpl_snd        ! routine called by step.F90
61   PUBLIC   sbc_cpl_ice_tau    ! routine called by sbc_ice_lim(_2).F90
62   PUBLIC   sbc_cpl_ice_flx    ! routine called by sbc_ice_lim(_2).F90
63   PUBLIC   sbc_cpl_alloc      ! routine called in sbcice_cice.F90
64
65   INTEGER, PARAMETER ::   jpr_otx1   =  1            ! 3 atmosphere-ocean stress components on grid 1
66   INTEGER, PARAMETER ::   jpr_oty1   =  2            !
67   INTEGER, PARAMETER ::   jpr_otz1   =  3            !
68   INTEGER, PARAMETER ::   jpr_otx2   =  4            ! 3 atmosphere-ocean stress components on grid 2
69   INTEGER, PARAMETER ::   jpr_oty2   =  5            !
70   INTEGER, PARAMETER ::   jpr_otz2   =  6            !
71   INTEGER, PARAMETER ::   jpr_itx1   =  7            ! 3 atmosphere-ice   stress components on grid 1
72   INTEGER, PARAMETER ::   jpr_ity1   =  8            !
73   INTEGER, PARAMETER ::   jpr_itz1   =  9            !
74   INTEGER, PARAMETER ::   jpr_itx2   = 10            ! 3 atmosphere-ice   stress components on grid 2
75   INTEGER, PARAMETER ::   jpr_ity2   = 11            !
76   INTEGER, PARAMETER ::   jpr_itz2   = 12            !
77   INTEGER, PARAMETER ::   jpr_qsroce = 13            ! Qsr above the ocean
78   INTEGER, PARAMETER ::   jpr_qsrice = 14            ! Qsr above the ice
79   INTEGER, PARAMETER ::   jpr_qsrmix = 15 
80   INTEGER, PARAMETER ::   jpr_qnsoce = 16            ! Qns above the ocean
81   INTEGER, PARAMETER ::   jpr_qnsice = 17            ! Qns above the ice
82   INTEGER, PARAMETER ::   jpr_qnsmix = 18
83   INTEGER, PARAMETER ::   jpr_rain   = 19            ! total liquid precipitation (rain)
84   INTEGER, PARAMETER ::   jpr_snow   = 20            ! solid precipitation over the ocean (snow)
85   INTEGER, PARAMETER ::   jpr_tevp   = 21            ! total evaporation
86   INTEGER, PARAMETER ::   jpr_ievp   = 22            ! solid evaporation (sublimation)
87   INTEGER, PARAMETER ::   jpr_sbpr   = 23            ! sublimation - liquid precipitation - solid precipitation
88   INTEGER, PARAMETER ::   jpr_semp   = 24            ! solid freshwater budget (sublimation - snow)
89   INTEGER, PARAMETER ::   jpr_oemp   = 25            ! ocean freshwater budget (evap - precip)
90   INTEGER, PARAMETER ::   jpr_w10m   = 26            ! 10m wind
91   INTEGER, PARAMETER ::   jpr_dqnsdt = 27            ! d(Q non solar)/d(temperature)
92   INTEGER, PARAMETER ::   jpr_rnf    = 28            ! runoffs
93   INTEGER, PARAMETER ::   jpr_cal    = 29            ! calving
94   INTEGER, PARAMETER ::   jpr_taum   = 30            ! wind stress module
95   INTEGER, PARAMETER ::   jpr_co2    = 31
96   INTEGER, PARAMETER ::   jpr_topm   = 32            ! topmeltn
97   INTEGER, PARAMETER ::   jpr_botm   = 33            ! botmeltn
98   INTEGER, PARAMETER ::   jpr_sflx   = 34            ! salt flux
99   INTEGER, PARAMETER ::   jpr_toce   = 35            ! ocean temperature
100   INTEGER, PARAMETER ::   jpr_soce   = 36            ! ocean salinity
101   INTEGER, PARAMETER ::   jpr_ocx1   = 37            ! ocean current on grid 1
102   INTEGER, PARAMETER ::   jpr_ocy1   = 38            !
103   INTEGER, PARAMETER ::   jpr_ssh    = 39            ! sea surface height
104   INTEGER, PARAMETER ::   jpr_fice   = 40            ! ice fraction         
105   INTEGER, PARAMETER ::   jpr_e3t1st = 41            ! first T level thickness
106   INTEGER, PARAMETER ::   jpr_fraqsr = 42            ! fraction of solar net radiation absorbed in the first ocean level
107   INTEGER, PARAMETER ::   jpr_ts_ice = 43            ! skin temperature of sea-ice (used for melt-ponds)
108   INTEGER, PARAMETER ::   jpr_grnm   = 44            ! Greenland ice mass
109   INTEGER, PARAMETER ::   jpr_antm   = 45            ! Antarctic ice mass
110   INTEGER, PARAMETER ::   jpr_atm_pco2 = 46          ! Incoming atm CO2 flux
111   INTEGER, PARAMETER ::   jpr_atm_dust = 47          ! Incoming atm aggregate dust
112   INTEGER, PARAMETER ::   jprcv      = 47            ! total number of fields received
113
114   INTEGER, PARAMETER ::   jps_fice   =  1            ! ice fraction sent to the atmosphere
115   INTEGER, PARAMETER ::   jps_toce   =  2            ! ocean temperature
116   INTEGER, PARAMETER ::   jps_tice   =  3            ! ice   temperature
117   INTEGER, PARAMETER ::   jps_tmix   =  4            ! mixed temperature (ocean+ice)
118   INTEGER, PARAMETER ::   jps_albice =  5            ! ice   albedo
119   INTEGER, PARAMETER ::   jps_albmix =  6            ! mixed albedo
120   INTEGER, PARAMETER ::   jps_hice   =  7            ! ice  thickness
121   INTEGER, PARAMETER ::   jps_hsnw   =  8            ! snow thickness
122   INTEGER, PARAMETER ::   jps_ocx1   =  9            ! ocean current on grid 1
123   INTEGER, PARAMETER ::   jps_ocy1   = 10            !
124   INTEGER, PARAMETER ::   jps_ocz1   = 11            !
125   INTEGER, PARAMETER ::   jps_ivx1   = 12            ! ice   current on grid 1
126   INTEGER, PARAMETER ::   jps_ivy1   = 13            !
127   INTEGER, PARAMETER ::   jps_ivz1   = 14            !
128   INTEGER, PARAMETER ::   jps_co2    = 15
129   INTEGER, PARAMETER ::   jps_soce   = 16            ! ocean salinity
130   INTEGER, PARAMETER ::   jps_ssh    = 17            ! sea surface height
131   INTEGER, PARAMETER ::   jps_qsroce = 18            ! Qsr above the ocean
132   INTEGER, PARAMETER ::   jps_qnsoce = 19            ! Qns above the ocean
133   INTEGER, PARAMETER ::   jps_oemp   = 20            ! ocean freshwater budget (evap - precip)
134   INTEGER, PARAMETER ::   jps_sflx   = 21            ! salt flux
135   INTEGER, PARAMETER ::   jps_otx1   = 22            ! 2 atmosphere-ocean stress components on grid 1
136   INTEGER, PARAMETER ::   jps_oty1   = 23            !
137   INTEGER, PARAMETER ::   jps_rnf    = 24            ! runoffs
138   INTEGER, PARAMETER ::   jps_taum   = 25            ! wind stress module
139   INTEGER, PARAMETER ::   jps_fice2  = 26            ! ice fraction sent to OPA (by SAS when doing SAS-OPA coupling)
140   INTEGER, PARAMETER ::   jps_e3t1st = 27            ! first level depth (vvl)
141   INTEGER, PARAMETER ::   jps_fraqsr = 28            ! fraction of solar net radiation absorbed in the first ocean level
142   INTEGER, PARAMETER ::   jps_a_p    = 29            ! meltpond fraction 
143   INTEGER, PARAMETER ::   jps_ht_p   = 30            ! meltpond depth (m)
144   INTEGER, PARAMETER ::   jps_kice   = 31            ! ice surface layer thermal conductivity
145   INTEGER, PARAMETER ::   jps_sstfrz = 32            ! sea-surface freezing temperature
146   INTEGER, PARAMETER ::   jps_fice1  = 33            ! first-order ice concentration (for time-travelling ice coupling)
147   INTEGER, PARAMETER ::   jps_bio_co2 = 34           ! MEDUSA air-sea CO2 flux in
148   INTEGER, PARAMETER ::   jps_bio_dms = 35           ! MEDUSA DMS surface concentration in
149   INTEGER, PARAMETER ::   jpsnd      = 35            ! total number of fields sent
150
151   REAL(wp), PARAMETER :: dms_unit_conv = 1.0e+6      ! Coversion factor to get outgong DMS in standard units for coupling
152                                                 ! i.e. specifically nmol/L (= umol/m3)
153
154   !                                                         !!** namelist namsbc_cpl **
155   TYPE ::   FLD_C
156      CHARACTER(len = 32) ::   cldes                  ! desciption of the coupling strategy
157      CHARACTER(len = 32) ::   clcat                  ! multiple ice categories strategy
158      CHARACTER(len = 32) ::   clvref                 ! reference of vector ('spherical' or 'cartesian')
159      CHARACTER(len = 32) ::   clvor                  ! orientation of vector fields ('eastward-northward' or 'local grid')
160      CHARACTER(len = 32) ::   clvgrd                 ! grids on which is located the vector fields
161   END TYPE FLD_C
162   ! Send to the atmosphere                           !
163   TYPE(FLD_C) ::   sn_snd_temp, sn_snd_alb, sn_snd_thick, sn_snd_crt, sn_snd_co2, sn_snd_cond, sn_snd_mpnd, sn_snd_sstfrz, sn_snd_thick1
164   TYPE(FLD_C) ::   sn_snd_bio_co2, sn_snd_bio_dms                       
165
166   ! Received from the atmosphere                     !
167   TYPE(FLD_C) ::   sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau, sn_rcv_dqnsdt, sn_rcv_qsr, sn_rcv_qns, sn_rcv_emp, sn_rcv_rnf
168   TYPE(FLD_C) ::   sn_rcv_cal, sn_rcv_iceflx, sn_rcv_co2, sn_rcv_ts_ice, sn_rcv_grnm, sn_rcv_antm
169   TYPE(FLD_C) ::   sn_rcv_atm_pco2, sn_rcv_atm_dust                         
170
171   ! Other namelist parameters                        !
172   INTEGER     ::   nn_cplmodel            ! Maximum number of models to/from which NEMO is potentialy sending/receiving data
173   LOGICAL     ::   ln_usecplmask          !  use a coupling mask file to merge data received from several models
174                                           !   -> file cplmask.nc with the float variable called cplmask (jpi,jpj,nn_cplmodel)
175   TYPE ::   DYNARR     
176      REAL(wp), POINTER, DIMENSION(:,:,:)    ::   z3   
177   END TYPE DYNARR
178
179   TYPE( DYNARR ), SAVE, DIMENSION(jprcv) ::   frcv                      ! all fields recieved from the atmosphere
180
181   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   albedo_oce_mix     ! ocean albedo sent to atmosphere (mix clear/overcast sky)
182
183   INTEGER , ALLOCATABLE, SAVE, DIMENSION(    :) ::   nrcvinfo           ! OASIS info argument
184
185   !! Substitution
186#  include "domzgr_substitute.h90"
187#  include "vectopt_loop_substitute.h90"
188   !!----------------------------------------------------------------------
189   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
190   !! $Id$
191   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
192   !!----------------------------------------------------------------------
193
194CONTAINS
195 
196   INTEGER FUNCTION sbc_cpl_alloc()
197      !!----------------------------------------------------------------------
198      !!             ***  FUNCTION sbc_cpl_alloc  ***
199      !!----------------------------------------------------------------------
200      INTEGER :: ierr(3)
201      !!----------------------------------------------------------------------
202      ierr(:) = 0
203      !
204      ALLOCATE( albedo_oce_mix(jpi,jpj), nrcvinfo(jprcv),  STAT=ierr(1) )
205     
206#if ! defined key_lim3 && ! defined key_lim2 && ! defined key_cice
207      ALLOCATE( a_i(jpi,jpj,1) , STAT=ierr(2) )  ! used in sbcice_if.F90 (done here as there is no sbc_ice_if_init)
208#endif
209      ALLOCATE( xcplmask(jpi,jpj,0:nn_cplmodel) , STAT=ierr(3) )
210      !
211      sbc_cpl_alloc = MAXVAL( ierr )
212      IF( lk_mpp            )   CALL mpp_sum ( sbc_cpl_alloc )
213      IF( sbc_cpl_alloc > 0 )   CALL ctl_warn('sbc_cpl_alloc: allocation of arrays failed')
214      !
215   END FUNCTION sbc_cpl_alloc
216
217
218   SUBROUTINE sbc_cpl_init( k_ice )     
219      !!----------------------------------------------------------------------
220      !!             ***  ROUTINE sbc_cpl_init  ***
221      !!
222      !! ** Purpose :   Initialisation of send and received information from
223      !!                the atmospheric component
224      !!
225      !! ** Method  : * Read namsbc_cpl namelist
226      !!              * define the receive interface
227      !!              * define the send    interface
228      !!              * initialise the OASIS coupler
229      !!----------------------------------------------------------------------
230      INTEGER, INTENT(in) ::   k_ice       ! ice management in the sbc (=0/1/2/3)
231      !!
232      INTEGER ::   jn   ! dummy loop index
233      INTEGER ::   ios  ! Local integer output status for namelist read
234      INTEGER ::   inum 
235      REAL(wp), POINTER, DIMENSION(:,:) ::   zacs, zaos
236      !!
237      NAMELIST/namsbc_cpl/  sn_snd_temp, sn_snd_alb   , sn_snd_thick , sn_snd_crt   , sn_snd_co2,     &
238         &                  sn_snd_cond, sn_snd_mpnd  , sn_snd_sstfrz, sn_snd_thick1,                 &
239         &                  sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau   , sn_rcv_dqnsdt, sn_rcv_qsr,     &
240         &                  sn_rcv_qns , sn_rcv_emp   , sn_rcv_rnf   , sn_rcv_cal   , sn_rcv_iceflx,  &
241         &                  sn_rcv_co2 , sn_rcv_grnm  , sn_rcv_antm  , sn_rcv_ts_ice, nn_cplmodel  ,  &
242         &                  ln_usecplmask, ln_coupled_iceshelf_fluxes, rn_greenland_calving_fraction, &
243         &                  rn_antarctica_calving_fraction, rn_iceshelf_fluxes_tolerance
244      !!---------------------------------------------------------------------
245
246      ! Add MEDUSA related fields to namelist
247      NAMELIST/namsbc_cpl/  sn_snd_bio_co2, sn_snd_bio_dms,                                           &
248         &                  sn_rcv_atm_pco2, sn_rcv_atm_dust
249
250      !!---------------------------------------------------------------------
251
252      !
253      IF( nn_timing == 1 )  CALL timing_start('sbc_cpl_init')
254      !
255      CALL wrk_alloc( jpi,jpj, zacs, zaos )
256
257      ! ================================ !
258      !      Namelist informations       !
259      ! ================================ !
260
261      REWIND( numnam_ref )              ! Namelist namsbc_cpl in reference namelist : Variables for OASIS coupling
262      READ  ( numnam_ref, namsbc_cpl, IOSTAT = ios, ERR = 901)
263901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_cpl in reference namelist', lwp )
264
265      REWIND( numnam_cfg )              ! Namelist namsbc_cpl in configuration namelist : Variables for OASIS coupling
266      READ  ( numnam_cfg, namsbc_cpl, IOSTAT = ios, ERR = 902 )
267902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_cpl in configuration namelist', lwp )
268      IF(lwm) WRITE ( numond, namsbc_cpl )
269
270      IF(lwp) THEN                        ! control print
271         WRITE(numout,*)
272         WRITE(numout,*)'sbc_cpl_init : namsbc_cpl namelist '
273         WRITE(numout,*)'~~~~~~~~~~~~'
274      ENDIF
275      IF( lwp .AND. ln_cpl ) THEN                        ! control print
276         WRITE(numout,*)'  received fields (mutiple ice categories)'
277         WRITE(numout,*)'      10m wind module                 = ', TRIM(sn_rcv_w10m%cldes  ), ' (', TRIM(sn_rcv_w10m%clcat  ), ')'
278         WRITE(numout,*)'      stress module                   = ', TRIM(sn_rcv_taumod%cldes), ' (', TRIM(sn_rcv_taumod%clcat), ')'
279         WRITE(numout,*)'      surface stress                  = ', TRIM(sn_rcv_tau%cldes   ), ' (', TRIM(sn_rcv_tau%clcat   ), ')'
280         WRITE(numout,*)'                     - referential    = ', sn_rcv_tau%clvref
281         WRITE(numout,*)'                     - orientation    = ', sn_rcv_tau%clvor
282         WRITE(numout,*)'                     - mesh           = ', sn_rcv_tau%clvgrd
283         WRITE(numout,*)'      non-solar heat flux sensitivity = ', TRIM(sn_rcv_dqnsdt%cldes), ' (', TRIM(sn_rcv_dqnsdt%clcat), ')'
284         WRITE(numout,*)'      solar heat flux                 = ', TRIM(sn_rcv_qsr%cldes   ), ' (', TRIM(sn_rcv_qsr%clcat   ), ')'
285         WRITE(numout,*)'      non-solar heat flux             = ', TRIM(sn_rcv_qns%cldes   ), ' (', TRIM(sn_rcv_qns%clcat   ), ')'
286         WRITE(numout,*)'      freshwater budget               = ', TRIM(sn_rcv_emp%cldes   ), ' (', TRIM(sn_rcv_emp%clcat   ), ')'
287         WRITE(numout,*)'      runoffs                         = ', TRIM(sn_rcv_rnf%cldes   ), ' (', TRIM(sn_rcv_rnf%clcat   ), ')'
288         WRITE(numout,*)'      calving                         = ', TRIM(sn_rcv_cal%cldes   ), ' (', TRIM(sn_rcv_cal%clcat   ), ')'
289         WRITE(numout,*)'      Greenland ice mass              = ', TRIM(sn_rcv_grnm%cldes  ), ' (', TRIM(sn_rcv_grnm%clcat  ), ')'
290         WRITE(numout,*)'      Antarctica ice mass             = ', TRIM(sn_rcv_antm%cldes  ), ' (', TRIM(sn_rcv_antm%clcat  ), ')'
291         WRITE(numout,*)'      sea ice heat fluxes             = ', TRIM(sn_rcv_iceflx%cldes), ' (', TRIM(sn_rcv_iceflx%clcat), ')'
292         WRITE(numout,*)'      atm co2                         = ', TRIM(sn_rcv_co2%cldes   ), ' (', TRIM(sn_rcv_co2%clcat   ), ')'
293         WRITE(numout,*)'      atm pco2                        = ', TRIM(sn_rcv_atm_pco2%cldes), ' (', TRIM(sn_rcv_atm_pco2%clcat), ')'
294         WRITE(numout,*)'      atm dust                        = ', TRIM(sn_rcv_atm_dust%cldes), ' (', TRIM(sn_rcv_atm_dust%clcat), ')'
295         WRITE(numout,*)'  sent fields (multiple ice categories)'
296         WRITE(numout,*)'      surface temperature             = ', TRIM(sn_snd_temp%cldes  ), ' (', TRIM(sn_snd_temp%clcat  ), ')'
297         WRITE(numout,*)'      albedo                          = ', TRIM(sn_snd_alb%cldes   ), ' (', TRIM(sn_snd_alb%clcat   ), ')'
298         WRITE(numout,*)'      ice/snow thickness              = ', TRIM(sn_snd_thick%cldes ), ' (', TRIM(sn_snd_thick%clcat ), ')'
299         WRITE(numout,*)'      surface current                 = ', TRIM(sn_snd_crt%cldes   ), ' (', TRIM(sn_snd_crt%clcat   ), ')'
300         WRITE(numout,*)'                      - referential   = ', sn_snd_crt%clvref 
301         WRITE(numout,*)'                      - orientation   = ', sn_snd_crt%clvor
302         WRITE(numout,*)'                      - mesh          = ', sn_snd_crt%clvgrd
303         WRITE(numout,*)'      bio co2 flux                    = ', TRIM(sn_snd_bio_co2%cldes), ' (', TRIM(sn_snd_bio_co2%clcat), ')'
304         WRITE(numout,*)'      bio dms flux                    = ', TRIM(sn_snd_bio_dms%cldes), ' (', TRIM(sn_snd_bio_dms%clcat), ')'
305         WRITE(numout,*)'      oce co2 flux                    = ', TRIM(sn_snd_co2%cldes   ), ' (', TRIM(sn_snd_co2%clcat   ), ')'
306         WRITE(numout,*)'      ice effective conductivity      = ', TRIM(sn_snd_cond%cldes   ), ' (', TRIM(sn_snd_cond%clcat   ), ')'
307         WRITE(numout,*)'      meltponds fraction & depth      = ', TRIM(sn_snd_mpnd%cldes  ), ' (', TRIM(sn_snd_mpnd%clcat   ), ')'
308         WRITE(numout,*)'      sea surface freezing temp       = ', TRIM(sn_snd_sstfrz%cldes   ), ' (', TRIM(sn_snd_sstfrz%clcat   ), ')'
309
310         WRITE(numout,*)'  nn_cplmodel                         = ', nn_cplmodel
311         WRITE(numout,*)'  ln_usecplmask                       = ', ln_usecplmask
312         WRITE(numout,*)'  ln_coupled_iceshelf_fluxes          = ', ln_coupled_iceshelf_fluxes
313         WRITE(numout,*)'  rn_greenland_calving_fraction       = ', rn_greenland_calving_fraction
314         WRITE(numout,*)'  rn_antarctica_calving_fraction      = ', rn_antarctica_calving_fraction
315         WRITE(numout,*)'  rn_iceshelf_fluxes_tolerance        = ', rn_iceshelf_fluxes_tolerance
316      ENDIF
317
318      !                                   ! allocate sbccpl arrays
319      IF( sbc_cpl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' )
320     
321      ! ================================ !
322      !   Define the receive interface   !
323      ! ================================ !
324      nrcvinfo(:) = OASIS_idle   ! needed by nrcvinfo(jpr_otx1) if we do not receive ocean stress
325
326      ! for each field: define the OASIS name                              (srcv(:)%clname)
327      !                 define receive or not from the namelist parameters (srcv(:)%laction)
328      !                 define the north fold type of lbc                  (srcv(:)%nsgn)
329
330      ! default definitions of srcv
331      srcv(:)%laction = .FALSE.   ;   srcv(:)%clgrid = 'T'   ;   srcv(:)%nsgn = 1.   ;   srcv(:)%nct = 1
332
333      !                                                      ! ------------------------- !
334      !                                                      ! ice and ocean wind stress !   
335      !                                                      ! ------------------------- !
336      !                                                           ! Name
337      srcv(jpr_otx1)%clname = 'O_OTaux1'      ! 1st ocean component on grid ONE (T or U)
338      srcv(jpr_oty1)%clname = 'O_OTauy1'      ! 2nd   -      -         -     -
339      srcv(jpr_otz1)%clname = 'O_OTauz1'      ! 3rd   -      -         -     -
340      srcv(jpr_otx2)%clname = 'O_OTaux2'      ! 1st ocean component on grid TWO (V)
341      srcv(jpr_oty2)%clname = 'O_OTauy2'      ! 2nd   -      -         -     -
342      srcv(jpr_otz2)%clname = 'O_OTauz2'      ! 3rd   -      -         -     -
343      !
344      srcv(jpr_itx1)%clname = 'O_ITaux1'      ! 1st  ice  component on grid ONE (T, F, I or U)
345      srcv(jpr_ity1)%clname = 'O_ITauy1'      ! 2nd   -      -         -     -
346      srcv(jpr_itz1)%clname = 'O_ITauz1'      ! 3rd   -      -         -     -
347      srcv(jpr_itx2)%clname = 'O_ITaux2'      ! 1st  ice  component on grid TWO (V)
348      srcv(jpr_ity2)%clname = 'O_ITauy2'      ! 2nd   -      -         -     -
349      srcv(jpr_itz2)%clname = 'O_ITauz2'      ! 3rd   -      -         -     -
350      !
351      ! Vectors: change of sign at north fold ONLY if on the local grid
352      IF( TRIM( sn_rcv_tau%clvor ) == 'local grid' )   srcv(jpr_otx1:jpr_itz2)%nsgn = -1.
353     
354      !                                                           ! Set grid and action
355      SELECT CASE( TRIM( sn_rcv_tau%clvgrd ) )      !  'T', 'U,V', 'U,V,I', 'U,V,F', 'T,I', 'T,F', or 'T,U,V'
356      CASE( 'T' ) 
357         srcv(jpr_otx1:jpr_itz2)%clgrid  = 'T'        ! oce and ice components given at T-point
358         srcv(jpr_otx1:jpr_otz1)%laction = .TRUE.     ! receive oce components on grid 1
359         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1
360      CASE( 'U,V' ) 
361         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'U'        ! oce components given at U-point
362         srcv(jpr_otx2:jpr_otz2)%clgrid  = 'V'        !           and           V-point
363         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'U'        ! ice components given at U-point
364         srcv(jpr_itx2:jpr_itz2)%clgrid  = 'V'        !           and           V-point
365         srcv(jpr_otx1:jpr_itz2)%laction = .TRUE.     ! receive oce and ice components on both grid 1 & 2
366      CASE( 'U,V,T' )
367         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'U'        ! oce components given at U-point
368         srcv(jpr_otx2:jpr_otz2)%clgrid  = 'V'        !           and           V-point
369         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'T'        ! ice components given at T-point
370         srcv(jpr_otx1:jpr_otz2)%laction = .TRUE.     ! receive oce components on grid 1 & 2
371         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1 only
372      CASE( 'U,V,I' )
373         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'U'        ! oce components given at U-point
374         srcv(jpr_otx2:jpr_otz2)%clgrid  = 'V'        !           and           V-point
375         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'I'        ! ice components given at I-point
376         srcv(jpr_otx1:jpr_otz2)%laction = .TRUE.     ! receive oce components on grid 1 & 2
377         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1 only
378      CASE( 'U,V,F' )
379         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'U'        ! oce components given at U-point
380         srcv(jpr_otx2:jpr_otz2)%clgrid  = 'V'        !           and           V-point
381         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'F'        ! ice components given at F-point
382         srcv(jpr_otx1:jpr_otz2)%laction = .TRUE.     ! receive oce components on grid 1 & 2
383         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1 only
384      CASE( 'T,I' ) 
385         srcv(jpr_otx1:jpr_itz2)%clgrid  = 'T'        ! oce and ice components given at T-point
386         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'I'        ! ice components given at I-point
387         srcv(jpr_otx1:jpr_otz1)%laction = .TRUE.     ! receive oce components on grid 1
388         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1
389      CASE( 'T,F' ) 
390         srcv(jpr_otx1:jpr_itz2)%clgrid  = 'T'        ! oce and ice components given at T-point
391         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'F'        ! ice components given at F-point
392         srcv(jpr_otx1:jpr_otz1)%laction = .TRUE.     ! receive oce components on grid 1
393         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1
394      CASE( 'T,U,V' )
395         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'T'        ! oce components given at T-point
396         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'U'        ! ice components given at U-point
397         srcv(jpr_itx2:jpr_itz2)%clgrid  = 'V'        !           and           V-point
398         srcv(jpr_otx1:jpr_otz1)%laction = .TRUE.     ! receive oce components on grid 1 only
399         srcv(jpr_itx1:jpr_itz2)%laction = .TRUE.     ! receive ice components on grid 1 & 2
400      CASE default   
401         CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_tau%clvgrd' )
402      END SELECT
403      !
404      IF( TRIM( sn_rcv_tau%clvref ) == 'spherical' )   &           ! spherical: 3rd component not received
405         &     srcv( (/jpr_otz1, jpr_otz2, jpr_itz1, jpr_itz2/) )%laction = .FALSE. 
406      !
407      IF( TRIM( sn_rcv_tau%clvor  ) == 'local grid' ) THEN        ! already on local grid -> no need of the second grid
408            srcv(jpr_otx2:jpr_otz2)%laction = .FALSE. 
409            srcv(jpr_itx2:jpr_itz2)%laction = .FALSE. 
410            srcv(jpr_oty1)%clgrid = srcv(jpr_oty2)%clgrid   ! not needed but cleaner...
411            srcv(jpr_ity1)%clgrid = srcv(jpr_ity2)%clgrid   ! not needed but cleaner...
412      ENDIF
413      !
414      IF( TRIM( sn_rcv_tau%cldes ) /= 'oce and ice' ) THEN        ! 'oce and ice' case ocean stress on ocean mesh used
415         srcv(jpr_itx1:jpr_itz2)%laction = .FALSE.    ! ice components not received
416         srcv(jpr_itx1)%clgrid = 'U'                  ! ocean stress used after its transformation
417         srcv(jpr_ity1)%clgrid = 'V'                  ! i.e. it is always at U- & V-points for i- & j-comp. resp.
418      ENDIF
419       
420      !                                                      ! ------------------------- !
421      !                                                      !    freshwater budget      !   E-P
422      !                                                      ! ------------------------- !
423      ! we suppose that atmosphere modele do not make the difference between precipiration (liquide or solid)
424      ! over ice of free ocean within the same atmospheric cell.cd
425      srcv(jpr_rain)%clname = 'OTotRain'      ! Rain = liquid precipitation
426      srcv(jpr_snow)%clname = 'OTotSnow'      ! Snow = solid precipitation
427      srcv(jpr_tevp)%clname = 'OTotEvap'      ! total evaporation (over oce + ice sublimation)
428      srcv(jpr_ievp)%clname = 'OIceEvp'      ! evaporation over ice = sublimation
429      srcv(jpr_sbpr)%clname = 'OSubMPre'      ! sublimation - liquid precipitation - solid precipitation
430      srcv(jpr_semp)%clname = 'OISubMSn'      ! ice solid water budget = sublimation - solid precipitation
431      srcv(jpr_oemp)%clname = 'OOEvaMPr'      ! ocean water budget = ocean Evap - ocean precip
432      SELECT CASE( TRIM( sn_rcv_emp%cldes ) )
433      CASE( 'none'          )       ! nothing to do
434      CASE( 'oce only'      )   ;   srcv(                                 jpr_oemp   )%laction = .TRUE. 
435      CASE( 'conservative'  )
436         srcv( (/jpr_rain, jpr_snow, jpr_ievp, jpr_tevp/) )%laction = .TRUE.
437         IF ( k_ice <= 1 )  srcv(jpr_ievp)%laction = .FALSE.
438      CASE( 'oce and ice'   )   ;   srcv( (/jpr_ievp, jpr_sbpr, jpr_semp, jpr_oemp/) )%laction = .TRUE.
439      CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_emp%cldes' )
440      END SELECT
441      !Set the number of categories for coupling of sublimation
442      IF ( TRIM( sn_rcv_emp%clcat ) == 'yes' ) srcv(jpr_ievp)%nct = jpl
443      !
444      !                                                      ! ------------------------- !
445      !                                                      !     Runoffs & Calving     !   
446      !                                                      ! ------------------------- !
447      srcv(jpr_rnf   )%clname = 'O_Runoff'
448      IF( TRIM( sn_rcv_rnf%cldes ) == 'coupled' ) THEN
449         srcv(jpr_rnf)%laction = .TRUE.
450         l_rnfcpl              = .TRUE.                      ! -> no need to read runoffs in sbcrnf
451         ln_rnf                = nn_components /= jp_iam_sas ! -> force to go through sbcrnf if not sas
452         IF(lwp) WRITE(numout,*)
453         IF(lwp) WRITE(numout,*) '   runoffs received from oasis -> force ln_rnf = ', ln_rnf
454      ENDIF
455      !
456      srcv(jpr_cal   )%clname = 'OCalving'   ;   IF( TRIM( sn_rcv_cal%cldes ) == 'coupled' )   srcv(jpr_cal)%laction = .TRUE.
457      srcv(jpr_grnm  )%clname = 'OGrnmass'   ;   IF( TRIM( sn_rcv_grnm%cldes ) == 'coupled' )   srcv(jpr_grnm)%laction = .TRUE.
458      srcv(jpr_antm  )%clname = 'OAntmass'   ;   IF( TRIM( sn_rcv_antm%cldes ) == 'coupled' )   srcv(jpr_antm)%laction = .TRUE.
459
460
461      !                                                      ! ------------------------- !
462      !                                                      !    non solar radiation    !   Qns
463      !                                                      ! ------------------------- !
464      srcv(jpr_qnsoce)%clname = 'O_QnsOce'
465      srcv(jpr_qnsice)%clname = 'O_QnsIce'
466      srcv(jpr_qnsmix)%clname = 'O_QnsMix'
467      SELECT CASE( TRIM( sn_rcv_qns%cldes ) )
468      CASE( 'none'          )       ! nothing to do
469      CASE( 'oce only'      )   ;   srcv(               jpr_qnsoce   )%laction = .TRUE.
470      CASE( 'conservative'  )   ;   srcv( (/jpr_qnsice, jpr_qnsmix/) )%laction = .TRUE.
471      CASE( 'oce and ice'   )   ;   srcv( (/jpr_qnsice, jpr_qnsoce/) )%laction = .TRUE.
472      CASE( 'mixed oce-ice' )   ;   srcv(               jpr_qnsmix   )%laction = .TRUE. 
473      CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_qns%cldes' )
474      END SELECT
475      IF( TRIM( sn_rcv_qns%cldes ) == 'mixed oce-ice' .AND. jpl > 1 ) &
476         CALL ctl_stop( 'sbc_cpl_init: sn_rcv_qns%cldes not currently allowed to be mixed oce-ice for multi-category ice' )
477      !                                                      ! ------------------------- !
478      !                                                      !    solar radiation        !   Qsr
479      !                                                      ! ------------------------- !
480      srcv(jpr_qsroce)%clname = 'O_QsrOce'
481      srcv(jpr_qsrice)%clname = 'O_QsrIce'
482      srcv(jpr_qsrmix)%clname = 'O_QsrMix'
483      SELECT CASE( TRIM( sn_rcv_qsr%cldes ) )
484      CASE( 'none'          )       ! nothing to do
485      CASE( 'oce only'      )   ;   srcv(               jpr_qsroce   )%laction = .TRUE.
486      CASE( 'conservative'  )   ;   srcv( (/jpr_qsrice, jpr_qsrmix/) )%laction = .TRUE.
487      CASE( 'oce and ice'   )   ;   srcv( (/jpr_qsrice, jpr_qsroce/) )%laction = .TRUE.
488      CASE( 'mixed oce-ice' )   ;   srcv(               jpr_qsrmix   )%laction = .TRUE. 
489      CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_qsr%cldes' )
490      END SELECT
491      IF( TRIM( sn_rcv_qsr%cldes ) == 'mixed oce-ice' .AND. jpl > 1 ) &
492         CALL ctl_stop( 'sbc_cpl_init: sn_rcv_qsr%cldes not currently allowed to be mixed oce-ice for multi-category ice' )
493      !                                                      ! ------------------------- !
494      !                                                      !   non solar sensitivity   !   d(Qns)/d(T)
495      !                                                      ! ------------------------- !
496      srcv(jpr_dqnsdt)%clname = 'O_dQnsdT'   
497      IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'coupled' )   srcv(jpr_dqnsdt)%laction = .TRUE.
498      !
499      ! non solar sensitivity mandatory for LIM ice model
500      IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'none' .AND. k_ice /= 0 .AND. k_ice /= 4 .AND. nn_components /= jp_iam_sas ) &
501         CALL ctl_stop( 'sbc_cpl_init: sn_rcv_dqnsdt%cldes must be coupled in namsbc_cpl namelist' )
502      ! non solar sensitivity mandatory for mixed oce-ice solar radiation coupling technique
503      IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'none' .AND. TRIM( sn_rcv_qns%cldes ) == 'mixed oce-ice' ) &
504         CALL ctl_stop( 'sbc_cpl_init: namsbc_cpl namelist mismatch between sn_rcv_qns%cldes and sn_rcv_dqnsdt%cldes' )
505      !                                                      ! ------------------------- !
506      !                                                      !      10m wind module      !   
507      !                                                      ! ------------------------- !
508      srcv(jpr_w10m)%clname = 'O_Wind10'   ;   IF( TRIM(sn_rcv_w10m%cldes  ) == 'coupled' )   srcv(jpr_w10m)%laction = .TRUE. 
509      !
510      !                                                      ! ------------------------- !
511      !                                                      !   wind stress module      !   
512      !                                                      ! ------------------------- !
513      srcv(jpr_taum)%clname = 'O_TauMod'   ;   IF( TRIM(sn_rcv_taumod%cldes) == 'coupled' )   srcv(jpr_taum)%laction = .TRUE.
514      lhftau = srcv(jpr_taum)%laction
515
516      !                                                      ! ------------------------- !
517      !                                                      !      Atmospheric CO2      !
518      !                                                      ! ------------------------- !
519      srcv(jpr_co2 )%clname = 'O_AtmCO2'   ;   IF( TRIM(sn_rcv_co2%cldes   ) == 'coupled' )    srcv(jpr_co2 )%laction = .TRUE.
520
521
522      !                                                      ! --------------------------------------- !   
523      !                                                      ! Incoming CO2 and DUST fluxes for MEDUSA !
524      !                                                      ! --------------------------------------- ! 
525      srcv(jpr_atm_pco2)%clname = 'OATMPCO2'
526
527      IF (TRIM(sn_rcv_atm_pco2%cldes) == 'medusa') THEN
528        srcv(jpr_atm_pco2)%laction = .TRUE.
529      END IF
530               
531      srcv(jpr_atm_dust)%clname = 'OATMDUST'   
532      IF (TRIM(sn_rcv_atm_dust%cldes) == 'medusa')  THEN
533        srcv(jpr_atm_dust)%laction = .TRUE.
534      END IF
535   
536      !                                                      ! ------------------------- !
537      !                                                      !   topmelt and botmelt     !   
538      !                                                      ! ------------------------- !
539      srcv(jpr_topm )%clname = 'OTopMlt'
540      srcv(jpr_botm )%clname = 'OBotMlt'
541      IF( TRIM(sn_rcv_iceflx%cldes) == 'coupled' ) THEN
542         IF ( TRIM( sn_rcv_iceflx%clcat ) == 'yes' ) THEN
543            srcv(jpr_topm:jpr_botm)%nct = jpl
544         ELSE
545            CALL ctl_stop( 'sbc_cpl_init: sn_rcv_iceflx%clcat should always be set to yes currently' )
546         ENDIF
547         srcv(jpr_topm:jpr_botm)%laction = .TRUE.
548      ENDIF
549     
550#if defined key_cice && ! defined key_cice4
551      !                                                      ! ----------------------------- !
552      !                                                      !  sea-ice skin temperature     !   
553      !                                                      !  used in meltpond scheme      !
554      !                                                      !  May be calculated in Atm     !
555      !                                                      ! ----------------------------- !
556      srcv(jpr_ts_ice)%clname = 'OTsfIce'
557      IF ( TRIM( sn_rcv_ts_ice%cldes ) == 'ice' ) srcv(jpr_ts_ice)%laction = .TRUE.
558      IF ( TRIM( sn_rcv_ts_ice%clcat ) == 'yes' ) srcv(jpr_ts_ice)%nct = jpl
559      !TODO: Should there be a consistency check here?
560#endif
561
562      !                                                      ! ------------------------------- !
563      !                                                      !   OPA-SAS coupling - rcv by opa !   
564      !                                                      ! ------------------------------- !
565      srcv(jpr_sflx)%clname = 'O_SFLX'
566      srcv(jpr_fice)%clname = 'RIceFrc'
567      !
568      IF( nn_components == jp_iam_opa ) THEN    ! OPA coupled to SAS via OASIS: force received field by OPA (sent by SAS)
569         srcv(:)%laction = .FALSE.   ! force default definition in case of opa <-> sas coupling
570         srcv(:)%clgrid  = 'T'       ! force default definition in case of opa <-> sas coupling
571         srcv(:)%nsgn    = 1.        ! force default definition in case of opa <-> sas coupling
572         srcv( (/jpr_qsroce, jpr_qnsoce, jpr_oemp, jpr_sflx, jpr_fice, jpr_otx1, jpr_oty1, jpr_taum/) )%laction = .TRUE.
573         srcv(jpr_otx1)%clgrid = 'U'        ! oce components given at U-point
574         srcv(jpr_oty1)%clgrid = 'V'        !           and           V-point
575         ! Vectors: change of sign at north fold ONLY if on the local grid
576         srcv( (/jpr_otx1,jpr_oty1/) )%nsgn = -1.
577         sn_rcv_tau%clvgrd = 'U,V'
578         sn_rcv_tau%clvor = 'local grid'
579         sn_rcv_tau%clvref = 'spherical'
580         sn_rcv_emp%cldes = 'oce only'
581         !
582         IF(lwp) THEN                        ! control print
583            WRITE(numout,*)
584            WRITE(numout,*)'               Special conditions for SAS-OPA coupling  '
585            WRITE(numout,*)'               OPA component  '
586            WRITE(numout,*)
587            WRITE(numout,*)'  received fields from SAS component '
588            WRITE(numout,*)'                  ice cover '
589            WRITE(numout,*)'                  oce only EMP  '
590            WRITE(numout,*)'                  salt flux  '
591            WRITE(numout,*)'                  mixed oce-ice solar flux  '
592            WRITE(numout,*)'                  mixed oce-ice non solar flux  '
593            WRITE(numout,*)'                  wind stress U,V on local grid and sperical coordinates '
594            WRITE(numout,*)'                  wind stress module'
595            WRITE(numout,*)
596         ENDIF
597      ENDIF
598      !                                                      ! -------------------------------- !
599      !                                                      !   OPA-SAS coupling - rcv by sas  !   
600      !                                                      ! -------------------------------- !
601      srcv(jpr_toce  )%clname = 'I_SSTSST'
602      srcv(jpr_soce  )%clname = 'I_SSSal'
603      srcv(jpr_ocx1  )%clname = 'I_OCurx1'
604      srcv(jpr_ocy1  )%clname = 'I_OCury1'
605      srcv(jpr_ssh   )%clname = 'I_SSHght'
606      srcv(jpr_e3t1st)%clname = 'I_E3T1st'   
607      srcv(jpr_fraqsr)%clname = 'I_FraQsr'   
608      !
609      IF( nn_components == jp_iam_sas ) THEN
610         IF( .NOT. ln_cpl ) srcv(:)%laction = .FALSE.   ! force default definition in case of opa <-> sas coupling
611         IF( .NOT. ln_cpl ) srcv(:)%clgrid  = 'T'       ! force default definition in case of opa <-> sas coupling
612         IF( .NOT. ln_cpl ) srcv(:)%nsgn    = 1.        ! force default definition in case of opa <-> sas coupling
613         srcv( (/jpr_toce, jpr_soce, jpr_ssh, jpr_fraqsr, jpr_ocx1, jpr_ocy1/) )%laction = .TRUE.
614         srcv( jpr_e3t1st )%laction = lk_vvl
615         srcv(jpr_ocx1)%clgrid = 'U'        ! oce components given at U-point
616         srcv(jpr_ocy1)%clgrid = 'V'        !           and           V-point
617         ! Vectors: change of sign at north fold ONLY if on the local grid
618         srcv(jpr_ocx1:jpr_ocy1)%nsgn = -1.
619         ! Change first letter to couple with atmosphere if already coupled OPA
620         ! this is nedeed as each variable name used in the namcouple must be unique:
621         ! for example O_Runoff received by OPA from SAS and therefore O_Runoff received by SAS from the Atmosphere
622         DO jn = 1, jprcv
623            IF ( srcv(jn)%clname(1:1) == "O" ) srcv(jn)%clname = "S"//srcv(jn)%clname(2:LEN(srcv(jn)%clname))
624         END DO
625         !
626         IF(lwp) THEN                        ! control print
627            WRITE(numout,*)
628            WRITE(numout,*)'               Special conditions for SAS-OPA coupling  '
629            WRITE(numout,*)'               SAS component  '
630            WRITE(numout,*)
631            IF( .NOT. ln_cpl ) THEN
632               WRITE(numout,*)'  received fields from OPA component '
633            ELSE
634               WRITE(numout,*)'  Additional received fields from OPA component : '
635            ENDIF
636            WRITE(numout,*)'               sea surface temperature (Celcius) '
637            WRITE(numout,*)'               sea surface salinity ' 
638            WRITE(numout,*)'               surface currents ' 
639            WRITE(numout,*)'               sea surface height ' 
640            WRITE(numout,*)'               thickness of first ocean T level '       
641            WRITE(numout,*)'               fraction of solar net radiation absorbed in the first ocean level'
642            WRITE(numout,*)
643         ENDIF
644      ENDIF
645     
646      ! =================================================== !
647      ! Allocate all parts of frcv used for received fields !
648      ! =================================================== !
649      DO jn = 1, jprcv
650         IF ( srcv(jn)%laction ) ALLOCATE( frcv(jn)%z3(jpi,jpj,srcv(jn)%nct) )
651      END DO
652      ! Allocate taum part of frcv which is used even when not received as coupling field
653      IF ( .NOT. srcv(jpr_taum)%laction ) ALLOCATE( frcv(jpr_taum)%z3(jpi,jpj,srcv(jpr_taum)%nct) )
654      ! Allocate w10m part of frcv which is used even when not received as coupling field
655      IF ( .NOT. srcv(jpr_w10m)%laction ) ALLOCATE( frcv(jpr_w10m)%z3(jpi,jpj,srcv(jpr_w10m)%nct) )
656      ! Allocate jpr_otx1 part of frcv which is used even when not received as coupling field
657      IF ( .NOT. srcv(jpr_otx1)%laction ) ALLOCATE( frcv(jpr_otx1)%z3(jpi,jpj,srcv(jpr_otx1)%nct) )
658      IF ( .NOT. srcv(jpr_oty1)%laction ) ALLOCATE( frcv(jpr_oty1)%z3(jpi,jpj,srcv(jpr_oty1)%nct) )
659      ! Allocate itx1 and ity1 as they are used in sbc_cpl_ice_tau even if srcv(jpr_itx1)%laction = .FALSE.
660      IF( k_ice /= 0 ) THEN
661         IF ( .NOT. srcv(jpr_itx1)%laction ) ALLOCATE( frcv(jpr_itx1)%z3(jpi,jpj,srcv(jpr_itx1)%nct) )
662         IF ( .NOT. srcv(jpr_ity1)%laction ) ALLOCATE( frcv(jpr_ity1)%z3(jpi,jpj,srcv(jpr_ity1)%nct) )
663      END IF
664
665      ! ================================ !
666      !     Define the send interface    !
667      ! ================================ !
668      ! for each field: define the OASIS name                           (ssnd(:)%clname)
669      !                 define send or not from the namelist parameters (ssnd(:)%laction)
670      !                 define the north fold type of lbc               (ssnd(:)%nsgn)
671     
672      ! default definitions of nsnd
673      ssnd(:)%laction = .FALSE.   ;   ssnd(:)%clgrid = 'T'   ;   ssnd(:)%nsgn = 1.  ; ssnd(:)%nct = 1
674         
675      !                                                      ! ------------------------- !
676      !                                                      !    Surface temperature    !
677      !                                                      ! ------------------------- !
678      ssnd(jps_toce)%clname = 'O_SSTSST'
679      ssnd(jps_tice)%clname = 'OTepIce'
680      ssnd(jps_tmix)%clname = 'O_TepMix'
681      SELECT CASE( TRIM( sn_snd_temp%cldes ) )
682      CASE( 'none'                                 )       ! nothing to do
683      CASE( 'oce only'                             )   ;   ssnd( jps_toce )%laction = .TRUE.
684      CASE( 'oce and ice' , 'weighted oce and ice' , 'oce and weighted ice')
685         ssnd( (/jps_toce, jps_tice/) )%laction = .TRUE.
686         IF ( TRIM( sn_snd_temp%clcat ) == 'yes' )  ssnd(jps_tice)%nct = jpl
687      CASE( 'mixed oce-ice'                        )   ;   ssnd( jps_tmix )%laction = .TRUE.
688      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_temp%cldes' )
689      END SELECT
690           
691      !                                                      ! ------------------------- !
692      !                                                      !          Albedo           !
693      !                                                      ! ------------------------- !
694      ssnd(jps_albice)%clname = 'O_AlbIce' 
695      ssnd(jps_albmix)%clname = 'O_AlbMix'
696      SELECT CASE( TRIM( sn_snd_alb%cldes ) )
697      CASE( 'none'                 )     ! nothing to do
698      CASE( 'ice' , 'weighted ice' )   ; ssnd(jps_albice)%laction = .TRUE.
699      CASE( 'mixed oce-ice'        )   ; ssnd(jps_albmix)%laction = .TRUE.
700      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_alb%cldes' )
701      END SELECT
702      !
703      ! Need to calculate oceanic albedo if
704      !     1. sending mixed oce-ice albedo or
705      !     2. receiving mixed oce-ice solar radiation
706      IF ( TRIM ( sn_snd_alb%cldes ) == 'mixed oce-ice' .OR. TRIM ( sn_rcv_qsr%cldes ) == 'mixed oce-ice' ) THEN
707         CALL albedo_oce( zaos, zacs )
708         ! Due to lack of information on nebulosity : mean clear/overcast sky
709         albedo_oce_mix(:,:) = ( zacs(:,:) + zaos(:,:) ) * 0.5
710      ENDIF
711
712      !                                                      ! ------------------------- !
713      !                                                      !  Ice fraction & Thickness
714      !                                                      ! ------------------------- !
715      ssnd(jps_fice)%clname = 'OIceFrc'
716      ssnd(jps_hice)%clname = 'OIceTck'
717      ssnd(jps_hsnw)%clname = 'OSnwTck'
718      ssnd(jps_a_p)%clname  = 'OPndFrc'
719      ssnd(jps_ht_p)%clname = 'OPndTck'
720      ssnd(jps_fice1)%clname = 'OIceFrd'
721      IF( k_ice /= 0 ) THEN
722         ssnd(jps_fice)%laction = .TRUE.                  ! if ice treated in the ocean (even in climato case)
723         ssnd(jps_fice1)%laction = .TRUE.                 ! First-order regridded ice concentration, to be used
724                                                     ! in producing atmos-to-ice fluxes
725! Currently no namelist entry to determine sending of multi-category ice fraction so use the thickness entry for now
726         IF ( TRIM( sn_snd_thick%clcat ) == 'yes' ) ssnd(jps_fice)%nct = jpl
727         IF ( TRIM( sn_snd_thick1%clcat ) == 'yes' ) ssnd(jps_fice1)%nct = jpl
728      ENDIF
729     
730      SELECT CASE ( TRIM( sn_snd_thick%cldes ) )
731      CASE( 'none'         )       ! nothing to do
732      CASE( 'ice and snow' ) 
733         ssnd(jps_hice:jps_hsnw)%laction = .TRUE.
734         IF ( TRIM( sn_snd_thick%clcat ) == 'yes' ) THEN
735            ssnd(jps_hice:jps_hsnw)%nct = jpl
736         ENDIF
737      CASE ( 'weighted ice and snow' ) 
738         ssnd(jps_hice:jps_hsnw)%laction = .TRUE.
739         IF ( TRIM( sn_snd_thick%clcat ) == 'yes' ) ssnd(jps_hice:jps_hsnw)%nct = jpl
740      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_thick%cldes' )
741      END SELECT
742
743      !                                                      ! ------------------------- !
744      !                                                      ! Ice Meltponds             !
745      !                                                      ! ------------------------- !
746#if defined key_cice && ! defined key_cice4
747      ! Meltponds only CICE5
748      ssnd(jps_a_p)%clname = 'OPndFrc'   
749      ssnd(jps_ht_p)%clname = 'OPndTck'   
750      SELECT CASE ( TRIM( sn_snd_mpnd%cldes ) )
751      CASE ( 'none' )
752         ssnd(jps_a_p)%laction = .FALSE.
753         ssnd(jps_ht_p)%laction = .FALSE.
754      CASE ( 'ice only' ) 
755         ssnd(jps_a_p)%laction = .TRUE.
756         ssnd(jps_ht_p)%laction = .TRUE.
757         IF ( TRIM( sn_snd_mpnd%clcat ) == 'yes' ) THEN
758            ssnd(jps_a_p)%nct = jpl
759            ssnd(jps_ht_p)%nct = jpl
760         ELSE
761            IF ( jpl > 1 ) THEN
762               CALL ctl_stop( 'sbc_cpl_init: use weighted ice option for sn_snd_mpnd%cldes if not exchanging category fields' )
763            ENDIF
764         ENDIF
765      CASE ( 'weighted ice' ) 
766         ssnd(jps_a_p)%laction = .TRUE.
767         ssnd(jps_ht_p)%laction = .TRUE.
768         IF ( TRIM( sn_snd_mpnd%clcat ) == 'yes' ) THEN
769            ssnd(jps_a_p)%nct = jpl 
770            ssnd(jps_ht_p)%nct = jpl 
771         ENDIF
772      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_mpnd%cldes' )
773      END SELECT
774#else
775      IF( TRIM( sn_snd_mpnd%cldes ) /= 'none' ) THEN
776         CALL ctl_stop('Meltponds can only be used with CICEv5')
777      ENDIF
778#endif
779
780      !                                                      ! ------------------------- !
781      !                                                      !      Surface current      !
782      !                                                      ! ------------------------- !
783      !        ocean currents              !            ice velocities
784      ssnd(jps_ocx1)%clname = 'O_OCurx1'   ;   ssnd(jps_ivx1)%clname = 'O_IVelx1'
785      ssnd(jps_ocy1)%clname = 'O_OCury1'   ;   ssnd(jps_ivy1)%clname = 'O_IVely1'
786      ssnd(jps_ocz1)%clname = 'O_OCurz1'   ;   ssnd(jps_ivz1)%clname = 'O_IVelz1'
787      !
788      ssnd(jps_ocx1:jps_ivz1)%nsgn = -1.   ! vectors: change of the sign at the north fold
789
790      IF( sn_snd_crt%clvgrd == 'U,V' ) THEN
791         ssnd(jps_ocx1)%clgrid = 'U' ; ssnd(jps_ocy1)%clgrid = 'V'
792      ELSE IF( sn_snd_crt%clvgrd /= 'T' ) THEN 
793         CALL ctl_stop( 'sn_snd_crt%clvgrd must be equal to T' )
794         ssnd(jps_ocx1:jps_ivz1)%clgrid  = 'T'      ! all oce and ice components on the same unique grid
795      ENDIF
796      ssnd(jps_ocx1:jps_ivz1)%laction = .TRUE.   ! default: all are send
797      IF( TRIM( sn_snd_crt%clvref ) == 'spherical' )   ssnd( (/jps_ocz1, jps_ivz1/) )%laction = .FALSE. 
798      IF( TRIM( sn_snd_crt%clvor ) == 'eastward-northward' ) ssnd(jps_ocx1:jps_ivz1)%nsgn = 1.
799      SELECT CASE( TRIM( sn_snd_crt%cldes ) )
800      CASE( 'none'                 )   ;   ssnd(jps_ocx1:jps_ivz1)%laction = .FALSE.
801      CASE( 'oce only'             )   ;   ssnd(jps_ivx1:jps_ivz1)%laction = .FALSE.
802      CASE( 'weighted oce and ice' )   !   nothing to do
803      CASE( 'mixed oce-ice'        )   ;   ssnd(jps_ivx1:jps_ivz1)%laction = .FALSE.
804      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_crt%cldes' )
805      END SELECT
806
807      !                                                      ! ------------------------- !
808      !                                                      !          CO2 flux         !
809      !                                                      ! ------------------------- !
810      ssnd(jps_co2)%clname = 'O_CO2FLX' ;  IF( TRIM(sn_snd_co2%cldes) == 'coupled' )    ssnd(jps_co2 )%laction = .TRUE.
811      !
812
813      !                                                      ! ------------------------- !
814      !                                                      !   MEDUSA output fields    !
815      !                                                      ! ------------------------- !
816      ! Surface dimethyl sulphide from Medusa
817      ssnd(jps_bio_dms)%clname = 'OBioDMS'   
818      IF( TRIM(sn_snd_bio_dms%cldes) == 'medusa' )    ssnd(jps_bio_dms )%laction = .TRUE.
819
820      ! Surface CO2 flux from Medusa
821      ssnd(jps_bio_co2)%clname = 'OBioCO2'   
822      IF( TRIM(sn_snd_bio_co2%cldes) == 'medusa' )    ssnd(jps_bio_co2 )%laction = .TRUE.
823     
824      !                                                      ! ------------------------- !
825      !                                                      ! Sea surface freezing temp !
826      !                                                      ! ------------------------- !
827      ssnd(jps_sstfrz)%clname = 'O_SSTFrz' ; IF( TRIM(sn_snd_sstfrz%cldes) == 'coupled' )  ssnd(jps_sstfrz)%laction = .TRUE.
828      !
829      !                                                      ! ------------------------- !
830      !                                                      !    Ice conductivity       !
831      !                                                      ! ------------------------- !
832      ! Note that ultimately we will move to passing an ocean effective conductivity as well so there
833      ! will be some changes to the parts of the code which currently relate only to ice conductivity
834      ssnd(jps_kice )%clname = 'OIceKn'
835      SELECT CASE ( TRIM( sn_snd_cond%cldes ) )
836      CASE ( 'none' )
837         ssnd(jps_kice)%laction = .FALSE.
838      CASE ( 'ice only' )
839         ssnd(jps_kice)%laction = .TRUE.
840         IF ( TRIM( sn_snd_cond%clcat ) == 'yes' ) THEN
841            ssnd(jps_kice)%nct = jpl
842         ELSE
843            IF ( jpl > 1 ) THEN
844               CALL ctl_stop( 'sbc_cpl_init: use weighted ice option for sn_snd_cond%cldes if not exchanging category fields' )
845            ENDIF
846         ENDIF
847      CASE ( 'weighted ice' )
848         ssnd(jps_kice)%laction = .TRUE.
849         IF ( TRIM( sn_snd_cond%clcat ) == 'yes' ) ssnd(jps_kice)%nct = jpl
850      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_cond%cldes' )
851      END SELECT
852      !
853     
854
855      !                                                      ! ------------------------------- !
856      !                                                      !   OPA-SAS coupling - snd by opa !   
857      !                                                      ! ------------------------------- !
858      ssnd(jps_ssh   )%clname = 'O_SSHght' 
859      ssnd(jps_soce  )%clname = 'O_SSSal' 
860      ssnd(jps_e3t1st)%clname = 'O_E3T1st'   
861      ssnd(jps_fraqsr)%clname = 'O_FraQsr'
862      !
863      IF( nn_components == jp_iam_opa ) THEN
864         ssnd(:)%laction = .FALSE.   ! force default definition in case of opa <-> sas coupling
865         ssnd( (/jps_toce, jps_soce, jps_ssh, jps_fraqsr, jps_ocx1, jps_ocy1/) )%laction = .TRUE.
866         ssnd( jps_e3t1st )%laction = lk_vvl
867         ! vector definition: not used but cleaner...
868         ssnd(jps_ocx1)%clgrid  = 'U'        ! oce components given at U-point
869         ssnd(jps_ocy1)%clgrid  = 'V'        !           and           V-point
870         sn_snd_crt%clvgrd = 'U,V'
871         sn_snd_crt%clvor = 'local grid'
872         sn_snd_crt%clvref = 'spherical'
873         !
874         IF(lwp) THEN                        ! control print
875            WRITE(numout,*)
876            WRITE(numout,*)'  sent fields to SAS component '
877            WRITE(numout,*)'               sea surface temperature (T before, Celcius) '
878            WRITE(numout,*)'               sea surface salinity ' 
879            WRITE(numout,*)'               surface currents U,V on local grid and spherical coordinates' 
880            WRITE(numout,*)'               sea surface height ' 
881            WRITE(numout,*)'               thickness of first ocean T level '       
882            WRITE(numout,*)'               fraction of solar net radiation absorbed in the first ocean level'
883            WRITE(numout,*)
884         ENDIF
885      ENDIF
886      !                                                      ! ------------------------------- !
887      !                                                      !   OPA-SAS coupling - snd by sas !   
888      !                                                      ! ------------------------------- !
889      ssnd(jps_sflx  )%clname = 'I_SFLX'     
890      ssnd(jps_fice2 )%clname = 'IIceFrc'
891      ssnd(jps_qsroce)%clname = 'I_QsrOce'   
892      ssnd(jps_qnsoce)%clname = 'I_QnsOce'   
893      ssnd(jps_oemp  )%clname = 'IOEvaMPr' 
894      ssnd(jps_otx1  )%clname = 'I_OTaux1'   
895      ssnd(jps_oty1  )%clname = 'I_OTauy1'   
896      ssnd(jps_rnf   )%clname = 'I_Runoff'   
897      ssnd(jps_taum  )%clname = 'I_TauMod'   
898      !
899      IF( nn_components == jp_iam_sas ) THEN
900         IF( .NOT. ln_cpl ) ssnd(:)%laction = .FALSE.   ! force default definition in case of opa <-> sas coupling
901         ssnd( (/jps_qsroce, jps_qnsoce, jps_oemp, jps_fice2, jps_sflx, jps_otx1, jps_oty1, jps_taum/) )%laction = .TRUE.
902         !
903         ! Change first letter to couple with atmosphere if already coupled with sea_ice
904         ! this is nedeed as each variable name used in the namcouple must be unique:
905         ! for example O_SSTSST sent by OPA to SAS and therefore S_SSTSST sent by SAS to the Atmosphere
906         DO jn = 1, jpsnd
907            IF ( ssnd(jn)%clname(1:1) == "O" ) ssnd(jn)%clname = "S"//ssnd(jn)%clname(2:LEN(ssnd(jn)%clname))
908         END DO
909         !
910         IF(lwp) THEN                        ! control print
911            WRITE(numout,*)
912            IF( .NOT. ln_cpl ) THEN
913               WRITE(numout,*)'  sent fields to OPA component '
914            ELSE
915               WRITE(numout,*)'  Additional sent fields to OPA component : '
916            ENDIF
917            WRITE(numout,*)'                  ice cover '
918            WRITE(numout,*)'                  oce only EMP  '
919            WRITE(numout,*)'                  salt flux  '
920            WRITE(numout,*)'                  mixed oce-ice solar flux  '
921            WRITE(numout,*)'                  mixed oce-ice non solar flux  '
922            WRITE(numout,*)'                  wind stress U,V components'
923            WRITE(numout,*)'                  wind stress module'
924         ENDIF
925      ENDIF
926
927      !
928      ! ================================ !
929      !   initialisation of the coupler  !
930      ! ================================ !
931
932      CALL cpl_define(jprcv, jpsnd, nn_cplmodel)
933     
934      IF (ln_usecplmask) THEN
935         xcplmask(:,:,:) = 0.
936         CALL iom_open( 'cplmask', inum )
937         CALL iom_get( inum, jpdom_unknown, 'cplmask', xcplmask(1:nlci,1:nlcj,1:nn_cplmodel),   &
938            &          kstart = (/ mig(1),mjg(1),1 /), kcount = (/ nlci,nlcj,nn_cplmodel /) )
939         CALL iom_close( inum )
940      ELSE
941         xcplmask(:,:,:) = 1.
942      ENDIF
943      xcplmask(:,:,0) = 1. - SUM( xcplmask(:,:,1:nn_cplmodel), dim = 3 )
944      !
945      ncpl_qsr_freq = cpl_freq( 'O_QsrOce' ) + cpl_freq( 'O_QsrMix' ) + cpl_freq( 'I_QsrOce' ) + cpl_freq( 'I_QsrMix' )
946      IF( ln_dm2dc .AND. ln_cpl .AND. ncpl_qsr_freq /= 86400 )   &
947         &   CALL ctl_stop( 'sbc_cpl_init: diurnal cycle reconstruction (ln_dm2dc) needs daily couping for solar radiation' )
948      ncpl_qsr_freq = 86400 / ncpl_qsr_freq
949
950      IF( ln_coupled_iceshelf_fluxes ) THEN
951          ! Crude masks to separate the Antarctic and Greenland icesheets. Obviously something
952          ! more complicated could be done if required.
953          greenland_icesheet_mask = 0.0
954          WHERE( gphit >= 0.0 ) greenland_icesheet_mask = 1.0
955          antarctica_icesheet_mask = 0.0
956          WHERE( gphit < 0.0 ) antarctica_icesheet_mask = 1.0
957
958          ! initialise other variables
959          greenland_icesheet_mass_array(:,:) = 0.0
960          antarctica_icesheet_mass_array(:,:) = 0.0
961
962          IF( .not. ln_rstart ) THEN
963             greenland_icesheet_mass = 0.0 
964             greenland_icesheet_mass_rate_of_change = 0.0 
965             greenland_icesheet_timelapsed = 0.0
966             antarctica_icesheet_mass = 0.0 
967             antarctica_icesheet_mass_rate_of_change = 0.0 
968             antarctica_icesheet_timelapsed = 0.0
969          ENDIF
970
971      ENDIF
972
973      CALL wrk_dealloc( jpi,jpj, zacs, zaos )
974      !
975      IF( nn_timing == 1 )  CALL timing_stop('sbc_cpl_init')
976      !
977   END SUBROUTINE sbc_cpl_init
978
979
980   SUBROUTINE sbc_cpl_rcv( kt, k_fsbc, k_ice )     
981      !!----------------------------------------------------------------------
982      !!             ***  ROUTINE sbc_cpl_rcv  ***
983      !!
984      !! ** Purpose :   provide the stress over the ocean and, if no sea-ice,
985      !!                provide the ocean heat and freshwater fluxes.
986      !!
987      !! ** Method  : - Receive all the atmospheric fields (stored in frcv array). called at each time step.
988      !!                OASIS controls if there is something do receive or not. nrcvinfo contains the info
989      !!                to know if the field was really received or not
990      !!
991      !!              --> If ocean stress was really received:
992      !!
993      !!                  - transform the received ocean stress vector from the received
994      !!                 referential and grid into an atmosphere-ocean stress in
995      !!                 the (i,j) ocean referencial and at the ocean velocity point.
996      !!                    The received stress are :
997      !!                     - defined by 3 components (if cartesian coordinate)
998      !!                            or by 2 components (if spherical)
999      !!                     - oriented along geographical   coordinate (if eastward-northward)
1000      !!                            or  along the local grid coordinate (if local grid)
1001      !!                     - given at U- and V-point, resp.   if received on 2 grids
1002      !!                            or at T-point               if received on 1 grid
1003      !!                    Therefore and if necessary, they are successively
1004      !!                  processed in order to obtain them
1005      !!                     first  as  2 components on the sphere
1006      !!                     second as  2 components oriented along the local grid
1007      !!                     third  as  2 components on the U,V grid
1008      !!
1009      !!              -->
1010      !!
1011      !!              - In 'ocean only' case, non solar and solar ocean heat fluxes
1012      !!             and total ocean freshwater fluxes 
1013      !!
1014      !! ** Method  :   receive all fields from the atmosphere and transform
1015      !!              them into ocean surface boundary condition fields
1016      !!
1017      !! ** Action  :   update  utau, vtau   ocean stress at U,V grid
1018      !!                        taum         wind stress module at T-point
1019      !!                        wndm         wind speed  module at T-point over free ocean or leads in presence of sea-ice
1020      !!                        qns          non solar heat fluxes including emp heat content    (ocean only case)
1021      !!                                     and the latent heat flux of solid precip. melting
1022      !!                        qsr          solar ocean heat fluxes   (ocean only case)
1023      !!                        emp          upward mass flux [evap. - precip. (- runoffs) (- calving)] (ocean only case)
1024      !!----------------------------------------------------------------------
1025      INTEGER, INTENT(in)           ::   kt          ! ocean model time step index
1026      INTEGER, INTENT(in)           ::   k_fsbc      ! frequency of sbc (-> ice model) computation
1027      INTEGER, INTENT(in)           ::   k_ice       ! ice management in the sbc (=0/1/2/3)
1028
1029      !!
1030      LOGICAL  ::   llnewtx, llnewtau      ! update wind stress components and module??
1031      INTEGER  ::   ji, jj, jl, jn         ! dummy loop indices
1032      INTEGER  ::   isec                   ! number of seconds since nit000 (assuming rdttra did not change since nit000)
1033      REAL(wp) ::   zcumulneg, zcumulpos   ! temporary scalars     
1034      REAL(wp) ::   zgreenland_icesheet_mass_in, zantarctica_icesheet_mass_in
1035      REAL(wp) ::   zgreenland_icesheet_mass_b, zantarctica_icesheet_mass_b
1036      REAL(wp) ::   zmask_sum, zepsilon     
1037      REAL(wp) ::   zcoef                  ! temporary scalar
1038      REAL(wp) ::   zrhoa  = 1.22          ! Air density kg/m3
1039      REAL(wp) ::   zcdrag = 1.5e-3        ! drag coefficient
1040      REAL(wp) ::   zzx, zzy               ! temporary variables
1041      REAL(wp), POINTER, DIMENSION(:,:) ::   ztx, zty, zmsk, zemp, zqns, zqsr
1042      !!----------------------------------------------------------------------
1043      !
1044      IF( nn_timing == 1 )  CALL timing_start('sbc_cpl_rcv')
1045      !
1046      CALL wrk_alloc( jpi,jpj, ztx, zty, zmsk, zemp, zqns, zqsr )
1047      !
1048      IF( ln_mixcpl )   zmsk(:,:) = 1. - xcplmask(:,:,0)
1049      !
1050      !                                                      ! ======================================================= !
1051      !                                                      ! Receive all the atmos. fields (including ice information)
1052      !                                                      ! ======================================================= !
1053      isec = ( kt - nit000 ) * NINT( rdttra(1) )                ! date of exchanges
1054      DO jn = 1, jprcv                                          ! received fields sent by the atmosphere
1055         IF( srcv(jn)%laction )   CALL cpl_rcv( jn, isec, frcv(jn)%z3, xcplmask(:,:,1:nn_cplmodel), nrcvinfo(jn) )
1056      END DO
1057
1058      !                                                      ! ========================= !
1059      IF( srcv(jpr_otx1)%laction ) THEN                      !  ocean stress components  !
1060         !                                                   ! ========================= !
1061         ! define frcv(jpr_otx1)%z3(:,:,1) and frcv(jpr_oty1)%z3(:,:,1): stress at U/V point along model grid
1062         ! => need to be done only when we receive the field
1063         IF(  nrcvinfo(jpr_otx1) == OASIS_Rcv ) THEN
1064            !
1065            IF( TRIM( sn_rcv_tau%clvref ) == 'cartesian' ) THEN            ! 2 components on the sphere
1066               !                                                       ! (cartesian to spherical -> 3 to 2 components)
1067               !
1068               CALL geo2oce( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), frcv(jpr_otz1)%z3(:,:,1),   &
1069                  &          srcv(jpr_otx1)%clgrid, ztx, zty )
1070               frcv(jpr_otx1)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 1st grid
1071               frcv(jpr_oty1)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 1st grid
1072               !
1073               IF( srcv(jpr_otx2)%laction ) THEN
1074                  CALL geo2oce( frcv(jpr_otx2)%z3(:,:,1), frcv(jpr_oty2)%z3(:,:,1), frcv(jpr_otz2)%z3(:,:,1),   &
1075                     &          srcv(jpr_otx2)%clgrid, ztx, zty )
1076                  frcv(jpr_otx2)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 2nd grid
1077                  frcv(jpr_oty2)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 2nd grid
1078               ENDIF
1079               !
1080            ENDIF
1081            !
1082            IF( TRIM( sn_rcv_tau%clvor ) == 'eastward-northward' ) THEN   ! 2 components oriented along the local grid
1083               !                                                       ! (geographical to local grid -> rotate the components)
1084               CALL rot_rep( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), srcv(jpr_otx1)%clgrid, 'en->i', ztx )   
1085               IF( srcv(jpr_otx2)%laction ) THEN
1086                  CALL rot_rep( frcv(jpr_otx2)%z3(:,:,1), frcv(jpr_oty2)%z3(:,:,1), srcv(jpr_otx2)%clgrid, 'en->j', zty )   
1087               ELSE 
1088                  CALL rot_rep( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), srcv(jpr_otx1)%clgrid, 'en->j', zty ) 
1089               ENDIF
1090               frcv(jpr_otx1)%z3(:,:,1) = ztx(:,:)      ! overwrite 1st component on the 1st grid
1091               frcv(jpr_oty1)%z3(:,:,1) = zty(:,:)      ! overwrite 2nd component on the 2nd grid
1092            ENDIF
1093            !                             
1094            IF( srcv(jpr_otx1)%clgrid == 'T' ) THEN
1095               DO jj = 2, jpjm1                                          ! T ==> (U,V)
1096                  DO ji = fs_2, fs_jpim1   ! vector opt.
1097                     frcv(jpr_otx1)%z3(ji,jj,1) = 0.5 * ( frcv(jpr_otx1)%z3(ji+1,jj  ,1) + frcv(jpr_otx1)%z3(ji,jj,1) )
1098                     frcv(jpr_oty1)%z3(ji,jj,1) = 0.5 * ( frcv(jpr_oty1)%z3(ji  ,jj+1,1) + frcv(jpr_oty1)%z3(ji,jj,1) )
1099                  END DO
1100               END DO
1101               CALL lbc_lnk( frcv(jpr_otx1)%z3(:,:,1), 'U',  -1. )   ;   CALL lbc_lnk( frcv(jpr_oty1)%z3(:,:,1), 'V',  -1. )
1102            ENDIF
1103            llnewtx = .TRUE.
1104         ELSE
1105            llnewtx = .FALSE.
1106         ENDIF
1107         !                                                   ! ========================= !
1108      ELSE                                                   !   No dynamical coupling   !
1109         !                                                   ! ========================= !
1110         frcv(jpr_otx1)%z3(:,:,1) = 0.e0                               ! here simply set to zero
1111         frcv(jpr_oty1)%z3(:,:,1) = 0.e0                               ! an external read in a file can be added instead
1112         llnewtx = .TRUE.
1113         !
1114      ENDIF
1115      !                                                      ! ========================= !
1116      !                                                      !    wind stress module     !   (taum)
1117      !                                                      ! ========================= !
1118      !
1119      IF( .NOT. srcv(jpr_taum)%laction ) THEN                    ! compute wind stress module from its components if not received
1120         ! => need to be done only when otx1 was changed
1121         IF( llnewtx ) THEN
1122!CDIR NOVERRCHK
1123            DO jj = 2, jpjm1
1124!CDIR NOVERRCHK
1125               DO ji = fs_2, fs_jpim1   ! vect. opt.
1126                  zzx = frcv(jpr_otx1)%z3(ji-1,jj  ,1) + frcv(jpr_otx1)%z3(ji,jj,1)
1127                  zzy = frcv(jpr_oty1)%z3(ji  ,jj-1,1) + frcv(jpr_oty1)%z3(ji,jj,1)
1128                  frcv(jpr_taum)%z3(ji,jj,1) = 0.5 * SQRT( zzx * zzx + zzy * zzy )
1129               END DO
1130            END DO
1131            CALL lbc_lnk( frcv(jpr_taum)%z3(:,:,1), 'T', 1. )
1132            llnewtau = .TRUE.
1133         ELSE
1134            llnewtau = .FALSE.
1135         ENDIF
1136      ELSE
1137         llnewtau = nrcvinfo(jpr_taum) == OASIS_Rcv
1138         ! Stress module can be negative when received (interpolation problem)
1139         IF( llnewtau ) THEN
1140            frcv(jpr_taum)%z3(:,:,1) = MAX( 0._wp, frcv(jpr_taum)%z3(:,:,1) )
1141         ENDIF
1142      ENDIF
1143      !
1144      !                                                      ! ========================= !
1145      !                                                      !      10 m wind speed      !   (wndm)
1146      !                                                      ! ========================= !
1147      !
1148      IF( .NOT. srcv(jpr_w10m)%laction ) THEN                    ! compute wind spreed from wind stress module if not received 
1149         ! => need to be done only when taumod was changed
1150         IF( llnewtau ) THEN
1151            zcoef = 1. / ( zrhoa * zcdrag ) 
1152!CDIR NOVERRCHK
1153            DO jj = 1, jpj
1154!CDIR NOVERRCHK
1155               DO ji = 1, jpi 
1156                  frcv(jpr_w10m)%z3(ji,jj,1) = SQRT( frcv(jpr_taum)%z3(ji,jj,1) * zcoef )
1157               END DO
1158            END DO
1159         ENDIF
1160      ENDIF
1161
1162      ! u(v)tau and taum will be modified by ice model
1163      ! -> need to be reset before each call of the ice/fsbc     
1164      IF( MOD( kt-1, k_fsbc ) == 0 ) THEN
1165         !
1166         IF( ln_mixcpl ) THEN
1167            utau(:,:) = utau(:,:) * xcplmask(:,:,0) + frcv(jpr_otx1)%z3(:,:,1) * zmsk(:,:)
1168            vtau(:,:) = vtau(:,:) * xcplmask(:,:,0) + frcv(jpr_oty1)%z3(:,:,1) * zmsk(:,:)
1169            taum(:,:) = taum(:,:) * xcplmask(:,:,0) + frcv(jpr_taum)%z3(:,:,1) * zmsk(:,:)
1170            wndm(:,:) = wndm(:,:) * xcplmask(:,:,0) + frcv(jpr_w10m)%z3(:,:,1) * zmsk(:,:)
1171         ELSE
1172            utau(:,:) = frcv(jpr_otx1)%z3(:,:,1)
1173            vtau(:,:) = frcv(jpr_oty1)%z3(:,:,1)
1174            taum(:,:) = frcv(jpr_taum)%z3(:,:,1)
1175            wndm(:,:) = frcv(jpr_w10m)%z3(:,:,1)
1176         ENDIF
1177         CALL iom_put( "taum_oce", taum )   ! output wind stress module
1178         
1179      ENDIF
1180
1181      IF (ln_medusa) THEN
1182        IF( srcv(jpr_atm_pco2)%laction) PCO2a_in_cpl(:,:) = frcv(jpr_atm_pco2)%z3(:,:,1)
1183        IF( srcv(jpr_atm_dust)%laction) Dust_in_cpl(:,:) = frcv(jpr_atm_dust)%z3(:,:,1)
1184      ENDIF
1185
1186#if defined key_cpl_carbon_cycle
1187      !                                                      ! ================== !
1188      !                                                      ! atmosph. CO2 (ppm) !
1189      !                                                      ! ================== !
1190      IF( srcv(jpr_co2)%laction )   atm_co2(:,:) = frcv(jpr_co2)%z3(:,:,1)
1191#endif
1192
1193#if defined key_cice && ! defined key_cice4
1194      !  ! Sea ice surface skin temp:
1195      IF( srcv(jpr_ts_ice)%laction ) THEN
1196        DO jl = 1, jpl
1197          DO jj = 1, jpj
1198            DO ji = 1, jpi
1199              IF (frcv(jpr_ts_ice)%z3(ji,jj,jl) > 0.0) THEN
1200                tsfc_ice(ji,jj,jl) = 0.0
1201              ELSE IF (frcv(jpr_ts_ice)%z3(ji,jj,jl) < -60.0) THEN
1202                tsfc_ice(ji,jj,jl) = -60.0
1203              ELSE
1204                tsfc_ice(ji,jj,jl) = frcv(jpr_ts_ice)%z3(ji,jj,jl)
1205              ENDIF
1206            END DO
1207          END DO
1208        END DO
1209      ENDIF
1210#endif
1211
1212      !  Fields received by SAS when OASIS coupling
1213      !  (arrays no more filled at sbcssm stage)
1214      !                                                      ! ================== !
1215      !                                                      !        SSS         !
1216      !                                                      ! ================== !
1217      IF( srcv(jpr_soce)%laction ) THEN                      ! received by sas in case of opa <-> sas coupling
1218         sss_m(:,:) = frcv(jpr_soce)%z3(:,:,1)
1219         CALL iom_put( 'sss_m', sss_m )
1220      ENDIF
1221      !                                               
1222      !                                                      ! ================== !
1223      !                                                      !        SST         !
1224      !                                                      ! ================== !
1225      IF( srcv(jpr_toce)%laction ) THEN                      ! received by sas in case of opa <-> sas coupling
1226         sst_m(:,:) = frcv(jpr_toce)%z3(:,:,1)
1227         IF( srcv(jpr_soce)%laction .AND. ln_useCT ) THEN    ! make sure that sst_m is the potential temperature
1228            sst_m(:,:) = eos_pt_from_ct( sst_m(:,:), sss_m(:,:) )
1229         ENDIF
1230      ENDIF
1231      !                                                      ! ================== !
1232      !                                                      !        SSH         !
1233      !                                                      ! ================== !
1234      IF( srcv(jpr_ssh )%laction ) THEN                      ! received by sas in case of opa <-> sas coupling
1235         ssh_m(:,:) = frcv(jpr_ssh )%z3(:,:,1)
1236         CALL iom_put( 'ssh_m', ssh_m )
1237      ENDIF
1238      !                                                      ! ================== !
1239      !                                                      !  surface currents  !
1240      !                                                      ! ================== !
1241      IF( srcv(jpr_ocx1)%laction ) THEN                      ! received by sas in case of opa <-> sas coupling
1242         ssu_m(:,:) = frcv(jpr_ocx1)%z3(:,:,1)
1243         ub (:,:,1) = ssu_m(:,:)                             ! will be used in sbcice_lim in the call of lim_sbc_tau
1244         CALL iom_put( 'ssu_m', ssu_m )
1245      ENDIF
1246      IF( srcv(jpr_ocy1)%laction ) THEN
1247         ssv_m(:,:) = frcv(jpr_ocy1)%z3(:,:,1)
1248         vb (:,:,1) = ssv_m(:,:)                             ! will be used in sbcice_lim in the call of lim_sbc_tau
1249         CALL iom_put( 'ssv_m', ssv_m )
1250      ENDIF
1251      !                                                      ! ======================== !
1252      !                                                      !  first T level thickness !
1253      !                                                      ! ======================== !
1254      IF( srcv(jpr_e3t1st )%laction ) THEN                   ! received by sas in case of opa <-> sas coupling
1255         e3t_m(:,:) = frcv(jpr_e3t1st )%z3(:,:,1)
1256         CALL iom_put( 'e3t_m', e3t_m(:,:) )
1257      ENDIF
1258      !                                                      ! ================================ !
1259      !                                                      !  fraction of solar net radiation !
1260      !                                                      ! ================================ !
1261      IF( srcv(jpr_fraqsr)%laction ) THEN                    ! received by sas in case of opa <-> sas coupling
1262         frq_m(:,:) = frcv(jpr_fraqsr)%z3(:,:,1)
1263         CALL iom_put( 'frq_m', frq_m )
1264      ENDIF
1265     
1266      !                                                      ! ========================= !
1267      IF( k_ice <= 1 .AND. MOD( kt-1, k_fsbc ) == 0 ) THEN   !  heat & freshwater fluxes ! (Ocean only case)
1268         !                                                   ! ========================= !
1269         !
1270         !                                                       ! total freshwater fluxes over the ocean (emp)
1271         IF( srcv(jpr_oemp)%laction .OR. srcv(jpr_rain)%laction ) THEN
1272            SELECT CASE( TRIM( sn_rcv_emp%cldes ) )                                    ! evaporation - precipitation
1273            CASE( 'conservative' )
1274               zemp(:,:) = frcv(jpr_tevp)%z3(:,:,1) - ( frcv(jpr_rain)%z3(:,:,1) + frcv(jpr_snow)%z3(:,:,1) )
1275            CASE( 'oce only', 'oce and ice' )
1276               zemp(:,:) = frcv(jpr_oemp)%z3(:,:,1)
1277            CASE default
1278               CALL ctl_stop( 'sbc_cpl_rcv: wrong definition of sn_rcv_emp%cldes' )
1279            END SELECT
1280         ELSE
1281            zemp(:,:) = 0._wp
1282         ENDIF
1283         !
1284         !                                                        ! runoffs and calving (added in emp)
1285         IF( srcv(jpr_rnf)%laction )     rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1)
1286         IF( srcv(jpr_cal)%laction )     zemp(:,:) = zemp(:,:) - frcv(jpr_cal)%z3(:,:,1)
1287         
1288         IF( ln_mixcpl ) THEN   ;   emp(:,:) = emp(:,:) * xcplmask(:,:,0) + zemp(:,:) * zmsk(:,:)
1289         ELSE                   ;   emp(:,:) =                              zemp(:,:)
1290         ENDIF
1291         !
1292         !                                                       ! non solar heat flux over the ocean (qns)
1293         IF(      srcv(jpr_qnsoce)%laction ) THEN   ;   zqns(:,:) = frcv(jpr_qnsoce)%z3(:,:,1)
1294         ELSE IF( srcv(jpr_qnsmix)%laction ) THEN   ;   zqns(:,:) = frcv(jpr_qnsmix)%z3(:,:,1)
1295         ELSE                                       ;   zqns(:,:) = 0._wp
1296         END IF
1297         ! update qns over the free ocean with:
1298         IF( nn_components /= jp_iam_opa ) THEN
1299            zqns(:,:) =  zqns(:,:) - zemp(:,:) * sst_m(:,:) * rcp         ! remove heat content due to mass flux (assumed to be at SST)
1300            IF( srcv(jpr_snow  )%laction ) THEN
1301               zqns(:,:) = zqns(:,:) - frcv(jpr_snow)%z3(:,:,1) * lfus    ! energy for melting solid precipitation over the free ocean
1302            ENDIF
1303         ENDIF
1304         IF( ln_mixcpl ) THEN   ;   qns(:,:) = qns(:,:) * xcplmask(:,:,0) + zqns(:,:) * zmsk(:,:)
1305         ELSE                   ;   qns(:,:) =                              zqns(:,:)
1306         ENDIF
1307
1308         !                                                       ! solar flux over the ocean          (qsr)
1309         IF     ( srcv(jpr_qsroce)%laction ) THEN   ;   zqsr(:,:) = frcv(jpr_qsroce)%z3(:,:,1)
1310         ELSE IF( srcv(jpr_qsrmix)%laction ) then   ;   zqsr(:,:) = frcv(jpr_qsrmix)%z3(:,:,1)
1311         ELSE                                       ;   zqsr(:,:) = 0._wp
1312         ENDIF
1313         IF( ln_dm2dc .AND. ln_cpl )   zqsr(:,:) = sbc_dcy( zqsr )   ! modify qsr to include the diurnal cycle
1314         IF( ln_mixcpl ) THEN   ;   qsr(:,:) = qsr(:,:) * xcplmask(:,:,0) + zqsr(:,:) * zmsk(:,:)
1315         ELSE                   ;   qsr(:,:) =                              zqsr(:,:)
1316         ENDIF
1317         !
1318         ! salt flux over the ocean (received by opa in case of opa <-> sas coupling)
1319         IF( srcv(jpr_sflx )%laction )   sfx(:,:) = frcv(jpr_sflx  )%z3(:,:,1)
1320         ! Ice cover  (received by opa in case of opa <-> sas coupling)
1321         IF( srcv(jpr_fice )%laction )   fr_i(:,:) = frcv(jpr_fice )%z3(:,:,1)
1322         !
1323
1324      ENDIF
1325     
1326      !                                                        ! land ice masses : Greenland
1327      zepsilon = rn_iceshelf_fluxes_tolerance
1328
1329
1330      ! See if we need zmask_sum...
1331      IF ( srcv(jpr_grnm)%laction .OR. srcv(jpr_antm)%laction ) THEN
1332         zmask_sum = glob_sum( tmask(:,:,1) )
1333      ENDIF
1334
1335      IF( srcv(jpr_grnm)%laction ) THEN
1336         greenland_icesheet_mass_array(:,:) = frcv(jpr_grnm)%z3(:,:,1)
1337         ! take average over ocean points of input array to avoid cumulative error over time
1338
1339         ! The following must be bit reproducible over different PE decompositions
1340         zgreenland_icesheet_mass_in = glob_sum( greenland_icesheet_mass_array(:,:) * tmask(:,:,1) )
1341
1342         zgreenland_icesheet_mass_in = zgreenland_icesheet_mass_in / zmask_sum
1343         greenland_icesheet_timelapsed = greenland_icesheet_timelapsed + rdt         
1344         IF( ABS( zgreenland_icesheet_mass_in - greenland_icesheet_mass ) > zepsilon ) THEN
1345            zgreenland_icesheet_mass_b = greenland_icesheet_mass
1346           
1347            ! Only update the mass if it has increased
1348            IF ( (zgreenland_icesheet_mass_in - greenland_icesheet_mass) > 0.0 ) THEN
1349               greenland_icesheet_mass = zgreenland_icesheet_mass_in
1350            ENDIF
1351           
1352            IF( zgreenland_icesheet_mass_b /= 0.0 ) &
1353           &     greenland_icesheet_mass_rate_of_change = ( greenland_icesheet_mass - zgreenland_icesheet_mass_b ) / greenland_icesheet_timelapsed 
1354            greenland_icesheet_timelapsed = 0.0_wp       
1355         ENDIF
1356         IF(lwp) WRITE(numout,*) 'Greenland icesheet mass (kg) read in is ', zgreenland_icesheet_mass_in
1357         IF(lwp) WRITE(numout,*) 'Greenland icesheet mass (kg) used is    ', greenland_icesheet_mass
1358         IF(lwp) WRITE(numout,*) 'Greenland icesheet mass rate of change (kg/s) is ', greenland_icesheet_mass_rate_of_change
1359         IF(lwp) WRITE(numout,*) 'Greenland icesheet seconds lapsed since last change is ', greenland_icesheet_timelapsed
1360      ENDIF
1361
1362      !                                                        ! land ice masses : Antarctica
1363      IF( srcv(jpr_antm)%laction ) THEN
1364         antarctica_icesheet_mass_array(:,:) = frcv(jpr_antm)%z3(:,:,1)
1365         ! take average over ocean points of input array to avoid cumulative error from rounding errors over time
1366         ! The following must be bit reproducible over different PE decompositions
1367         zantarctica_icesheet_mass_in = glob_sum( antarctica_icesheet_mass_array(:,:) * tmask(:,:,1) )
1368
1369         zantarctica_icesheet_mass_in = zantarctica_icesheet_mass_in / zmask_sum
1370         antarctica_icesheet_timelapsed = antarctica_icesheet_timelapsed + rdt         
1371         IF( ABS( zantarctica_icesheet_mass_in - antarctica_icesheet_mass ) > zepsilon ) THEN
1372            zantarctica_icesheet_mass_b = antarctica_icesheet_mass
1373           
1374            ! Only update the mass if it has increased
1375            IF ( (zantarctica_icesheet_mass_in - antarctica_icesheet_mass) > 0.0 ) THEN
1376               antarctica_icesheet_mass = zantarctica_icesheet_mass_in
1377            END IF
1378           
1379            IF( zantarctica_icesheet_mass_b /= 0.0 ) &
1380          &      antarctica_icesheet_mass_rate_of_change = ( antarctica_icesheet_mass - zantarctica_icesheet_mass_b ) / antarctica_icesheet_timelapsed 
1381            antarctica_icesheet_timelapsed = 0.0_wp       
1382         ENDIF
1383         IF(lwp) WRITE(numout,*) 'Antarctica icesheet mass (kg) read in is ', zantarctica_icesheet_mass_in
1384         IF(lwp) WRITE(numout,*) 'Antarctica icesheet mass (kg) used is    ', antarctica_icesheet_mass
1385         IF(lwp) WRITE(numout,*) 'Antarctica icesheet mass rate of change (kg/s) is ', antarctica_icesheet_mass_rate_of_change
1386         IF(lwp) WRITE(numout,*) 'Antarctica icesheet seconds lapsed since last change is ', antarctica_icesheet_timelapsed
1387      ENDIF
1388
1389      !
1390      CALL wrk_dealloc( jpi,jpj, ztx, zty, zmsk, zemp, zqns, zqsr )
1391      !
1392      IF( nn_timing == 1 )  CALL timing_stop('sbc_cpl_rcv')
1393      !
1394   END SUBROUTINE sbc_cpl_rcv
1395   
1396
1397   SUBROUTINE sbc_cpl_ice_tau( p_taui, p_tauj )     
1398      !!----------------------------------------------------------------------
1399      !!             ***  ROUTINE sbc_cpl_ice_tau  ***
1400      !!
1401      !! ** Purpose :   provide the stress over sea-ice in coupled mode
1402      !!
1403      !! ** Method  :   transform the received stress from the atmosphere into
1404      !!             an atmosphere-ice stress in the (i,j) ocean referencial
1405      !!             and at the velocity point of the sea-ice model (cp_ice_msh):
1406      !!                'C'-grid : i- (j-) components given at U- (V-) point
1407      !!                'I'-grid : B-grid lower-left corner: both components given at I-point
1408      !!
1409      !!                The received stress are :
1410      !!                 - defined by 3 components (if cartesian coordinate)
1411      !!                        or by 2 components (if spherical)
1412      !!                 - oriented along geographical   coordinate (if eastward-northward)
1413      !!                        or  along the local grid coordinate (if local grid)
1414      !!                 - given at U- and V-point, resp.   if received on 2 grids
1415      !!                        or at a same point (T or I) if received on 1 grid
1416      !!                Therefore and if necessary, they are successively
1417      !!             processed in order to obtain them
1418      !!                 first  as  2 components on the sphere
1419      !!                 second as  2 components oriented along the local grid
1420      !!                 third  as  2 components on the cp_ice_msh point
1421      !!
1422      !!                Except in 'oce and ice' case, only one vector stress field
1423      !!             is received. It has already been processed in sbc_cpl_rcv
1424      !!             so that it is now defined as (i,j) components given at U-
1425      !!             and V-points, respectively. Therefore, only the third
1426      !!             transformation is done and only if the ice-grid is a 'I'-grid.
1427      !!
1428      !! ** Action  :   return ptau_i, ptau_j, the stress over the ice at cp_ice_msh point
1429      !!----------------------------------------------------------------------
1430      REAL(wp), INTENT(out), DIMENSION(:,:) ::   p_taui   ! i- & j-components of atmos-ice stress [N/m2]
1431      REAL(wp), INTENT(out), DIMENSION(:,:) ::   p_tauj   ! at I-point (B-grid) or U & V-point (C-grid)
1432      !!
1433      INTEGER ::   ji, jj                          ! dummy loop indices
1434      INTEGER ::   itx                             ! index of taux over ice
1435      REAL(wp), POINTER, DIMENSION(:,:) ::   ztx, zty 
1436      !!----------------------------------------------------------------------
1437      !
1438      IF( nn_timing == 1 )  CALL timing_start('sbc_cpl_ice_tau')
1439      !
1440      CALL wrk_alloc( jpi,jpj, ztx, zty )
1441
1442      IF( srcv(jpr_itx1)%laction ) THEN   ;   itx =  jpr_itx1   
1443      ELSE                                ;   itx =  jpr_otx1
1444      ENDIF
1445
1446      ! do something only if we just received the stress from atmosphere
1447      IF(  nrcvinfo(itx) == OASIS_Rcv ) THEN
1448
1449         !                                                      ! ======================= !
1450         IF( srcv(jpr_itx1)%laction ) THEN                      !   ice stress received   !
1451            !                                                   ! ======================= !
1452           
1453            IF( TRIM( sn_rcv_tau%clvref ) == 'cartesian' ) THEN            ! 2 components on the sphere
1454               !                                                       ! (cartesian to spherical -> 3 to 2 components)
1455               CALL geo2oce(  frcv(jpr_itx1)%z3(:,:,1), frcv(jpr_ity1)%z3(:,:,1), frcv(jpr_itz1)%z3(:,:,1),   &
1456                  &          srcv(jpr_itx1)%clgrid, ztx, zty )
1457               frcv(jpr_itx1)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 1st grid
1458               frcv(jpr_ity1)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 1st grid
1459               !
1460               IF( srcv(jpr_itx2)%laction ) THEN
1461                  CALL geo2oce( frcv(jpr_itx2)%z3(:,:,1), frcv(jpr_ity2)%z3(:,:,1), frcv(jpr_itz2)%z3(:,:,1),   &
1462                     &          srcv(jpr_itx2)%clgrid, ztx, zty )
1463                  frcv(jpr_itx2)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 2nd grid
1464                  frcv(jpr_ity2)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 2nd grid
1465               ENDIF
1466               !
1467            ENDIF
1468            !
1469            IF( TRIM( sn_rcv_tau%clvor ) == 'eastward-northward' ) THEN   ! 2 components oriented along the local grid
1470               !                                                       ! (geographical to local grid -> rotate the components)
1471               CALL rot_rep( frcv(jpr_itx1)%z3(:,:,1), frcv(jpr_ity1)%z3(:,:,1), srcv(jpr_itx1)%clgrid, 'en->i', ztx )   
1472               IF( srcv(jpr_itx2)%laction ) THEN
1473                  CALL rot_rep( frcv(jpr_itx2)%z3(:,:,1), frcv(jpr_ity2)%z3(:,:,1), srcv(jpr_itx2)%clgrid, 'en->j', zty )   
1474               ELSE
1475                  CALL rot_rep( frcv(jpr_itx1)%z3(:,:,1), frcv(jpr_ity1)%z3(:,:,1), srcv(jpr_itx1)%clgrid, 'en->j', zty ) 
1476               ENDIF
1477               frcv(jpr_itx1)%z3(:,:,1) = ztx(:,:)      ! overwrite 1st component on the 1st grid
1478               frcv(jpr_ity1)%z3(:,:,1) = zty(:,:)      ! overwrite 2nd component on the 1st grid
1479            ENDIF
1480            !                                                   ! ======================= !
1481         ELSE                                                   !     use ocean stress    !
1482            !                                                   ! ======================= !
1483            frcv(jpr_itx1)%z3(:,:,1) = frcv(jpr_otx1)%z3(:,:,1)
1484            frcv(jpr_ity1)%z3(:,:,1) = frcv(jpr_oty1)%z3(:,:,1)
1485            !
1486         ENDIF
1487         !                                                      ! ======================= !
1488         !                                                      !     put on ice grid     !
1489         !                                                      ! ======================= !
1490         !   
1491         !                                                  j+1   j     -----V---F
1492         ! ice stress on ice velocity point (cp_ice_msh)                 !       |
1493         ! (C-grid ==>(U,V) or B-grid ==> I or F)                 j      |   T   U
1494         !                                                               |       |
1495         !                                                   j    j-1   -I-------|
1496         !                                               (for I)         |       |
1497         !                                                              i-1  i   i
1498         !                                                               i      i+1 (for I)
1499         SELECT CASE ( cp_ice_msh )
1500            !
1501         CASE( 'I' )                                         ! B-grid ==> I
1502            SELECT CASE ( srcv(jpr_itx1)%clgrid )
1503            CASE( 'U' )
1504               DO jj = 2, jpjm1                                   ! (U,V) ==> I
1505                  DO ji = 2, jpim1   ! NO vector opt.
1506                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji-1,jj  ,1) + frcv(jpr_itx1)%z3(ji-1,jj-1,1) )
1507                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji  ,jj-1,1) + frcv(jpr_ity1)%z3(ji-1,jj-1,1) )
1508                  END DO
1509               END DO
1510            CASE( 'F' )
1511               DO jj = 2, jpjm1                                   ! F ==> I
1512                  DO ji = 2, jpim1   ! NO vector opt.
1513                     p_taui(ji,jj) = frcv(jpr_itx1)%z3(ji-1,jj-1,1)
1514                     p_tauj(ji,jj) = frcv(jpr_ity1)%z3(ji-1,jj-1,1)
1515                  END DO
1516               END DO
1517            CASE( 'T' )
1518               DO jj = 2, jpjm1                                   ! T ==> I
1519                  DO ji = 2, jpim1   ! NO vector opt.
1520                     p_taui(ji,jj) = 0.25 * ( frcv(jpr_itx1)%z3(ji,jj  ,1) + frcv(jpr_itx1)%z3(ji-1,jj  ,1)   &
1521                        &                   + frcv(jpr_itx1)%z3(ji,jj-1,1) + frcv(jpr_itx1)%z3(ji-1,jj-1,1) ) 
1522                     p_tauj(ji,jj) = 0.25 * ( frcv(jpr_ity1)%z3(ji,jj  ,1) + frcv(jpr_ity1)%z3(ji-1,jj  ,1)   &
1523                        &                   + frcv(jpr_oty1)%z3(ji,jj-1,1) + frcv(jpr_ity1)%z3(ji-1,jj-1,1) )
1524                  END DO
1525               END DO
1526            CASE( 'I' )
1527               p_taui(:,:) = frcv(jpr_itx1)%z3(:,:,1)                   ! I ==> I
1528               p_tauj(:,:) = frcv(jpr_ity1)%z3(:,:,1)
1529            END SELECT
1530            IF( srcv(jpr_itx1)%clgrid /= 'I' ) THEN
1531               CALL lbc_lnk( p_taui, 'I',  -1. )   ;   CALL lbc_lnk( p_tauj, 'I',  -1. )
1532            ENDIF
1533            !
1534         CASE( 'F' )                                         ! B-grid ==> F
1535            SELECT CASE ( srcv(jpr_itx1)%clgrid )
1536            CASE( 'U' )
1537               DO jj = 2, jpjm1                                   ! (U,V) ==> F
1538                  DO ji = fs_2, fs_jpim1   ! vector opt.
1539                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji,jj,1) + frcv(jpr_itx1)%z3(ji  ,jj+1,1) )
1540                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji,jj,1) + frcv(jpr_ity1)%z3(ji+1,jj  ,1) )
1541                  END DO
1542               END DO
1543            CASE( 'I' )
1544               DO jj = 2, jpjm1                                   ! I ==> F
1545                  DO ji = 2, jpim1   ! NO vector opt.
1546                     p_taui(ji,jj) = frcv(jpr_itx1)%z3(ji+1,jj+1,1)
1547                     p_tauj(ji,jj) = frcv(jpr_ity1)%z3(ji+1,jj+1,1)
1548                  END DO
1549               END DO
1550            CASE( 'T' )
1551               DO jj = 2, jpjm1                                   ! T ==> F
1552                  DO ji = 2, jpim1   ! NO vector opt.
1553                     p_taui(ji,jj) = 0.25 * ( frcv(jpr_itx1)%z3(ji,jj  ,1) + frcv(jpr_itx1)%z3(ji+1,jj  ,1)   &
1554                        &                   + frcv(jpr_itx1)%z3(ji,jj+1,1) + frcv(jpr_itx1)%z3(ji+1,jj+1,1) ) 
1555                     p_tauj(ji,jj) = 0.25 * ( frcv(jpr_ity1)%z3(ji,jj  ,1) + frcv(jpr_ity1)%z3(ji+1,jj  ,1)   &
1556                        &                   + frcv(jpr_ity1)%z3(ji,jj+1,1) + frcv(jpr_ity1)%z3(ji+1,jj+1,1) )
1557                  END DO
1558               END DO
1559            CASE( 'F' )
1560               p_taui(:,:) = frcv(jpr_itx1)%z3(:,:,1)                   ! F ==> F
1561               p_tauj(:,:) = frcv(jpr_ity1)%z3(:,:,1)
1562            END SELECT
1563            IF( srcv(jpr_itx1)%clgrid /= 'F' ) THEN
1564               CALL lbc_lnk( p_taui, 'F',  -1. )   ;   CALL lbc_lnk( p_tauj, 'F',  -1. )
1565            ENDIF
1566            !
1567         CASE( 'C' )                                         ! C-grid ==> U,V
1568            SELECT CASE ( srcv(jpr_itx1)%clgrid )
1569            CASE( 'U' )
1570               p_taui(:,:) = frcv(jpr_itx1)%z3(:,:,1)                   ! (U,V) ==> (U,V)
1571               p_tauj(:,:) = frcv(jpr_ity1)%z3(:,:,1)
1572            CASE( 'F' )
1573               DO jj = 2, jpjm1                                   ! F ==> (U,V)
1574                  DO ji = fs_2, fs_jpim1   ! vector opt.
1575                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji,jj,1) + frcv(jpr_itx1)%z3(ji  ,jj-1,1) )
1576                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(jj,jj,1) + frcv(jpr_ity1)%z3(ji-1,jj  ,1) )
1577                  END DO
1578               END DO
1579            CASE( 'T' )
1580               DO jj = 2, jpjm1                                   ! T ==> (U,V)
1581                  DO ji = fs_2, fs_jpim1   ! vector opt.
1582                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji+1,jj  ,1) + frcv(jpr_itx1)%z3(ji,jj,1) )
1583                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji  ,jj+1,1) + frcv(jpr_ity1)%z3(ji,jj,1) )
1584                  END DO
1585               END DO
1586            CASE( 'I' )
1587               DO jj = 2, jpjm1                                   ! I ==> (U,V)
1588                  DO ji = 2, jpim1   ! NO vector opt.
1589                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji+1,jj+1,1) + frcv(jpr_itx1)%z3(ji+1,jj  ,1) )
1590                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji+1,jj+1,1) + frcv(jpr_ity1)%z3(ji  ,jj+1,1) )
1591                  END DO
1592               END DO
1593            END SELECT
1594            IF( srcv(jpr_itx1)%clgrid /= 'U' ) THEN
1595               CALL lbc_lnk( p_taui, 'U',  -1. )   ;   CALL lbc_lnk( p_tauj, 'V',  -1. )
1596            ENDIF
1597         END SELECT
1598
1599      ENDIF
1600      !   
1601      CALL wrk_dealloc( jpi,jpj, ztx, zty )
1602      !
1603      IF( nn_timing == 1 )  CALL timing_stop('sbc_cpl_ice_tau')
1604      !
1605   END SUBROUTINE sbc_cpl_ice_tau
1606   
1607
1608   SUBROUTINE sbc_cpl_ice_flx( p_frld, palbi, psst, pist )
1609      !!----------------------------------------------------------------------
1610      !!             ***  ROUTINE sbc_cpl_ice_flx  ***
1611      !!
1612      !! ** Purpose :   provide the heat and freshwater fluxes of the
1613      !!              ocean-ice system.
1614      !!
1615      !! ** Method  :   transform the fields received from the atmosphere into
1616      !!             surface heat and fresh water boundary condition for the
1617      !!             ice-ocean system. The following fields are provided:
1618      !!              * total non solar, solar and freshwater fluxes (qns_tot,
1619      !!             qsr_tot and emp_tot) (total means weighted ice-ocean flux)
1620      !!             NB: emp_tot include runoffs and calving.
1621      !!              * fluxes over ice (qns_ice, qsr_ice, emp_ice) where
1622      !!             emp_ice = sublimation - solid precipitation as liquid
1623      !!             precipitation are re-routed directly to the ocean and
1624      !!             runoffs and calving directly enter the ocean.
1625      !!              * solid precipitation (sprecip), used to add to qns_tot
1626      !!             the heat lost associated to melting solid precipitation
1627      !!             over the ocean fraction.
1628      !!       ===>> CAUTION here this changes the net heat flux received from
1629      !!             the atmosphere
1630      !!
1631      !!                  - the fluxes have been separated from the stress as
1632      !!                 (a) they are updated at each ice time step compare to
1633      !!                 an update at each coupled time step for the stress, and
1634      !!                 (b) the conservative computation of the fluxes over the
1635      !!                 sea-ice area requires the knowledge of the ice fraction
1636      !!                 after the ice advection and before the ice thermodynamics,
1637      !!                 so that the stress is updated before the ice dynamics
1638      !!                 while the fluxes are updated after it.
1639      !!
1640      !! ** Action  :   update at each nf_ice time step:
1641      !!                   qns_tot, qsr_tot  non-solar and solar total heat fluxes
1642      !!                   qns_ice, qsr_ice  non-solar and solar heat fluxes over the ice
1643      !!                   emp_tot            total evaporation - precipitation(liquid and solid) (-runoff)(-calving)
1644      !!                   emp_ice            ice sublimation - solid precipitation over the ice
1645      !!                   dqns_ice           d(non-solar heat flux)/d(Temperature) over the ice
1646      !!                   sprecip             solid precipitation over the ocean 
1647      !!----------------------------------------------------------------------
1648      REAL(wp), INTENT(in   ), DIMENSION(:,:)   ::   p_frld     ! lead fraction                [0 to 1]
1649      ! optional arguments, used only in 'mixed oce-ice' case
1650      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   palbi      ! all skies ice albedo
1651      REAL(wp), INTENT(in   ), DIMENSION(:,:  ), OPTIONAL ::   psst       ! sea surface temperature     [Celsius]
1652      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   pist       ! ice surface temperature     [Kelvin]
1653      !
1654      INTEGER ::   jl         ! dummy loop index
1655      REAL(wp), POINTER, DIMENSION(:,:  ) ::   zcptn, ztmp, zicefr, zmsk
1656      REAL(wp), POINTER, DIMENSION(:,:  ) ::   zemp_tot, zemp_ice, zsprecip, ztprecip, zqns_tot, zqsr_tot
1657      REAL(wp), POINTER, DIMENSION(:,:,:) ::   zqns_ice, zqsr_ice, zdqns_ice
1658      REAL(wp), POINTER, DIMENSION(:,:  ) ::   zevap, zsnw, zqns_oce, zqsr_oce, zqprec_ice, zqemp_oce ! for LIM3
1659      !!----------------------------------------------------------------------
1660      !
1661      IF( nn_timing == 1 )  CALL timing_start('sbc_cpl_ice_flx')
1662      !
1663      CALL wrk_alloc( jpi,jpj,     zcptn, ztmp, zicefr, zmsk, zemp_tot, zemp_ice, zsprecip, ztprecip, zqns_tot, zqsr_tot )
1664      CALL wrk_alloc( jpi,jpj,jpl, zqns_ice, zqsr_ice, zdqns_ice )
1665
1666      IF( ln_mixcpl )   zmsk(:,:) = 1. - xcplmask(:,:,0)
1667      zicefr(:,:) = 1.- p_frld(:,:)
1668      zcptn(:,:) = rcp * sst_m(:,:)
1669      !
1670      !                                                      ! ========================= !
1671      !                                                      !    freshwater budget      !   (emp)
1672      !                                                      ! ========================= !
1673      !
1674      !                                                           ! total Precipitation - total Evaporation (emp_tot)
1675      !                                                           ! solid precipitation - sublimation       (emp_ice)
1676      !                                                           ! solid Precipitation                     (sprecip)
1677      !                                                           ! liquid + solid Precipitation            (tprecip)
1678      SELECT CASE( TRIM( sn_rcv_emp%cldes ) )
1679      CASE( 'conservative'  )   ! received fields: jpr_rain, jpr_snow, jpr_ievp, jpr_tevp
1680         zsprecip(:,:) = frcv(jpr_snow)%z3(:,:,1)                  ! May need to ensure positive here
1681         ztprecip(:,:) = frcv(jpr_rain)%z3(:,:,1) + zsprecip(:,:)  ! May need to ensure positive here
1682         zemp_tot(:,:) = frcv(jpr_tevp)%z3(:,:,1) - ztprecip(:,:)         
1683#if defined key_cice
1684         IF ( TRIM(sn_rcv_emp%clcat) == 'yes' ) THEN
1685            ! zemp_ice is the sum of frcv(jpr_ievp)%z3(:,:,1) over all layers - snow
1686            zemp_ice(:,:) = - frcv(jpr_snow)%z3(:,:,1)
1687            DO jl=1,jpl
1688               zemp_ice(:,:   ) = zemp_ice(:,:) + frcv(jpr_ievp)%z3(:,:,jl)
1689            ENDDO
1690            ! latent heat coupled for each category in CICE
1691            qla_ice(:,:,1:jpl) = - frcv(jpr_ievp)%z3(:,:,1:jpl) * lsub
1692         ELSE
1693            ! If CICE has multicategories it still expects coupling fields for
1694            ! each even if we treat as a single field
1695            ! The latent heat flux is split between the ice categories according
1696            ! to the fraction of the ice in each category
1697            zemp_ice(:,:) = frcv(jpr_ievp)%z3(:,:,1) - frcv(jpr_snow)%z3(:,:,1)
1698            WHERE ( zicefr(:,:) /= 0._wp ) 
1699               ztmp(:,:) = 1./zicefr(:,:)
1700            ELSEWHERE 
1701               ztmp(:,:) = 0.e0
1702            END WHERE 
1703            DO jl=1,jpl
1704               qla_ice(:,:,jl) = - a_i(:,:,jl) * ztmp(:,:) * frcv(jpr_ievp)%z3(:,:,1) * lsub 
1705            END DO
1706            WHERE ( zicefr(:,:) == 0._wp )  qla_ice(:,:,1) = -frcv(jpr_ievp)%z3(:,:,1) * lsub 
1707         ENDIF
1708#else         
1709         zemp_ice(:,:) = frcv(jpr_ievp)%z3(:,:,1) - frcv(jpr_snow)%z3(:,:,1)
1710#endif                 
1711            CALL iom_put( 'rain'         , frcv(jpr_rain)%z3(:,:,1)              )   ! liquid precipitation
1712         IF( iom_use('hflx_rain_cea') )   &
1713            CALL iom_put( 'hflx_rain_cea', frcv(jpr_rain)%z3(:,:,1) * zcptn(:,:) )   ! heat flux from liq. precip.
1714         IF( iom_use('evap_ao_cea') .OR. iom_use('hflx_evap_cea') )   &
1715            ztmp(:,:) = frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:)
1716         IF( iom_use('evap_ao_cea'  ) )   &
1717            CALL iom_put( 'evap_ao_cea'  , ztmp                   )   ! ice-free oce evap (cell average)
1718         IF( iom_use('hflx_evap_cea') )   &
1719            CALL iom_put( 'hflx_evap_cea', ztmp(:,:) * zcptn(:,:) )   ! heat flux from from evap (cell average)
1720      CASE( 'oce and ice'   )   ! received fields: jpr_sbpr, jpr_semp, jpr_oemp, jpr_ievp
1721         zemp_tot(:,:) = p_frld(:,:) * frcv(jpr_oemp)%z3(:,:,1) + zicefr(:,:) * frcv(jpr_sbpr)%z3(:,:,1)
1722         zemp_ice(:,:) = frcv(jpr_semp)%z3(:,:,1)
1723         zsprecip(:,:) = frcv(jpr_ievp)%z3(:,:,1) - frcv(jpr_semp)%z3(:,:,1)
1724         ztprecip(:,:) = frcv(jpr_semp)%z3(:,:,1) - frcv(jpr_sbpr)%z3(:,:,1) + zsprecip(:,:)
1725      END SELECT
1726
1727      IF( iom_use('subl_ai_cea') )   &
1728         CALL iom_put( 'subl_ai_cea', frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) )   ! Sublimation over sea-ice         (cell average)
1729      !   
1730      !                                                           ! runoffs and calving (put in emp_tot)
1731      IF( srcv(jpr_rnf)%laction )   rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1)
1732      IF( srcv(jpr_cal)%laction ) THEN
1733         zemp_tot(:,:) = zemp_tot(:,:) - frcv(jpr_cal)%z3(:,:,1)
1734         CALL iom_put( 'calving_cea', frcv(jpr_cal)%z3(:,:,1) )
1735      ENDIF
1736
1737      IF( ln_mixcpl ) THEN
1738         emp_tot(:,:) = emp_tot(:,:) * xcplmask(:,:,0) + zemp_tot(:,:) * zmsk(:,:)
1739         emp_ice(:,:) = emp_ice(:,:) * xcplmask(:,:,0) + zemp_ice(:,:) * zmsk(:,:)
1740         sprecip(:,:) = sprecip(:,:) * xcplmask(:,:,0) + zsprecip(:,:) * zmsk(:,:)
1741         tprecip(:,:) = tprecip(:,:) * xcplmask(:,:,0) + ztprecip(:,:) * zmsk(:,:)
1742      ELSE
1743         emp_tot(:,:) =                                  zemp_tot(:,:)
1744         emp_ice(:,:) =                                  zemp_ice(:,:)
1745         sprecip(:,:) =                                  zsprecip(:,:)
1746         tprecip(:,:) =                                  ztprecip(:,:)
1747      ENDIF
1748
1749         CALL iom_put( 'snowpre'    , sprecip                                )   ! Snow
1750      IF( iom_use('snow_ao_cea') )   &
1751         CALL iom_put( 'snow_ao_cea', sprecip(:,:) * p_frld(:,:)             )   ! Snow        over ice-free ocean  (cell average)
1752      IF( iom_use('snow_ai_cea') )   &
1753         CALL iom_put( 'snow_ai_cea', sprecip(:,:) * zicefr(:,:)             )   ! Snow        over sea-ice         (cell average)
1754
1755      !                                                      ! ========================= !
1756      SELECT CASE( TRIM( sn_rcv_qns%cldes ) )                !   non solar heat fluxes   !   (qns)
1757      !                                                      ! ========================= !
1758      CASE( 'oce only' )                                     ! the required field is directly provided
1759         zqns_tot(:,:  ) = frcv(jpr_qnsoce)%z3(:,:,1)
1760      CASE( 'conservative' )                                      ! the required fields are directly provided
1761         zqns_tot(:,:  ) = frcv(jpr_qnsmix)%z3(:,:,1)
1762         IF ( TRIM(sn_rcv_qns%clcat) == 'yes' ) THEN
1763            zqns_ice(:,:,1:jpl) = frcv(jpr_qnsice)%z3(:,:,1:jpl)
1764         ELSE
1765            ! Set all category values equal for the moment
1766            DO jl=1,jpl
1767               zqns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,1)
1768            ENDDO
1769         ENDIF
1770      CASE( 'oce and ice' )       ! the total flux is computed from ocean and ice fluxes
1771         zqns_tot(:,:  ) =  p_frld(:,:) * frcv(jpr_qnsoce)%z3(:,:,1)
1772         IF ( TRIM(sn_rcv_qns%clcat) == 'yes' ) THEN
1773            DO jl=1,jpl
1774               zqns_tot(:,:   ) = zqns_tot(:,:) + a_i(:,:,jl) * frcv(jpr_qnsice)%z3(:,:,jl)   
1775               zqns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,jl)
1776            ENDDO
1777         ELSE
1778            qns_tot(:,:   ) = qns_tot(:,:) + zicefr(:,:) * frcv(jpr_qnsice)%z3(:,:,1)
1779            DO jl=1,jpl
1780               zqns_tot(:,:   ) = zqns_tot(:,:) + zicefr(:,:) * frcv(jpr_qnsice)%z3(:,:,1)
1781               zqns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,1)
1782            ENDDO
1783         ENDIF
1784      CASE( 'mixed oce-ice' )     ! the ice flux is cumputed from the total flux, the SST and ice informations
1785! ** NEED TO SORT OUT HOW THIS SHOULD WORK IN THE MULTI-CATEGORY CASE - CURRENTLY NOT ALLOWED WHEN INTERFACE INITIALISED **
1786         zqns_tot(:,:  ) = frcv(jpr_qnsmix)%z3(:,:,1)
1787         zqns_ice(:,:,1) = frcv(jpr_qnsmix)%z3(:,:,1)    &
1788            &            + frcv(jpr_dqnsdt)%z3(:,:,1) * ( pist(:,:,1) - ( (rt0 + psst(:,:  ) ) * p_frld(:,:)   &
1789            &                                                   +          pist(:,:,1)   * zicefr(:,:) ) )
1790      END SELECT
1791!!gm
1792!!    currently it is taken into account in leads budget but not in the zqns_tot, and thus not in
1793!!    the flux that enter the ocean....
1794!!    moreover 1 - it is not diagnose anywhere....
1795!!             2 - it is unclear for me whether this heat lost is taken into account in the atmosphere or not...
1796!!
1797!! similar job should be done for snow and precipitation temperature
1798      !                                     
1799      IF( srcv(jpr_cal)%laction ) THEN                            ! Iceberg melting
1800         ztmp(:,:) = frcv(jpr_cal)%z3(:,:,1) * lfus               ! add the latent heat of iceberg melting
1801         zqns_tot(:,:) = zqns_tot(:,:) - ztmp(:,:)
1802         IF( iom_use('hflx_cal_cea') )   &
1803            CALL iom_put( 'hflx_cal_cea', ztmp + frcv(jpr_cal)%z3(:,:,1) * zcptn(:,:) )   ! heat flux from calving
1804      ENDIF
1805
1806      ztmp(:,:) = p_frld(:,:) * zsprecip(:,:) * lfus
1807      IF( iom_use('hflx_snow_cea') )    CALL iom_put( 'hflx_snow_cea', ztmp + sprecip(:,:) * zcptn(:,:) )   ! heat flux from snow (cell average)
1808
1809#if defined key_lim3
1810      CALL wrk_alloc( jpi,jpj, zevap, zsnw, zqns_oce, zqprec_ice, zqemp_oce ) 
1811
1812      ! --- evaporation --- !
1813      ! clem: evap_ice is set to 0 for LIM3 since we still do not know what to do with sublimation
1814      ! the problem is: the atm. imposes both mass evaporation and heat removed from the snow/ice
1815      !                 but it is incoherent WITH the ice model 
1816      DO jl=1,jpl
1817         evap_ice(:,:,jl) = 0._wp  ! should be: frcv(jpr_ievp)%z3(:,:,1)
1818      ENDDO
1819      zevap(:,:) = zemp_tot(:,:) + ztprecip(:,:) ! evaporation over ocean
1820
1821      ! --- evaporation minus precipitation --- !
1822      emp_oce(:,:) = emp_tot(:,:) - emp_ice(:,:)
1823
1824      ! --- non solar flux over ocean --- !
1825      !         note: p_frld cannot be = 0 since we limit the ice concentration to amax
1826      zqns_oce = 0._wp
1827      WHERE( p_frld /= 0._wp )  zqns_oce(:,:) = ( zqns_tot(:,:) - SUM( a_i * zqns_ice, dim=3 ) ) / p_frld(:,:)
1828
1829      ! --- heat flux associated with emp --- !
1830      zsnw(:,:) = 0._wp
1831      CALL lim_thd_snwblow( p_frld, zsnw )  ! snow distribution over ice after wind blowing
1832      zqemp_oce(:,:) = -      zevap(:,:)                   * p_frld(:,:)      *   zcptn(:,:)   &      ! evap
1833         &             + ( ztprecip(:,:) - zsprecip(:,:) )                    *   zcptn(:,:)   &      ! liquid precip
1834         &             +   zsprecip(:,:)                   * ( 1._wp - zsnw ) * ( zcptn(:,:) - lfus ) ! solid precip over ocean
1835      qemp_ice(:,:)  = -   frcv(jpr_ievp)%z3(:,:,1)        * zicefr(:,:)      *   zcptn(:,:)   &      ! ice evap
1836         &             +   zsprecip(:,:)                   * zsnw             * ( zcptn(:,:) - lfus ) ! solid precip over ice
1837
1838      ! --- heat content of precip over ice in J/m3 (to be used in 1D-thermo) --- !
1839      zqprec_ice(:,:) = rhosn * ( zcptn(:,:) - lfus )
1840
1841      ! --- total non solar flux --- !
1842      zqns_tot(:,:) = zqns_tot(:,:) + qemp_ice(:,:) + zqemp_oce(:,:)
1843
1844      ! --- in case both coupled/forced are active, we must mix values --- !
1845      IF( ln_mixcpl ) THEN
1846         qns_tot(:,:) = qns_tot(:,:) * xcplmask(:,:,0) + zqns_tot(:,:)* zmsk(:,:)
1847         qns_oce(:,:) = qns_oce(:,:) * xcplmask(:,:,0) + zqns_oce(:,:)* zmsk(:,:)
1848         DO jl=1,jpl
1849            qns_ice(:,:,jl) = qns_ice(:,:,jl) * xcplmask(:,:,0) +  zqns_ice(:,:,jl)* zmsk(:,:)
1850         ENDDO
1851         qprec_ice(:,:) = qprec_ice(:,:) * xcplmask(:,:,0) + zqprec_ice(:,:)* zmsk(:,:)
1852         qemp_oce (:,:) =  qemp_oce(:,:) * xcplmask(:,:,0) +  zqemp_oce(:,:)* zmsk(:,:)
1853!!clem         evap_ice(:,:) = evap_ice(:,:) * xcplmask(:,:,0)
1854      ELSE
1855         qns_tot  (:,:  ) = zqns_tot  (:,:  )
1856         qns_oce  (:,:  ) = zqns_oce  (:,:  )
1857         qns_ice  (:,:,:) = zqns_ice  (:,:,:)
1858         qprec_ice(:,:)   = zqprec_ice(:,:)
1859         qemp_oce (:,:)   = zqemp_oce (:,:)
1860      ENDIF
1861
1862      CALL wrk_dealloc( jpi,jpj, zevap, zsnw, zqns_oce, zqprec_ice, zqemp_oce ) 
1863#else
1864
1865      ! clem: this formulation is certainly wrong... but better than it was...
1866      zqns_tot(:,:) = zqns_tot(:,:)                       &            ! zqns_tot update over free ocean with:
1867         &          - ztmp(:,:)                           &            ! remove the latent heat flux of solid precip. melting
1868         &          - (  zemp_tot(:,:)                    &            ! remove the heat content of mass flux (assumed to be at SST)
1869         &             - zemp_ice(:,:) * zicefr(:,:)  ) * zcptn(:,:) 
1870
1871     IF( ln_mixcpl ) THEN
1872         qns_tot(:,:) = qns(:,:) * p_frld(:,:) + SUM( qns_ice(:,:,:) * a_i(:,:,:), dim=3 )   ! total flux from blk
1873         qns_tot(:,:) = qns_tot(:,:) * xcplmask(:,:,0) +  zqns_tot(:,:)* zmsk(:,:)
1874         DO jl=1,jpl
1875            qns_ice(:,:,jl) = qns_ice(:,:,jl) * xcplmask(:,:,0) +  zqns_ice(:,:,jl)* zmsk(:,:)
1876         ENDDO
1877      ELSE
1878         qns_tot(:,:  ) = zqns_tot(:,:  )
1879         qns_ice(:,:,:) = zqns_ice(:,:,:)
1880      ENDIF
1881
1882#endif
1883
1884      !                                                      ! ========================= !
1885      SELECT CASE( TRIM( sn_rcv_qsr%cldes ) )                !      solar heat fluxes    !   (qsr)
1886      !                                                      ! ========================= !
1887      CASE( 'oce only' )
1888         zqsr_tot(:,:  ) = MAX( 0._wp , frcv(jpr_qsroce)%z3(:,:,1) )
1889      CASE( 'conservative' )
1890         zqsr_tot(:,:  ) = frcv(jpr_qsrmix)%z3(:,:,1)
1891         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN
1892            zqsr_ice(:,:,1:jpl) = frcv(jpr_qsrice)%z3(:,:,1:jpl)
1893         ELSE
1894            ! Set all category values equal for the moment
1895            DO jl=1,jpl
1896               zqsr_ice(:,:,jl) = frcv(jpr_qsrice)%z3(:,:,1)
1897            ENDDO
1898         ENDIF
1899         zqsr_tot(:,:  ) = frcv(jpr_qsrmix)%z3(:,:,1)
1900         zqsr_ice(:,:,1) = frcv(jpr_qsrice)%z3(:,:,1)
1901      CASE( 'oce and ice' )
1902         zqsr_tot(:,:  ) =  p_frld(:,:) * frcv(jpr_qsroce)%z3(:,:,1)
1903         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN
1904            DO jl=1,jpl
1905               zqsr_tot(:,:   ) = zqsr_tot(:,:) + a_i(:,:,jl) * frcv(jpr_qsrice)%z3(:,:,jl)   
1906               zqsr_ice(:,:,jl) = frcv(jpr_qsrice)%z3(:,:,jl)
1907            ENDDO
1908         ELSE
1909            qsr_tot(:,:   ) = qsr_tot(:,:) + zicefr(:,:) * frcv(jpr_qsrice)%z3(:,:,1)
1910            DO jl=1,jpl
1911               zqsr_tot(:,:   ) = zqsr_tot(:,:) + zicefr(:,:) * frcv(jpr_qsrice)%z3(:,:,1)
1912               zqsr_ice(:,:,jl) = frcv(jpr_qsrice)%z3(:,:,1)
1913            ENDDO
1914         ENDIF
1915      CASE( 'mixed oce-ice' )
1916         zqsr_tot(:,:  ) = frcv(jpr_qsrmix)%z3(:,:,1)
1917! ** NEED TO SORT OUT HOW THIS SHOULD WORK IN THE MULTI-CATEGORY CASE - CURRENTLY NOT ALLOWED WHEN INTERFACE INITIALISED **
1918!       Create solar heat flux over ice using incoming solar heat flux and albedos
1919!       ( see OASIS3 user guide, 5th edition, p39 )
1920         zqsr_ice(:,:,1) = frcv(jpr_qsrmix)%z3(:,:,1) * ( 1.- palbi(:,:,1) )   &
1921            &            / (  1.- ( albedo_oce_mix(:,:  ) * p_frld(:,:)       &
1922            &                     + palbi         (:,:,1) * zicefr(:,:) ) )
1923      END SELECT
1924      IF( ln_dm2dc .AND. ln_cpl ) THEN   ! modify qsr to include the diurnal cycle
1925         zqsr_tot(:,:  ) = sbc_dcy( zqsr_tot(:,:  ) )
1926         DO jl=1,jpl
1927            zqsr_ice(:,:,jl) = sbc_dcy( zqsr_ice(:,:,jl) )
1928         ENDDO
1929      ENDIF
1930
1931#if defined key_lim3
1932      CALL wrk_alloc( jpi,jpj, zqsr_oce ) 
1933      ! --- solar flux over ocean --- !
1934      !         note: p_frld cannot be = 0 since we limit the ice concentration to amax
1935      zqsr_oce = 0._wp
1936      WHERE( p_frld /= 0._wp )  zqsr_oce(:,:) = ( zqsr_tot(:,:) - SUM( a_i * zqsr_ice, dim=3 ) ) / p_frld(:,:)
1937
1938      IF( ln_mixcpl ) THEN   ;   qsr_oce(:,:) = qsr_oce(:,:) * xcplmask(:,:,0) +  zqsr_oce(:,:)* zmsk(:,:)
1939      ELSE                   ;   qsr_oce(:,:) = zqsr_oce(:,:)   ;   ENDIF
1940
1941      CALL wrk_dealloc( jpi,jpj, zqsr_oce ) 
1942#endif
1943
1944      IF( ln_mixcpl ) THEN
1945         qsr_tot(:,:) = qsr(:,:) * p_frld(:,:) + SUM( qsr_ice(:,:,:) * a_i(:,:,:), dim=3 )   ! total flux from blk
1946         qsr_tot(:,:) = qsr_tot(:,:) * xcplmask(:,:,0) +  zqsr_tot(:,:)* zmsk(:,:)
1947         DO jl=1,jpl
1948            qsr_ice(:,:,jl) = qsr_ice(:,:,jl) * xcplmask(:,:,0) +  zqsr_ice(:,:,jl)* zmsk(:,:)
1949         ENDDO
1950      ELSE
1951         qsr_tot(:,:  ) = zqsr_tot(:,:  )
1952         qsr_ice(:,:,:) = zqsr_ice(:,:,:)
1953      ENDIF
1954
1955      !                                                      ! ========================= !
1956      SELECT CASE( TRIM( sn_rcv_dqnsdt%cldes ) )             !          d(qns)/dt        !
1957      !                                                      ! ========================= !
1958      CASE ('coupled')
1959         IF ( TRIM(sn_rcv_dqnsdt%clcat) == 'yes' ) THEN
1960            zdqns_ice(:,:,1:jpl) = frcv(jpr_dqnsdt)%z3(:,:,1:jpl)
1961         ELSE
1962            ! Set all category values equal for the moment
1963            DO jl=1,jpl
1964               zdqns_ice(:,:,jl) = frcv(jpr_dqnsdt)%z3(:,:,1)
1965            ENDDO
1966         ENDIF
1967      END SELECT
1968     
1969      IF( ln_mixcpl ) THEN
1970         DO jl=1,jpl
1971            dqns_ice(:,:,jl) = dqns_ice(:,:,jl) * xcplmask(:,:,0) + zdqns_ice(:,:,jl) * zmsk(:,:)
1972         ENDDO
1973      ELSE
1974         dqns_ice(:,:,:) = zdqns_ice(:,:,:)
1975      ENDIF
1976     
1977      !                                                      ! ========================= !
1978      SELECT CASE( TRIM( sn_rcv_iceflx%cldes ) )             !    topmelt and botmelt    !
1979      !                                                      ! ========================= !
1980      CASE ('coupled')
1981         topmelt(:,:,:)=frcv(jpr_topm)%z3(:,:,:)
1982         botmelt(:,:,:)=frcv(jpr_botm)%z3(:,:,:)
1983      END SELECT
1984
1985      ! Surface transimission parameter io (Maykut Untersteiner , 1971 ; Ebert and Curry, 1993 )
1986      ! Used for LIM2 and LIM3
1987      ! Coupled case: since cloud cover is not received from atmosphere
1988      !               ===> used prescribed cloud fraction representative for polar oceans in summer (0.81)
1989      fr1_i0(:,:) = ( 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice )
1990      fr2_i0(:,:) = ( 0.82 * ( 1.0 - cldf_ice ) + 0.65 * cldf_ice )
1991
1992      CALL wrk_dealloc( jpi,jpj,     zcptn, ztmp, zicefr, zmsk, zemp_tot, zemp_ice, zsprecip, ztprecip, zqns_tot, zqsr_tot )
1993      CALL wrk_dealloc( jpi,jpj,jpl, zqns_ice, zqsr_ice, zdqns_ice )
1994      !
1995      IF( nn_timing == 1 )  CALL timing_stop('sbc_cpl_ice_flx')
1996      !
1997   END SUBROUTINE sbc_cpl_ice_flx
1998   
1999   
2000   SUBROUTINE sbc_cpl_snd( kt )
2001      !!----------------------------------------------------------------------
2002      !!             ***  ROUTINE sbc_cpl_snd  ***
2003      !!
2004      !! ** Purpose :   provide the ocean-ice informations to the atmosphere
2005      !!
2006      !! ** Method  :   send to the atmosphere through a call to cpl_snd
2007      !!              all the needed fields (as defined in sbc_cpl_init)
2008      !!----------------------------------------------------------------------
2009      INTEGER, INTENT(in) ::   kt
2010      !
2011      INTEGER ::   ji, jj, jl   ! dummy loop indices
2012      INTEGER ::   isec, info   ! local integer
2013      REAL(wp) ::   zumax, zvmax
2014      REAL(wp), POINTER, DIMENSION(:,:)   ::   zfr_l, ztmp1, ztmp2, zotx1, zoty1, zotz1, zitx1, zity1, zitz1
2015      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztmp3, ztmp4   
2016      !!----------------------------------------------------------------------
2017      !
2018      IF( nn_timing == 1 )  CALL timing_start('sbc_cpl_snd')
2019      !
2020      CALL wrk_alloc( jpi,jpj, zfr_l, ztmp1, ztmp2, zotx1, zoty1, zotz1, zitx1, zity1, zitz1 )
2021      CALL wrk_alloc( jpi,jpj,jpl, ztmp3, ztmp4 )
2022
2023      isec = ( kt - nit000 ) * NINT(rdttra(1))        ! date of exchanges
2024
2025      zfr_l(:,:) = 1.- fr_i(:,:)
2026      !                                                      ! ------------------------- !
2027      !                                                      !    Surface temperature    !   in Kelvin
2028      !                                                      ! ------------------------- !
2029      IF( ssnd(jps_toce)%laction .OR. ssnd(jps_tice)%laction .OR. ssnd(jps_tmix)%laction ) THEN
2030         
2031         IF ( nn_components == jp_iam_opa ) THEN
2032            ztmp1(:,:) = tsn(:,:,1,jp_tem)   ! send temperature as it is (potential or conservative) -> use of ln_useCT on the received part
2033         ELSE
2034            ! we must send the surface potential temperature
2035            IF( ln_useCT )  THEN    ;   ztmp1(:,:) = eos_pt_from_ct( tsn(:,:,1,jp_tem), tsn(:,:,1,jp_sal) )
2036            ELSE                    ;   ztmp1(:,:) = tsn(:,:,1,jp_tem)
2037            ENDIF
2038            !
2039            SELECT CASE( sn_snd_temp%cldes)
2040            CASE( 'oce only'             )   ;   ztmp1(:,:) =   ztmp1(:,:) + rt0
2041            CASE( 'oce and ice'          )   ;   ztmp1(:,:) =   ztmp1(:,:) + rt0
2042               SELECT CASE( sn_snd_temp%clcat )
2043               CASE( 'yes' )   
2044                  ztmp3(:,:,1:jpl) = tn_ice(:,:,1:jpl)
2045               CASE( 'no' )
2046                  WHERE( SUM( a_i, dim=3 ) /= 0. )
2047                     ztmp3(:,:,1) = SUM( tn_ice * a_i, dim=3 ) / SUM( a_i, dim=3 )
2048                  ELSEWHERE
2049                     ztmp3(:,:,1) = rt0 ! TODO: Is freezing point a good default? (Maybe SST is better?)
2050                  END WHERE
2051               CASE default   ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%clcat' )
2052               END SELECT
2053            CASE( 'weighted oce and ice' )   ;   ztmp1(:,:) = ( ztmp1(:,:) + rt0 ) * zfr_l(:,:)   
2054               SELECT CASE( sn_snd_temp%clcat )
2055               CASE( 'yes' )   
2056                  ztmp3(:,:,1:jpl) = tn_ice(:,:,1:jpl) * a_i(:,:,1:jpl)
2057               CASE( 'no' )
2058                  ztmp3(:,:,:) = 0.0
2059                  DO jl=1,jpl
2060                     ztmp3(:,:,1) = ztmp3(:,:,1) + tn_ice(:,:,jl) * a_i(:,:,jl)
2061                  ENDDO
2062               CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%clcat' )
2063               END SELECT
2064            CASE( 'oce and weighted ice' )   ;   ztmp1(:,:) =   tsn(:,:,1,jp_tem) + rt0 
2065               SELECT CASE( sn_snd_temp%clcat )
2066               CASE( 'yes' )   
2067           ztmp3(:,:,1:jpl) = tn_ice(:,:,1:jpl) * a_i(:,:,1:jpl)
2068               CASE( 'no' )
2069           ztmp3(:,:,:) = 0.0
2070           DO jl=1,jpl
2071                     ztmp3(:,:,1) = ztmp3(:,:,1) + tn_ice(:,:,jl) * a_i(:,:,jl)
2072           ENDDO
2073               CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%clcat' )
2074               END SELECT
2075            CASE( 'mixed oce-ice'        )   
2076               ztmp1(:,:) = ( ztmp1(:,:) + rt0 ) * zfr_l(:,:) 
2077               DO jl=1,jpl
2078                  ztmp1(:,:) = ztmp1(:,:) + tn_ice(:,:,jl) * a_i(:,:,jl)
2079               ENDDO
2080            CASE default                     ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%cldes' )
2081            END SELECT
2082         ENDIF
2083         IF( ssnd(jps_toce)%laction )   CALL cpl_snd( jps_toce, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info )
2084         IF( ssnd(jps_tice)%laction )   CALL cpl_snd( jps_tice, isec, ztmp3, info )
2085         IF( ssnd(jps_tmix)%laction )   CALL cpl_snd( jps_tmix, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info )
2086      ENDIF
2087      !                                                      ! ------------------------- !
2088      !                                                      !           Albedo          !
2089      !                                                      ! ------------------------- !
2090      IF( ssnd(jps_albice)%laction ) THEN                         ! ice
2091         SELECT CASE( sn_snd_alb%cldes )
2092         CASE( 'ice'          )   ; ztmp3(:,:,1:jpl) = alb_ice(:,:,1:jpl)
2093         CASE( 'weighted ice' )   ; ztmp3(:,:,1:jpl) = alb_ice(:,:,1:jpl) * a_i(:,:,1:jpl)
2094         CASE default             ; CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_alb%cldes' )
2095         END SELECT
2096         CALL cpl_snd( jps_albice, isec, ztmp3, info )
2097      ENDIF
2098      IF( ssnd(jps_albmix)%laction ) THEN                         ! mixed ice-ocean
2099         ztmp1(:,:) = albedo_oce_mix(:,:) * zfr_l(:,:)
2100         DO jl=1,jpl
2101            ztmp1(:,:) = ztmp1(:,:) + alb_ice(:,:,jl) * a_i(:,:,jl)
2102         ENDDO
2103         CALL cpl_snd( jps_albmix, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info )
2104      ENDIF
2105      !                                                      ! ------------------------- !
2106      !                                                      !  Ice fraction & Thickness !
2107      !                                                      ! ------------------------- !
2108      ! Send ice fraction field to atmosphere
2109      IF( ssnd(jps_fice)%laction ) THEN
2110         SELECT CASE( sn_snd_thick%clcat )
2111         CASE( 'yes' )   ;   ztmp3(:,:,1:jpl) =  a_i(:,:,1:jpl)
2112         CASE( 'no'  )   ;   ztmp3(:,:,1    ) = fr_i(:,:      )
2113         CASE default    ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%clcat' )
2114         END SELECT
2115         IF( ssnd(jps_fice)%laction )   CALL cpl_snd( jps_fice, isec, ztmp3, info )
2116      ENDIF
2117     
2118      ! Send ice fraction field (first order interpolation), for weighting UM fluxes to be passed to NEMO
2119      IF (ssnd(jps_fice1)%laction) THEN
2120         SELECT CASE (sn_snd_thick1%clcat)
2121         CASE( 'yes' )   ;   ztmp3(:,:,1:jpl) =  a_i(:,:,1:jpl)
2122         CASE( 'no' )    ;   ztmp3(:,:,1) = fr_i(:,:)
2123         CASE default    ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick1%clcat' )
2124    END SELECT
2125         CALL cpl_snd (jps_fice1, isec, ztmp3, info)
2126      ENDIF
2127     
2128      ! Send ice fraction field to OPA (sent by SAS in SAS-OPA coupling)
2129      IF( ssnd(jps_fice2)%laction ) THEN
2130         ztmp3(:,:,1) = fr_i(:,:)
2131         IF( ssnd(jps_fice2)%laction )   CALL cpl_snd( jps_fice2, isec, ztmp3, info )
2132      ENDIF
2133
2134      ! Send ice and snow thickness field
2135      IF( ssnd(jps_hice)%laction .OR. ssnd(jps_hsnw)%laction ) THEN
2136         SELECT CASE( sn_snd_thick%cldes)
2137         CASE( 'none'                  )       ! nothing to do
2138         CASE( 'weighted ice and snow' )   
2139            SELECT CASE( sn_snd_thick%clcat )
2140            CASE( 'yes' )   
2141               ztmp3(:,:,1:jpl) =  ht_i(:,:,1:jpl) * a_i(:,:,1:jpl)
2142               ztmp4(:,:,1:jpl) =  ht_s(:,:,1:jpl) * a_i(:,:,1:jpl)
2143            CASE( 'no' )
2144               ztmp3(:,:,:) = 0.0   ;  ztmp4(:,:,:) = 0.0
2145               DO jl=1,jpl
2146                  ztmp3(:,:,1) = ztmp3(:,:,1) + ht_i(:,:,jl) * a_i(:,:,jl)
2147                  ztmp4(:,:,1) = ztmp4(:,:,1) + ht_s(:,:,jl) * a_i(:,:,jl)
2148               ENDDO
2149            CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%clcat' )
2150            END SELECT
2151         CASE( 'ice and snow'         )   
2152            SELECT CASE( sn_snd_thick%clcat )
2153            CASE( 'yes' )
2154               ztmp3(:,:,1:jpl) = ht_i(:,:,1:jpl)
2155               ztmp4(:,:,1:jpl) = ht_s(:,:,1:jpl)
2156            CASE( 'no' )
2157               WHERE( SUM( a_i, dim=3 ) /= 0. )
2158                  ztmp3(:,:,1) = SUM( ht_i * a_i, dim=3 ) / SUM( a_i, dim=3 )
2159                  ztmp4(:,:,1) = SUM( ht_s * a_i, dim=3 ) / SUM( a_i, dim=3 )
2160               ELSEWHERE
2161                 ztmp3(:,:,1) = 0.
2162                 ztmp4(:,:,1) = 0.
2163               END WHERE
2164            CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%clcat' )
2165            END SELECT
2166         CASE default                     ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%cldes' )
2167         END SELECT
2168         IF( ssnd(jps_hice)%laction )   CALL cpl_snd( jps_hice, isec, ztmp3, info )
2169         IF( ssnd(jps_hsnw)%laction )   CALL cpl_snd( jps_hsnw, isec, ztmp4, info )
2170      ENDIF
2171      !
2172#if defined key_cice && ! defined key_cice4
2173      ! Send meltpond fields
2174      IF( ssnd(jps_a_p)%laction .OR. ssnd(jps_ht_p)%laction ) THEN
2175         SELECT CASE( sn_snd_mpnd%cldes) 
2176         CASE( 'weighted ice' ) 
2177            SELECT CASE( sn_snd_mpnd%clcat ) 
2178            CASE( 'yes' ) 
2179               ztmp3(:,:,1:jpl) =  a_p(:,:,1:jpl) * a_i(:,:,1:jpl) 
2180               ztmp4(:,:,1:jpl) =  ht_p(:,:,1:jpl) * a_i(:,:,1:jpl) 
2181            CASE( 'no' ) 
2182               ztmp3(:,:,:) = 0.0 
2183               ztmp4(:,:,:) = 0.0 
2184               DO jl=1,jpl 
2185                 ztmp3(:,:,1) = ztmp3(:,:,1) + a_p(:,:,jpl) * a_i(:,:,jpl) 
2186                 ztmp4(:,:,1) = ztmp4(:,:,1) + ht_p(:,:,jpl) * a_i(:,:,jpl) 
2187               ENDDO 
2188            CASE default    ;   CALL ctl_stop( 'sbc_cpl_mpd: wrong definition of sn_snd_mpnd%clcat' ) 
2189            END SELECT
2190         CASE( 'ice only' )   
2191            ztmp3(:,:,1:jpl) = a_p(:,:,1:jpl) 
2192            ztmp4(:,:,1:jpl) = ht_p(:,:,1:jpl) 
2193         END SELECT
2194         IF( ssnd(jps_a_p)%laction )   CALL cpl_snd( jps_a_p, isec, ztmp3, info )   
2195         IF( ssnd(jps_ht_p)%laction )   CALL cpl_snd( jps_ht_p, isec, ztmp4, info )   
2196         !
2197         ! Send ice effective conductivity
2198         SELECT CASE( sn_snd_cond%cldes)
2199         CASE( 'weighted ice' )   
2200            SELECT CASE( sn_snd_cond%clcat )
2201            CASE( 'yes' )   
2202               ztmp3(:,:,1:jpl) =  kn_ice(:,:,1:jpl) * a_i(:,:,1:jpl)
2203            CASE( 'no' )
2204               ztmp3(:,:,:) = 0.0
2205               DO jl=1,jpl
2206                 ztmp3(:,:,1) = ztmp3(:,:,1) + kn_ice(:,:,jl) * a_i(:,:,jl)
2207               ENDDO
2208            CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_cond%clcat' )
2209            END SELECT
2210         CASE( 'ice only' )   
2211           ztmp3(:,:,1:jpl) = kn_ice(:,:,1:jpl)
2212         END SELECT
2213         IF( ssnd(jps_kice)%laction )   CALL cpl_snd( jps_kice, isec, ztmp3, info )
2214      ENDIF
2215#endif
2216      !
2217      !
2218#if defined key_cpl_carbon_cycle
2219      !                                                      ! ------------------------- !
2220      !                                                      !  CO2 flux from PISCES     !
2221      !                                                      ! ------------------------- !
2222      IF( ssnd(jps_co2)%laction )   CALL cpl_snd( jps_co2, isec, RESHAPE ( oce_co2, (/jpi,jpj,1/) ) , info )
2223      !
2224#endif
2225
2226
2227
2228      IF (ln_medusa) THEN
2229      !                                                      ! --------------------------------- !
2230      !                                                      !  CO2 flux and DMS from MEDUSA     !
2231      !                                                      ! --------------------------------- !
2232         IF ( ssnd(jps_bio_co2)%laction ) THEN
2233            CALL cpl_snd( jps_bio_co2, isec, RESHAPE( CO2Flux_out_cpl, (/jpi,jpj,1/) ), info )
2234         ENDIF
2235
2236         IF ( ssnd(jps_bio_dms)%laction )  THEN
2237            CALL cpl_snd( jps_bio_dms, isec, RESHAPE( DMS_out_cpl, (/jpi,jpj,1/) ), info )
2238         ENDIF
2239      ENDIF
2240
2241      !                                                      ! ------------------------- !
2242      IF( ssnd(jps_ocx1)%laction ) THEN                      !      Surface current      !
2243         !                                                   ! ------------------------- !
2244         !   
2245         !                                                  j+1   j     -----V---F
2246         ! surface velocity always sent from T point                     !       |
2247         !                                                        j      |   T   U
2248         !                                                               |       |
2249         !                                                   j    j-1   -I-------|
2250         !                                               (for I)         |       |
2251         !                                                              i-1  i   i
2252         !                                                               i      i+1 (for I)
2253         IF( nn_components == jp_iam_opa ) THEN
2254            zotx1(:,:) = un(:,:,1) 
2255            zoty1(:,:) = vn(:,:,1) 
2256         ELSE       
2257            SELECT CASE( TRIM( sn_snd_crt%cldes ) )
2258            CASE( 'oce only'             )      ! C-grid ==> T
2259               DO jj = 2, jpjm1
2260                  DO ji = fs_2, fs_jpim1   ! vector opt.
2261                     zotx1(ji,jj) = 0.5 * ( un(ji,jj,1) + un(ji-1,jj  ,1) )
2262                     zoty1(ji,jj) = 0.5 * ( vn(ji,jj,1) + vn(ji  ,jj-1,1) ) 
2263                  END DO
2264               END DO
2265            CASE( 'weighted oce and ice' )   
2266               SELECT CASE ( cp_ice_msh )
2267               CASE( 'C' )                      ! Ocean and Ice on C-grid ==> T
2268                  DO jj = 2, jpjm1
2269                     DO ji = fs_2, fs_jpim1   ! vector opt.
2270                        zotx1(ji,jj) = 0.5 * ( un   (ji,jj,1) + un   (ji-1,jj  ,1) ) * zfr_l(ji,jj) 
2271                        zoty1(ji,jj) = 0.5 * ( vn   (ji,jj,1) + vn   (ji  ,jj-1,1) ) * zfr_l(ji,jj)
2272                        zitx1(ji,jj) = 0.5 * ( u_ice(ji,jj  ) + u_ice(ji-1,jj    ) ) *  fr_i(ji,jj)
2273                        zity1(ji,jj) = 0.5 * ( v_ice(ji,jj  ) + v_ice(ji  ,jj-1  ) ) *  fr_i(ji,jj)
2274                     END DO
2275                  END DO
2276               CASE( 'I' )                      ! Ocean on C grid, Ice on I-point (B-grid) ==> T
2277                  DO jj = 2, jpjm1
2278                     DO ji = 2, jpim1   ! NO vector opt.
2279                        zotx1(ji,jj) = 0.5  * ( un(ji,jj,1)      + un(ji-1,jj  ,1) ) * zfr_l(ji,jj) 
2280                        zoty1(ji,jj) = 0.5  * ( vn(ji,jj,1)      + vn(ji  ,jj-1,1) ) * zfr_l(ji,jj) 
2281                        zitx1(ji,jj) = 0.25 * ( u_ice(ji+1,jj+1) + u_ice(ji,jj+1)                     &
2282                           &                  + u_ice(ji+1,jj  ) + u_ice(ji,jj  )  ) *  fr_i(ji,jj)
2283                        zity1(ji,jj) = 0.25 * ( v_ice(ji+1,jj+1) + v_ice(ji,jj+1)                     &
2284                           &                  + v_ice(ji+1,jj  ) + v_ice(ji,jj  )  ) *  fr_i(ji,jj)
2285                     END DO
2286                  END DO
2287               CASE( 'F' )                      ! Ocean on C grid, Ice on F-point (B-grid) ==> T
2288                  DO jj = 2, jpjm1
2289                     DO ji = 2, jpim1   ! NO vector opt.
2290                        zotx1(ji,jj) = 0.5  * ( un(ji,jj,1)      + un(ji-1,jj  ,1) ) * zfr_l(ji,jj) 
2291                        zoty1(ji,jj) = 0.5  * ( vn(ji,jj,1)      + vn(ji  ,jj-1,1) ) * zfr_l(ji,jj) 
2292                        zitx1(ji,jj) = 0.25 * ( u_ice(ji-1,jj-1) + u_ice(ji,jj-1)                     &
2293                           &                  + u_ice(ji-1,jj  ) + u_ice(ji,jj  )  ) *  fr_i(ji,jj)
2294                        zity1(ji,jj) = 0.25 * ( v_ice(ji-1,jj-1) + v_ice(ji,jj-1)                     &
2295                           &                  + v_ice(ji-1,jj  ) + v_ice(ji,jj  )  ) *  fr_i(ji,jj)
2296                     END DO
2297                  END DO
2298               END SELECT
2299               CALL lbc_lnk( zitx1, 'T', -1. )   ;   CALL lbc_lnk( zity1, 'T', -1. )
2300            CASE( 'mixed oce-ice'        )
2301               SELECT CASE ( cp_ice_msh )
2302               CASE( 'C' )                      ! Ocean and Ice on C-grid ==> T
2303                  DO jj = 2, jpjm1
2304                     DO ji = fs_2, fs_jpim1   ! vector opt.
2305                        zotx1(ji,jj) = 0.5 * ( un   (ji,jj,1) + un   (ji-1,jj  ,1) ) * zfr_l(ji,jj)   &
2306                           &         + 0.5 * ( u_ice(ji,jj  ) + u_ice(ji-1,jj    ) ) *  fr_i(ji,jj)
2307                        zoty1(ji,jj) = 0.5 * ( vn   (ji,jj,1) + vn   (ji  ,jj-1,1) ) * zfr_l(ji,jj)   &
2308                           &         + 0.5 * ( v_ice(ji,jj  ) + v_ice(ji  ,jj-1  ) ) *  fr_i(ji,jj)
2309                     END DO
2310                  END DO
2311               CASE( 'I' )                      ! Ocean on C grid, Ice on I-point (B-grid) ==> T
2312                  DO jj = 2, jpjm1
2313                     DO ji = 2, jpim1   ! NO vector opt.
2314                        zotx1(ji,jj) = 0.5  * ( un(ji,jj,1)      + un(ji-1,jj  ,1) ) * zfr_l(ji,jj)   &   
2315                           &         + 0.25 * ( u_ice(ji+1,jj+1) + u_ice(ji,jj+1)                     &
2316                           &                  + u_ice(ji+1,jj  ) + u_ice(ji,jj  )  ) *  fr_i(ji,jj)
2317                        zoty1(ji,jj) = 0.5  * ( vn(ji,jj,1)      + vn(ji  ,jj-1,1) ) * zfr_l(ji,jj)   & 
2318                           &         + 0.25 * ( v_ice(ji+1,jj+1) + v_ice(ji,jj+1)                     &
2319                           &                  + v_ice(ji+1,jj  ) + v_ice(ji,jj  )  ) *  fr_i(ji,jj)
2320                     END DO
2321                  END DO
2322               CASE( 'F' )                      ! Ocean on C grid, Ice on F-point (B-grid) ==> T
2323                  DO jj = 2, jpjm1
2324                     DO ji = 2, jpim1   ! NO vector opt.
2325                        zotx1(ji,jj) = 0.5  * ( un(ji,jj,1)      + un(ji-1,jj  ,1) ) * zfr_l(ji,jj)   &   
2326                           &         + 0.25 * ( u_ice(ji-1,jj-1) + u_ice(ji,jj-1)                     &
2327                           &                  + u_ice(ji-1,jj  ) + u_ice(ji,jj  )  ) *  fr_i(ji,jj)
2328                        zoty1(ji,jj) = 0.5  * ( vn(ji,jj,1)      + vn(ji  ,jj-1,1) ) * zfr_l(ji,jj)   & 
2329                           &         + 0.25 * ( v_ice(ji-1,jj-1) + v_ice(ji,jj-1)                     &
2330                           &                  + v_ice(ji-1,jj  ) + v_ice(ji,jj  )  ) *  fr_i(ji,jj)
2331                     END DO
2332                  END DO
2333               END SELECT
2334            END SELECT
2335            CALL lbc_lnk( zotx1, ssnd(jps_ocx1)%clgrid, -1. )   ;   CALL lbc_lnk( zoty1, ssnd(jps_ocy1)%clgrid, -1. )
2336            !
2337         ENDIF
2338         !
2339         !
2340         IF( TRIM( sn_snd_crt%clvor ) == 'eastward-northward' ) THEN             ! Rotation of the components
2341            !                                                                     ! Ocean component
2342            CALL rot_rep( zotx1, zoty1, ssnd(jps_ocx1)%clgrid, 'ij->e', ztmp1 )       ! 1st component
2343            CALL rot_rep( zotx1, zoty1, ssnd(jps_ocx1)%clgrid, 'ij->n', ztmp2 )       ! 2nd component
2344            zotx1(:,:) = ztmp1(:,:)                                                   ! overwrite the components
2345            zoty1(:,:) = ztmp2(:,:)
2346            IF( ssnd(jps_ivx1)%laction ) THEN                                     ! Ice component
2347               CALL rot_rep( zitx1, zity1, ssnd(jps_ivx1)%clgrid, 'ij->e', ztmp1 )    ! 1st component
2348               CALL rot_rep( zitx1, zity1, ssnd(jps_ivx1)%clgrid, 'ij->n', ztmp2 )    ! 2nd component
2349               zitx1(:,:) = ztmp1(:,:)                                                ! overwrite the components
2350               zity1(:,:) = ztmp2(:,:)
2351            ENDIF
2352         ENDIF
2353         !
2354         ! spherical coordinates to cartesian -> 2 components to 3 components
2355         IF( TRIM( sn_snd_crt%clvref ) == 'cartesian' ) THEN
2356            ztmp1(:,:) = zotx1(:,:)                     ! ocean currents
2357            ztmp2(:,:) = zoty1(:,:)
2358            CALL oce2geo ( ztmp1, ztmp2, 'T', zotx1, zoty1, zotz1 )
2359            !
2360            IF( ssnd(jps_ivx1)%laction ) THEN           ! ice velocities
2361               ztmp1(:,:) = zitx1(:,:)
2362               ztmp1(:,:) = zity1(:,:)
2363               CALL oce2geo ( ztmp1, ztmp2, 'T', zitx1, zity1, zitz1 )
2364            ENDIF
2365         ENDIF
2366         !
2367         IF( ssnd(jps_ocx1)%laction )   CALL cpl_snd( jps_ocx1, isec, RESHAPE ( zotx1, (/jpi,jpj,1/) ), info )   ! ocean x current 1st grid
2368         IF( ssnd(jps_ocy1)%laction )   CALL cpl_snd( jps_ocy1, isec, RESHAPE ( zoty1, (/jpi,jpj,1/) ), info )   ! ocean y current 1st grid
2369         IF( ssnd(jps_ocz1)%laction )   CALL cpl_snd( jps_ocz1, isec, RESHAPE ( zotz1, (/jpi,jpj,1/) ), info )   ! ocean z current 1st grid
2370         !
2371         IF( ssnd(jps_ivx1)%laction )   CALL cpl_snd( jps_ivx1, isec, RESHAPE ( zitx1, (/jpi,jpj,1/) ), info )   ! ice   x current 1st grid
2372         IF( ssnd(jps_ivy1)%laction )   CALL cpl_snd( jps_ivy1, isec, RESHAPE ( zity1, (/jpi,jpj,1/) ), info )   ! ice   y current 1st grid
2373         IF( ssnd(jps_ivz1)%laction )   CALL cpl_snd( jps_ivz1, isec, RESHAPE ( zitz1, (/jpi,jpj,1/) ), info )   ! ice   z current 1st grid
2374         !
2375      ENDIF
2376      !
2377      !
2378      !  Fields sent by OPA to SAS when doing OPA<->SAS coupling
2379      !                                                        ! SSH
2380      IF( ssnd(jps_ssh )%laction )  THEN
2381         !                          ! removed inverse barometer ssh when Patm
2382         !                          forcing is used (for sea-ice dynamics)
2383         IF( ln_apr_dyn ) THEN   ;   ztmp1(:,:) = sshb(:,:) - 0.5 * ( ssh_ib(:,:) + ssh_ibb(:,:) )
2384         ELSE                    ;   ztmp1(:,:) = sshn(:,:)
2385         ENDIF
2386         CALL cpl_snd( jps_ssh   , isec, RESHAPE ( ztmp1            , (/jpi,jpj,1/) ), info )
2387
2388      ENDIF
2389      !                                                        ! SSS
2390      IF( ssnd(jps_soce  )%laction )  THEN
2391         CALL cpl_snd( jps_soce  , isec, RESHAPE ( tsn(:,:,1,jp_sal), (/jpi,jpj,1/) ), info )
2392      ENDIF
2393      !                                                        ! first T level thickness
2394      IF( ssnd(jps_e3t1st )%laction )  THEN
2395         CALL cpl_snd( jps_e3t1st, isec, RESHAPE ( fse3t_n(:,:,1)   , (/jpi,jpj,1/) ), info )
2396      ENDIF
2397      !                                                        ! Qsr fraction
2398      IF( ssnd(jps_fraqsr)%laction )  THEN
2399         CALL cpl_snd( jps_fraqsr, isec, RESHAPE ( fraqsr_1lev(:,:) , (/jpi,jpj,1/) ), info )
2400      ENDIF
2401      !
2402      !  Fields sent by SAS to OPA when OASIS coupling
2403      !                                                        ! Solar heat flux
2404      IF( ssnd(jps_qsroce)%laction )  CALL cpl_snd( jps_qsroce, isec, RESHAPE ( qsr , (/jpi,jpj,1/) ), info )
2405      IF( ssnd(jps_qnsoce)%laction )  CALL cpl_snd( jps_qnsoce, isec, RESHAPE ( qns , (/jpi,jpj,1/) ), info )
2406      IF( ssnd(jps_oemp  )%laction )  CALL cpl_snd( jps_oemp  , isec, RESHAPE ( emp , (/jpi,jpj,1/) ), info )
2407      IF( ssnd(jps_sflx  )%laction )  CALL cpl_snd( jps_sflx  , isec, RESHAPE ( sfx , (/jpi,jpj,1/) ), info )
2408      IF( ssnd(jps_otx1  )%laction )  CALL cpl_snd( jps_otx1  , isec, RESHAPE ( utau, (/jpi,jpj,1/) ), info )
2409      IF( ssnd(jps_oty1  )%laction )  CALL cpl_snd( jps_oty1  , isec, RESHAPE ( vtau, (/jpi,jpj,1/) ), info )
2410      IF( ssnd(jps_rnf   )%laction )  CALL cpl_snd( jps_rnf   , isec, RESHAPE ( rnf , (/jpi,jpj,1/) ), info )
2411      IF( ssnd(jps_taum  )%laction )  CALL cpl_snd( jps_taum  , isec, RESHAPE ( taum, (/jpi,jpj,1/) ), info )
2412     
2413#if defined key_cice
2414      ztmp1(:,:) = sstfrz(:,:) + rt0
2415      IF( ssnd(jps_sstfrz)%laction )  CALL cpl_snd( jps_sstfrz, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info )
2416#endif
2417      !
2418      CALL wrk_dealloc( jpi,jpj, zfr_l, ztmp1, ztmp2, zotx1, zoty1, zotz1, zitx1, zity1, zitz1 )
2419      CALL wrk_dealloc( jpi,jpj,jpl, ztmp3, ztmp4 )
2420      !
2421      IF( nn_timing == 1 )  CALL timing_stop('sbc_cpl_snd')
2422      !
2423   END SUBROUTINE sbc_cpl_snd
2424   
2425   !!======================================================================
2426END MODULE sbccpl
Note: See TracBrowser for help on using the repository browser.