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/2020/dev_r13648_ASINTER-04_laurent_bulk_ice/src/OCE/SBC – NEMO

source: NEMO/branches/2020/dev_r13648_ASINTER-04_laurent_bulk_ice/src/OCE/SBC/sbccpl.F90 @ 14021

Last change on this file since 14021 was 14021, checked in by laurent, 3 years ago

Caught up with trunk rev 14020...

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