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 NEMO/branches/UKMO/NEMO_4.0.4_penetrating_solar/src/OCE/SBC – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.4_penetrating_solar/src/OCE/SBC/sbccpl.F90 @ 14392

Last change on this file since 14392 was 14392, checked in by dancopsey, 3 years ago

Include heat involved in sublimation in the qns_ice flux. Weight qsr_tot by the leads fraction (ziceld).

File size: 161.4 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   !!----------------------------------------------------------------------
13   !!   namsbc_cpl      : coupled formulation namlist
14   !!   sbc_cpl_init    : initialisation of the coupled exchanges
15   !!   sbc_cpl_rcv     : receive fields from the atmosphere over the ocean (ocean only)
16   !!                     receive stress from the atmosphere over the ocean (ocean-ice case)
17   !!   sbc_cpl_ice_tau : receive stress from the atmosphere over ice
18   !!   sbc_cpl_ice_flx : receive fluxes from the atmosphere over ice
19   !!   sbc_cpl_snd     : send     fields to the atmosphere
20   !!----------------------------------------------------------------------
21   USE dom_oce         ! ocean space and time domain
22   USE sbc_oce         ! Surface boundary condition: ocean fields
23   USE trc_oce         ! share SMS/Ocean variables
24   USE sbc_ice         ! Surface boundary condition: ice fields
25   USE sbcapr          ! Stochastic param. : ???
26   USE sbcdcy          ! surface boundary condition: diurnal cycle
27   USE sbcwave         ! surface boundary condition: waves
28   USE phycst          ! physical constants
29#if defined key_si3
30   USE ice            ! ice variables
31#endif
32   USE cpl_oasis3     ! OASIS3 coupling
33   USE geo2ocean      !
34   USE oce     , ONLY : tsn, un, vn, sshn, ub, vb, sshb, fraqsr_1lev
35   USE ocealb         !
36   USE eosbn2         !
37   USE sbcrnf  , ONLY : l_rnfcpl
38   USE sbcisf  , ONLY : l_isfcpl
39#if defined key_cice
40   USE ice_domain_size, only: ncat
41#endif
42#if defined key_si3
43   USE icevar         ! for CALL ice_var_snwblow
44#endif
45   !
46   USE in_out_manager ! I/O manager
47   USE iom            ! NetCDF library
48   USE lib_mpp        ! distribued memory computing library
49   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
50
51#if defined key_oasis3 
52   USE mod_oasis, ONLY : OASIS_Sent, OASIS_ToRest, OASIS_SentOut, OASIS_ToRestOut 
53#endif
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 icestp.F90
60   PUBLIC   sbc_cpl_snd       ! routine called by step.F90
61   PUBLIC   sbc_cpl_ice_tau   ! routine called by icestp.F90
62   PUBLIC   sbc_cpl_ice_flx   ! routine called by icestp.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_mslp   = 43   ! mean sea level pressure
108   INTEGER, PARAMETER ::   jpr_hsig   = 44   ! Hsig
109   INTEGER, PARAMETER ::   jpr_phioc  = 45   ! Wave=>ocean energy flux
110   INTEGER, PARAMETER ::   jpr_sdrftx = 46   ! Stokes drift on grid 1
111   INTEGER, PARAMETER ::   jpr_sdrfty = 47   ! Stokes drift on grid 2
112   INTEGER, PARAMETER ::   jpr_wper   = 48   ! Mean wave period
113   INTEGER, PARAMETER ::   jpr_wnum   = 49   ! Mean wavenumber
114   INTEGER, PARAMETER ::   jpr_tauwoc = 50   ! Stress fraction adsorbed by waves
115   INTEGER, PARAMETER ::   jpr_wdrag  = 51   ! Neutral surface drag coefficient
116   INTEGER, PARAMETER ::   jpr_isf    = 52
117   INTEGER, PARAMETER ::   jpr_icb    = 53
118   INTEGER, PARAMETER ::   jpr_wfreq  = 54   ! Wave peak frequency
119   INTEGER, PARAMETER ::   jpr_tauwx  = 55   ! x component of the ocean stress from waves
120   INTEGER, PARAMETER ::   jpr_tauwy  = 56   ! y component of the ocean stress from waves
121   INTEGER, PARAMETER ::   jpr_ts_ice = 57   ! Sea ice surface temp
122   INTEGER, PARAMETER ::   jpr_grnm   = 58   ! Greenland ice mass
123   INTEGER, PARAMETER ::   jpr_antm   = 59   ! Antarctic ice mass
124   INTEGER, PARAMETER ::   jpr_rnf_1d = 60   ! 1D river runoff
125   INTEGER, PARAMETER ::   jpr_qtr    = 61   ! Transmitted solar
126
127   INTEGER, PARAMETER ::   jprcv      = 61   ! total number of fields received
128
129   INTEGER, PARAMETER ::   jps_fice   =  1   ! ice fraction sent to the atmosphere
130   INTEGER, PARAMETER ::   jps_toce   =  2   ! ocean temperature
131   INTEGER, PARAMETER ::   jps_tice   =  3   ! ice   temperature
132   INTEGER, PARAMETER ::   jps_tmix   =  4   ! mixed temperature (ocean+ice)
133   INTEGER, PARAMETER ::   jps_albice =  5   ! ice   albedo
134   INTEGER, PARAMETER ::   jps_albmix =  6   ! mixed albedo
135   INTEGER, PARAMETER ::   jps_hice   =  7   ! ice  thickness
136   INTEGER, PARAMETER ::   jps_hsnw   =  8   ! snow thickness
137   INTEGER, PARAMETER ::   jps_ocx1   =  9   ! ocean current on grid 1
138   INTEGER, PARAMETER ::   jps_ocy1   = 10   !
139   INTEGER, PARAMETER ::   jps_ocz1   = 11   !
140   INTEGER, PARAMETER ::   jps_ivx1   = 12   ! ice   current on grid 1
141   INTEGER, PARAMETER ::   jps_ivy1   = 13   !
142   INTEGER, PARAMETER ::   jps_ivz1   = 14   !
143   INTEGER, PARAMETER ::   jps_co2    = 15
144   INTEGER, PARAMETER ::   jps_soce   = 16   ! ocean salinity
145   INTEGER, PARAMETER ::   jps_ssh    = 17   ! sea surface height
146   INTEGER, PARAMETER ::   jps_qsroce = 18   ! Qsr above the ocean
147   INTEGER, PARAMETER ::   jps_qnsoce = 19   ! Qns above the ocean
148   INTEGER, PARAMETER ::   jps_oemp   = 20   ! ocean freshwater budget (evap - precip)
149   INTEGER, PARAMETER ::   jps_sflx   = 21   ! salt flux
150   INTEGER, PARAMETER ::   jps_otx1   = 22   ! 2 atmosphere-ocean stress components on grid 1
151   INTEGER, PARAMETER ::   jps_oty1   = 23   !
152   INTEGER, PARAMETER ::   jps_rnf    = 24   ! runoffs
153   INTEGER, PARAMETER ::   jps_taum   = 25   ! wind stress module
154   INTEGER, PARAMETER ::   jps_fice2  = 26   ! ice fraction sent to OPA (by SAS when doing SAS-OPA coupling)
155   INTEGER, PARAMETER ::   jps_e3t1st = 27   ! first level depth (vvl)
156   INTEGER, PARAMETER ::   jps_fraqsr = 28   ! fraction of solar net radiation absorbed in the first ocean level
157   INTEGER, PARAMETER ::   jps_ficet  = 29   ! total ice fraction 
158   INTEGER, PARAMETER ::   jps_ocxw   = 30   ! currents on grid 1 
159   INTEGER, PARAMETER ::   jps_ocyw   = 31   ! currents on grid 2
160   INTEGER, PARAMETER ::   jps_wlev   = 32   ! water level
161   INTEGER, PARAMETER ::   jps_fice1  = 33   ! first-order ice concentration (for semi-implicit coupling of atmos-ice fluxes)
162   INTEGER, PARAMETER ::   jps_a_p    = 34   ! meltpond area fraction
163   INTEGER, PARAMETER ::   jps_ht_p   = 35   ! meltpond thickness
164   INTEGER, PARAMETER ::   jps_kice   = 36   ! sea ice effective conductivity
165   INTEGER, PARAMETER ::   jps_sstfrz = 37   ! sea surface freezing temperature
166   INTEGER, PARAMETER ::   jps_ttilyr = 38   ! sea ice top layer temp
167
168   INTEGER, PARAMETER ::   jpsnd      = 38   ! total number of fields sent
169
170#if ! defined key_oasis3
171   ! Dummy variables to enable compilation when oasis3 is not being used
172   INTEGER                    ::   OASIS_Sent        = -1 
173   INTEGER                    ::   OASIS_SentOut     = -1 
174   INTEGER                    ::   OASIS_ToRest      = -1 
175   INTEGER                    ::   OASIS_ToRestOut   = -1 
176#endif 
177
178   !                                  !!** namelist namsbc_cpl **
179   TYPE ::   FLD_C                     !   
180      CHARACTER(len = 32) ::   cldes      ! desciption of the coupling strategy
181      CHARACTER(len = 32) ::   clcat      ! multiple ice categories strategy
182      CHARACTER(len = 32) ::   clvref     ! reference of vector ('spherical' or 'cartesian')
183      CHARACTER(len = 32) ::   clvor      ! orientation of vector fields ('eastward-northward' or 'local grid')
184      CHARACTER(len = 32) ::   clvgrd     ! grids on which is located the vector fields
185   END TYPE FLD_C
186   !                                   ! Send to the atmosphere 
187   TYPE(FLD_C) ::   sn_snd_temp  , sn_snd_alb , sn_snd_thick, sn_snd_crt   , sn_snd_co2,  &
188      &             sn_snd_thick1, sn_snd_cond, sn_snd_mpnd , sn_snd_sstfrz, sn_snd_ttilyr
189   !                                   ! Received from the atmosphere
190   TYPE(FLD_C) ::   sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau, sn_rcv_tauw, sn_rcv_dqnsdt, sn_rcv_qsr,  &
191      &             sn_rcv_qns , sn_rcv_emp   , sn_rcv_rnf, sn_rcv_ts_ice
192   TYPE(FLD_C) ::   sn_rcv_cal, sn_rcv_iceflx, sn_rcv_co2, sn_rcv_mslp, sn_rcv_icb, sn_rcv_isf
193   ! Send to waves
194   TYPE(FLD_C) ::   sn_snd_ifrac, sn_snd_crtw, sn_snd_wlev 
195   ! Received from waves
196   TYPE(FLD_C) ::   sn_rcv_hsig, sn_rcv_phioc, sn_rcv_sdrfx, sn_rcv_sdrfy, sn_rcv_wper, sn_rcv_wnum, sn_rcv_tauwoc, &
197                    sn_rcv_wdrag, sn_rcv_wfreq
198   ! Transmitted solar
199   TYPE(FLD_C) ::   sn_rcv_qtr
200   !                                   ! Other namelist parameters
201   INTEGER     ::   nn_cplmodel           ! Maximum number of models to/from which NEMO is potentialy sending/receiving data
202   LOGICAL     ::   ln_usecplmask         !  use a coupling mask file to merge data received from several models
203                                          !   -> file cplmask.nc with the float variable called cplmask (jpi,jpj,nn_cplmodel)
204   LOGICAL     ::   ln_scale_ice_flux     !  use ice fluxes that are already "ice weighted" ( i.e. multiplied ice concentration)
205
206   TYPE ::   DYNARR     
207      REAL(wp), POINTER, DIMENSION(:,:,:) ::   z3   
208   END TYPE DYNARR
209
210   TYPE( DYNARR ), SAVE, DIMENSION(jprcv) ::   frcv                ! all fields recieved from the atmosphere
211
212   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   alb_oce_mix    ! ocean albedo sent to atmosphere (mix clear/overcast sky)
213#if defined key_si3 || defined key_cice
214   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_i_last_couple !: Ice fractional area at last coupling time
215#endif
216
217   REAL(wp) ::   rpref = 101000._wp   ! reference atmospheric pressure[N/m2]
218   REAL(wp) ::   r1_grau              ! = 1.e0 / (grav * rau0)
219
220   INTEGER , ALLOCATABLE, SAVE, DIMENSION(:) ::   nrcvinfo           ! OASIS info argument
221
222   !! Substitution
223#  include "vectopt_loop_substitute.h90"
224   !!----------------------------------------------------------------------
225   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
226   !! $Id$
227   !! Software governed by the CeCILL license (see ./LICENSE)
228   !!----------------------------------------------------------------------
229CONTAINS
230 
231   INTEGER FUNCTION sbc_cpl_alloc()
232      !!----------------------------------------------------------------------
233      !!             ***  FUNCTION sbc_cpl_alloc  ***
234      !!----------------------------------------------------------------------
235      INTEGER :: ierr(5)
236      !!----------------------------------------------------------------------
237      ierr(:) = 0
238      !
239      ALLOCATE( alb_oce_mix(jpi,jpj), nrcvinfo(jprcv),  STAT=ierr(1) )
240     
241#if ! defined key_si3 && ! defined key_cice
242      ALLOCATE( a_i(jpi,jpj,1) , STAT=ierr(2) )  ! used in sbcice_if.F90 (done here as there is no sbc_ice_if_init)
243#endif
244      ALLOCATE( xcplmask(jpi,jpj,0:nn_cplmodel) , STAT=ierr(3) )
245#if defined key_si3 || defined key_cice
246      ALLOCATE( a_i_last_couple(jpi,jpj,jpl) , STAT=ierr(4) )
247#endif
248      !
249      IF( .NOT. ln_apr_dyn ) ALLOCATE( ssh_ib(jpi,jpj), ssh_ibb(jpi,jpj), apr(jpi, jpj), STAT=ierr(5) )
250
251      sbc_cpl_alloc = MAXVAL( ierr )
252      CALL mpp_sum ( 'sbccpl', sbc_cpl_alloc )
253      IF( sbc_cpl_alloc > 0 )   CALL ctl_warn('sbc_cpl_alloc: allocation of arrays failed')
254      !
255   END FUNCTION sbc_cpl_alloc
256
257
258   SUBROUTINE sbc_cpl_init( k_ice )     
259      !!----------------------------------------------------------------------
260      !!             ***  ROUTINE sbc_cpl_init  ***
261      !!
262      !! ** Purpose :   Initialisation of send and received information from
263      !!                the atmospheric component
264      !!
265      !! ** Method  : * Read namsbc_cpl namelist
266      !!              * define the receive interface
267      !!              * define the send    interface
268      !!              * initialise the OASIS coupler
269      !!----------------------------------------------------------------------
270      INTEGER, INTENT(in) ::   k_ice   ! ice management in the sbc (=0/1/2/3)
271      !
272      INTEGER ::   jn          ! dummy loop index
273      INTEGER ::   ios, inum   ! Local integer
274      REAL(wp), DIMENSION(jpi,jpj) ::   zacs, zaos
275      !!
276      NAMELIST/namsbc_cpl/  nn_cplmodel  , ln_usecplmask, nn_cats_cpl , ln_scale_ice_flux,             &
277         &                  sn_snd_temp  , sn_snd_alb   , sn_snd_thick, sn_snd_crt   , sn_snd_co2   ,  & 
278         &                  sn_snd_ttilyr, sn_snd_cond  , sn_snd_mpnd , sn_snd_sstfrz, sn_snd_thick1,  & 
279         &                  sn_snd_ifrac , sn_snd_crtw  , sn_snd_wlev , sn_rcv_hsig  , sn_rcv_phioc ,  & 
280         &                  sn_rcv_w10m  , sn_rcv_taumod, sn_rcv_tau  , sn_rcv_dqnsdt, sn_rcv_qsr   ,  & 
281         &                  sn_rcv_sdrfx , sn_rcv_sdrfy , sn_rcv_wper , sn_rcv_wnum  , sn_rcv_tauwoc,  &
282         &                  sn_rcv_qtr   ,                                                             &
283         &                  sn_rcv_wdrag , sn_rcv_qns   , sn_rcv_emp  , sn_rcv_rnf   , sn_rcv_cal   ,  &
284         &                  sn_rcv_iceflx, sn_rcv_co2   , sn_rcv_mslp ,                                &
285         &                  sn_rcv_icb   , sn_rcv_isf   , sn_rcv_wfreq, sn_rcv_tauw  ,                 &
286         &                  sn_rcv_ts_ice
287      !!---------------------------------------------------------------------
288      !
289      ! ================================ !
290      !      Namelist informations       !
291      ! ================================ !
292      !
293      REWIND( numnam_ref )              ! Namelist namsbc_cpl in reference namelist : Variables for OASIS coupling
294      READ  ( numnam_ref, namsbc_cpl, IOSTAT = ios, ERR = 901)
295901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc_cpl in reference namelist' )
296      !
297      REWIND( numnam_cfg )              ! Namelist namsbc_cpl in configuration namelist : Variables for OASIS coupling
298      READ  ( numnam_cfg, namsbc_cpl, IOSTAT = ios, ERR = 902 )
299902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc_cpl in configuration namelist' )
300      IF(lwm) WRITE ( numond, namsbc_cpl )
301      !
302      IF(lwp) THEN                        ! control print
303         WRITE(numout,*)
304         WRITE(numout,*)'sbc_cpl_init : namsbc_cpl namelist '
305         WRITE(numout,*)'~~~~~~~~~~~~'
306      ENDIF
307      IF( lwp .AND. ln_cpl ) THEN                        ! control print
308         WRITE(numout,*)'  nn_cplmodel                         = ', nn_cplmodel
309         WRITE(numout,*)'  ln_usecplmask                       = ', ln_usecplmask
310         WRITE(numout,*)'  ln_scale_ice_flux                   = ', ln_scale_ice_flux
311         WRITE(numout,*)'  nn_cats_cpl                         = ', nn_cats_cpl
312         WRITE(numout,*)'  received fields (mutiple ice categogies)'
313         WRITE(numout,*)'      10m wind module                 = ', TRIM(sn_rcv_w10m%cldes  ), ' (', TRIM(sn_rcv_w10m%clcat  ), ')'
314         WRITE(numout,*)'      stress module                   = ', TRIM(sn_rcv_taumod%cldes), ' (', TRIM(sn_rcv_taumod%clcat), ')'
315         WRITE(numout,*)'      surface stress                  = ', TRIM(sn_rcv_tau%cldes   ), ' (', TRIM(sn_rcv_tau%clcat   ), ')'
316         WRITE(numout,*)'                     - referential    = ', sn_rcv_tau%clvref
317         WRITE(numout,*)'                     - orientation    = ', sn_rcv_tau%clvor
318         WRITE(numout,*)'                     - mesh           = ', sn_rcv_tau%clvgrd
319         WRITE(numout,*)'      non-solar heat flux sensitivity = ', TRIM(sn_rcv_dqnsdt%cldes), ' (', TRIM(sn_rcv_dqnsdt%clcat), ')'
320         WRITE(numout,*)'      solar heat flux                 = ', TRIM(sn_rcv_qsr%cldes   ), ' (', TRIM(sn_rcv_qsr%clcat   ), ')'
321         WRITE(numout,*)'      non-solar heat flux             = ', TRIM(sn_rcv_qns%cldes   ), ' (', TRIM(sn_rcv_qns%clcat   ), ')'
322         WRITE(numout,*)'      freshwater budget               = ', TRIM(sn_rcv_emp%cldes   ), ' (', TRIM(sn_rcv_emp%clcat   ), ')'
323         WRITE(numout,*)'      runoffs                         = ', TRIM(sn_rcv_rnf%cldes   ), ' (', TRIM(sn_rcv_rnf%clcat   ), ')'
324         WRITE(numout,*)'      calving                         = ', TRIM(sn_rcv_cal%cldes   ), ' (', TRIM(sn_rcv_cal%clcat   ), ')'
325         WRITE(numout,*)'      iceberg                         = ', TRIM(sn_rcv_icb%cldes   ), ' (', TRIM(sn_rcv_icb%clcat   ), ')'
326         WRITE(numout,*)'      ice shelf                       = ', TRIM(sn_rcv_isf%cldes   ), ' (', TRIM(sn_rcv_isf%clcat   ), ')'
327         WRITE(numout,*)'      sea ice heat fluxes             = ', TRIM(sn_rcv_iceflx%cldes), ' (', TRIM(sn_rcv_iceflx%clcat), ')'
328         WRITE(numout,*)'      transmitted solar               = ', TRIM(sn_rcv_qtr%cldes   ), ' (', TRIM(sn_rcv_qtr%clcat   ), ')'
329         WRITE(numout,*)'      atm co2                         = ', TRIM(sn_rcv_co2%cldes   ), ' (', TRIM(sn_rcv_co2%clcat   ), ')'
330         WRITE(numout,*)'      significant wave heigth         = ', TRIM(sn_rcv_hsig%cldes  ), ' (', TRIM(sn_rcv_hsig%clcat  ), ')' 
331         WRITE(numout,*)'      wave to oce energy flux         = ', TRIM(sn_rcv_phioc%cldes ), ' (', TRIM(sn_rcv_phioc%clcat ), ')' 
332         WRITE(numout,*)'      Surface Stokes drift grid u     = ', TRIM(sn_rcv_sdrfx%cldes ), ' (', TRIM(sn_rcv_sdrfx%clcat ), ')' 
333         WRITE(numout,*)'      Surface Stokes drift grid v     = ', TRIM(sn_rcv_sdrfy%cldes ), ' (', TRIM(sn_rcv_sdrfy%clcat ), ')' 
334         WRITE(numout,*)'      Mean wave period                = ', TRIM(sn_rcv_wper%cldes  ), ' (', TRIM(sn_rcv_wper%clcat  ), ')' 
335         WRITE(numout,*)'      Mean wave number                = ', TRIM(sn_rcv_wnum%cldes  ), ' (', TRIM(sn_rcv_wnum%clcat  ), ')' 
336         WRITE(numout,*)'      Wave peak frequency             = ', TRIM(sn_rcv_wfreq%cldes ), ' (', TRIM(sn_rcv_wfreq%clcat ), ')'
337         WRITE(numout,*)'      Stress frac adsorbed by waves   = ', TRIM(sn_rcv_tauwoc%cldes), ' (', TRIM(sn_rcv_tauwoc%clcat ), ')' 
338         WRITE(numout,*)'      Stress components by waves      = ', TRIM(sn_rcv_tauw%cldes  ), ' (', TRIM(sn_rcv_tauw%clcat  ), ')'
339         WRITE(numout,*)'      Neutral surf drag coefficient   = ', TRIM(sn_rcv_wdrag%cldes ), ' (', TRIM(sn_rcv_wdrag%clcat ), ')' 
340         WRITE(numout,*)'      Sea ice surface skin temperature= ', TRIM(sn_rcv_ts_ice%cldes), ' (', TRIM(sn_rcv_ts_ice%clcat), ')' 
341         WRITE(numout,*)'  sent fields (multiple ice categories)'
342         WRITE(numout,*)'      surface temperature             = ', TRIM(sn_snd_temp%cldes  ), ' (', TRIM(sn_snd_temp%clcat  ), ')'
343         WRITE(numout,*)'      top ice layer temperature       = ', TRIM(sn_snd_ttilyr%cldes), ' (', TRIM(sn_snd_ttilyr%clcat), ')'
344         WRITE(numout,*)'      albedo                          = ', TRIM(sn_snd_alb%cldes   ), ' (', TRIM(sn_snd_alb%clcat   ), ')'
345         WRITE(numout,*)'      ice/snow thickness              = ', TRIM(sn_snd_thick%cldes ), ' (', TRIM(sn_snd_thick%clcat ), ')'
346         WRITE(numout,*)'      total ice fraction              = ', TRIM(sn_snd_ifrac%cldes ), ' (', TRIM(sn_snd_ifrac%clcat ), ')' 
347         WRITE(numout,*)'      surface current                 = ', TRIM(sn_snd_crt%cldes   ), ' (', TRIM(sn_snd_crt%clcat   ), ')'
348         WRITE(numout,*)'                      - referential   = ', sn_snd_crt%clvref 
349         WRITE(numout,*)'                      - orientation   = ', sn_snd_crt%clvor
350         WRITE(numout,*)'                      - mesh          = ', sn_snd_crt%clvgrd
351         WRITE(numout,*)'      oce co2 flux                    = ', TRIM(sn_snd_co2%cldes   ), ' (', TRIM(sn_snd_co2%clcat   ), ')'
352         WRITE(numout,*)'      ice effective conductivity      = ', TRIM(sn_snd_cond%cldes  ), ' (', TRIM(sn_snd_cond%clcat  ), ')'
353         WRITE(numout,*)'      meltponds fraction and depth    = ', TRIM(sn_snd_mpnd%cldes  ), ' (', TRIM(sn_snd_mpnd%clcat  ), ')'
354         WRITE(numout,*)'      sea surface freezing temp       = ', TRIM(sn_snd_sstfrz%cldes), ' (', TRIM(sn_snd_sstfrz%clcat), ')'
355         WRITE(numout,*)'      water level                     = ', TRIM(sn_snd_wlev%cldes  ), ' (', TRIM(sn_snd_wlev%clcat  ), ')' 
356         WRITE(numout,*)'      mean sea level pressure         = ', TRIM(sn_rcv_mslp%cldes  ), ' (', TRIM(sn_rcv_mslp%clcat  ), ')' 
357         WRITE(numout,*)'      surface current to waves        = ', TRIM(sn_snd_crtw%cldes  ), ' (', TRIM(sn_snd_crtw%clcat  ), ')' 
358         WRITE(numout,*)'                      - referential   = ', sn_snd_crtw%clvref 
359         WRITE(numout,*)'                      - orientation   = ', sn_snd_crtw%clvor 
360         WRITE(numout,*)'                      - mesh          = ', sn_snd_crtw%clvgrd 
361      ENDIF
362
363      !                                   ! allocate sbccpl arrays
364      IF( sbc_cpl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' )
365     
366      ! ================================ !
367      !   Define the receive interface   !
368      ! ================================ !
369      nrcvinfo(:) = OASIS_idle   ! needed by nrcvinfo(jpr_otx1) if we do not receive ocean stress
370
371      ! for each field: define the OASIS name                              (srcv(:)%clname)
372      !                 define receive or not from the namelist parameters (srcv(:)%laction)
373      !                 define the north fold type of lbc                  (srcv(:)%nsgn)
374
375      ! default definitions of srcv
376      srcv(:)%laction = .FALSE.   ;   srcv(:)%clgrid = 'T'   ;   srcv(:)%nsgn = 1.   ;   srcv(:)%nct = 1
377
378      !                                                      ! ------------------------- !
379      !                                                      ! ice and ocean wind stress !   
380      !                                                      ! ------------------------- !
381      !                                                           ! Name
382      srcv(jpr_otx1)%clname = 'O_OTaux1'      ! 1st ocean component on grid ONE (T or U)
383      srcv(jpr_oty1)%clname = 'O_OTauy1'      ! 2nd   -      -         -     -
384      srcv(jpr_otz1)%clname = 'O_OTauz1'      ! 3rd   -      -         -     -
385      srcv(jpr_otx2)%clname = 'O_OTaux2'      ! 1st ocean component on grid TWO (V)
386      srcv(jpr_oty2)%clname = 'O_OTauy2'      ! 2nd   -      -         -     -
387      srcv(jpr_otz2)%clname = 'O_OTauz2'      ! 3rd   -      -         -     -
388      !
389      srcv(jpr_itx1)%clname = 'O_ITaux1'      ! 1st  ice  component on grid ONE (T, F, I or U)
390      srcv(jpr_ity1)%clname = 'O_ITauy1'      ! 2nd   -      -         -     -
391      srcv(jpr_itz1)%clname = 'O_ITauz1'      ! 3rd   -      -         -     -
392      srcv(jpr_itx2)%clname = 'O_ITaux2'      ! 1st  ice  component on grid TWO (V)
393      srcv(jpr_ity2)%clname = 'O_ITauy2'      ! 2nd   -      -         -     -
394      srcv(jpr_itz2)%clname = 'O_ITauz2'      ! 3rd   -      -         -     -
395      !
396      ! Vectors: change of sign at north fold ONLY if on the local grid
397      IF(       TRIM( sn_rcv_tau%cldes ) == 'oce only' .OR. TRIM( sn_rcv_tau%cldes ) == 'oce and ice'  &
398           .OR. TRIM( sn_rcv_tau%cldes ) == 'mixed oce-ice' ) THEN ! avoid working with the atmospheric fields if they are not coupled
399      !
400      IF( TRIM( sn_rcv_tau%clvor ) == 'local grid' )   srcv(jpr_otx1:jpr_itz2)%nsgn = -1.
401     
402      !                                                           ! Set grid and action
403      SELECT CASE( TRIM( sn_rcv_tau%clvgrd ) )      !  'T', 'U,V', 'U,V,I', 'U,V,F', 'T,I', 'T,F', or 'T,U,V'
404      CASE( 'T' ) 
405         srcv(jpr_otx1:jpr_itz2)%clgrid  = 'T'        ! oce and ice components given at T-point
406         srcv(jpr_otx1:jpr_otz1)%laction = .TRUE.     ! receive oce components on grid 1
407         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1
408      CASE( 'U,V' ) 
409         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'U'        ! oce components given at U-point
410         srcv(jpr_otx2:jpr_otz2)%clgrid  = 'V'        !           and           V-point
411         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'U'        ! ice components given at U-point
412         srcv(jpr_itx2:jpr_itz2)%clgrid  = 'V'        !           and           V-point
413         srcv(jpr_otx1:jpr_itz2)%laction = .TRUE.     ! receive oce and ice components on both grid 1 & 2
414      CASE( 'U,V,T' )
415         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'U'        ! oce components given at U-point
416         srcv(jpr_otx2:jpr_otz2)%clgrid  = 'V'        !           and           V-point
417         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'T'        ! ice components given at T-point
418         srcv(jpr_otx1:jpr_otz2)%laction = .TRUE.     ! receive oce components on grid 1 & 2
419         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1 only
420      CASE( 'U,V,I' )
421         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'U'        ! oce components given at U-point
422         srcv(jpr_otx2:jpr_otz2)%clgrid  = 'V'        !           and           V-point
423         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'I'        ! ice components given at I-point
424         srcv(jpr_otx1:jpr_otz2)%laction = .TRUE.     ! receive oce components on grid 1 & 2
425         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1 only
426      CASE( 'U,V,F' )
427         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'U'        ! oce components given at U-point
428         srcv(jpr_otx2:jpr_otz2)%clgrid  = 'V'        !           and           V-point
429         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'F'        ! ice components given at F-point
430         srcv(jpr_otx1:jpr_otz2)%laction = .TRUE.     ! receive oce components on grid 1 & 2
431         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1 only
432      CASE( 'T,I' ) 
433         srcv(jpr_otx1:jpr_itz2)%clgrid  = 'T'        ! oce and ice components given at T-point
434         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'I'        ! ice components given at I-point
435         srcv(jpr_otx1:jpr_otz1)%laction = .TRUE.     ! receive oce components on grid 1
436         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1
437      CASE( 'T,F' ) 
438         srcv(jpr_otx1:jpr_itz2)%clgrid  = 'T'        ! oce and ice components given at T-point
439         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'F'        ! ice components given at F-point
440         srcv(jpr_otx1:jpr_otz1)%laction = .TRUE.     ! receive oce components on grid 1
441         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1
442      CASE( 'T,U,V' )
443         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'T'        ! oce components given at T-point
444         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'U'        ! ice components given at U-point
445         srcv(jpr_itx2:jpr_itz2)%clgrid  = 'V'        !           and           V-point
446         srcv(jpr_otx1:jpr_otz1)%laction = .TRUE.     ! receive oce components on grid 1 only
447         srcv(jpr_itx1:jpr_itz2)%laction = .TRUE.     ! receive ice components on grid 1 & 2
448      CASE default   
449         CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_tau%clvgrd' )
450      END SELECT
451      !
452      IF( TRIM( sn_rcv_tau%clvref ) == 'spherical' )   &           ! spherical: 3rd component not received
453         &     srcv( (/jpr_otz1, jpr_otz2, jpr_itz1, jpr_itz2/) )%laction = .FALSE. 
454      !
455      IF( TRIM( sn_rcv_tau%clvor  ) == 'local grid' ) THEN        ! already on local grid -> no need of the second grid
456            srcv(jpr_otx2:jpr_otz2)%laction = .FALSE. 
457            srcv(jpr_itx2:jpr_itz2)%laction = .FALSE. 
458            srcv(jpr_oty1)%clgrid = srcv(jpr_oty2)%clgrid   ! not needed but cleaner...
459            srcv(jpr_ity1)%clgrid = srcv(jpr_ity2)%clgrid   ! not needed but cleaner...
460      ENDIF
461      !
462      IF( TRIM( sn_rcv_tau%cldes ) /= 'oce and ice' ) THEN        ! 'oce and ice' case ocean stress on ocean mesh used
463         srcv(jpr_itx1:jpr_itz2)%laction = .FALSE.    ! ice components not received
464         srcv(jpr_itx1)%clgrid = 'U'                  ! ocean stress used after its transformation
465         srcv(jpr_ity1)%clgrid = 'V'                  ! i.e. it is always at U- & V-points for i- & j-comp. resp.
466      ENDIF
467      ENDIF
468
469      !                                                      ! ------------------------- !
470      !                                                      !    freshwater budget      !   E-P
471      !                                                      ! ------------------------- !
472      ! we suppose that atmosphere modele do not make the difference between precipiration (liquide or solid)
473      ! over ice of free ocean within the same atmospheric cell.cd
474      srcv(jpr_rain)%clname = 'OTotRain'      ! Rain = liquid precipitation
475      srcv(jpr_snow)%clname = 'OTotSnow'      ! Snow = solid precipitation
476      srcv(jpr_tevp)%clname = 'OTotEvap'      ! total evaporation (over oce + ice sublimation)
477      srcv(jpr_ievp)%clname = 'OIceEvap'      ! evaporation over ice = sublimation
478      srcv(jpr_sbpr)%clname = 'OSubMPre'      ! sublimation - liquid precipitation - solid precipitation
479      srcv(jpr_semp)%clname = 'OISubMSn'      ! ice solid water budget = sublimation - solid precipitation
480      srcv(jpr_oemp)%clname = 'OOEvaMPr'      ! ocean water budget = ocean Evap - ocean precip
481      SELECT CASE( TRIM( sn_rcv_emp%cldes ) )
482      CASE( 'none'          )       ! nothing to do
483      CASE( 'oce only'      )   ;   srcv(jpr_oemp)%laction = .TRUE. 
484      CASE( 'conservative'  )
485         srcv( (/jpr_rain, jpr_snow, jpr_ievp, jpr_tevp/) )%laction = .TRUE.
486         IF ( k_ice <= 1 )  srcv(jpr_ievp)%laction = .FALSE.
487      CASE( 'oce and ice'   )   ;   srcv( (/jpr_ievp, jpr_sbpr, jpr_semp, jpr_oemp/) )%laction = .TRUE.
488      CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_emp%cldes' )
489      END SELECT
490      !
491      !                                                      ! ------------------------- !
492      !                                                      !     Runoffs & Calving     !   
493      !                                                      ! ------------------------- !
494      srcv(jpr_rnf   )%clname = 'O_Runoff'
495      IF( TRIM( sn_rcv_rnf%cldes ) == 'coupled' ) THEN
496         srcv(jpr_rnf)%laction = .TRUE.
497         l_rnfcpl              = .TRUE.                      ! -> no need to read runoffs in sbcrnf
498         ln_rnf                = nn_components /= jp_iam_sas ! -> force to go through sbcrnf if not sas
499         IF(lwp) WRITE(numout,*)
500         IF(lwp) WRITE(numout,*) '   runoffs received from oasis -> force ln_rnf = ', ln_rnf
501      ENDIF
502      !
503      srcv(jpr_cal)%clname = 'OCalving'   ;  IF( TRIM( sn_rcv_cal%cldes) == 'coupled' )   srcv(jpr_cal)%laction = .TRUE.
504      srcv(jpr_isf)%clname = 'OIcshelf'   ;  IF( TRIM( sn_rcv_isf%cldes) == 'coupled' )   srcv(jpr_isf)%laction = .TRUE.
505      srcv(jpr_icb)%clname = 'OIceberg'   ;  IF( TRIM( sn_rcv_icb%cldes) == 'coupled' )   srcv(jpr_icb)%laction = .TRUE.
506
507      IF( srcv(jpr_isf)%laction .AND. ln_isf ) THEN
508         l_isfcpl             = .TRUE.                      ! -> no need to read isf in sbcisf
509         IF(lwp) WRITE(numout,*)
510         IF(lwp) WRITE(numout,*) '   iceshelf received from oasis '
511      ENDIF
512      !
513      !                                                      ! ------------------------- !
514      !                                                      !    non solar radiation    !   Qns
515      !                                                      ! ------------------------- !
516      srcv(jpr_qnsoce)%clname = 'O_QnsOce'
517      srcv(jpr_qnsice)%clname = 'O_QnsIce'
518      srcv(jpr_qnsmix)%clname = 'O_QnsMix'
519      SELECT CASE( TRIM( sn_rcv_qns%cldes ) )
520      CASE( 'none'          )       ! nothing to do
521      CASE( 'oce only'      )   ;   srcv(               jpr_qnsoce   )%laction = .TRUE.
522      CASE( 'conservative'  )   ;   srcv( (/jpr_qnsice, jpr_qnsmix/) )%laction = .TRUE.
523      CASE( 'oce and ice'   )   ;   srcv( (/jpr_qnsice, jpr_qnsoce/) )%laction = .TRUE.
524      CASE( 'mixed oce-ice' )   ;   srcv(               jpr_qnsmix   )%laction = .TRUE. 
525      CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_qns%cldes' )
526      END SELECT
527      IF( TRIM( sn_rcv_qns%cldes ) == 'mixed oce-ice' .AND. nn_cats_cpl > 1 ) &
528         CALL ctl_stop( 'sbc_cpl_init: sn_rcv_qns%cldes not currently allowed to be mixed oce-ice for multi-category ice' )
529      !
530      !                                                      ! ------------------------- !
531      !                                                      !    solar radiation        !   Qsr
532      !                                                      ! ------------------------- !
533      srcv(jpr_qsroce)%clname = 'O_QsrOce'
534      srcv(jpr_qsrice)%clname = 'O_QsrIce'
535      srcv(jpr_qsrmix)%clname = 'O_QsrMix'
536      SELECT CASE( TRIM( sn_rcv_qsr%cldes ) )
537      CASE( 'none'          )       ! nothing to do
538      CASE( 'oce only'      )   ;   srcv(               jpr_qsroce   )%laction = .TRUE.
539      CASE( 'conservative'  )   ;   srcv( (/jpr_qsrice, jpr_qsrmix/) )%laction = .TRUE.
540      CASE( 'oce and ice'   )   ;   srcv( (/jpr_qsrice, jpr_qsroce/) )%laction = .TRUE.
541      CASE( 'mixed oce-ice' )   ;   srcv(               jpr_qsrmix   )%laction = .TRUE. 
542      CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_qsr%cldes' )
543      END SELECT
544      IF( TRIM( sn_rcv_qsr%cldes ) == 'mixed oce-ice' .AND. nn_cats_cpl > 1 ) &
545         CALL ctl_stop( 'sbc_cpl_init: sn_rcv_qsr%cldes not currently allowed to be mixed oce-ice for multi-category ice' )
546      !
547      !                                                      ! ------------------------- !
548      !                                                      !   non solar sensitivity   !   d(Qns)/d(T)
549      !                                                      ! ------------------------- !
550      srcv(jpr_dqnsdt)%clname = 'O_dQnsdT'   
551      IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'coupled' )   srcv(jpr_dqnsdt)%laction = .TRUE.
552      !
553      ! non solar sensitivity mandatory for mixed oce-ice solar radiation coupling technique
554      IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'none' .AND. TRIM( sn_rcv_qns%cldes ) == 'mixed oce-ice' )  &
555         &   CALL ctl_stop( 'sbc_cpl_init: namsbc_cpl namelist mismatch between sn_rcv_qns%cldes and sn_rcv_dqnsdt%cldes' )
556      !
557      !                                                      ! ------------------------- !
558      !                                                      !      10m wind module      !   
559      !                                                      ! ------------------------- !
560      srcv(jpr_w10m)%clname = 'O_Wind10'   ;   IF( TRIM(sn_rcv_w10m%cldes  ) == 'coupled' )   srcv(jpr_w10m)%laction = .TRUE. 
561      !
562      !                                                      ! ------------------------- !
563      !                                                      !   wind stress module      !   
564      !                                                      ! ------------------------- !
565      srcv(jpr_taum)%clname = 'O_TauMod'   ;   IF( TRIM(sn_rcv_taumod%cldes) == 'coupled' )   srcv(jpr_taum)%laction = .TRUE.
566      lhftau = srcv(jpr_taum)%laction
567      !
568      !                                                      ! ------------------------- !
569      !                                                      !      Atmospheric CO2      !
570      !                                                      ! ------------------------- !
571      srcv(jpr_co2 )%clname = 'O_AtmCO2'   
572      IF( TRIM(sn_rcv_co2%cldes   ) == 'coupled' )  THEN
573         srcv(jpr_co2 )%laction = .TRUE.
574         l_co2cpl = .TRUE.
575         IF(lwp) WRITE(numout,*)
576         IF(lwp) WRITE(numout,*) '   Atmospheric pco2 received from oasis '
577         IF(lwp) WRITE(numout,*)
578      ENDIF
579      !
580      !                                                      ! ------------------------- !
581      !                                                      ! Mean Sea Level Pressure   !
582      !                                                      ! ------------------------- !
583      srcv(jpr_mslp)%clname = 'O_MSLP'     ;   IF( TRIM(sn_rcv_mslp%cldes  ) == 'coupled' )    srcv(jpr_mslp)%laction = .TRUE. 
584      !
585      !                                                      ! ------------------------- !
586      !                                                      !  ice topmelt and botmelt  !   
587      !                                                      ! ------------------------- !
588      srcv(jpr_topm )%clname = 'OTopMlt'
589      srcv(jpr_botm )%clname = 'OBotMlt'
590      IF( TRIM(sn_rcv_iceflx%cldes) == 'coupled' ) THEN
591         IF ( TRIM( sn_rcv_iceflx%clcat ) == 'yes' ) THEN
592            srcv(jpr_topm:jpr_botm)%nct = nn_cats_cpl
593         ELSE
594            CALL ctl_stop( 'sbc_cpl_init: sn_rcv_iceflx%clcat should always be set to yes currently' )
595         ENDIF
596         srcv(jpr_topm:jpr_botm)%laction = .TRUE.
597      ENDIF
598      !                                                      ! ------------------------- !
599      !                                                      !    transmitted solar      !   
600      !                                                      ! ------------------------- !
601      srcv(jpr_qtr )%clname = 'OQtr'
602      IF( TRIM(sn_rcv_qtr%cldes) == 'coupled' ) THEN
603         IF ( TRIM( sn_rcv_qtr%clcat ) == 'yes' ) THEN
604            srcv(jpr_qtr)%nct = nn_cats_cpl
605         ELSE
606            CALL ctl_stop( 'sbc_cpl_init: sn_rcv_qtr%clcat should always be set to yes currently' )
607         ENDIF
608         srcv(jpr_qtr)%laction = .TRUE.
609      ENDIF
610
611      !                                                      ! ------------------------- !
612      !                                                      !    ice skin temperature   !   
613      !                                                      ! ------------------------- !
614      srcv(jpr_ts_ice)%clname = 'OTsfIce'    ! needed by Met Office
615      IF ( TRIM( sn_rcv_ts_ice%cldes ) == 'ice' )   srcv(jpr_ts_ice)%laction = .TRUE.
616      IF ( TRIM( sn_rcv_ts_ice%clcat ) == 'yes' )   srcv(jpr_ts_ice)%nct     = nn_cats_cpl
617      IF ( TRIM( sn_rcv_emp%clcat    ) == 'yes' )   srcv(jpr_ievp)%nct       = nn_cats_cpl
618
619#if defined key_si3
620      IF( ln_cndflx .AND. .NOT.ln_cndemulate ) THEN
621         IF( .NOT.srcv(jpr_ts_ice)%laction )  &
622            &   CALL ctl_stop( 'sbc_cpl_init: srcv(jpr_ts_ice)%laction should be set to true when ln_cndflx=T' )     
623      ENDIF
624#endif
625      !                                                      ! ------------------------- !
626      !                                                      !      Wave breaking        !   
627      !                                                      ! ------------------------- !
628      srcv(jpr_hsig)%clname  = 'O_Hsigwa'    ! significant wave height
629      IF( TRIM(sn_rcv_hsig%cldes  ) == 'coupled' )  THEN
630         srcv(jpr_hsig)%laction = .TRUE.
631         cpl_hsig = .TRUE.
632      ENDIF
633      srcv(jpr_phioc)%clname = 'O_PhiOce'    ! wave to ocean energy
634      IF( TRIM(sn_rcv_phioc%cldes ) == 'coupled' )  THEN
635         srcv(jpr_phioc)%laction = .TRUE.
636         cpl_phioc = .TRUE.
637      ENDIF
638      srcv(jpr_sdrftx)%clname = 'O_Sdrfx'    ! Stokes drift in the u direction
639      IF( TRIM(sn_rcv_sdrfx%cldes ) == 'coupled' )  THEN
640         srcv(jpr_sdrftx)%laction = .TRUE.
641         cpl_sdrftx = .TRUE.
642      ENDIF
643      srcv(jpr_sdrfty)%clname = 'O_Sdrfy'    ! Stokes drift in the v direction
644      IF( TRIM(sn_rcv_sdrfy%cldes ) == 'coupled' )  THEN
645         srcv(jpr_sdrfty)%laction = .TRUE.
646         cpl_sdrfty = .TRUE.
647      ENDIF
648      srcv(jpr_wper)%clname = 'O_WPer'       ! mean wave period
649      IF( TRIM(sn_rcv_wper%cldes  ) == 'coupled' )  THEN
650         srcv(jpr_wper)%laction = .TRUE.
651         cpl_wper = .TRUE.
652      ENDIF
653      srcv(jpr_wfreq)%clname = 'O_WFreq'     ! wave peak frequency
654      IF( TRIM(sn_rcv_wfreq%cldes ) == 'coupled' )  THEN
655         srcv(jpr_wfreq)%laction = .TRUE.
656         cpl_wfreq = .TRUE.
657      ENDIF
658      srcv(jpr_wnum)%clname = 'O_WNum'       ! mean wave number
659      IF( TRIM(sn_rcv_wnum%cldes ) == 'coupled' )  THEN
660         srcv(jpr_wnum)%laction = .TRUE.
661         cpl_wnum = .TRUE.
662      ENDIF
663      srcv(jpr_tauwoc)%clname = 'O_TauOce'   ! stress fraction adsorbed by the wave
664      IF( TRIM(sn_rcv_tauwoc%cldes ) == 'coupled' )  THEN
665         srcv(jpr_tauwoc)%laction = .TRUE.
666         cpl_tauwoc = .TRUE.
667      ENDIF
668      srcv(jpr_tauwx)%clname = 'O_Tauwx'      ! ocean stress from wave in the x direction
669      srcv(jpr_tauwy)%clname = 'O_Tauwy'      ! ocean stress from wave in the y direction
670      IF( TRIM(sn_rcv_tauw%cldes ) == 'coupled' )  THEN
671         srcv(jpr_tauwx)%laction = .TRUE.
672         srcv(jpr_tauwy)%laction = .TRUE.
673         cpl_tauw = .TRUE.
674      ENDIF
675      srcv(jpr_wdrag)%clname = 'O_WDrag'     ! neutral surface drag coefficient
676      IF( TRIM(sn_rcv_wdrag%cldes ) == 'coupled' )  THEN
677         srcv(jpr_wdrag)%laction = .TRUE.
678         cpl_wdrag = .TRUE.
679      ENDIF
680      IF( srcv(jpr_tauwoc)%laction .AND. srcv(jpr_tauwx)%laction .AND. srcv(jpr_tauwy)%laction ) &
681            CALL ctl_stop( 'More than one method for modifying the ocean stress has been selected ', &
682                                     '(sn_rcv_tauwoc=coupled and sn_rcv_tauw=coupled)' )
683      !
684      !                                                      ! ------------------------------- !
685      !                                                      !   OPA-SAS coupling - rcv by opa !   
686      !                                                      ! ------------------------------- !
687      srcv(jpr_sflx)%clname = 'O_SFLX'
688      srcv(jpr_fice)%clname = 'RIceFrc'
689      !
690      IF( nn_components == jp_iam_opa ) THEN    ! OPA coupled to SAS via OASIS: force received field by OPA (sent by SAS)
691         srcv(:)%laction = .FALSE.   ! force default definition in case of opa <-> sas coupling
692         srcv(:)%clgrid  = 'T'       ! force default definition in case of opa <-> sas coupling
693         srcv(:)%nsgn    = 1.        ! force default definition in case of opa <-> sas coupling
694         srcv( (/jpr_qsroce, jpr_qnsoce, jpr_oemp, jpr_sflx, jpr_fice, jpr_otx1, jpr_oty1, jpr_taum/) )%laction = .TRUE.
695         srcv(jpr_otx1)%clgrid = 'U'        ! oce components given at U-point
696         srcv(jpr_oty1)%clgrid = 'V'        !           and           V-point
697         ! Vectors: change of sign at north fold ONLY if on the local grid
698         srcv( (/jpr_otx1,jpr_oty1/) )%nsgn = -1.
699         sn_rcv_tau%clvgrd = 'U,V'
700         sn_rcv_tau%clvor = 'local grid'
701         sn_rcv_tau%clvref = 'spherical'
702         sn_rcv_emp%cldes = 'oce only'
703         !
704         IF(lwp) THEN                        ! control print
705            WRITE(numout,*)
706            WRITE(numout,*)'               Special conditions for SAS-OPA coupling  '
707            WRITE(numout,*)'               OPA component  '
708            WRITE(numout,*)
709            WRITE(numout,*)'  received fields from SAS component '
710            WRITE(numout,*)'                  ice cover '
711            WRITE(numout,*)'                  oce only EMP  '
712            WRITE(numout,*)'                  salt flux  '
713            WRITE(numout,*)'                  mixed oce-ice solar flux  '
714            WRITE(numout,*)'                  mixed oce-ice non solar flux  '
715            WRITE(numout,*)'                  wind stress U,V on local grid and sperical coordinates '
716            WRITE(numout,*)'                  wind stress module'
717            WRITE(numout,*)
718         ENDIF
719      ENDIF
720      !                                                      ! -------------------------------- !
721      !                                                      !   OPA-SAS coupling - rcv by sas  !   
722      !                                                      ! -------------------------------- !
723      srcv(jpr_toce  )%clname = 'I_SSTSST'
724      srcv(jpr_soce  )%clname = 'I_SSSal'
725      srcv(jpr_ocx1  )%clname = 'I_OCurx1'
726      srcv(jpr_ocy1  )%clname = 'I_OCury1'
727      srcv(jpr_ssh   )%clname = 'I_SSHght'
728      srcv(jpr_e3t1st)%clname = 'I_E3T1st'   
729      srcv(jpr_fraqsr)%clname = 'I_FraQsr'   
730      !
731      IF( nn_components == jp_iam_sas ) THEN
732         IF( .NOT. ln_cpl ) srcv(:)%laction = .FALSE.   ! force default definition in case of opa <-> sas coupling
733         IF( .NOT. ln_cpl ) srcv(:)%clgrid  = 'T'       ! force default definition in case of opa <-> sas coupling
734         IF( .NOT. ln_cpl ) srcv(:)%nsgn    = 1.        ! force default definition in case of opa <-> sas coupling
735         srcv( (/jpr_toce, jpr_soce, jpr_ssh, jpr_fraqsr, jpr_ocx1, jpr_ocy1/) )%laction = .TRUE.
736         srcv( jpr_e3t1st )%laction = .NOT.ln_linssh
737         srcv(jpr_ocx1)%clgrid = 'U'        ! oce components given at U-point
738         srcv(jpr_ocy1)%clgrid = 'V'        !           and           V-point
739         ! Vectors: change of sign at north fold ONLY if on the local grid
740         srcv(jpr_ocx1:jpr_ocy1)%nsgn = -1.
741         ! Change first letter to couple with atmosphere if already coupled OPA
742         ! this is nedeed as each variable name used in the namcouple must be unique:
743         ! for example O_Runoff received by OPA from SAS and therefore O_Runoff received by SAS from the Atmosphere
744         DO jn = 1, jprcv
745            IF ( srcv(jn)%clname(1:1) == "O" ) srcv(jn)%clname = "S"//srcv(jn)%clname(2:LEN(srcv(jn)%clname))
746         END DO
747         !
748         IF(lwp) THEN                        ! control print
749            WRITE(numout,*)
750            WRITE(numout,*)'               Special conditions for SAS-OPA coupling  '
751            WRITE(numout,*)'               SAS component  '
752            WRITE(numout,*)
753            IF( .NOT. ln_cpl ) THEN
754               WRITE(numout,*)'  received fields from OPA component '
755            ELSE
756               WRITE(numout,*)'  Additional received fields from OPA component : '
757            ENDIF
758            WRITE(numout,*)'               sea surface temperature (Celsius) '
759            WRITE(numout,*)'               sea surface salinity ' 
760            WRITE(numout,*)'               surface currents ' 
761            WRITE(numout,*)'               sea surface height ' 
762            WRITE(numout,*)'               thickness of first ocean T level '       
763            WRITE(numout,*)'               fraction of solar net radiation absorbed in the first ocean level'
764            WRITE(numout,*)
765         ENDIF
766      ENDIF
767     
768      ! =================================================== !
769      ! Allocate all parts of frcv used for received fields !
770      ! =================================================== !
771      DO jn = 1, jprcv
772         IF ( srcv(jn)%laction ) ALLOCATE( frcv(jn)%z3(jpi,jpj,srcv(jn)%nct) )
773      END DO
774      ! Allocate taum part of frcv which is used even when not received as coupling field
775      IF ( .NOT. srcv(jpr_taum)%laction ) ALLOCATE( frcv(jpr_taum)%z3(jpi,jpj,srcv(jpr_taum)%nct) )
776      ! Allocate w10m part of frcv which is used even when not received as coupling field
777      IF ( .NOT. srcv(jpr_w10m)%laction ) ALLOCATE( frcv(jpr_w10m)%z3(jpi,jpj,srcv(jpr_w10m)%nct) )
778      ! Allocate jpr_otx1 part of frcv which is used even when not received as coupling field
779      IF ( .NOT. srcv(jpr_otx1)%laction ) ALLOCATE( frcv(jpr_otx1)%z3(jpi,jpj,srcv(jpr_otx1)%nct) )
780      IF ( .NOT. srcv(jpr_oty1)%laction ) ALLOCATE( frcv(jpr_oty1)%z3(jpi,jpj,srcv(jpr_oty1)%nct) )
781      ! Allocate itx1 and ity1 as they are used in sbc_cpl_ice_tau even if srcv(jpr_itx1)%laction = .FALSE.
782      IF( k_ice /= 0 ) THEN
783         IF ( .NOT. srcv(jpr_itx1)%laction ) ALLOCATE( frcv(jpr_itx1)%z3(jpi,jpj,srcv(jpr_itx1)%nct) )
784         IF ( .NOT. srcv(jpr_ity1)%laction ) ALLOCATE( frcv(jpr_ity1)%z3(jpi,jpj,srcv(jpr_ity1)%nct) )
785      END IF
786
787      ! ================================ !
788      !     Define the send interface    !
789      ! ================================ !
790      ! for each field: define the OASIS name                           (ssnd(:)%clname)
791      !                 define send or not from the namelist parameters (ssnd(:)%laction)
792      !                 define the north fold type of lbc               (ssnd(:)%nsgn)
793     
794      ! default definitions of nsnd
795      ssnd(:)%laction = .FALSE.   ;   ssnd(:)%clgrid = 'T'   ;   ssnd(:)%nsgn = 1.  ; ssnd(:)%nct = 1
796         
797      !                                                      ! ------------------------- !
798      !                                                      !    Surface temperature    !
799      !                                                      ! ------------------------- !
800      ssnd(jps_toce)%clname   = 'O_SSTSST'
801      ssnd(jps_tice)%clname   = 'O_TepIce'
802      ssnd(jps_ttilyr)%clname = 'O_TtiLyr'
803      ssnd(jps_tmix)%clname   = 'O_TepMix'
804      SELECT CASE( TRIM( sn_snd_temp%cldes ) )
805      CASE( 'none'                                 )       ! nothing to do
806      CASE( 'oce only'                             )   ;   ssnd( jps_toce )%laction = .TRUE.
807      CASE( 'oce and ice' , 'weighted oce and ice' , 'oce and weighted ice' )
808         ssnd( (/jps_toce, jps_tice/) )%laction = .TRUE.
809         IF ( TRIM( sn_snd_temp%clcat ) == 'yes' )  ssnd(jps_tice)%nct = nn_cats_cpl
810      CASE( 'mixed oce-ice'                        )   ;   ssnd( jps_tmix )%laction = .TRUE.
811      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_temp%cldes' )
812      END SELECT
813           
814      !                                                      ! ------------------------- !
815      !                                                      !          Albedo           !
816      !                                                      ! ------------------------- !
817      ssnd(jps_albice)%clname = 'O_AlbIce' 
818      ssnd(jps_albmix)%clname = 'O_AlbMix'
819      SELECT CASE( TRIM( sn_snd_alb%cldes ) )
820      CASE( 'none'                 )     ! nothing to do
821      CASE( 'ice' , 'weighted ice' )   ; ssnd(jps_albice)%laction = .TRUE.
822      CASE( 'mixed oce-ice'        )   ; ssnd(jps_albmix)%laction = .TRUE.
823      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_alb%cldes' )
824      END SELECT
825      !
826      ! Need to calculate oceanic albedo if
827      !     1. sending mixed oce-ice albedo or
828      !     2. receiving mixed oce-ice solar radiation
829      IF ( TRIM ( sn_snd_alb%cldes ) == 'mixed oce-ice' .OR. TRIM ( sn_rcv_qsr%cldes ) == 'mixed oce-ice' ) THEN
830         CALL oce_alb( zaos, zacs )
831         ! Due to lack of information on nebulosity : mean clear/overcast sky
832         alb_oce_mix(:,:) = ( zacs(:,:) + zaos(:,:) ) * 0.5
833      ENDIF
834      !                                                      ! ------------------------- !
835      !                                                      !  Ice fraction & Thickness !
836      !                                                      ! ------------------------- !
837      ssnd(jps_fice)%clname  = 'OIceFrc'
838      ssnd(jps_ficet)%clname = 'OIceFrcT' 
839      ssnd(jps_hice)%clname  = 'OIceTck'
840      ssnd(jps_a_p)%clname   = 'OPndFrc'
841      ssnd(jps_ht_p)%clname  = 'OPndTck'
842      ssnd(jps_hsnw)%clname  = 'OSnwTck'
843      ssnd(jps_fice1)%clname = 'OIceFrd'
844      IF( k_ice /= 0 ) THEN
845         ssnd(jps_fice)%laction  = .TRUE.                 ! if ice treated in the ocean (even in climato case)
846         ssnd(jps_fice1)%laction = .TRUE.                 ! First-order regridded ice concentration, to be used producing atmos-to-ice fluxes (Met Office requirement)
847! Currently no namelist entry to determine sending of multi-category ice fraction so use the thickness entry for now
848         IF ( TRIM( sn_snd_thick%clcat  ) == 'yes' ) ssnd(jps_fice)%nct  = nn_cats_cpl
849         IF ( TRIM( sn_snd_thick1%clcat ) == 'yes' ) ssnd(jps_fice1)%nct = nn_cats_cpl
850      ENDIF
851     
852      IF (TRIM( sn_snd_ifrac%cldes )  == 'coupled') ssnd(jps_ficet)%laction = .TRUE. 
853
854      SELECT CASE ( TRIM( sn_snd_thick%cldes ) )
855      CASE( 'none'         )       ! nothing to do
856      CASE( 'ice and snow' ) 
857         ssnd(jps_hice:jps_hsnw)%laction = .TRUE.
858         IF ( TRIM( sn_snd_thick%clcat ) == 'yes' ) THEN
859            ssnd(jps_hice:jps_hsnw)%nct = nn_cats_cpl
860         ENDIF
861      CASE ( 'weighted ice and snow' ) 
862         ssnd(jps_hice:jps_hsnw)%laction = .TRUE.
863         IF ( TRIM( sn_snd_thick%clcat ) == 'yes' ) ssnd(jps_hice:jps_hsnw)%nct = nn_cats_cpl
864      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_thick%cldes' )
865      END SELECT
866
867      ! Initialise ice fractions from last coupling time to zero (needed by Met-Office)
868#if defined key_si3 || defined key_cice
869       a_i_last_couple(:,:,:) = 0._wp
870#endif
871      !                                                      ! ------------------------- !
872      !                                                      !      Ice Meltponds        !
873      !                                                      ! ------------------------- !
874      ! Needed by Met Office
875      ssnd(jps_a_p)%clname  = 'OPndFrc'   
876      ssnd(jps_ht_p)%clname = 'OPndTck'   
877      SELECT CASE ( TRIM( sn_snd_mpnd%cldes ) ) 
878      CASE ( 'none' ) 
879         ssnd(jps_a_p)%laction  = .FALSE. 
880         ssnd(jps_ht_p)%laction = .FALSE. 
881      CASE ( 'ice only' ) 
882         ssnd(jps_a_p)%laction  = .TRUE. 
883         ssnd(jps_ht_p)%laction = .TRUE. 
884         IF ( TRIM( sn_snd_mpnd%clcat ) == 'yes' ) THEN
885            ssnd(jps_a_p)%nct  = nn_cats_cpl 
886            ssnd(jps_ht_p)%nct = nn_cats_cpl 
887         ELSE
888            IF ( nn_cats_cpl > 1 ) THEN
889               CALL ctl_stop( 'sbc_cpl_init: use weighted ice option for sn_snd_mpnd%cldes if not exchanging category fields' ) 
890            ENDIF
891         ENDIF
892      CASE ( 'weighted ice' ) 
893         ssnd(jps_a_p)%laction  = .TRUE. 
894         ssnd(jps_ht_p)%laction = .TRUE. 
895         IF ( TRIM( sn_snd_mpnd%clcat ) == 'yes' ) THEN
896            ssnd(jps_a_p)%nct  = nn_cats_cpl 
897            ssnd(jps_ht_p)%nct = nn_cats_cpl 
898         ENDIF
899      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_mpnd%cldes; '//sn_snd_mpnd%cldes ) 
900      END SELECT 
901 
902      !                                                      ! ------------------------- !
903      !                                                      !      Surface current      !
904      !                                                      ! ------------------------- !
905      !        ocean currents              !            ice velocities
906      ssnd(jps_ocx1)%clname = 'O_OCurx1'   ;   ssnd(jps_ivx1)%clname = 'O_IVelx1'
907      ssnd(jps_ocy1)%clname = 'O_OCury1'   ;   ssnd(jps_ivy1)%clname = 'O_IVely1'
908      ssnd(jps_ocz1)%clname = 'O_OCurz1'   ;   ssnd(jps_ivz1)%clname = 'O_IVelz1'
909      ssnd(jps_ocxw)%clname = 'O_OCurxw' 
910      ssnd(jps_ocyw)%clname = 'O_OCuryw' 
911      !
912      ssnd(jps_ocx1:jps_ivz1)%nsgn = -1.   ! vectors: change of the sign at the north fold
913
914      IF( sn_snd_crt%clvgrd == 'U,V' ) THEN
915         ssnd(jps_ocx1)%clgrid = 'U' ; ssnd(jps_ocy1)%clgrid = 'V'
916      ELSE IF( sn_snd_crt%clvgrd /= 'T' ) THEN 
917         CALL ctl_stop( 'sn_snd_crt%clvgrd must be equal to T' )
918      ENDIF
919      ssnd(jps_ocx1:jps_ivz1)%laction = .TRUE.   ! default: all are send
920      IF( TRIM( sn_snd_crt%clvref ) == 'spherical' )   ssnd( (/jps_ocz1, jps_ivz1/) )%laction = .FALSE. 
921      IF( TRIM( sn_snd_crt%clvor ) == 'eastward-northward' ) ssnd(jps_ocx1:jps_ivz1)%nsgn = 1.
922      SELECT CASE( TRIM( sn_snd_crt%cldes ) )
923      CASE( 'none'                 )   ;   ssnd(jps_ocx1:jps_ivz1)%laction = .FALSE.
924      CASE( 'oce only'             )   ;   ssnd(jps_ivx1:jps_ivz1)%laction = .FALSE.
925      CASE( 'weighted oce and ice' )   !   nothing to do
926      CASE( 'mixed oce-ice'        )   ;   ssnd(jps_ivx1:jps_ivz1)%laction = .FALSE.
927      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_crt%cldes' )
928      END SELECT
929
930      ssnd(jps_ocxw:jps_ocyw)%nsgn = -1.   ! vectors: change of the sign at the north fold
931       
932      IF( sn_snd_crtw%clvgrd == 'U,V' ) THEN
933         ssnd(jps_ocxw)%clgrid = 'U' ; ssnd(jps_ocyw)%clgrid = 'V' 
934      ELSE IF( sn_snd_crtw%clvgrd /= 'T' ) THEN
935         CALL ctl_stop( 'sn_snd_crtw%clvgrd must be equal to T' ) 
936      ENDIF
937      IF( TRIM( sn_snd_crtw%clvor ) == 'eastward-northward' ) ssnd(jps_ocxw:jps_ocyw)%nsgn = 1. 
938      SELECT CASE( TRIM( sn_snd_crtw%cldes ) ) 
939         CASE( 'none'                 )   ; ssnd(jps_ocxw:jps_ocyw)%laction = .FALSE. 
940         CASE( 'oce only'             )   ; ssnd(jps_ocxw:jps_ocyw)%laction = .TRUE. 
941         CASE( 'weighted oce and ice' )   !   nothing to do
942         CASE( 'mixed oce-ice'        )   ; ssnd(jps_ivx1:jps_ivz1)%laction = .FALSE. 
943         CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_crtw%cldes' ) 
944      END SELECT 
945
946      !                                                      ! ------------------------- !
947      !                                                      !          CO2 flux         !
948      !                                                      ! ------------------------- !
949      ssnd(jps_co2)%clname = 'O_CO2FLX' ;  IF( TRIM(sn_snd_co2%cldes) == 'coupled' )    ssnd(jps_co2 )%laction = .TRUE.
950      !
951      !                                                      ! ------------------------- !
952      !                                                      ! Sea surface freezing temp !
953      !                                                      ! ------------------------- !
954      ! needed by Met Office
955      ssnd(jps_sstfrz)%clname = 'O_SSTFrz' ; IF( TRIM(sn_snd_sstfrz%cldes) == 'coupled' )  ssnd(jps_sstfrz)%laction = .TRUE. 
956      !
957      !                                                      ! ------------------------- !
958      !                                                      !    Ice conductivity       !
959      !                                                      ! ------------------------- !
960      ! needed by Met Office
961      ! Note that ultimately we will move to passing an ocean effective conductivity as well so there
962      ! will be some changes to the parts of the code which currently relate only to ice conductivity
963      ssnd(jps_ttilyr )%clname = 'O_TtiLyr' 
964      SELECT CASE ( TRIM( sn_snd_ttilyr%cldes ) ) 
965      CASE ( 'none' ) 
966         ssnd(jps_ttilyr)%laction = .FALSE. 
967      CASE ( 'ice only' ) 
968         ssnd(jps_ttilyr)%laction = .TRUE. 
969         IF ( TRIM( sn_snd_ttilyr%clcat ) == 'yes' ) THEN
970            ssnd(jps_ttilyr)%nct = nn_cats_cpl 
971         ELSE
972            IF ( nn_cats_cpl > 1 ) THEN
973               CALL ctl_stop( 'sbc_cpl_init: use weighted ice option for sn_snd_ttilyr%cldes if not exchanging category fields' ) 
974            ENDIF
975         ENDIF
976      CASE ( 'weighted ice' ) 
977         ssnd(jps_ttilyr)%laction = .TRUE. 
978         IF ( TRIM( sn_snd_ttilyr%clcat ) == 'yes' ) ssnd(jps_ttilyr)%nct = nn_cats_cpl 
979      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_ttilyr%cldes;'//sn_snd_ttilyr%cldes ) 
980      END SELECT
981
982      ssnd(jps_kice )%clname = 'OIceKn' 
983      SELECT CASE ( TRIM( sn_snd_cond%cldes ) ) 
984      CASE ( 'none' ) 
985         ssnd(jps_kice)%laction = .FALSE. 
986      CASE ( 'ice only' ) 
987         ssnd(jps_kice)%laction = .TRUE. 
988         IF ( TRIM( sn_snd_cond%clcat ) == 'yes' ) THEN
989            ssnd(jps_kice)%nct = nn_cats_cpl 
990         ELSE
991            IF ( nn_cats_cpl > 1 ) THEN
992               CALL ctl_stop( 'sbc_cpl_init: use weighted ice option for sn_snd_cond%cldes if not exchanging category fields' ) 
993            ENDIF
994         ENDIF
995      CASE ( 'weighted ice' ) 
996         ssnd(jps_kice)%laction = .TRUE. 
997         IF ( TRIM( sn_snd_cond%clcat ) == 'yes' ) ssnd(jps_kice)%nct = nn_cats_cpl 
998      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_cond%cldes;'//sn_snd_cond%cldes ) 
999      END SELECT 
1000      !
1001      !                                                      ! ------------------------- !
1002      !                                                      !     Sea surface height    !
1003      !                                                      ! ------------------------- !
1004      ssnd(jps_wlev)%clname = 'O_Wlevel' ;  IF( TRIM(sn_snd_wlev%cldes) == 'coupled' )   ssnd(jps_wlev)%laction = .TRUE. 
1005
1006      !                                                      ! ------------------------------- !
1007      !                                                      !   OPA-SAS coupling - snd by opa !   
1008      !                                                      ! ------------------------------- !
1009      ssnd(jps_ssh   )%clname = 'O_SSHght' 
1010      ssnd(jps_soce  )%clname = 'O_SSSal' 
1011      ssnd(jps_e3t1st)%clname = 'O_E3T1st'   
1012      ssnd(jps_fraqsr)%clname = 'O_FraQsr'
1013      !
1014      IF( nn_components == jp_iam_opa ) THEN
1015         ssnd(:)%laction = .FALSE.   ! force default definition in case of opa <-> sas coupling
1016         ssnd( (/jps_toce, jps_soce, jps_ssh, jps_fraqsr, jps_ocx1, jps_ocy1/) )%laction = .TRUE.
1017         ssnd( jps_e3t1st )%laction = .NOT.ln_linssh
1018         ! vector definition: not used but cleaner...
1019         ssnd(jps_ocx1)%clgrid  = 'U'        ! oce components given at U-point
1020         ssnd(jps_ocy1)%clgrid  = 'V'        !           and           V-point
1021         sn_snd_crt%clvgrd = 'U,V'
1022         sn_snd_crt%clvor = 'local grid'
1023         sn_snd_crt%clvref = 'spherical'
1024         !
1025         IF(lwp) THEN                        ! control print
1026            WRITE(numout,*)
1027            WRITE(numout,*)'  sent fields to SAS component '
1028            WRITE(numout,*)'               sea surface temperature (T before, Celsius) '
1029            WRITE(numout,*)'               sea surface salinity ' 
1030            WRITE(numout,*)'               surface currents U,V on local grid and spherical coordinates' 
1031            WRITE(numout,*)'               sea surface height ' 
1032            WRITE(numout,*)'               thickness of first ocean T level '       
1033            WRITE(numout,*)'               fraction of solar net radiation absorbed in the first ocean level'
1034            WRITE(numout,*)
1035         ENDIF
1036      ENDIF
1037      !                                                      ! ------------------------------- !
1038      !                                                      !   OPA-SAS coupling - snd by sas !   
1039      !                                                      ! ------------------------------- !
1040      ssnd(jps_sflx  )%clname = 'I_SFLX'     
1041      ssnd(jps_fice2 )%clname = 'IIceFrc'
1042      ssnd(jps_qsroce)%clname = 'I_QsrOce'   
1043      ssnd(jps_qnsoce)%clname = 'I_QnsOce'   
1044      ssnd(jps_oemp  )%clname = 'IOEvaMPr' 
1045      ssnd(jps_otx1  )%clname = 'I_OTaux1'   
1046      ssnd(jps_oty1  )%clname = 'I_OTauy1'   
1047      ssnd(jps_rnf   )%clname = 'I_Runoff'   
1048      ssnd(jps_taum  )%clname = 'I_TauMod'   
1049      !
1050      IF( nn_components == jp_iam_sas ) THEN
1051         IF( .NOT. ln_cpl ) ssnd(:)%laction = .FALSE.   ! force default definition in case of opa <-> sas coupling
1052         ssnd( (/jps_qsroce, jps_qnsoce, jps_oemp, jps_fice2, jps_sflx, jps_otx1, jps_oty1, jps_taum/) )%laction = .TRUE.
1053         !
1054         ! Change first letter to couple with atmosphere if already coupled with sea_ice
1055         ! this is nedeed as each variable name used in the namcouple must be unique:
1056         ! for example O_SSTSST sent by OPA to SAS and therefore S_SSTSST sent by SAS to the Atmosphere
1057         DO jn = 1, jpsnd
1058            IF ( ssnd(jn)%clname(1:1) == "O" ) ssnd(jn)%clname = "S"//ssnd(jn)%clname(2:LEN(ssnd(jn)%clname))
1059         END DO
1060         !
1061         IF(lwp) THEN                        ! control print
1062            WRITE(numout,*)
1063            IF( .NOT. ln_cpl ) THEN
1064               WRITE(numout,*)'  sent fields to OPA component '
1065            ELSE
1066               WRITE(numout,*)'  Additional sent fields to OPA component : '
1067            ENDIF
1068            WRITE(numout,*)'                  ice cover '
1069            WRITE(numout,*)'                  oce only EMP  '
1070            WRITE(numout,*)'                  salt flux  '
1071            WRITE(numout,*)'                  mixed oce-ice solar flux  '
1072            WRITE(numout,*)'                  mixed oce-ice non solar flux  '
1073            WRITE(numout,*)'                  wind stress U,V components'
1074            WRITE(numout,*)'                  wind stress module'
1075         ENDIF
1076      ENDIF
1077
1078      !
1079      ! ================================ !
1080      !   initialisation of the coupler  !
1081      ! ================================ !
1082
1083      CALL cpl_define(jprcv, jpsnd, nn_cplmodel)
1084     
1085      IF (ln_usecplmask) THEN
1086         xcplmask(:,:,:) = 0.
1087         CALL iom_open( 'cplmask', inum )
1088         CALL iom_get( inum, jpdom_unknown, 'cplmask', xcplmask(1:nlci,1:nlcj,1:nn_cplmodel),   &
1089            &          kstart = (/ mig(1),mjg(1),1 /), kcount = (/ nlci,nlcj,nn_cplmodel /) )
1090         CALL iom_close( inum )
1091      ELSE
1092         xcplmask(:,:,:) = 1.
1093      ENDIF
1094      xcplmask(:,:,0) = 1. - SUM( xcplmask(:,:,1:nn_cplmodel), dim = 3 )
1095      !
1096   END SUBROUTINE sbc_cpl_init
1097
1098
1099   SUBROUTINE sbc_cpl_rcv( kt, k_fsbc, k_ice )     
1100      !!----------------------------------------------------------------------
1101      !!             ***  ROUTINE sbc_cpl_rcv  ***
1102      !!
1103      !! ** Purpose :   provide the stress over the ocean and, if no sea-ice,
1104      !!                provide the ocean heat and freshwater fluxes.
1105      !!
1106      !! ** Method  : - Receive all the atmospheric fields (stored in frcv array). called at each time step.
1107      !!                OASIS controls if there is something do receive or not. nrcvinfo contains the info
1108      !!                to know if the field was really received or not
1109      !!
1110      !!              --> If ocean stress was really received:
1111      !!
1112      !!                  - transform the received ocean stress vector from the received
1113      !!                 referential and grid into an atmosphere-ocean stress in
1114      !!                 the (i,j) ocean referencial and at the ocean velocity point.
1115      !!                    The received stress are :
1116      !!                     - defined by 3 components (if cartesian coordinate)
1117      !!                            or by 2 components (if spherical)
1118      !!                     - oriented along geographical   coordinate (if eastward-northward)
1119      !!                            or  along the local grid coordinate (if local grid)
1120      !!                     - given at U- and V-point, resp.   if received on 2 grids
1121      !!                            or at T-point               if received on 1 grid
1122      !!                    Therefore and if necessary, they are successively
1123      !!                  processed in order to obtain them
1124      !!                     first  as  2 components on the sphere
1125      !!                     second as  2 components oriented along the local grid
1126      !!                     third  as  2 components on the U,V grid
1127      !!
1128      !!              -->
1129      !!
1130      !!              - In 'ocean only' case, non solar and solar ocean heat fluxes
1131      !!             and total ocean freshwater fluxes 
1132      !!
1133      !! ** Method  :   receive all fields from the atmosphere and transform
1134      !!              them into ocean surface boundary condition fields
1135      !!
1136      !! ** Action  :   update  utau, vtau   ocean stress at U,V grid
1137      !!                        taum         wind stress module at T-point
1138      !!                        wndm         wind speed  module at T-point over free ocean or leads in presence of sea-ice
1139      !!                        qns          non solar heat fluxes including emp heat content    (ocean only case)
1140      !!                                     and the latent heat flux of solid precip. melting
1141      !!                        qsr          solar ocean heat fluxes   (ocean only case)
1142      !!                        emp          upward mass flux [evap. - precip. (- runoffs) (- calving)] (ocean only case)
1143      !!----------------------------------------------------------------------
1144      USE zdf_oce,  ONLY :   ln_zdfswm
1145      !
1146      INTEGER, INTENT(in) ::   kt          ! ocean model time step index
1147      INTEGER, INTENT(in) ::   k_fsbc      ! frequency of sbc (-> ice model) computation
1148      INTEGER, INTENT(in) ::   k_ice       ! ice management in the sbc (=0/1/2/3)
1149      !!
1150      LOGICAL  ::   llnewtx, llnewtau      ! update wind stress components and module??
1151      INTEGER  ::   ji, jj, jn             ! dummy loop indices
1152      INTEGER  ::   isec                   ! number of seconds since nit000 (assuming rdt did not change since nit000)
1153      REAL(wp) ::   zcumulneg, zcumulpos   ! temporary scalars     
1154      REAL(wp) ::   zcoef                  ! temporary scalar
1155      REAL(wp) ::   zrhoa  = 1.22          ! Air density kg/m3
1156      REAL(wp) ::   zcdrag = 1.5e-3        ! drag coefficient
1157      REAL(wp) ::   zzx, zzy               ! temporary variables
1158      REAL(wp), DIMENSION(jpi,jpj) ::   ztx, zty, zmsk, zemp, zqns, zqsr, zcloud_fra
1159      !!----------------------------------------------------------------------
1160      !
1161      IF( kt == nit000 ) THEN
1162      !   cannot be done in the init phase when we use agrif as cpl_freq requires that oasis_enddef is done
1163         ncpl_qsr_freq = cpl_freq( 'O_QsrOce' ) + cpl_freq( 'O_QsrMix' ) + cpl_freq( 'I_QsrOce' ) + cpl_freq( 'I_QsrMix' )
1164         IF( ln_dm2dc .AND. ncpl_qsr_freq /= 86400 )   &
1165            &   CALL ctl_stop( 'sbc_cpl_rcv: diurnal cycle reconstruction (ln_dm2dc) needs daily couping for solar radiation' )
1166         ncpl_qsr_freq = 86400 / ncpl_qsr_freq   ! used by top
1167      ENDIF
1168      !
1169      IF( ln_mixcpl )   zmsk(:,:) = 1. - xcplmask(:,:,0)
1170      !
1171      !                                                      ! ======================================================= !
1172      !                                                      ! Receive all the atmos. fields (including ice information)
1173      !                                                      ! ======================================================= !
1174      isec = ( kt - nit000 ) * NINT( rdt )                      ! date of exchanges
1175      DO jn = 1, jprcv                                          ! received fields sent by the atmosphere
1176         IF( srcv(jn)%laction )   CALL cpl_rcv( jn, isec, frcv(jn)%z3, xcplmask(:,:,1:nn_cplmodel), nrcvinfo(jn) )
1177      END DO
1178
1179      !                                                      ! ========================= !
1180      IF( srcv(jpr_otx1)%laction ) THEN                      !  ocean stress components  !
1181         !                                                   ! ========================= !
1182         ! define frcv(jpr_otx1)%z3(:,:,1) and frcv(jpr_oty1)%z3(:,:,1): stress at U/V point along model grid
1183         ! => need to be done only when we receive the field
1184         IF(  nrcvinfo(jpr_otx1) == OASIS_Rcv ) THEN
1185            !
1186            IF( TRIM( sn_rcv_tau%clvref ) == 'cartesian' ) THEN            ! 2 components on the sphere
1187               !                                                       ! (cartesian to spherical -> 3 to 2 components)
1188               !
1189               CALL geo2oce( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), frcv(jpr_otz1)%z3(:,:,1),   &
1190                  &          srcv(jpr_otx1)%clgrid, ztx, zty )
1191               frcv(jpr_otx1)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 1st grid
1192               frcv(jpr_oty1)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 1st grid
1193               !
1194               IF( srcv(jpr_otx2)%laction ) THEN
1195                  CALL geo2oce( frcv(jpr_otx2)%z3(:,:,1), frcv(jpr_oty2)%z3(:,:,1), frcv(jpr_otz2)%z3(:,:,1),   &
1196                     &          srcv(jpr_otx2)%clgrid, ztx, zty )
1197                  frcv(jpr_otx2)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 2nd grid
1198                  frcv(jpr_oty2)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 2nd grid
1199               ENDIF
1200               !
1201            ENDIF
1202            !
1203            IF( TRIM( sn_rcv_tau%clvor ) == 'eastward-northward' ) THEN   ! 2 components oriented along the local grid
1204               !                                                       ! (geographical to local grid -> rotate the components)
1205               CALL rot_rep( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), srcv(jpr_otx1)%clgrid, 'en->i', ztx )   
1206               IF( srcv(jpr_otx2)%laction ) THEN
1207                  CALL rot_rep( frcv(jpr_otx2)%z3(:,:,1), frcv(jpr_oty2)%z3(:,:,1), srcv(jpr_otx2)%clgrid, 'en->j', zty )   
1208               ELSE
1209                  CALL rot_rep( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), srcv(jpr_otx1)%clgrid, 'en->j', zty ) 
1210               ENDIF
1211               frcv(jpr_otx1)%z3(:,:,1) = ztx(:,:)      ! overwrite 1st component on the 1st grid
1212               frcv(jpr_oty1)%z3(:,:,1) = zty(:,:)      ! overwrite 2nd component on the 2nd grid
1213            ENDIF
1214            !                             
1215            IF( srcv(jpr_otx1)%clgrid == 'T' ) THEN
1216               DO jj = 2, jpjm1                                          ! T ==> (U,V)
1217                  DO ji = fs_2, fs_jpim1   ! vector opt.
1218                     frcv(jpr_otx1)%z3(ji,jj,1) = 0.5 * ( frcv(jpr_otx1)%z3(ji+1,jj  ,1) + frcv(jpr_otx1)%z3(ji,jj,1) )
1219                     frcv(jpr_oty1)%z3(ji,jj,1) = 0.5 * ( frcv(jpr_oty1)%z3(ji  ,jj+1,1) + frcv(jpr_oty1)%z3(ji,jj,1) )
1220                  END DO
1221               END DO
1222               CALL lbc_lnk_multi( 'sbccpl', frcv(jpr_otx1)%z3(:,:,1), 'U',  -1., frcv(jpr_oty1)%z3(:,:,1), 'V',  -1. )
1223            ENDIF
1224            llnewtx = .TRUE.
1225         ELSE
1226            llnewtx = .FALSE.
1227         ENDIF
1228         !                                                   ! ========================= !
1229      ELSE                                                   !   No dynamical coupling   !
1230         !                                                   ! ========================= !
1231         frcv(jpr_otx1)%z3(:,:,1) = 0.e0                               ! here simply set to zero
1232         frcv(jpr_oty1)%z3(:,:,1) = 0.e0                               ! an external read in a file can be added instead
1233         llnewtx = .TRUE.
1234         !
1235      ENDIF
1236      !                                                      ! ========================= !
1237      !                                                      !    wind stress module     !   (taum)
1238      !                                                      ! ========================= !
1239      IF( .NOT. srcv(jpr_taum)%laction ) THEN                    ! compute wind stress module from its components if not received
1240         ! => need to be done only when otx1 was changed
1241         IF( llnewtx ) THEN
1242            DO jj = 2, jpjm1
1243               DO ji = fs_2, fs_jpim1   ! vect. opt.
1244                  zzx = frcv(jpr_otx1)%z3(ji-1,jj  ,1) + frcv(jpr_otx1)%z3(ji,jj,1)
1245                  zzy = frcv(jpr_oty1)%z3(ji  ,jj-1,1) + frcv(jpr_oty1)%z3(ji,jj,1)
1246                  frcv(jpr_taum)%z3(ji,jj,1) = 0.5 * SQRT( zzx * zzx + zzy * zzy )
1247               END DO
1248            END DO
1249            CALL lbc_lnk( 'sbccpl', frcv(jpr_taum)%z3(:,:,1), 'T', 1. )
1250            llnewtau = .TRUE.
1251         ELSE
1252            llnewtau = .FALSE.
1253         ENDIF
1254      ELSE
1255         llnewtau = nrcvinfo(jpr_taum) == OASIS_Rcv
1256         ! Stress module can be negative when received (interpolation problem)
1257         IF( llnewtau ) THEN
1258            frcv(jpr_taum)%z3(:,:,1) = MAX( 0._wp, frcv(jpr_taum)%z3(:,:,1) )
1259         ENDIF
1260      ENDIF
1261      !
1262      !                                                      ! ========================= !
1263      !                                                      !      10 m wind speed      !   (wndm)
1264      !                                                      ! ========================= !
1265      IF( .NOT. srcv(jpr_w10m)%laction ) THEN                    ! compute wind spreed from wind stress module if not received 
1266         ! => need to be done only when taumod was changed
1267         IF( llnewtau ) THEN
1268            zcoef = 1. / ( zrhoa * zcdrag ) 
1269            DO jj = 1, jpj
1270               DO ji = 1, jpi 
1271                  frcv(jpr_w10m)%z3(ji,jj,1) = SQRT( frcv(jpr_taum)%z3(ji,jj,1) * zcoef )
1272               END DO
1273            END DO
1274         ENDIF
1275      ENDIF
1276!!$      !                                                      ! ========================= !
1277!!$      SELECT CASE( TRIM( sn_rcv_clouds%cldes ) )             !       cloud fraction      !
1278!!$      !                                                      ! ========================= !
1279!!$      cloud_fra(:,:) = frcv(jpr_clfra)*z3(:,:,1)
1280!!$      END SELECT
1281!!$
1282      zcloud_fra(:,:) = pp_cldf   ! should be real cloud fraction instead (as in the bulk) but needs to be read from atm.
1283      IF( ln_mixcpl ) THEN
1284         cloud_fra(:,:) = cloud_fra(:,:) * xcplmask(:,:,0) + zcloud_fra(:,:)* zmsk(:,:)
1285      ELSE
1286         cloud_fra(:,:) = zcloud_fra(:,:)
1287      ENDIF
1288      !                                                      ! ========================= !
1289      ! u(v)tau and taum will be modified by ice model
1290      ! -> need to be reset before each call of the ice/fsbc     
1291      IF( MOD( kt-1, k_fsbc ) == 0 ) THEN
1292         !
1293         IF( ln_mixcpl ) THEN
1294            utau(:,:) = utau(:,:) * xcplmask(:,:,0) + frcv(jpr_otx1)%z3(:,:,1) * zmsk(:,:)
1295            vtau(:,:) = vtau(:,:) * xcplmask(:,:,0) + frcv(jpr_oty1)%z3(:,:,1) * zmsk(:,:)
1296            taum(:,:) = taum(:,:) * xcplmask(:,:,0) + frcv(jpr_taum)%z3(:,:,1) * zmsk(:,:)
1297            wndm(:,:) = wndm(:,:) * xcplmask(:,:,0) + frcv(jpr_w10m)%z3(:,:,1) * zmsk(:,:)
1298         ELSE
1299            utau(:,:) = frcv(jpr_otx1)%z3(:,:,1)
1300            vtau(:,:) = frcv(jpr_oty1)%z3(:,:,1)
1301            taum(:,:) = frcv(jpr_taum)%z3(:,:,1)
1302            wndm(:,:) = frcv(jpr_w10m)%z3(:,:,1)
1303         ENDIF
1304         CALL iom_put( "taum_oce", taum )   ! output wind stress module
1305         
1306      ENDIF
1307
1308      !                                                      ! ================== !
1309      !                                                      ! atmosph. CO2 (ppm) !
1310      !                                                      ! ================== !
1311      IF( srcv(jpr_co2)%laction )   atm_co2(:,:) = frcv(jpr_co2)%z3(:,:,1)
1312      !
1313      !                                                      ! ========================= !
1314      !                                                      ! Mean Sea Level Pressure   !   (taum)
1315      !                                                      ! ========================= !
1316      IF( srcv(jpr_mslp)%laction ) THEN                    ! UKMO SHELF effect of atmospheric pressure on SSH
1317          IF( kt /= nit000 )   ssh_ibb(:,:) = ssh_ib(:,:)    !* Swap of ssh_ib fields
1318
1319          r1_grau = 1.e0 / (grav * rau0)               !* constant for optimization
1320          ssh_ib(:,:) = - ( frcv(jpr_mslp)%z3(:,:,1) - rpref ) * r1_grau    ! equivalent ssh (inverse barometer)
1321          apr   (:,:) =     frcv(jpr_mslp)%z3(:,:,1)                         !atmospheric pressure
1322   
1323          IF( kt == nit000 ) ssh_ibb(:,:) = ssh_ib(:,:)  ! correct this later (read from restart if possible)
1324      END IF 
1325      !
1326      IF( ln_sdw ) THEN  ! Stokes Drift correction activated
1327      !                                                      ! ========================= !
1328      !                                                      !       Stokes drift u      !
1329      !                                                      ! ========================= !
1330         IF( srcv(jpr_sdrftx)%laction ) ut0sd(:,:) = frcv(jpr_sdrftx)%z3(:,:,1)
1331      !
1332      !                                                      ! ========================= !
1333      !                                                      !       Stokes drift v      !
1334      !                                                      ! ========================= !
1335         IF( srcv(jpr_sdrfty)%laction ) vt0sd(:,:) = frcv(jpr_sdrfty)%z3(:,:,1)
1336      !
1337      !                                                      ! ========================= !
1338      !                                                      !      Wave mean period     !
1339      !                                                      ! ========================= !
1340         IF( srcv(jpr_wper)%laction ) wmp(:,:) = frcv(jpr_wper)%z3(:,:,1)
1341      !
1342      !                                                      ! ========================= !
1343      !                                                      !  Significant wave height  !
1344      !                                                      ! ========================= !
1345         IF( srcv(jpr_hsig)%laction ) hsw(:,:) = frcv(jpr_hsig)%z3(:,:,1)
1346      !
1347      !                                                      ! ========================= ! 
1348      !                                                      !    Wave peak frequency    !
1349      !                                                      ! ========================= ! 
1350         IF( srcv(jpr_wfreq)%laction ) wfreq(:,:) = frcv(jpr_wfreq)%z3(:,:,1)
1351      !
1352      !                                                      ! ========================= !
1353      !                                                      !    Vertical mixing Qiao   !
1354      !                                                      ! ========================= !
1355         IF( srcv(jpr_wnum)%laction .AND. ln_zdfswm ) wnum(:,:) = frcv(jpr_wnum)%z3(:,:,1)
1356
1357         ! Calculate the 3D Stokes drift both in coupled and not fully uncoupled mode
1358         IF( srcv(jpr_sdrftx)%laction .OR. srcv(jpr_sdrfty)%laction .OR. srcv(jpr_wper)%laction &
1359                                      .OR. srcv(jpr_hsig)%laction   .OR. srcv(jpr_wfreq)%laction) THEN
1360            CALL sbc_stokes()
1361         ENDIF
1362      ENDIF
1363      !                                                      ! ========================= !
1364      !                                                      ! Stress adsorbed by waves  !
1365      !                                                      ! ========================= !
1366      IF( srcv(jpr_tauwoc)%laction .AND. ln_tauwoc ) tauoc_wave(:,:) = frcv(jpr_tauwoc)%z3(:,:,1)
1367
1368      !                                                      ! ========================= ! 
1369      !                                                      ! Stress component by waves !
1370      !                                                      ! ========================= ! 
1371      IF( srcv(jpr_tauwx)%laction .AND. srcv(jpr_tauwy)%laction .AND. ln_tauw ) THEN
1372         tauw_x(:,:) = frcv(jpr_tauwx)%z3(:,:,1)
1373         tauw_y(:,:) = frcv(jpr_tauwy)%z3(:,:,1)
1374      ENDIF
1375
1376      !                                                      ! ========================= !
1377      !                                                      !   Wave drag coefficient   !
1378      !                                                      ! ========================= !
1379      IF( srcv(jpr_wdrag)%laction .AND. ln_cdgw )   cdn_wave(:,:) = frcv(jpr_wdrag)%z3(:,:,1)
1380
1381      !  Fields received by SAS when OASIS coupling
1382      !  (arrays no more filled at sbcssm stage)
1383      !                                                      ! ================== !
1384      !                                                      !        SSS         !
1385      !                                                      ! ================== !
1386      IF( srcv(jpr_soce)%laction ) THEN                      ! received by sas in case of opa <-> sas coupling
1387         sss_m(:,:) = frcv(jpr_soce)%z3(:,:,1)
1388         CALL iom_put( 'sss_m', sss_m )
1389      ENDIF
1390      !                                               
1391      !                                                      ! ================== !
1392      !                                                      !        SST         !
1393      !                                                      ! ================== !
1394      IF( srcv(jpr_toce)%laction ) THEN                      ! received by sas in case of opa <-> sas coupling
1395         sst_m(:,:) = frcv(jpr_toce)%z3(:,:,1)
1396         IF( srcv(jpr_soce)%laction .AND. l_useCT ) THEN    ! make sure that sst_m is the potential temperature
1397            sst_m(:,:) = eos_pt_from_ct( sst_m(:,:), sss_m(:,:) )
1398         ENDIF
1399      ENDIF
1400      !                                                      ! ================== !
1401      !                                                      !        SSH         !
1402      !                                                      ! ================== !
1403      IF( srcv(jpr_ssh )%laction ) THEN                      ! received by sas in case of opa <-> sas coupling
1404         ssh_m(:,:) = frcv(jpr_ssh )%z3(:,:,1)
1405         CALL iom_put( 'ssh_m', ssh_m )
1406      ENDIF
1407      !                                                      ! ================== !
1408      !                                                      !  surface currents  !
1409      !                                                      ! ================== !
1410      IF( srcv(jpr_ocx1)%laction ) THEN                      ! received by sas in case of opa <-> sas coupling
1411         ssu_m(:,:) = frcv(jpr_ocx1)%z3(:,:,1)
1412         ub (:,:,1) = ssu_m(:,:)                             ! will be used in icestp in the call of ice_forcing_tau
1413         un (:,:,1) = ssu_m(:,:)                             ! will be used in sbc_cpl_snd if atmosphere coupling
1414         CALL iom_put( 'ssu_m', ssu_m )
1415      ENDIF
1416      IF( srcv(jpr_ocy1)%laction ) THEN
1417         ssv_m(:,:) = frcv(jpr_ocy1)%z3(:,:,1)
1418         vb (:,:,1) = ssv_m(:,:)                             ! will be used in icestp in the call of ice_forcing_tau
1419         vn (:,:,1) = ssv_m(:,:)                             ! will be used in sbc_cpl_snd if atmosphere coupling
1420         CALL iom_put( 'ssv_m', ssv_m )
1421      ENDIF
1422      !                                                      ! ======================== !
1423      !                                                      !  first T level thickness !
1424      !                                                      ! ======================== !
1425      IF( srcv(jpr_e3t1st )%laction ) THEN                   ! received by sas in case of opa <-> sas coupling
1426         e3t_m(:,:) = frcv(jpr_e3t1st )%z3(:,:,1)
1427         CALL iom_put( 'e3t_m', e3t_m(:,:) )
1428      ENDIF
1429      !                                                      ! ================================ !
1430      !                                                      !  fraction of solar net radiation !
1431      !                                                      ! ================================ !
1432      IF( srcv(jpr_fraqsr)%laction ) THEN                    ! received by sas in case of opa <-> sas coupling
1433         frq_m(:,:) = frcv(jpr_fraqsr)%z3(:,:,1)
1434         CALL iom_put( 'frq_m', frq_m )
1435      ENDIF
1436     
1437      !                                                      ! ========================= !
1438      IF( k_ice <= 1 .AND. MOD( kt-1, k_fsbc ) == 0 ) THEN   !  heat & freshwater fluxes ! (Ocean only case)
1439         !                                                   ! ========================= !
1440         !
1441         !                                                       ! total freshwater fluxes over the ocean (emp)
1442         IF( srcv(jpr_oemp)%laction .OR. srcv(jpr_rain)%laction ) THEN
1443            SELECT CASE( TRIM( sn_rcv_emp%cldes ) )                                    ! evaporation - precipitation
1444            CASE( 'conservative' )
1445               zemp(:,:) = frcv(jpr_tevp)%z3(:,:,1) - ( frcv(jpr_rain)%z3(:,:,1) + frcv(jpr_snow)%z3(:,:,1) )
1446            CASE( 'oce only', 'oce and ice' )
1447               zemp(:,:) = frcv(jpr_oemp)%z3(:,:,1)
1448            CASE default
1449               CALL ctl_stop( 'sbc_cpl_rcv: wrong definition of sn_rcv_emp%cldes' )
1450            END SELECT
1451         ELSE
1452            zemp(:,:) = 0._wp
1453         ENDIF
1454         !
1455         !                                                        ! runoffs and calving (added in emp)
1456         IF( srcv(jpr_rnf)%laction )     rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1)
1457         IF( srcv(jpr_cal)%laction )     zemp(:,:) = zemp(:,:) - frcv(jpr_cal)%z3(:,:,1)
1458 
1459         IF( srcv(jpr_icb)%laction )  THEN
1460             fwficb(:,:) = frcv(jpr_icb)%z3(:,:,1)
1461             rnf(:,:)    = rnf(:,:) + fwficb(:,:)   ! iceberg added to runfofs
1462         ENDIF
1463         IF( srcv(jpr_isf)%laction )  fwfisf(:,:) = - frcv(jpr_isf)%z3(:,:,1)  ! fresh water flux from the isf (fwfisf <0 mean melting) 
1464       
1465         IF( ln_mixcpl ) THEN   ;   emp(:,:) = emp(:,:) * xcplmask(:,:,0) + zemp(:,:) * zmsk(:,:)
1466         ELSE                   ;   emp(:,:) =                              zemp(:,:)
1467         ENDIF
1468         !
1469         !                                                       ! non solar heat flux over the ocean (qns)
1470         IF(      srcv(jpr_qnsoce)%laction ) THEN   ;   zqns(:,:) = frcv(jpr_qnsoce)%z3(:,:,1)
1471         ELSE IF( srcv(jpr_qnsmix)%laction ) THEN   ;   zqns(:,:) = frcv(jpr_qnsmix)%z3(:,:,1)
1472         ELSE                                       ;   zqns(:,:) = 0._wp
1473         END IF
1474         ! update qns over the free ocean with:
1475         IF( nn_components /= jp_iam_opa ) THEN
1476            zqns(:,:) =  zqns(:,:) - zemp(:,:) * sst_m(:,:) * rcp         ! remove heat content due to mass flux (assumed to be at SST)
1477            IF( srcv(jpr_snow  )%laction ) THEN
1478               zqns(:,:) = zqns(:,:) - frcv(jpr_snow)%z3(:,:,1) * rLfus   ! energy for melting solid precipitation over the free ocean
1479            ENDIF
1480         ENDIF
1481         !
1482         IF( srcv(jpr_icb)%laction )  zqns(:,:) = zqns(:,:) - frcv(jpr_icb)%z3(:,:,1) * rLfus ! remove heat content associated to iceberg melting
1483         !
1484         IF( ln_mixcpl ) THEN   ;   qns(:,:) = qns(:,:) * xcplmask(:,:,0) + zqns(:,:) * zmsk(:,:)
1485         ELSE                   ;   qns(:,:) =                              zqns(:,:)
1486         ENDIF
1487
1488         !                                                       ! solar flux over the ocean          (qsr)
1489         IF     ( srcv(jpr_qsroce)%laction ) THEN   ;   zqsr(:,:) = frcv(jpr_qsroce)%z3(:,:,1)
1490         ELSE IF( srcv(jpr_qsrmix)%laction ) then   ;   zqsr(:,:) = frcv(jpr_qsrmix)%z3(:,:,1)
1491         ELSE                                       ;   zqsr(:,:) = 0._wp
1492         ENDIF
1493         IF( ln_dm2dc .AND. ln_cpl )   zqsr(:,:) = sbc_dcy( zqsr )   ! modify qsr to include the diurnal cycle
1494         IF( ln_mixcpl ) THEN   ;   qsr(:,:) = qsr(:,:) * xcplmask(:,:,0) + zqsr(:,:) * zmsk(:,:)
1495         ELSE                   ;   qsr(:,:) =                              zqsr(:,:)
1496         ENDIF
1497         !
1498         ! salt flux over the ocean (received by opa in case of opa <-> sas coupling)
1499         IF( srcv(jpr_sflx )%laction )   sfx(:,:) = frcv(jpr_sflx  )%z3(:,:,1)
1500         ! Ice cover  (received by opa in case of opa <-> sas coupling)
1501         IF( srcv(jpr_fice )%laction )   fr_i(:,:) = frcv(jpr_fice )%z3(:,:,1)
1502         !
1503      ENDIF
1504      !
1505   END SUBROUTINE sbc_cpl_rcv
1506   
1507
1508   SUBROUTINE sbc_cpl_ice_tau( p_taui, p_tauj )     
1509      !!----------------------------------------------------------------------
1510      !!             ***  ROUTINE sbc_cpl_ice_tau  ***
1511      !!
1512      !! ** Purpose :   provide the stress over sea-ice in coupled mode
1513      !!
1514      !! ** Method  :   transform the received stress from the atmosphere into
1515      !!             an atmosphere-ice stress in the (i,j) ocean referencial
1516      !!             and at the velocity point of the sea-ice model:
1517      !!                'C'-grid : i- (j-) components given at U- (V-) point
1518      !!
1519      !!                The received stress are :
1520      !!                 - defined by 3 components (if cartesian coordinate)
1521      !!                        or by 2 components (if spherical)
1522      !!                 - oriented along geographical   coordinate (if eastward-northward)
1523      !!                        or  along the local grid coordinate (if local grid)
1524      !!                 - given at U- and V-point, resp.   if received on 2 grids
1525      !!                        or at a same point (T or I) if received on 1 grid
1526      !!                Therefore and if necessary, they are successively
1527      !!             processed in order to obtain them
1528      !!                 first  as  2 components on the sphere
1529      !!                 second as  2 components oriented along the local grid
1530      !!                 third  as  2 components on the ice grid point
1531      !!
1532      !!                Except in 'oce and ice' case, only one vector stress field
1533      !!             is received. It has already been processed in sbc_cpl_rcv
1534      !!             so that it is now defined as (i,j) components given at U-
1535      !!             and V-points, respectively. 
1536      !!
1537      !! ** Action  :   return ptau_i, ptau_j, the stress over the ice
1538      !!----------------------------------------------------------------------
1539      REAL(wp), INTENT(out), DIMENSION(:,:) ::   p_taui   ! i- & j-components of atmos-ice stress [N/m2]
1540      REAL(wp), INTENT(out), DIMENSION(:,:) ::   p_tauj   ! at I-point (B-grid) or U & V-point (C-grid)
1541      !!
1542      INTEGER ::   ji, jj   ! dummy loop indices
1543      INTEGER ::   itx      ! index of taux over ice
1544      REAL(wp)                     ::   zztmp1, zztmp2
1545      REAL(wp), DIMENSION(jpi,jpj) ::   ztx, zty 
1546      !!----------------------------------------------------------------------
1547      !
1548      IF( srcv(jpr_itx1)%laction ) THEN   ;   itx =  jpr_itx1   
1549      ELSE                                ;   itx =  jpr_otx1
1550      ENDIF
1551
1552      ! do something only if we just received the stress from atmosphere
1553      IF(  nrcvinfo(itx) == OASIS_Rcv ) THEN
1554         !                                                      ! ======================= !
1555         IF( srcv(jpr_itx1)%laction ) THEN                      !   ice stress received   !
1556            !                                                   ! ======================= !
1557           
1558            IF( TRIM( sn_rcv_tau%clvref ) == 'cartesian' ) THEN            ! 2 components on the sphere
1559               !                                                       ! (cartesian to spherical -> 3 to 2 components)
1560               CALL geo2oce(  frcv(jpr_itx1)%z3(:,:,1), frcv(jpr_ity1)%z3(:,:,1), frcv(jpr_itz1)%z3(:,:,1),   &
1561                  &          srcv(jpr_itx1)%clgrid, ztx, zty )
1562               frcv(jpr_itx1)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 1st grid
1563               frcv(jpr_ity1)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 1st grid
1564               !
1565               IF( srcv(jpr_itx2)%laction ) THEN
1566                  CALL geo2oce( frcv(jpr_itx2)%z3(:,:,1), frcv(jpr_ity2)%z3(:,:,1), frcv(jpr_itz2)%z3(:,:,1),   &
1567                     &          srcv(jpr_itx2)%clgrid, ztx, zty )
1568                  frcv(jpr_itx2)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 2nd grid
1569                  frcv(jpr_ity2)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 2nd grid
1570               ENDIF
1571               !
1572            ENDIF
1573            !
1574            IF( TRIM( sn_rcv_tau%clvor ) == 'eastward-northward' ) THEN   ! 2 components oriented along the local grid
1575               !                                                       ! (geographical to local grid -> rotate the components)
1576               CALL rot_rep( frcv(jpr_itx1)%z3(:,:,1), frcv(jpr_ity1)%z3(:,:,1), srcv(jpr_itx1)%clgrid, 'en->i', ztx )   
1577               IF( srcv(jpr_itx2)%laction ) THEN
1578                  CALL rot_rep( frcv(jpr_itx2)%z3(:,:,1), frcv(jpr_ity2)%z3(:,:,1), srcv(jpr_itx2)%clgrid, 'en->j', zty )   
1579               ELSE
1580                  CALL rot_rep( frcv(jpr_itx1)%z3(:,:,1), frcv(jpr_ity1)%z3(:,:,1), srcv(jpr_itx1)%clgrid, 'en->j', zty ) 
1581               ENDIF
1582               frcv(jpr_itx1)%z3(:,:,1) = ztx(:,:)      ! overwrite 1st component on the 1st grid
1583               frcv(jpr_ity1)%z3(:,:,1) = zty(:,:)      ! overwrite 2nd component on the 1st grid
1584            ENDIF
1585            !                                                   ! ======================= !
1586         ELSE                                                   !     use ocean stress    !
1587            !                                                   ! ======================= !
1588            frcv(jpr_itx1)%z3(:,:,1) = frcv(jpr_otx1)%z3(:,:,1)
1589            frcv(jpr_ity1)%z3(:,:,1) = frcv(jpr_oty1)%z3(:,:,1)
1590            !
1591         ENDIF
1592         !                                                      ! ======================= !
1593         !                                                      !     put on ice grid     !
1594         !                                                      ! ======================= !
1595         !   
1596         !                                                  j+1   j     -----V---F
1597         ! ice stress on ice velocity point                              !       |
1598         ! (C-grid ==>(U,V))                                      j      |   T   U
1599         !                                                               |       |
1600         !                                                   j    j-1   -I-------|
1601         !                                               (for I)         |       |
1602         !                                                              i-1  i   i
1603         !                                                               i      i+1 (for I)
1604         SELECT CASE ( srcv(jpr_itx1)%clgrid )
1605         CASE( 'U' )
1606            p_taui(:,:) = frcv(jpr_itx1)%z3(:,:,1)                   ! (U,V) ==> (U,V)
1607            p_tauj(:,:) = frcv(jpr_ity1)%z3(:,:,1)
1608         CASE( 'T' )
1609            DO jj = 2, jpjm1                                   ! T ==> (U,V)
1610               DO ji = fs_2, fs_jpim1   ! vector opt.
1611                  ! take care of the land-sea mask to avoid "pollution" of coastal stress. p[uv]taui used in frazil and  rheology
1612                  zztmp1 = 0.5_wp * ( 2. - umask(ji,jj,1) ) * MAX( tmask(ji,jj,1),tmask(ji+1,jj  ,1) )
1613                  zztmp2 = 0.5_wp * ( 2. - vmask(ji,jj,1) ) * MAX( tmask(ji,jj,1),tmask(ji  ,jj+1,1) )
1614                  p_taui(ji,jj) = zztmp1 * ( frcv(jpr_itx1)%z3(ji+1,jj  ,1) + frcv(jpr_itx1)%z3(ji,jj,1) )
1615                  p_tauj(ji,jj) = zztmp2 * ( frcv(jpr_ity1)%z3(ji  ,jj+1,1) + frcv(jpr_ity1)%z3(ji,jj,1) )
1616               END DO
1617            END DO
1618            CALL lbc_lnk_multi( 'sbccpl', p_taui, 'U',  -1., p_tauj, 'V',  -1. )
1619         END SELECT
1620         
1621      ENDIF
1622      !
1623   END SUBROUTINE sbc_cpl_ice_tau
1624   
1625
1626   SUBROUTINE sbc_cpl_ice_flx( picefr, palbi, psst, pist, phs, phi )
1627      !!----------------------------------------------------------------------
1628      !!             ***  ROUTINE sbc_cpl_ice_flx  ***
1629      !!
1630      !! ** Purpose :   provide the heat and freshwater fluxes of the ocean-ice system
1631      !!
1632      !! ** Method  :   transform the fields received from the atmosphere into
1633      !!             surface heat and fresh water boundary condition for the
1634      !!             ice-ocean system. The following fields are provided:
1635      !!               * total non solar, solar and freshwater fluxes (qns_tot,
1636      !!             qsr_tot and emp_tot) (total means weighted ice-ocean flux)
1637      !!             NB: emp_tot include runoffs and calving.
1638      !!               * fluxes over ice (qns_ice, qsr_ice, emp_ice) where
1639      !!             emp_ice = sublimation - solid precipitation as liquid
1640      !!             precipitation are re-routed directly to the ocean and
1641      !!             calving directly enter the ocean (runoffs are read but included in trasbc.F90)
1642      !!               * solid precipitation (sprecip), used to add to qns_tot
1643      !!             the heat lost associated to melting solid precipitation
1644      !!             over the ocean fraction.
1645      !!               * heat content of rain, snow and evap can also be provided,
1646      !!             otherwise heat flux associated with these mass flux are
1647      !!             guessed (qemp_oce, qemp_ice)
1648      !!
1649      !!             - the fluxes have been separated from the stress as
1650      !!               (a) they are updated at each ice time step compare to
1651      !!               an update at each coupled time step for the stress, and
1652      !!               (b) the conservative computation of the fluxes over the
1653      !!               sea-ice area requires the knowledge of the ice fraction
1654      !!               after the ice advection and before the ice thermodynamics,
1655      !!               so that the stress is updated before the ice dynamics
1656      !!               while the fluxes are updated after it.
1657      !!
1658      !! ** Details
1659      !!             qns_tot = (1-a) * qns_oce + a * qns_ice               => provided
1660      !!                     + qemp_oce + qemp_ice                         => recalculated and added up to qns
1661      !!
1662      !!             qsr_tot = (1-a) * qsr_oce + a * qsr_ice               => provided
1663      !!
1664      !!             emp_tot = emp_oce + emp_ice                           => calving is provided and added to emp_tot (and emp_oce).
1665      !!                                                                      runoff (which includes rivers+icebergs) and iceshelf
1666      !!                                                                      are provided but not included in emp here. Only runoff will
1667      !!                                                                      be included in emp in other parts of NEMO code
1668      !! ** Action  :   update at each nf_ice time step:
1669      !!                   qns_tot, qsr_tot  non-solar and solar total heat fluxes
1670      !!                   qns_ice, qsr_ice  non-solar and solar heat fluxes over the ice
1671      !!                   emp_tot           total evaporation - precipitation(liquid and solid) (-calving)
1672      !!                   emp_ice           ice sublimation - solid precipitation over the ice
1673      !!                   dqns_ice          d(non-solar heat flux)/d(Temperature) over the ice
1674      !!                   sprecip           solid precipitation over the ocean 
1675      !!----------------------------------------------------------------------
1676      REAL(wp), INTENT(in)   , DIMENSION(:,:)             ::   picefr     ! ice fraction                [0 to 1]
1677      !                                                   !!           ! optional arguments, used only in 'mixed oce-ice' case or for Met-Office coupling
1678      REAL(wp), INTENT(in)   , DIMENSION(:,:,:), OPTIONAL ::   palbi      ! all skies ice albedo
1679      REAL(wp), INTENT(in)   , DIMENSION(:,:  ), OPTIONAL ::   psst       ! sea surface temperature     [Celsius]
1680      REAL(wp), INTENT(inout), DIMENSION(:,:,:), OPTIONAL ::   pist       ! ice surface temperature     [Kelvin] => inout for Met-Office
1681      REAL(wp), INTENT(in)   , DIMENSION(:,:,:), OPTIONAL ::   phs        ! snow depth                  [m]
1682      REAL(wp), INTENT(in)   , DIMENSION(:,:,:), OPTIONAL ::   phi        ! ice thickness               [m]
1683      !
1684      INTEGER  ::   ji, jj, jl   ! dummy loop index
1685      REAL(wp), DIMENSION(jpi,jpj)     ::   zcptn, zcptrain, zcptsnw, ziceld, zmsk, zsnw
1686      REAL(wp), DIMENSION(jpi,jpj)     ::   zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip  , zevap_oce, zdevap_ice
1687      REAL(wp), DIMENSION(jpi,jpj)     ::   zqns_tot, zqns_oce, zqsr_tot, zqsr_oce, zqprec_ice, zqemp_oce, zqemp_ice
1688      REAL(wp), DIMENSION(jpi,jpj)     ::   zevap_ice_total
1689      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice, zevap_ice, zqtr_ice_top, ztsu
1690      REAL(wp), DIMENSION(jpi,jpj)     ::   ztri
1691      !!----------------------------------------------------------------------
1692      !
1693      IF( ln_mixcpl )   zmsk(:,:) = 1. - xcplmask(:,:,0)
1694      ziceld(:,:) = 1._wp - picefr(:,:)
1695      zcptn (:,:) = rcp * sst_m(:,:)
1696
1697#if defined key_si3     
1698      !                                                      ! ========================= !
1699      SELECT CASE( TRIM( sn_rcv_iceflx%cldes ) )             !  ice topmelt and botmelt  !
1700      !                                                      ! ========================= !
1701      CASE ('coupled')
1702         IF (ln_scale_ice_flux) THEN
1703            WHERE( a_i(:,:,:) > 1.e-10_wp )
1704               qml_ice(:,:,:) = frcv(jpr_topm)%z3(:,:,:) * a_i_last_couple(:,:,:) / a_i(:,:,:)
1705               qcn_ice(:,:,:) = frcv(jpr_botm)%z3(:,:,:) * a_i_last_couple(:,:,:) / a_i(:,:,:)
1706            ELSEWHERE
1707               qml_ice(:,:,:) = 0.0_wp
1708               qcn_ice(:,:,:) = 0.0_wp
1709            END WHERE
1710         ELSE
1711            qml_ice(:,:,:) = frcv(jpr_topm)%z3(:,:,:)
1712            qcn_ice(:,:,:) = frcv(jpr_botm)%z3(:,:,:)
1713         ENDIF
1714      END SELECT
1715#endif
1716
1717      !
1718      !                                                      ! ========================= !
1719      !                                                      !    freshwater budget      !   (emp_tot)
1720      !                                                      ! ========================= !
1721      !
1722      !                                                           ! solid Precipitation                                (sprecip)
1723      !                                                           ! liquid + solid Precipitation                       (tprecip)
1724      !                                                           ! total Evaporation - total Precipitation            (emp_tot)
1725      !                                                           ! sublimation - solid precipitation (cell average)   (emp_ice)
1726      SELECT CASE( TRIM( sn_rcv_emp%cldes ) )
1727      CASE( 'conservative' )   ! received fields: jpr_rain, jpr_snow, jpr_ievp, jpr_tevp
1728         zsprecip(:,:) =   frcv(jpr_snow)%z3(:,:,1)                  ! May need to ensure positive here
1729         ztprecip(:,:) =   frcv(jpr_rain)%z3(:,:,1) + zsprecip(:,:)  ! May need to ensure positive here
1730         zemp_tot(:,:) =   frcv(jpr_tevp)%z3(:,:,1) - ztprecip(:,:)
1731      CASE( 'oce and ice'   )   ! received fields: jpr_sbpr, jpr_semp, jpr_oemp, jpr_ievp
1732         zemp_tot(:,:) = ziceld(:,:) * frcv(jpr_oemp)%z3(:,:,1) + picefr(:,:) * frcv(jpr_sbpr)%z3(:,:,1)
1733         zemp_ice(:,:) = frcv(jpr_semp)%z3(:,:,1) * picefr(:,:)
1734         zsprecip(:,:) = frcv(jpr_ievp)%z3(:,:,1) - frcv(jpr_semp)%z3(:,:,1)
1735         ztprecip(:,:) = frcv(jpr_semp)%z3(:,:,1) - frcv(jpr_sbpr)%z3(:,:,1) + zsprecip(:,:)
1736      CASE( 'none'      )       ! Not available as for now: needs additional coding below when computing zevap_oce
1737      !                         ! since fields received are not defined with none option
1738         CALL ctl_stop( 'STOP', 'sbccpl/sbc_cpl_ice_flx: some fields are not defined. Change sn_rcv_emp value in namelist namsbc_cpl' )
1739      END SELECT
1740
1741#if defined key_si3
1742
1743      ! --- evaporation over ice (kg/m2/s) --- !
1744      IF (ln_scale_ice_flux) THEN ! typically met-office requirements
1745         IF (sn_rcv_emp%clcat == 'yes') THEN
1746            WHERE( a_i(:,:,:) > 1.e-10 )  ; zevap_ice(:,:,:) = frcv(jpr_ievp)%z3(:,:,:) * a_i_last_couple(:,:,:) / a_i(:,:,:)
1747            ELSEWHERE                     ; zevap_ice(:,:,:) = 0._wp
1748            END WHERE
1749            WHERE( picefr(:,:) > 1.e-10 ) ; zevap_ice_total(:,:) = SUM( zevap_ice(:,:,:) * a_i(:,:,:), dim=3 ) / picefr(:,:)
1750            ELSEWHERE                     ; zevap_ice_total(:,:) = 0._wp
1751            END WHERE
1752         ELSE
1753            WHERE( picefr(:,:) > 1.e-10 ) ; zevap_ice(:,:,1) = frcv(jpr_ievp)%z3(:,:,1) * SUM( a_i_last_couple, dim=3 ) / picefr(:,:)
1754            ELSEWHERE                     ; zevap_ice(:,:,1) = 0._wp
1755            END WHERE
1756            zevap_ice_total(:,:) = zevap_ice(:,:,1)
1757            DO jl = 2, jpl
1758               zevap_ice(:,:,jl) = zevap_ice(:,:,1)
1759            ENDDO
1760         ENDIF
1761      ELSE
1762         IF (sn_rcv_emp%clcat == 'yes') THEN
1763            zevap_ice(:,:,1:jpl) = frcv(jpr_ievp)%z3(:,:,1:jpl)
1764            WHERE( picefr(:,:) > 1.e-10 ) ; zevap_ice_total(:,:) = SUM( zevap_ice(:,:,:) * a_i(:,:,:), dim=3 ) / picefr(:,:)
1765            ELSEWHERE                     ; zevap_ice_total(:,:) = 0._wp
1766            END WHERE
1767         ELSE
1768            zevap_ice(:,:,1) = frcv(jpr_ievp)%z3(:,:,1)
1769            zevap_ice_total(:,:) = zevap_ice(:,:,1)
1770            DO jl = 2, jpl
1771               zevap_ice(:,:,jl) = zevap_ice(:,:,1)
1772            ENDDO
1773         ENDIF
1774      ENDIF
1775
1776      IF ( TRIM( sn_rcv_emp%cldes ) == 'conservative' ) THEN
1777         ! For conservative case zemp_ice has not been defined yet. Do it now.
1778         zemp_ice(:,:) = zevap_ice_total(:,:) * picefr(:,:) - frcv(jpr_snow)%z3(:,:,1) * picefr(:,:)
1779      ENDIF
1780
1781      ! zsnw = snow fraction over ice after wind blowing (=picefr if no blowing)
1782      zsnw(:,:) = 0._wp   ;   CALL ice_var_snwblow( ziceld, zsnw )
1783     
1784      ! --- evaporation minus precipitation corrected (because of wind blowing on snow) --- !
1785      zemp_ice(:,:) = zemp_ice(:,:) + zsprecip(:,:) * ( picefr(:,:) - zsnw(:,:) )  ! emp_ice = A * sublimation - zsnw * sprecip
1786      zemp_oce(:,:) = zemp_tot(:,:) - zemp_ice(:,:)                                ! emp_oce = emp_tot - emp_ice
1787
1788      ! --- evaporation over ocean (used later for qemp) --- !
1789      zevap_oce(:,:) = frcv(jpr_tevp)%z3(:,:,1) - zevap_ice_total(:,:) * picefr(:,:)
1790
1791      ! since the sensitivity of evap to temperature (devap/dT) is not prescribed by the atmosphere, we set it to 0
1792      ! therefore, sublimation is not redistributed over the ice categories when no subgrid scale fluxes are provided by atm.
1793      zdevap_ice(:,:) = 0._wp
1794     
1795      ! --- Continental fluxes --- !
1796      IF( srcv(jpr_rnf)%laction ) THEN   ! runoffs (included in emp later on)
1797         rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1)
1798      ENDIF
1799      IF( srcv(jpr_cal)%laction ) THEN   ! calving (put in emp_tot and emp_oce)
1800         zemp_tot(:,:) = zemp_tot(:,:) - frcv(jpr_cal)%z3(:,:,1)
1801         zemp_oce(:,:) = zemp_oce(:,:) - frcv(jpr_cal)%z3(:,:,1)
1802      ENDIF
1803      IF( srcv(jpr_icb)%laction ) THEN   ! iceberg added to runoffs
1804         fwficb(:,:) = frcv(jpr_icb)%z3(:,:,1)
1805         rnf(:,:)    = rnf(:,:) + fwficb(:,:)
1806      ENDIF
1807      IF( srcv(jpr_isf)%laction ) THEN   ! iceshelf (fwfisf <0 mean melting)
1808        fwfisf(:,:) = - frcv(jpr_isf)%z3(:,:,1) 
1809      ENDIF
1810
1811      IF( ln_mixcpl ) THEN
1812         emp_tot(:,:) = emp_tot(:,:) * xcplmask(:,:,0) + zemp_tot(:,:) * zmsk(:,:)
1813         emp_ice(:,:) = emp_ice(:,:) * xcplmask(:,:,0) + zemp_ice(:,:) * zmsk(:,:)
1814         emp_oce(:,:) = emp_oce(:,:) * xcplmask(:,:,0) + zemp_oce(:,:) * zmsk(:,:)
1815         sprecip(:,:) = sprecip(:,:) * xcplmask(:,:,0) + zsprecip(:,:) * zmsk(:,:)
1816         tprecip(:,:) = tprecip(:,:) * xcplmask(:,:,0) + ztprecip(:,:) * zmsk(:,:)
1817         DO jl = 1, jpl
1818            evap_ice (:,:,jl) = evap_ice (:,:,jl) * xcplmask(:,:,0) + zevap_ice (:,:,jl) * zmsk(:,:)
1819            devap_ice(:,:,jl) = devap_ice(:,:,jl) * xcplmask(:,:,0) + zdevap_ice(:,:)    * zmsk(:,:)
1820         END DO
1821      ELSE
1822         emp_tot (:,:)   = zemp_tot (:,:)
1823         emp_ice (:,:)   = zemp_ice (:,:)
1824         emp_oce (:,:)   = zemp_oce (:,:)     
1825         sprecip (:,:)   = zsprecip (:,:)
1826         tprecip (:,:)   = ztprecip (:,:)
1827         evap_ice(:,:,:) = zevap_ice(:,:,:)
1828         DO jl = 1, jpl
1829            devap_ice(:,:,jl) = zdevap_ice(:,:)
1830         END DO
1831      ENDIF
1832
1833#else
1834      zsnw(:,:) = picefr(:,:)
1835      ! --- Continental fluxes --- !
1836      IF( srcv(jpr_rnf)%laction ) THEN   ! runoffs (included in emp later on)
1837         rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1)
1838      ENDIF
1839      IF( srcv(jpr_cal)%laction ) THEN   ! calving (put in emp_tot)
1840         zemp_tot(:,:) = zemp_tot(:,:) - frcv(jpr_cal)%z3(:,:,1)
1841      ENDIF
1842      IF( srcv(jpr_icb)%laction ) THEN   ! iceberg added to runoffs
1843         fwficb(:,:) = frcv(jpr_icb)%z3(:,:,1)
1844         rnf(:,:)    = rnf(:,:) + fwficb(:,:)
1845      ENDIF
1846      IF( srcv(jpr_isf)%laction ) THEN   ! iceshelf (fwfisf <0 mean melting)
1847        fwfisf(:,:) = - frcv(jpr_isf)%z3(:,:,1)
1848      ENDIF
1849      !
1850      IF( ln_mixcpl ) THEN
1851         emp_tot(:,:) = emp_tot(:,:) * xcplmask(:,:,0) + zemp_tot(:,:) * zmsk(:,:)
1852         emp_ice(:,:) = emp_ice(:,:) * xcplmask(:,:,0) + zemp_ice(:,:) * zmsk(:,:)
1853         sprecip(:,:) = sprecip(:,:) * xcplmask(:,:,0) + zsprecip(:,:) * zmsk(:,:)
1854         tprecip(:,:) = tprecip(:,:) * xcplmask(:,:,0) + ztprecip(:,:) * zmsk(:,:)
1855      ELSE
1856         emp_tot(:,:) =                                  zemp_tot(:,:)
1857         emp_ice(:,:) =                                  zemp_ice(:,:)
1858         sprecip(:,:) =                                  zsprecip(:,:)
1859         tprecip(:,:) =                                  ztprecip(:,:)
1860      ENDIF
1861      !
1862#endif
1863
1864      ! outputs
1865!!      IF( srcv(jpr_rnf)%laction )   CALL iom_put( 'runoffs' , rnf(:,:) * tmask(:,:,1)                                 )  ! runoff
1866!!      IF( srcv(jpr_isf)%laction )   CALL iom_put( 'iceshelf_cea', -fwfisf(:,:) * tmask(:,:,1)                         )  ! iceshelf
1867      IF( srcv(jpr_cal)%laction )    CALL iom_put( 'calving_cea' , frcv(jpr_cal)%z3(:,:,1) * tmask(:,:,1)                )  ! calving
1868      IF( srcv(jpr_icb)%laction )    CALL iom_put( 'iceberg_cea' , frcv(jpr_icb)%z3(:,:,1) * tmask(:,:,1)                )  ! icebergs
1869      IF( iom_use('snowpre') )       CALL iom_put( 'snowpre'     , sprecip(:,:)                                          )  ! Snow
1870      IF( iom_use('precip') )        CALL iom_put( 'precip'      , tprecip(:,:)                                          )  ! total  precipitation
1871      IF( iom_use('rain') )          CALL iom_put( 'rain'        , tprecip(:,:) - sprecip(:,:)                           )  ! liquid precipitation
1872      IF( iom_use('snow_ao_cea') )   CALL iom_put( 'snow_ao_cea' , sprecip(:,:) * ( 1._wp - zsnw(:,:) )                  )  ! Snow over ice-free ocean  (cell average)
1873      IF( iom_use('snow_ai_cea') )   CALL iom_put( 'snow_ai_cea' , sprecip(:,:) *           zsnw(:,:)                    )  ! Snow over sea-ice         (cell average)
1874      IF( iom_use('rain_ao_cea') )   CALL iom_put( 'rain_ao_cea' , ( tprecip(:,:) - sprecip(:,:) ) * picefr(:,:)         )  ! liquid precipitation over ocean (cell average)
1875      IF( iom_use('subl_ai_cea') )   CALL iom_put( 'subl_ai_cea' , frcv(jpr_ievp)%z3(:,:,1) * picefr(:,:) * tmask(:,:,1) )     ! Sublimation over sea-ice (cell average)
1876      IF( iom_use('evap_ao_cea') )   CALL iom_put( 'evap_ao_cea' , ( frcv(jpr_tevp)%z3(:,:,1)  &
1877         &                                                         - frcv(jpr_ievp)%z3(:,:,1) * picefr(:,:) ) * tmask(:,:,1) ) ! ice-free oce evap (cell average)
1878      ! note: runoff output is done in sbcrnf (which includes icebergs too) and iceshelf output is done in sbcisf
1879      !
1880      !                                                      ! ========================= !
1881      SELECT CASE( TRIM( sn_rcv_qns%cldes ) )                !   non solar heat fluxes   !   (qns)
1882      !                                                      ! ========================= !
1883      CASE( 'oce only' )         ! the required field is directly provided
1884
1885         ! Get the sea ice non solar heat flux from conductive, melting and sublimation fluxes
1886         IF( TRIM(sn_rcv_iceflx%cldes) == 'coupled' ) THEN
1887            zqns_ice(:,:,:) = qml_ice(:,:,:) + qcn_ice(:,:,:) + evap_ice(:,:,:) * rLsub
1888         ELSE
1889            zqns_ice(:,:,:) = 0._wp
1890         ENDIF
1891
1892         ! Calculate the total non solar heat flux. The ocean only non solar heat flux (zqns_oce) will be recalculated after this CASE
1893         ! statement to be consistent with other coupling methods even though .zqns_oce = frcv(jpr_qnsoce)%z3(:,:,1)
1894         zqns_tot(:,:) = frcv(jpr_qnsoce)%z3(:,:,1) * ziceld(:,:) + SUM( zqns_ice(:,:,:) * a_i(:,:,:), dim=3 )
1895         
1896      CASE( 'conservative' )     ! the required fields are directly provided
1897         zqns_tot(:,:) = frcv(jpr_qnsmix)%z3(:,:,1)
1898         IF ( TRIM(sn_rcv_qns%clcat) == 'yes' ) THEN
1899            zqns_ice(:,:,1:jpl) = frcv(jpr_qnsice)%z3(:,:,1:jpl)
1900         ELSE
1901            DO jl = 1, jpl
1902               zqns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,1) ! Set all category values equal
1903            END DO
1904         ENDIF
1905      CASE( 'oce and ice' )      ! the total flux is computed from ocean and ice fluxes
1906         zqns_tot(:,:) =  ziceld(:,:) * frcv(jpr_qnsoce)%z3(:,:,1)
1907         IF ( TRIM(sn_rcv_qns%clcat) == 'yes' ) THEN
1908            DO jl=1,jpl
1909               zqns_tot(:,:   ) = zqns_tot(:,:) + a_i(:,:,jl) * frcv(jpr_qnsice)%z3(:,:,jl)   
1910               zqns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,jl)
1911            ENDDO
1912         ELSE
1913            zqns_tot(:,:) = zqns_tot(:,:) + picefr(:,:) * frcv(jpr_qnsice)%z3(:,:,1)
1914            DO jl = 1, jpl
1915               zqns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,1)
1916            END DO
1917         ENDIF
1918      CASE( 'mixed oce-ice' )    ! the ice flux is cumputed from the total flux, the SST and ice informations
1919! ** NEED TO SORT OUT HOW THIS SHOULD WORK IN THE MULTI-CATEGORY CASE - CURRENTLY NOT ALLOWED WHEN INTERFACE INITIALISED **
1920         zqns_tot(:,:  ) = frcv(jpr_qnsmix)%z3(:,:,1)
1921         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN
1922            DO jl = 1, jpl
1923               zqns_ice(:,:,jl) = frcv(jpr_qnsmix)%z3(:,:,jl)    &
1924                  &             + frcv(jpr_dqnsdt)%z3(:,:,jl) * ( pist(:,:,jl) - ( ( rt0 + psst(:,:) ) * ziceld(:,:)   &
1925                  &                                             + pist(:,:,jl) * picefr(:,:) ) )
1926            END DO
1927         ELSE
1928            DO jl = 1, jpl
1929               zqns_ice(:,:,jl) = frcv(jpr_qnsmix)%z3(:,:, 1)    &
1930                  &             + frcv(jpr_dqnsdt)%z3(:,:, 1) * ( pist(:,:,jl) - ( ( rt0 + psst(:,:) ) * ziceld(:,:)   &
1931                  &                                             + pist(:,:,jl) * picefr(:,:) ) )
1932            END DO
1933         ENDIF
1934      END SELECT
1935      !                                     
1936      ! --- calving (removed from qns_tot) --- !
1937      IF( srcv(jpr_cal)%laction )   zqns_tot(:,:) = zqns_tot(:,:) - frcv(jpr_cal)%z3(:,:,1) * rLfus  ! remove latent heat of calving
1938                                                                                                     ! we suppose it melts at 0deg, though it should be temp. of surrounding ocean
1939      ! --- iceberg (removed from qns_tot) --- !
1940      IF( srcv(jpr_icb)%laction )   zqns_tot(:,:) = zqns_tot(:,:) - frcv(jpr_icb)%z3(:,:,1) * rLfus  ! remove latent heat of iceberg melting
1941
1942#if defined key_si3     
1943      ! --- non solar flux over ocean --- !
1944      !         note: ziceld cannot be = 0 since we limit the ice concentration to amax
1945      zqns_oce = 0._wp
1946      WHERE( ziceld /= 0._wp )   zqns_oce(:,:) = ( zqns_tot(:,:) - SUM( a_i * zqns_ice, dim=3 ) ) / ziceld(:,:)
1947
1948      ! Heat content per unit mass of snow (J/kg)
1949      WHERE( SUM( a_i, dim=3 ) > 1.e-10 )   ;   zcptsnw(:,:) = rcpi * SUM( (tn_ice - rt0) * a_i, dim=3 ) / SUM( a_i, dim=3 )
1950      ELSEWHERE                             ;   zcptsnw(:,:) = zcptn(:,:)
1951      ENDWHERE
1952      ! Heat content per unit mass of rain (J/kg)
1953      zcptrain(:,:) = rcp * ( SUM( (tn_ice(:,:,:) - rt0) * a_i(:,:,:), dim=3 ) + sst_m(:,:) * ziceld(:,:) ) 
1954
1955      ! --- enthalpy of snow precip over ice in J/m3 (to be used in 1D-thermo) --- !
1956      zqprec_ice(:,:) = rhos * ( zcptsnw(:,:) - rLfus )
1957
1958      ! --- heat content of evap over ice in W/m2 (to be used in 1D-thermo) --- !
1959      DO jl = 1, jpl
1960         zqevap_ice(:,:,jl) = 0._wp ! should be -evap * ( ( Tice - rt0 ) * rcpi ) but atm. does not take it into account
1961      END DO
1962
1963      ! --- heat flux associated with emp (W/m2) --- !
1964      zqemp_oce(:,:) = -  zevap_oce(:,:)                                      *   zcptn   (:,:)   &        ! evap
1965         &             + ( ztprecip(:,:) - zsprecip(:,:) )                    *   zcptrain(:,:)   &        ! liquid precip
1966         &             +   zsprecip(:,:)                   * ( 1._wp - zsnw ) * ( zcptsnw (:,:) - rLfus )  ! solid precip over ocean + snow melting
1967      zqemp_ice(:,:) =     zsprecip(:,:)                   * zsnw             * ( zcptsnw (:,:) - rLfus )  ! solid precip over ice (qevap_ice=0 since atm. does not take it into account)
1968!!    zqemp_ice(:,:) = -   frcv(jpr_ievp)%z3(:,:,1)        * picefr(:,:)      *   zcptsnw (:,:)   &        ! ice evap
1969!!       &             +   zsprecip(:,:)                   * zsnw             * zqprec_ice(:,:) * r1_rhos  ! solid precip over ice
1970     
1971      ! --- total non solar flux (including evap/precip) --- !
1972      zqns_tot(:,:) = zqns_tot(:,:) + zqemp_ice(:,:) + zqemp_oce(:,:)
1973
1974      ! --- in case both coupled/forced are active, we must mix values --- !
1975      IF( ln_mixcpl ) THEN
1976         qns_tot(:,:) = qns_tot(:,:) * xcplmask(:,:,0) + zqns_tot(:,:)* zmsk(:,:)
1977         qns_oce(:,:) = qns_oce(:,:) * xcplmask(:,:,0) + zqns_oce(:,:)* zmsk(:,:)
1978         DO jl=1,jpl
1979            qns_ice  (:,:,jl) = qns_ice  (:,:,jl) * xcplmask(:,:,0) +  zqns_ice  (:,:,jl)* zmsk(:,:)
1980            qevap_ice(:,:,jl) = qevap_ice(:,:,jl) * xcplmask(:,:,0) +  zqevap_ice(:,:,jl)* zmsk(:,:)
1981         ENDDO
1982         qprec_ice(:,:) = qprec_ice(:,:) * xcplmask(:,:,0) + zqprec_ice(:,:)* zmsk(:,:)
1983         qemp_oce (:,:) =  qemp_oce(:,:) * xcplmask(:,:,0) +  zqemp_oce(:,:)* zmsk(:,:)
1984         qemp_ice (:,:) =  qemp_ice(:,:) * xcplmask(:,:,0) +  zqemp_ice(:,:)* zmsk(:,:)
1985      ELSE
1986         qns_tot  (:,:  ) = zqns_tot  (:,:  )
1987         qns_oce  (:,:  ) = zqns_oce  (:,:  )
1988         qns_ice  (:,:,:) = zqns_ice  (:,:,:)
1989         qevap_ice(:,:,:) = zqevap_ice(:,:,:)
1990         qprec_ice(:,:  ) = zqprec_ice(:,:  )
1991         qemp_oce (:,:  ) = zqemp_oce (:,:  )
1992         qemp_ice (:,:  ) = zqemp_ice (:,:  )
1993      ENDIF
1994
1995#else
1996      zcptsnw (:,:) = zcptn(:,:)
1997      zcptrain(:,:) = zcptn(:,:)
1998     
1999      ! clem: this formulation is certainly wrong... but better than it was...
2000      zqns_tot(:,:) = zqns_tot(:,:)                             &          ! zqns_tot update over free ocean with:
2001         &          - (  ziceld(:,:) * zsprecip(:,:) * rLfus )  &          ! remove the latent heat flux of solid precip. melting
2002         &          - (  zemp_tot(:,:)                          &          ! remove the heat content of mass flux (assumed to be at SST)
2003         &             - zemp_ice(:,:) ) * zcptn(:,:) 
2004
2005     IF( ln_mixcpl ) THEN
2006         qns_tot(:,:) = qns(:,:) * ziceld(:,:) + SUM( qns_ice(:,:,:) * a_i(:,:,:), dim=3 )   ! total flux from blk
2007         qns_tot(:,:) = qns_tot(:,:) * xcplmask(:,:,0) +  zqns_tot(:,:)* zmsk(:,:)
2008         DO jl=1,jpl
2009            qns_ice(:,:,jl) = qns_ice(:,:,jl) * xcplmask(:,:,0) +  zqns_ice(:,:,jl)* zmsk(:,:)
2010         ENDDO
2011      ELSE
2012         qns_tot(:,:  ) = zqns_tot(:,:  )
2013         qns_ice(:,:,:) = zqns_ice(:,:,:)
2014      ENDIF
2015
2016#endif
2017      ! outputs
2018      IF ( srcv(jpr_cal)%laction ) CALL iom_put('hflx_cal_cea'    , - frcv(jpr_cal)%z3(:,:,1) * rLfus )   ! latent heat from calving
2019      IF ( srcv(jpr_icb)%laction ) CALL iom_put('hflx_icb_cea'    , - frcv(jpr_icb)%z3(:,:,1) * rLfus )   ! latent heat from icebergs melting
2020      IF ( iom_use(   'hflx_rain_cea') ) CALL iom_put('hflx_rain_cea' , ( tprecip(:,:) - sprecip(:,:) ) * zcptrain(:,:) )        ! heat flux from rain (cell average)
2021      IF ( iom_use(   'hflx_evap_cea') ) CALL iom_put('hflx_evap_cea' , ( frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) * picefr(:,:) )  &
2022           &                         * zcptn(:,:) * tmask(:,:,1) )            ! heat flux from evap (cell average)
2023      IF ( iom_use(   'hflx_prec_cea') ) CALL iom_put('hflx_prec_cea' ,    sprecip(:,:) * ( zcptsnw(:,:) - rLfus )  &                    ! heat flux from all precip (cell avg)
2024         &                          + ( tprecip(:,:) - sprecip(:,:) ) * zcptrain(:,:) )
2025      IF ( iom_use(   'hflx_snow_cea') ) CALL iom_put('hflx_snow_cea'   , sprecip(:,:) * ( zcptsnw(:,:) - rLfus )  )               ! heat flux from snow (cell average)
2026      IF ( iom_use('hflx_snow_ao_cea') ) CALL iom_put('hflx_snow_ao_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) * ( 1._wp - zsnw(:,:) ) )   ! heat flux from snow (over ocean)
2027      IF ( iom_use('hflx_snow_ai_cea') ) CALL iom_put('hflx_snow_ai_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) *  zsnw(:,:) )              ! heat flux from snow (over ice)
2028      ! note: hflx for runoff and iceshelf are done in sbcrnf and sbcisf resp.
2029      !
2030      !                                                      ! ========================= !
2031      SELECT CASE( TRIM( sn_rcv_qsr%cldes ) )                !      solar heat fluxes    !   (qsr)
2032      !                                                      ! ========================= !
2033      CASE( 'oce only' )
2034         zqsr_tot(:,:  ) = MAX( 0._wp , frcv(jpr_qsroce)%z3(:,:,1) ) * ziceld(:,:)
2035         ! For Met Office sea ice solar fluxes are already delt with by JULES so setting to zero
2036         ! here so the only flux is the ocean only one.
2037         zqsr_ice(:,:,:) = 0._wp
2038      CASE( 'conservative' )
2039         zqsr_tot(:,:  ) = frcv(jpr_qsrmix)%z3(:,:,1)
2040         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN
2041            zqsr_ice(:,:,1:jpl) = frcv(jpr_qsrice)%z3(:,:,1:jpl)
2042         ELSE
2043            ! Set all category values equal for the moment
2044            DO jl = 1, jpl
2045               zqsr_ice(:,:,jl) = frcv(jpr_qsrice)%z3(:,:,1)
2046            END DO
2047         ENDIF
2048      CASE( 'oce and ice' )
2049         zqsr_tot(:,:  ) =  ziceld(:,:) * frcv(jpr_qsroce)%z3(:,:,1)
2050         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN
2051            DO jl = 1, jpl
2052               zqsr_tot(:,:   ) = zqsr_tot(:,:) + a_i(:,:,jl) * frcv(jpr_qsrice)%z3(:,:,jl)   
2053               zqsr_ice(:,:,jl) = frcv(jpr_qsrice)%z3(:,:,jl)
2054            END DO
2055         ELSE
2056            zqsr_tot(:,:) = zqsr_tot(:,:) + picefr(:,:) * frcv(jpr_qsrice)%z3(:,:,1)
2057            DO jl = 1, jpl
2058               zqsr_ice(:,:,jl) = frcv(jpr_qsrice)%z3(:,:,1)
2059            END DO
2060         ENDIF
2061      CASE( 'mixed oce-ice' )
2062         zqsr_tot(:,:  ) = frcv(jpr_qsrmix)%z3(:,:,1)
2063! ** NEED TO SORT OUT HOW THIS SHOULD WORK IN THE MULTI-CATEGORY CASE - CURRENTLY NOT ALLOWED WHEN INTERFACE INITIALISED **
2064!       Create solar heat flux over ice using incoming solar heat flux and albedos
2065!       ( see OASIS3 user guide, 5th edition, p39 )
2066         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN
2067            DO jl = 1, jpl
2068               zqsr_ice(:,:,jl) = frcv(jpr_qsrmix)%z3(:,:,jl) * ( 1.- palbi(:,:,jl) )   &
2069                  &            / (  1.- ( alb_oce_mix(:,:   ) * ziceld(:,:)       &
2070                  &                     + palbi      (:,:,jl) * picefr(:,:) ) )
2071            END DO
2072         ELSE
2073            DO jl = 1, jpl
2074               zqsr_ice(:,:,jl) = frcv(jpr_qsrmix)%z3(:,:, 1) * ( 1.- palbi(:,:,jl) )   &
2075                  &            / (  1.- ( alb_oce_mix(:,:   ) * ziceld(:,:)       &
2076                  &                     + palbi      (:,:,jl) * picefr(:,:) ) )
2077            END DO
2078         ENDIF
2079      CASE( 'none'      )       ! Not available as for now: needs additional coding 
2080      !                         ! since fields received, here zqsr_tot,  are not defined with none option
2081         CALL ctl_stop( 'STOP', 'sbccpl/sbc_cpl_ice_flx: some fields are not defined. Change sn_rcv_qsr value in namelist namsbc_cpl' )
2082      END SELECT
2083      IF( ln_dm2dc .AND. ln_cpl ) THEN   ! modify qsr to include the diurnal cycle
2084         zqsr_tot(:,:  ) = sbc_dcy( zqsr_tot(:,:  ) )
2085         DO jl = 1, jpl
2086            zqsr_ice(:,:,jl) = sbc_dcy( zqsr_ice(:,:,jl) )
2087         END DO
2088      ENDIF
2089
2090#if defined key_si3
2091      ! --- solar flux over ocean --- !
2092      !         note: ziceld cannot be = 0 since we limit the ice concentration to amax
2093      zqsr_oce = 0._wp
2094      WHERE( ziceld /= 0._wp )  zqsr_oce(:,:) = ( zqsr_tot(:,:) - SUM( a_i * zqsr_ice, dim=3 ) ) / ziceld(:,:)
2095
2096      IF( ln_mixcpl ) THEN   ;   qsr_oce(:,:) = qsr_oce(:,:) * xcplmask(:,:,0) +  zqsr_oce(:,:)* zmsk(:,:)
2097      ELSE                   ;   qsr_oce(:,:) = zqsr_oce(:,:)   ;   ENDIF
2098#endif
2099
2100      IF( ln_mixcpl ) THEN
2101         qsr_tot(:,:) = qsr(:,:) * ziceld(:,:) + SUM( qsr_ice(:,:,:) * a_i(:,:,:), dim=3 )   ! total flux from blk
2102         qsr_tot(:,:) = qsr_tot(:,:) * xcplmask(:,:,0) +  zqsr_tot(:,:)* zmsk(:,:)
2103         DO jl = 1, jpl
2104            qsr_ice(:,:,jl) = qsr_ice(:,:,jl) * xcplmask(:,:,0) +  zqsr_ice(:,:,jl)* zmsk(:,:)
2105         END DO
2106      ELSE
2107         qsr_tot(:,:  ) = zqsr_tot(:,:  )
2108         qsr_ice(:,:,:) = zqsr_ice(:,:,:)
2109      ENDIF
2110
2111      !                                                      ! ========================= !
2112      SELECT CASE( TRIM( sn_rcv_dqnsdt%cldes ) )             !          d(qns)/dt        !
2113      !                                                      ! ========================= !
2114      CASE ('coupled')
2115         IF ( TRIM(sn_rcv_dqnsdt%clcat) == 'yes' ) THEN
2116            zdqns_ice(:,:,1:jpl) = frcv(jpr_dqnsdt)%z3(:,:,1:jpl)
2117         ELSE
2118            ! Set all category values equal for the moment
2119            DO jl=1,jpl
2120               zdqns_ice(:,:,jl) = frcv(jpr_dqnsdt)%z3(:,:,1)
2121            ENDDO
2122         ENDIF
2123      CASE( 'none' ) 
2124         zdqns_ice(:,:,:) = 0._wp
2125      END SELECT
2126     
2127      IF( ln_mixcpl ) THEN
2128         DO jl=1,jpl
2129            dqns_ice(:,:,jl) = dqns_ice(:,:,jl) * xcplmask(:,:,0) + zdqns_ice(:,:,jl) * zmsk(:,:)
2130         ENDDO
2131      ELSE
2132         dqns_ice(:,:,:) = zdqns_ice(:,:,:)
2133      ENDIF
2134
2135#if defined key_si3     
2136      !                                                      ! ========================= !
2137      !                                                      !      Transmitted Qsr      !   [W/m2]
2138      !                                                      ! ========================= !
2139      IF( .NOT.ln_cndflx ) THEN                              !==  No conduction flux as surface forcing  ==!
2140         !
2141         IF( nn_qtrice == 0 ) THEN
2142            ! formulation derived from Grenfell and Maykut (1977), where transmission rate
2143            !    1) depends on cloudiness
2144            !       ! ===> used prescribed cloud fraction representative for polar oceans in summer (0.81)
2145            !       !      should be real cloud fraction instead (as in the bulk) but needs to be read from atm.
2146            !    2) is 0 when there is any snow
2147            !    3) tends to 1 for thin ice
2148            ztri(:,:) = 0.18 * ( 1.0 - cloud_fra(:,:) ) + 0.35 * cloud_fra(:,:)  ! surface transmission when hi>10cm
2149            DO jl = 1, jpl
2150               WHERE    ( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) <  0.1_wp )       ! linear decrease from hi=0 to 10cm 
2151                  zqtr_ice_top(:,:,jl) = zqsr_ice(:,:,jl) * ( ztri(:,:) + ( 1._wp - ztri(:,:) ) * ( 1._wp - phi(:,:,jl) * 10._wp ) )
2152               ELSEWHERE( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) >= 0.1_wp )       ! constant (ztri) when hi>10cm
2153                  zqtr_ice_top(:,:,jl) = zqsr_ice(:,:,jl) * ztri(:,:)
2154               ELSEWHERE                                                           ! zero when hs>0
2155                  zqtr_ice_top(:,:,jl) = 0._wp 
2156               END WHERE
2157            ENDDO
2158         ELSEIF( nn_qtrice == 1 ) THEN
2159            ! formulation is derived from the thesis of M. Lebrun (2019).
2160            !    It represents the best fit using several sets of observations
2161            !    It comes with snow conductivities adapted to freezing/melting conditions (see icethd_zdf_bl99.F90)
2162            zqtr_ice_top(:,:,:) = 0.3_wp * zqsr_ice(:,:,:)
2163         ENDIF
2164         !     
2165      ELSEIF( ln_cndflx .AND. .NOT.ln_cndemulate ) THEN      !==  conduction flux as surface forcing  ==!
2166         !
2167         SELECT CASE( TRIM( sn_rcv_qtr%cldes ) )
2168         !
2169         !      ! ===> here we receive the qtr_ice_top array from the coupler
2170         CASE ('coupled')
2171            IF (ln_scale_ice_flux) THEN
2172               WHERE( a_i(:,:,:) > 0.0_wp ) zqtr_ice_top(:,:,:) = frcv(jpr_qtr)%z3(:,:,:) * a_i_last_couple(:,:,:) / a_i(:,:,:)
2173               WHERE( a_i(:,:,:) <= 0.0_wp ) zqtr_ice_top(:,:,:) = 0.0_wp
2174            ELSE
2175               zqtr_ice_top(:,:,:) = frcv(jpr_qtr)%z3(:,:,:)
2176            ENDIF
2177
2178         !      if we are not getting this data from the coupler then assume zero (fully opaque ice)
2179         CASE ('none')
2180            zqtr_ice_top(:,:,:) = 0._wp
2181         END SELECT
2182         !
2183      ENDIF
2184      !
2185      IF( ln_mixcpl ) THEN
2186         DO jl=1,jpl
2187            qtr_ice_top(:,:,jl) = qtr_ice_top(:,:,jl) * xcplmask(:,:,0) + zqtr_ice_top(:,:,jl) * zmsk(:,:)
2188         ENDDO
2189      ELSE
2190         qtr_ice_top(:,:,:) = zqtr_ice_top(:,:,:)
2191      ENDIF
2192      !                                                      ! ================== !
2193      !                                                      !   ice skin temp.   !
2194      !                                                      ! ================== !
2195      ! needed by Met Office
2196      IF( srcv(jpr_ts_ice)%laction ) THEN
2197         WHERE    ( frcv(jpr_ts_ice)%z3(:,:,:) > 0.0  )   ;   ztsu(:,:,:) =   0. + rt0 
2198         ELSEWHERE( frcv(jpr_ts_ice)%z3(:,:,:) < -60. )   ;   ztsu(:,:,:) = -60. + rt0
2199         ELSEWHERE                                        ;   ztsu(:,:,:) = frcv(jpr_ts_ice)%z3(:,:,:) + rt0
2200         END WHERE
2201         !
2202         IF( ln_mixcpl ) THEN
2203            DO jl=1,jpl
2204               pist(:,:,jl) = pist(:,:,jl) * xcplmask(:,:,0) + ztsu(:,:,jl) * zmsk(:,:)
2205            ENDDO
2206         ELSE
2207            pist(:,:,:) = ztsu(:,:,:)
2208         ENDIF
2209         !
2210      ENDIF
2211      !
2212#endif
2213      !
2214   END SUBROUTINE sbc_cpl_ice_flx
2215   
2216   
2217   SUBROUTINE sbc_cpl_snd( kt )
2218      !!----------------------------------------------------------------------
2219      !!             ***  ROUTINE sbc_cpl_snd  ***
2220      !!
2221      !! ** Purpose :   provide the ocean-ice informations to the atmosphere
2222      !!
2223      !! ** Method  :   send to the atmosphere through a call to cpl_snd
2224      !!              all the needed fields (as defined in sbc_cpl_init)
2225      !!----------------------------------------------------------------------
2226      INTEGER, INTENT(in) ::   kt
2227      !
2228      INTEGER ::   ji, jj, jl   ! dummy loop indices
2229      INTEGER ::   isec, info   ! local integer
2230      REAL(wp) ::   zumax, zvmax
2231      REAL(wp), DIMENSION(jpi,jpj)     ::   zfr_l, ztmp1, ztmp2, zotx1, zoty1, zotz1, zitx1, zity1, zitz1
2232      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   ztmp3, ztmp4   
2233      !!----------------------------------------------------------------------
2234      !
2235      isec = ( kt - nit000 ) * NINT( rdt )        ! date of exchanges
2236      info = OASIS_idle
2237
2238      zfr_l(:,:) = 1.- fr_i(:,:)
2239      !                                                      ! ------------------------- !
2240      !                                                      !    Surface temperature    !   in Kelvin
2241      !                                                      ! ------------------------- !
2242      IF( ssnd(jps_toce)%laction .OR. ssnd(jps_tice)%laction .OR. ssnd(jps_tmix)%laction ) THEN
2243         
2244         IF ( nn_components == jp_iam_opa ) THEN
2245            ztmp1(:,:) = tsn(:,:,1,jp_tem)   ! send temperature as it is (potential or conservative) -> use of l_useCT on the received part
2246         ELSE
2247            ! we must send the surface potential temperature
2248            IF( l_useCT )  THEN    ;   ztmp1(:,:) = eos_pt_from_ct( tsn(:,:,1,jp_tem), tsn(:,:,1,jp_sal) )
2249            ELSE                   ;   ztmp1(:,:) = tsn(:,:,1,jp_tem)
2250            ENDIF
2251            !
2252            SELECT CASE( sn_snd_temp%cldes)
2253            CASE( 'oce only'             )   ;   ztmp1(:,:) =   ztmp1(:,:) + rt0
2254            CASE( 'oce and ice'          )   ;   ztmp1(:,:) =   ztmp1(:,:) + rt0
2255               SELECT CASE( sn_snd_temp%clcat )
2256               CASE( 'yes' )   
2257                  ztmp3(:,:,1:jpl) = tn_ice(:,:,1:jpl)
2258               CASE( 'no' )
2259                  WHERE( SUM( a_i, dim=3 ) /= 0. )
2260                     ztmp3(:,:,1) = SUM( tn_ice * a_i, dim=3 ) / SUM( a_i, dim=3 )
2261                  ELSEWHERE
2262                     ztmp3(:,:,1) = rt0
2263                  END WHERE
2264               CASE default   ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%clcat' )
2265               END SELECT
2266            CASE( 'weighted oce and ice' )   ;   ztmp1(:,:) = ( ztmp1(:,:) + rt0 ) * zfr_l(:,:)   
2267               SELECT CASE( sn_snd_temp%clcat )
2268               CASE( 'yes' )   
2269                  ztmp3(:,:,1:jpl) = tn_ice(:,:,1:jpl) * a_i(:,:,1:jpl)
2270               CASE( 'no' )
2271                  ztmp3(:,:,:) = 0.0
2272                  DO jl=1,jpl
2273                     ztmp3(:,:,1) = ztmp3(:,:,1) + tn_ice(:,:,jl) * a_i(:,:,jl)
2274                  ENDDO
2275               CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%clcat' )
2276               END SELECT
2277            CASE( 'oce and weighted ice')    ;   ztmp1(:,:) =   tsn(:,:,1,jp_tem) + rt0 
2278               SELECT CASE( sn_snd_temp%clcat ) 
2279               CASE( 'yes' )   
2280                  ztmp3(:,:,1:jpl) = tn_ice(:,:,1:jpl) * a_i(:,:,1:jpl) 
2281               CASE( 'no' ) 
2282                  ztmp3(:,:,:) = 0.0 
2283                  DO jl=1,jpl 
2284                     ztmp3(:,:,1) = ztmp3(:,:,1) + tn_ice(:,:,jl) * a_i(:,:,jl) 
2285                  ENDDO 
2286               CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%clcat' ) 
2287               END SELECT
2288            CASE( 'mixed oce-ice'        )   
2289               ztmp1(:,:) = ( ztmp1(:,:) + rt0 ) * zfr_l(:,:) 
2290               DO jl=1,jpl
2291                  ztmp1(:,:) = ztmp1(:,:) + tn_ice(:,:,jl) * a_i(:,:,jl)
2292               ENDDO
2293            CASE default                     ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%cldes' )
2294            END SELECT
2295         ENDIF
2296         IF( ssnd(jps_toce)%laction )   CALL cpl_snd( jps_toce, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info )
2297         IF( ssnd(jps_tice)%laction )   CALL cpl_snd( jps_tice, isec, ztmp3, info )
2298         IF( ssnd(jps_tmix)%laction )   CALL cpl_snd( jps_tmix, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info )
2299      ENDIF
2300      !
2301      !                                                      ! ------------------------- !
2302      !                                                      ! 1st layer ice/snow temp.  !
2303      !                                                      ! ------------------------- !
2304#if defined key_si3
2305      ! needed by  Met Office
2306      IF( ssnd(jps_ttilyr)%laction) THEN
2307         SELECT CASE( sn_snd_ttilyr%cldes)
2308         CASE ('weighted ice')
2309            ztmp3(:,:,1:jpl) = t1_ice(:,:,1:jpl) * a_i(:,:,1:jpl) 
2310         CASE default                     ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_ttilyr%cldes' )
2311         END SELECT
2312         IF( ssnd(jps_ttilyr)%laction )   CALL cpl_snd( jps_ttilyr, isec, ztmp3, info )
2313      ENDIF
2314#endif
2315      !                                                      ! ------------------------- !
2316      !                                                      !           Albedo          !
2317      !                                                      ! ------------------------- !
2318      IF( ssnd(jps_albice)%laction ) THEN                         ! ice
2319          SELECT CASE( sn_snd_alb%cldes )
2320          CASE( 'ice' )
2321             SELECT CASE( sn_snd_alb%clcat )
2322             CASE( 'yes' )   
2323                ztmp3(:,:,1:jpl) = alb_ice(:,:,1:jpl)
2324             CASE( 'no' )
2325                WHERE( SUM( a_i, dim=3 ) /= 0. )
2326                   ztmp1(:,:) = SUM( alb_ice (:,:,1:jpl) * a_i(:,:,1:jpl), dim=3 ) / SUM( a_i(:,:,1:jpl), dim=3 )
2327                ELSEWHERE
2328                   ztmp1(:,:) = alb_oce_mix(:,:)
2329                END WHERE
2330             CASE default   ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_alb%clcat' )
2331             END SELECT
2332          CASE( 'weighted ice' )   ;
2333             SELECT CASE( sn_snd_alb%clcat )
2334             CASE( 'yes' )   
2335                ztmp3(:,:,1:jpl) =  alb_ice(:,:,1:jpl) * a_i(:,:,1:jpl)
2336             CASE( 'no' )
2337                WHERE( fr_i (:,:) > 0. )
2338                   ztmp1(:,:) = SUM (  alb_ice(:,:,1:jpl) * a_i(:,:,1:jpl), dim=3 )
2339                ELSEWHERE
2340                   ztmp1(:,:) = 0.
2341                END WHERE
2342             CASE default   ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_ice%clcat' )
2343             END SELECT
2344          CASE default      ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_alb%cldes' )
2345         END SELECT
2346
2347         SELECT CASE( sn_snd_alb%clcat )
2348            CASE( 'yes' )   
2349               CALL cpl_snd( jps_albice, isec, ztmp3, info )      !-> MV this has never been checked in coupled mode
2350            CASE( 'no'  )   
2351               CALL cpl_snd( jps_albice, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info ) 
2352         END SELECT
2353      ENDIF
2354
2355      IF( ssnd(jps_albmix)%laction ) THEN                         ! mixed ice-ocean
2356         ztmp1(:,:) = alb_oce_mix(:,:) * zfr_l(:,:)
2357         DO jl = 1, jpl
2358            ztmp1(:,:) = ztmp1(:,:) + alb_ice(:,:,jl) * a_i(:,:,jl)
2359         END DO
2360         CALL cpl_snd( jps_albmix, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info )
2361      ENDIF
2362      !                                                      ! ------------------------- !
2363      !                                                      !  Ice fraction & Thickness !
2364      !                                                      ! ------------------------- !
2365      ! Send ice fraction field to atmosphere
2366      IF( ssnd(jps_fice)%laction ) THEN
2367         SELECT CASE( sn_snd_thick%clcat )
2368         CASE( 'yes' )   ;   ztmp3(:,:,1:jpl) =  a_i(:,:,1:jpl)
2369         CASE( 'no'  )   ;   ztmp3(:,:,1    ) = fr_i(:,:      )
2370         CASE default    ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%clcat' )
2371         END SELECT
2372         CALL cpl_snd( jps_fice, isec, ztmp3, info )
2373      ENDIF
2374
2375#if defined key_si3 || defined key_cice
2376      ! If this coupling was successful then save ice fraction for use between coupling points.
2377      ! This is needed for some calculations where the ice fraction at the last coupling point
2378      ! is needed.
2379      IF(  info == OASIS_Sent    .OR. info == OASIS_ToRest .OR. & 
2380         & info == OASIS_SentOut .OR. info == OASIS_ToRestOut ) THEN
2381         IF ( sn_snd_thick%clcat == 'yes' ) THEN
2382           a_i_last_couple(:,:,1:jpl) = a_i(:,:,1:jpl)
2383         ENDIF
2384      ENDIF
2385#endif
2386
2387      IF( ssnd(jps_fice1)%laction ) THEN
2388         SELECT CASE( sn_snd_thick1%clcat )
2389         CASE( 'yes' )   ;   ztmp3(:,:,1:jpl) =  a_i(:,:,1:jpl)
2390         CASE( 'no'  )   ;   ztmp3(:,:,1    ) = fr_i(:,:      )
2391         CASE default    ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick1%clcat' )
2392         END SELECT
2393         CALL cpl_snd( jps_fice1, isec, ztmp3, info )
2394      ENDIF
2395     
2396      ! Send ice fraction field to OPA (sent by SAS in SAS-OPA coupling)
2397      IF( ssnd(jps_fice2)%laction ) THEN
2398         ztmp3(:,:,1) = fr_i(:,:)
2399         IF( ssnd(jps_fice2)%laction )   CALL cpl_snd( jps_fice2, isec, ztmp3, info )
2400      ENDIF
2401
2402      ! Send ice and snow thickness field
2403      IF( ssnd(jps_hice)%laction .OR. ssnd(jps_hsnw)%laction ) THEN
2404         SELECT CASE( sn_snd_thick%cldes)
2405         CASE( 'none'                  )       ! nothing to do
2406         CASE( 'weighted ice and snow' )   
2407            SELECT CASE( sn_snd_thick%clcat )
2408            CASE( 'yes' )   
2409               ztmp3(:,:,1:jpl) =  h_i(:,:,1:jpl) * a_i(:,:,1:jpl)
2410               ztmp4(:,:,1:jpl) =  h_s(:,:,1:jpl) * a_i(:,:,1:jpl)
2411            CASE( 'no' )
2412               ztmp3(:,:,:) = 0.0   ;  ztmp4(:,:,:) = 0.0
2413               DO jl=1,jpl
2414                  ztmp3(:,:,1) = ztmp3(:,:,1) + h_i(:,:,jl) * a_i(:,:,jl)
2415                  ztmp4(:,:,1) = ztmp4(:,:,1) + h_s(:,:,jl) * a_i(:,:,jl)
2416               ENDDO
2417            CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%clcat' )
2418            END SELECT
2419         CASE( 'ice and snow'         )   
2420            SELECT CASE( sn_snd_thick%clcat )
2421            CASE( 'yes' )
2422               ztmp3(:,:,1:jpl) = h_i(:,:,1:jpl)
2423               ztmp4(:,:,1:jpl) = h_s(:,:,1:jpl)
2424            CASE( 'no' )
2425               WHERE( SUM( a_i, dim=3 ) /= 0. )
2426                  ztmp3(:,:,1) = SUM( h_i * a_i, dim=3 ) / SUM( a_i, dim=3 )
2427                  ztmp4(:,:,1) = SUM( h_s * a_i, dim=3 ) / SUM( a_i, dim=3 )
2428               ELSEWHERE
2429                 ztmp3(:,:,1) = 0.
2430                 ztmp4(:,:,1) = 0.
2431               END WHERE
2432            CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%clcat' )
2433            END SELECT
2434         CASE default                     ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%cldes' )
2435         END SELECT
2436         IF( ssnd(jps_hice)%laction )   CALL cpl_snd( jps_hice, isec, ztmp3, info )
2437         IF( ssnd(jps_hsnw)%laction )   CALL cpl_snd( jps_hsnw, isec, ztmp4, info )
2438      ENDIF
2439
2440#if defined key_si3
2441      !                                                      ! ------------------------- !
2442      !                                                      !      Ice melt ponds       !
2443      !                                                      ! ------------------------- !
2444      ! needed by Met Office: 1) fraction of ponded ice 2) local/actual pond depth
2445      IF( ssnd(jps_a_p)%laction .OR. ssnd(jps_ht_p)%laction ) THEN
2446         SELECT CASE( sn_snd_mpnd%cldes) 
2447         CASE( 'ice only' ) 
2448            SELECT CASE( sn_snd_mpnd%clcat ) 
2449            CASE( 'yes' ) 
2450               ztmp3(:,:,1:jpl) =  a_ip_eff(:,:,1:jpl)
2451               ztmp4(:,:,1:jpl) =  h_ip(:,:,1:jpl) 
2452            CASE( 'no' ) 
2453               ztmp3(:,:,:) = 0.0 
2454               ztmp4(:,:,:) = 0.0 
2455               DO jl=1,jpl 
2456                 ztmp3(:,:,1) = ztmp3(:,:,1) + a_ip_frac(:,:,jpl)
2457                 ztmp4(:,:,1) = ztmp4(:,:,1) + h_ip(:,:,jpl)
2458               ENDDO 
2459            CASE default   ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_mpnd%clcat' ) 
2460            END SELECT 
2461         CASE default      ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_mpnd%cldes' )     
2462         END SELECT 
2463         IF( ssnd(jps_a_p)%laction  )   CALL cpl_snd( jps_a_p , isec, ztmp3, info )     
2464         IF( ssnd(jps_ht_p)%laction )   CALL cpl_snd( jps_ht_p, isec, ztmp4, info )     
2465      ENDIF 
2466      !
2467      !                                                      ! ------------------------- !
2468      !                                                      !     Ice conductivity      !
2469      !                                                      ! ------------------------- !
2470      ! needed by Met Office
2471      IF( ssnd(jps_kice)%laction ) THEN
2472         SELECT CASE( sn_snd_cond%cldes) 
2473         CASE( 'weighted ice' )   
2474            SELECT CASE( sn_snd_cond%clcat ) 
2475            CASE( 'yes' )   
2476          ztmp3(:,:,1:jpl) =  cnd_ice(:,:,1:jpl) * a_i(:,:,1:jpl) 
2477            CASE( 'no' ) 
2478               ztmp3(:,:,:) = 0.0 
2479               DO jl=1,jpl 
2480                 ztmp3(:,:,1) = ztmp3(:,:,1) + cnd_ice(:,:,jl) * a_i(:,:,jl) 
2481               ENDDO 
2482            CASE default   ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_cond%clcat' ) 
2483            END SELECT
2484         CASE( 'ice only' )   
2485           ztmp3(:,:,1:jpl) = cnd_ice(:,:,1:jpl) 
2486         CASE default      ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_cond%cldes' )     
2487         END SELECT
2488         IF( ssnd(jps_kice)%laction )   CALL cpl_snd( jps_kice, isec, ztmp3, info ) 
2489      ENDIF 
2490#endif
2491
2492      !                                                      ! ------------------------- !
2493      !                                                      !  CO2 flux from PISCES     !
2494      !                                                      ! ------------------------- !
2495      IF( ssnd(jps_co2)%laction .AND. l_co2cpl )   THEN 
2496         ztmp1(:,:) = oce_co2(:,:) * 1000.  ! conversion in molC/m2/s
2497         CALL cpl_snd( jps_co2, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ) , info ) 
2498      ENDIF 
2499      !
2500      !                                                      ! ------------------------- !
2501      IF( ssnd(jps_ocx1)%laction ) THEN                      !      Surface current      !
2502         !                                                   ! ------------------------- !
2503         !   
2504         !                                                  j+1   j     -----V---F
2505         ! surface velocity always sent from T point                     !       |
2506         !                                                        j      |   T   U
2507         !                                                               |       |
2508         !                                                   j    j-1   -I-------|
2509         !                                               (for I)         |       |
2510         !                                                              i-1  i   i
2511         !                                                               i      i+1 (for I)
2512         IF( nn_components == jp_iam_opa ) THEN
2513            zotx1(:,:) = un(:,:,1) 
2514            zoty1(:,:) = vn(:,:,1) 
2515         ELSE       
2516            SELECT CASE( TRIM( sn_snd_crt%cldes ) )
2517            CASE( 'oce only'             )      ! C-grid ==> T
2518               DO jj = 2, jpjm1
2519                  DO ji = fs_2, fs_jpim1   ! vector opt.
2520                     zotx1(ji,jj) = 0.5 * ( un(ji,jj,1) + un(ji-1,jj  ,1) )
2521                     zoty1(ji,jj) = 0.5 * ( vn(ji,jj,1) + vn(ji  ,jj-1,1) ) 
2522                  END DO
2523               END DO
2524            CASE( 'weighted oce and ice' )      ! Ocean and Ice on C-grid ==> T 
2525               DO jj = 2, jpjm1
2526                  DO ji = fs_2, fs_jpim1   ! vector opt.
2527                     zotx1(ji,jj) = 0.5 * ( un   (ji,jj,1) + un   (ji-1,jj  ,1) ) * zfr_l(ji,jj) 
2528                     zoty1(ji,jj) = 0.5 * ( vn   (ji,jj,1) + vn   (ji  ,jj-1,1) ) * zfr_l(ji,jj)
2529                     zitx1(ji,jj) = 0.5 * ( u_ice(ji,jj  ) + u_ice(ji-1,jj    ) ) *  fr_i(ji,jj)
2530                     zity1(ji,jj) = 0.5 * ( v_ice(ji,jj  ) + v_ice(ji  ,jj-1  ) ) *  fr_i(ji,jj)
2531                  END DO
2532               END DO
2533               CALL lbc_lnk_multi( 'sbccpl', zitx1, 'T', -1., zity1, 'T', -1. )
2534            CASE( 'mixed oce-ice'        )      ! Ocean and Ice on C-grid ==> T
2535               DO jj = 2, jpjm1
2536                  DO ji = fs_2, fs_jpim1   ! vector opt.
2537                     zotx1(ji,jj) = 0.5 * ( un   (ji,jj,1) + un   (ji-1,jj  ,1) ) * zfr_l(ji,jj)   &
2538                        &         + 0.5 * ( u_ice(ji,jj  ) + u_ice(ji-1,jj    ) ) *  fr_i(ji,jj)
2539                     zoty1(ji,jj) = 0.5 * ( vn   (ji,jj,1) + vn   (ji  ,jj-1,1) ) * zfr_l(ji,jj)   &
2540                        &         + 0.5 * ( v_ice(ji,jj  ) + v_ice(ji  ,jj-1  ) ) *  fr_i(ji,jj)
2541                  END DO
2542               END DO
2543            END SELECT
2544            CALL lbc_lnk_multi( 'sbccpl', zotx1, ssnd(jps_ocx1)%clgrid, -1.,  zoty1, ssnd(jps_ocy1)%clgrid, -1. )
2545            !
2546         ENDIF
2547         !
2548         !
2549         IF( TRIM( sn_snd_crt%clvor ) == 'eastward-northward' ) THEN             ! Rotation of the components
2550            !                                                                     ! Ocean component
2551            CALL rot_rep( zotx1, zoty1, ssnd(jps_ocx1)%clgrid, 'ij->e', ztmp1 )       ! 1st component
2552            CALL rot_rep( zotx1, zoty1, ssnd(jps_ocx1)%clgrid, 'ij->n', ztmp2 )       ! 2nd component
2553            zotx1(:,:) = ztmp1(:,:)                                                   ! overwrite the components
2554            zoty1(:,:) = ztmp2(:,:)
2555            IF( ssnd(jps_ivx1)%laction ) THEN                                     ! Ice component
2556               CALL rot_rep( zitx1, zity1, ssnd(jps_ivx1)%clgrid, 'ij->e', ztmp1 )    ! 1st component
2557               CALL rot_rep( zitx1, zity1, ssnd(jps_ivx1)%clgrid, 'ij->n', ztmp2 )    ! 2nd component
2558               zitx1(:,:) = ztmp1(:,:)                                                ! overwrite the components
2559               zity1(:,:) = ztmp2(:,:)
2560            ENDIF
2561         ENDIF
2562         !
2563         ! spherical coordinates to cartesian -> 2 components to 3 components
2564         IF( TRIM( sn_snd_crt%clvref ) == 'cartesian' ) THEN
2565            ztmp1(:,:) = zotx1(:,:)                     ! ocean currents
2566            ztmp2(:,:) = zoty1(:,:)
2567            CALL oce2geo ( ztmp1, ztmp2, 'T', zotx1, zoty1, zotz1 )
2568            !
2569            IF( ssnd(jps_ivx1)%laction ) THEN           ! ice velocities
2570               ztmp1(:,:) = zitx1(:,:)
2571               ztmp1(:,:) = zity1(:,:)
2572               CALL oce2geo ( ztmp1, ztmp2, 'T', zitx1, zity1, zitz1 )
2573            ENDIF
2574         ENDIF
2575         !
2576         IF( ssnd(jps_ocx1)%laction )   CALL cpl_snd( jps_ocx1, isec, RESHAPE ( zotx1, (/jpi,jpj,1/) ), info )   ! ocean x current 1st grid
2577         IF( ssnd(jps_ocy1)%laction )   CALL cpl_snd( jps_ocy1, isec, RESHAPE ( zoty1, (/jpi,jpj,1/) ), info )   ! ocean y current 1st grid
2578         IF( ssnd(jps_ocz1)%laction )   CALL cpl_snd( jps_ocz1, isec, RESHAPE ( zotz1, (/jpi,jpj,1/) ), info )   ! ocean z current 1st grid
2579         !
2580         IF( ssnd(jps_ivx1)%laction )   CALL cpl_snd( jps_ivx1, isec, RESHAPE ( zitx1, (/jpi,jpj,1/) ), info )   ! ice   x current 1st grid
2581         IF( ssnd(jps_ivy1)%laction )   CALL cpl_snd( jps_ivy1, isec, RESHAPE ( zity1, (/jpi,jpj,1/) ), info )   ! ice   y current 1st grid
2582         IF( ssnd(jps_ivz1)%laction )   CALL cpl_snd( jps_ivz1, isec, RESHAPE ( zitz1, (/jpi,jpj,1/) ), info )   ! ice   z current 1st grid
2583         !
2584      ENDIF
2585      !
2586      !                                                      ! ------------------------- !
2587      !                                                      !  Surface current to waves !
2588      !                                                      ! ------------------------- !
2589      IF( ssnd(jps_ocxw)%laction .OR. ssnd(jps_ocyw)%laction ) THEN 
2590          !     
2591          !                                                  j+1  j     -----V---F
2592          ! surface velocity always sent from T point                    !       |
2593          !                                                       j      |   T   U
2594          !                                                              |       |
2595          !                                                   j   j-1   -I-------|
2596          !                                               (for I)        |       |
2597          !                                                             i-1  i   i
2598          !                                                              i      i+1 (for I)
2599          SELECT CASE( TRIM( sn_snd_crtw%cldes ) ) 
2600          CASE( 'oce only'             )      ! C-grid ==> T
2601             DO jj = 2, jpjm1 
2602                DO ji = fs_2, fs_jpim1   ! vector opt.
2603                   zotx1(ji,jj) = 0.5 * ( un(ji,jj,1) + un(ji-1,jj  ,1) ) 
2604                   zoty1(ji,jj) = 0.5 * ( vn(ji,jj,1) + vn(ji , jj-1,1) ) 
2605                END DO
2606             END DO
2607          CASE( 'weighted oce and ice' )      ! Ocean and Ice on C-grid ==> T   
2608             DO jj = 2, jpjm1 
2609                DO ji = fs_2, fs_jpim1   ! vector opt.
2610                   zotx1(ji,jj) = 0.5 * ( un   (ji,jj,1) + un   (ji-1,jj  ,1) ) * zfr_l(ji,jj)   
2611                   zoty1(ji,jj) = 0.5 * ( vn   (ji,jj,1) + vn   (ji  ,jj-1,1) ) * zfr_l(ji,jj) 
2612                   zitx1(ji,jj) = 0.5 * ( u_ice(ji,jj  ) + u_ice(ji-1,jj    ) ) *  fr_i(ji,jj) 
2613                   zity1(ji,jj) = 0.5 * ( v_ice(ji,jj  ) + v_ice(ji  ,jj-1  ) ) *  fr_i(ji,jj) 
2614                END DO
2615             END DO
2616             CALL lbc_lnk_multi( 'sbccpl', zitx1, 'T', -1.,  zity1, 'T', -1. ) 
2617          CASE( 'mixed oce-ice'        )      ! Ocean and Ice on C-grid ==> T 
2618             DO jj = 2, jpjm1 
2619                DO ji = fs_2, fs_jpim1   ! vector opt.
2620                   zotx1(ji,jj) = 0.5 * ( un   (ji,jj,1) + un   (ji-1,jj  ,1) ) * zfr_l(ji,jj)   & 
2621                      &         + 0.5 * ( u_ice(ji,jj  ) + u_ice(ji-1,jj    ) ) *  fr_i(ji,jj) 
2622                   zoty1(ji,jj) = 0.5 * ( vn   (ji,jj,1) + vn   (ji  ,jj-1,1) ) * zfr_l(ji,jj)   & 
2623                      &         + 0.5 * ( v_ice(ji,jj  ) + v_ice(ji  ,jj-1  ) ) *  fr_i(ji,jj) 
2624                END DO
2625             END DO
2626          END SELECT
2627         CALL lbc_lnk_multi( 'sbccpl', zotx1, ssnd(jps_ocxw)%clgrid, -1., zoty1, ssnd(jps_ocyw)%clgrid, -1. ) 
2628         !
2629         !
2630         IF( TRIM( sn_snd_crtw%clvor ) == 'eastward-northward' ) THEN             ! Rotation of the components
2631         !                                                                        ! Ocean component
2632            CALL rot_rep( zotx1, zoty1, ssnd(jps_ocxw)%clgrid, 'ij->e', ztmp1 )       ! 1st component 
2633            CALL rot_rep( zotx1, zoty1, ssnd(jps_ocxw)%clgrid, 'ij->n', ztmp2 )       ! 2nd component 
2634            zotx1(:,:) = ztmp1(:,:)                                                   ! overwrite the components 
2635            zoty1(:,:) = ztmp2(:,:) 
2636            IF( ssnd(jps_ivx1)%laction ) THEN                                     ! Ice component
2637               CALL rot_rep( zitx1, zity1, ssnd(jps_ivx1)%clgrid, 'ij->e', ztmp1 )    ! 1st component 
2638               CALL rot_rep( zitx1, zity1, ssnd(jps_ivx1)%clgrid, 'ij->n', ztmp2 )    ! 2nd component 
2639               zitx1(:,:) = ztmp1(:,:)                                                ! overwrite the components 
2640               zity1(:,:) = ztmp2(:,:) 
2641            ENDIF
2642         ENDIF 
2643         !
2644!         ! spherical coordinates to cartesian -> 2 components to 3 components
2645!         IF( TRIM( sn_snd_crtw%clvref ) == 'cartesian' ) THEN
2646!            ztmp1(:,:) = zotx1(:,:)                     ! ocean currents
2647!            ztmp2(:,:) = zoty1(:,:)
2648!            CALL oce2geo ( ztmp1, ztmp2, 'T', zotx1, zoty1, zotz1 )
2649!            !
2650!            IF( ssnd(jps_ivx1)%laction ) THEN           ! ice velocities
2651!               ztmp1(:,:) = zitx1(:,:)
2652!               ztmp1(:,:) = zity1(:,:)
2653!               CALL oce2geo ( ztmp1, ztmp2, 'T', zitx1, zity1, zitz1 )
2654!            ENDIF
2655!         ENDIF
2656         !
2657         IF( ssnd(jps_ocxw)%laction )   CALL cpl_snd( jps_ocxw, isec, RESHAPE ( zotx1, (/jpi,jpj,1/) ), info )   ! ocean x current 1st grid
2658         IF( ssnd(jps_ocyw)%laction )   CALL cpl_snd( jps_ocyw, isec, RESHAPE ( zoty1, (/jpi,jpj,1/) ), info )   ! ocean y current 1st grid
2659         
2660      ENDIF 
2661      !
2662      IF( ssnd(jps_ficet)%laction ) THEN
2663         CALL cpl_snd( jps_ficet, isec, RESHAPE ( fr_i, (/jpi,jpj,1/) ), info ) 
2664      END IF 
2665      !                                                      ! ------------------------- !
2666      !                                                      !   Water levels to waves   !
2667      !                                                      ! ------------------------- !
2668      IF( ssnd(jps_wlev)%laction ) THEN
2669         IF( ln_apr_dyn ) THEN 
2670            IF( kt /= nit000 ) THEN 
2671               ztmp1(:,:) = sshb(:,:) - 0.5 * ( ssh_ib(:,:) + ssh_ibb(:,:) ) 
2672            ELSE 
2673               ztmp1(:,:) = sshb(:,:) 
2674            ENDIF 
2675         ELSE 
2676            ztmp1(:,:) = sshn(:,:) 
2677         ENDIF 
2678         CALL cpl_snd( jps_wlev  , isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info ) 
2679      END IF 
2680      !
2681      !  Fields sent by OPA to SAS when doing OPA<->SAS coupling
2682      !                                                        ! SSH
2683      IF( ssnd(jps_ssh )%laction )  THEN
2684         !                          ! removed inverse barometer ssh when Patm
2685         !                          forcing is used (for sea-ice dynamics)
2686         IF( ln_apr_dyn ) THEN   ;   ztmp1(:,:) = sshb(:,:) - 0.5 * ( ssh_ib(:,:) + ssh_ibb(:,:) )
2687         ELSE                    ;   ztmp1(:,:) = sshn(:,:)
2688         ENDIF
2689         CALL cpl_snd( jps_ssh   , isec, RESHAPE ( ztmp1            , (/jpi,jpj,1/) ), info )
2690
2691      ENDIF
2692      !                                                        ! SSS
2693      IF( ssnd(jps_soce  )%laction )  THEN
2694         CALL cpl_snd( jps_soce  , isec, RESHAPE ( tsn(:,:,1,jp_sal), (/jpi,jpj,1/) ), info )
2695      ENDIF
2696      !                                                        ! first T level thickness
2697      IF( ssnd(jps_e3t1st )%laction )  THEN
2698         CALL cpl_snd( jps_e3t1st, isec, RESHAPE ( e3t_n(:,:,1)   , (/jpi,jpj,1/) ), info )
2699      ENDIF
2700      !                                                        ! Qsr fraction
2701      IF( ssnd(jps_fraqsr)%laction )  THEN
2702         CALL cpl_snd( jps_fraqsr, isec, RESHAPE ( fraqsr_1lev(:,:) , (/jpi,jpj,1/) ), info )
2703      ENDIF
2704      !
2705      !  Fields sent by SAS to OPA when OASIS coupling
2706      !                                                        ! Solar heat flux
2707      IF( ssnd(jps_qsroce)%laction )  CALL cpl_snd( jps_qsroce, isec, RESHAPE ( qsr , (/jpi,jpj,1/) ), info )
2708      IF( ssnd(jps_qnsoce)%laction )  CALL cpl_snd( jps_qnsoce, isec, RESHAPE ( qns , (/jpi,jpj,1/) ), info )
2709      IF( ssnd(jps_oemp  )%laction )  CALL cpl_snd( jps_oemp  , isec, RESHAPE ( emp , (/jpi,jpj,1/) ), info )
2710      IF( ssnd(jps_sflx  )%laction )  CALL cpl_snd( jps_sflx  , isec, RESHAPE ( sfx , (/jpi,jpj,1/) ), info )
2711      IF( ssnd(jps_otx1  )%laction )  CALL cpl_snd( jps_otx1  , isec, RESHAPE ( utau, (/jpi,jpj,1/) ), info )
2712      IF( ssnd(jps_oty1  )%laction )  CALL cpl_snd( jps_oty1  , isec, RESHAPE ( vtau, (/jpi,jpj,1/) ), info )
2713      IF( ssnd(jps_rnf   )%laction )  CALL cpl_snd( jps_rnf   , isec, RESHAPE ( rnf , (/jpi,jpj,1/) ), info )
2714      IF( ssnd(jps_taum  )%laction )  CALL cpl_snd( jps_taum  , isec, RESHAPE ( taum, (/jpi,jpj,1/) ), info )
2715
2716#if defined key_si3
2717      !                                                      ! ------------------------- !
2718      !                                                      ! Sea surface freezing temp !
2719      !                                                      ! ------------------------- !
2720      ! needed by Met Office
2721      CALL eos_fzp(tsn(:,:,1,jp_sal), sstfrz)
2722      ztmp1(:,:) = sstfrz(:,:) + rt0
2723      IF( ssnd(jps_sstfrz)%laction )  CALL cpl_snd( jps_sstfrz, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info)
2724#endif
2725      !
2726   END SUBROUTINE sbc_cpl_snd
2727   
2728   !!======================================================================
2729END MODULE sbccpl
Note: See TracBrowser for help on using the repository browser.