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_GO6M_dev/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_r5518_GO6M_dev/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 @ 8200

Last change on this file since 8200 was 8200, checked in by frrh, 7 years ago

Merge branches/UKMO/dev_r5518_GC3_couple_pkg@7985 using command:

svn merge -r 6574:7985 svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/UKMO/dev_r5518_GC3_couple_pkg

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