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

source: branches/UKMO/dev_r5518_ww3_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 @ 5846

Last change on this file since 5846 was 5846, checked in by jcastill, 8 years ago

Changes as in vn3.4_WWIII/vn3.4_ww3_coupling

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