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

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

source: branches/UKMO/dev_r5518_medusa_cpl_rh/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 @ 6653

Last change on this file since 6653 was 6653, checked in by frrh, 8 years ago

Reorder code in an attempt to avoid as many clashes as possible
with other branches.

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