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 @ 8948

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

forgotten commits. All sette tests passed except isomip as expected

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