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

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

source: branches/UKMO/dev_r5518_cleanup_1d_cpl/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 @ 9218

Last change on this file since 9218 was 9218, checked in by frrh, 6 years ago

First working version defining and receiveing 0D couping
fields on PE 0 and broadcasting values using MPI_BCAST.

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