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/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 @ 7422

Last change on this file since 7422 was 7422, checked in by gm, 7 years ago

#1805 dev_INGV_UKMO_2016: improve Stokes drift (including dynspg_ts , Stokes-Coriolis force , and GLS surface roughness

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