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 NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/OCE/SBC – NEMO

source: NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/OCE/SBC/sbccpl.F90 @ 12374

Last change on this file since 12374 was 12374, checked in by dancopsey, 4 years ago

Get skin temperature to be passed from the atmosphere

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