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/UKMO/AMM15_v3_6_STABLE_package_collate_xeps/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/AMM15_v3_6_STABLE_package_collate_xeps/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 @ 11286

Last change on this file since 11286 was 11286, checked in by dford, 5 years ago

Merge in latest version of AMM15_v3_6_STABLE_package_collate.

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