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.1_penetrating_solar/src/OCE/SBC – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.1_penetrating_solar/src/OCE/SBC/sbccpl.F90 @ 13347

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

First lot of code added

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