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

source: branches/2015/dev_r5836_NOC3_vvl_by_default/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 @ 6004

Last change on this file since 6004 was 6004, checked in by gm, 8 years ago

#1613: vvl by default, step III: Merge with the trunk (free surface simplification) (see wiki)

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