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

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

source: branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 @ 8934

Last change on this file since 8934 was 8934, checked in by clem, 6 years ago

dev_CNRS_2017: debug coupling

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