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/releases/r4.0/r4.0-HEAD/src/OCE/SBC – NEMO

source: NEMO/releases/r4.0/r4.0-HEAD/src/OCE/SBC/sbccpl.F90 @ 13066

Last change on this file since 13066 was 13066, checked in by smasson, 4 years ago

r4.0-HEAD: sbccpl bugfix when sending 'oce and ice' without ice categories, see #2434

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