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

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

source: branches/2016/dev_CNRS_2016/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 @ 7357

Last change on this file since 7357 was 7355, checked in by flavoni, 8 years ago

merge branch dev_CNRS_2016 & dev_CNRS_AGRIF_LIM3

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