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

source: branches/2012/dev_LOCEAN_2012/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 @ 3648

Last change on this file since 3648 was 3648, checked in by smasson, 11 years ago

enable "mini restart", see ticket:1019

  • Property svn:keywords set to Id
File size: 96.2 KB
Line 
1MODULE sbccpl
2   !!======================================================================
3   !!                       ***  MODULE  sbccpl  ***
4   !! Surface Boundary Condition :  momentum, heat and freshwater fluxes in coupled mode
5   !!======================================================================
6   !! History :  2.0  ! 2007-06  (R. Redler, N. Keenlyside, W. Park) Original code split into flxmod & taumod
7   !!            3.0  ! 2008-02  (G. Madec, C Talandier)  surface module
8   !!            3.1  ! 2009_02  (G. Madec, S. Masson, E. Maisonave, A. Caubel) generic coupled interface
9   !!            3.4  ! 2011_11  (C. Harris) more flexibility + multi-category fields
10   !!----------------------------------------------------------------------
11#if defined key_oasis3 || defined key_oasis4
12   !!----------------------------------------------------------------------
13   !!   'key_oasis3' or 'key_oasis4'   Coupled Ocean/Atmosphere formulation
14   !!----------------------------------------------------------------------
15   !!   namsbc_cpl      : coupled formulation namlist
16   !!   sbc_cpl_init    : initialisation of the coupled exchanges
17   !!   sbc_cpl_rcv     : receive fields from the atmosphere over the ocean (ocean only)
18   !!                     receive stress from the atmosphere over the ocean (ocean-ice case)
19   !!   sbc_cpl_ice_tau : receive stress from the atmosphere over ice
20   !!   sbc_cpl_ice_flx : receive fluxes from the atmosphere over ice
21   !!   sbc_cpl_snd     : send     fields to the atmosphere
22   !!----------------------------------------------------------------------
23   USE dom_oce         ! ocean space and time domain
24   USE sbc_oce         ! Surface boundary condition: ocean fields
25   USE sbc_ice         ! Surface boundary condition: ice fields
26   USE sbcdcy          ! surface boundary condition: diurnal cycle
27   USE phycst          ! physical constants
28#if defined key_lim3
29   USE par_ice         ! ice parameters
30   USE ice             ! ice variables
31#endif
32#if defined key_lim2
33   USE par_ice_2       ! ice parameters
34   USE ice_2           ! ice variables
35#endif
36#if defined key_oasis3
37   USE cpl_oasis3      ! OASIS3 coupling
38#endif
39#if defined key_oasis4
40   USE cpl_oasis4      ! OASIS4 coupling
41#endif
42   USE geo2ocean       !
43   USE oce   , ONLY : tsn, un, vn
44   USE albedo          !
45   USE in_out_manager  ! I/O manager
46   USE iom             ! NetCDF library
47   USE lib_mpp         ! distribued memory computing library
48   USE wrk_nemo        ! work arrays
49   USE timing          ! Timing
50   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
51#if defined key_cpl_carbon_cycle
52   USE p4zflx, ONLY : oce_co2
53#endif
54   USE diaar5, ONLY :   lk_diaar5
55#if defined key_cice
56   USE ice_domain_size, only: ncat
57#endif
58   IMPLICIT NONE
59   PRIVATE
60
61   PUBLIC   sbc_cpl_rcv        ! routine called by sbc_ice_lim(_2).F90
62   PUBLIC   sbc_cpl_snd        ! routine called by step.F90
63   PUBLIC   sbc_cpl_ice_tau    ! routine called by sbc_ice_lim(_2).F90
64   PUBLIC   sbc_cpl_ice_flx    ! routine called by sbc_ice_lim(_2).F90
65
66   INTEGER, PARAMETER ::   jpr_otx1   =  1            ! 3 atmosphere-ocean stress components on grid 1
67   INTEGER, PARAMETER ::   jpr_oty1   =  2            !
68   INTEGER, PARAMETER ::   jpr_otz1   =  3            !
69   INTEGER, PARAMETER ::   jpr_otx2   =  4            ! 3 atmosphere-ocean stress components on grid 2
70   INTEGER, PARAMETER ::   jpr_oty2   =  5            !
71   INTEGER, PARAMETER ::   jpr_otz2   =  6            !
72   INTEGER, PARAMETER ::   jpr_itx1   =  7            ! 3 atmosphere-ice   stress components on grid 1
73   INTEGER, PARAMETER ::   jpr_ity1   =  8            !
74   INTEGER, PARAMETER ::   jpr_itz1   =  9            !
75   INTEGER, PARAMETER ::   jpr_itx2   = 10            ! 3 atmosphere-ice   stress components on grid 2
76   INTEGER, PARAMETER ::   jpr_ity2   = 11            !
77   INTEGER, PARAMETER ::   jpr_itz2   = 12            !
78   INTEGER, PARAMETER ::   jpr_qsroce = 13            ! Qsr above the ocean
79   INTEGER, PARAMETER ::   jpr_qsrice = 14            ! Qsr above the ice
80   INTEGER, PARAMETER ::   jpr_qsrmix = 15 
81   INTEGER, PARAMETER ::   jpr_qnsoce = 16            ! Qns above the ocean
82   INTEGER, PARAMETER ::   jpr_qnsice = 17            ! Qns above the ice
83   INTEGER, PARAMETER ::   jpr_qnsmix = 18
84   INTEGER, PARAMETER ::   jpr_rain   = 19            ! total liquid precipitation (rain)
85   INTEGER, PARAMETER ::   jpr_snow   = 20            ! solid precipitation over the ocean (snow)
86   INTEGER, PARAMETER ::   jpr_tevp   = 21            ! total evaporation
87   INTEGER, PARAMETER ::   jpr_ievp   = 22            ! solid evaporation (sublimation)
88   INTEGER, PARAMETER ::   jpr_sbpr   = 23            ! sublimation - liquid precipitation - solid precipitation
89   INTEGER, PARAMETER ::   jpr_semp   = 24            ! solid freshwater budget (sublimation - snow)
90   INTEGER, PARAMETER ::   jpr_oemp   = 25            ! ocean freshwater budget (evap - precip)
91   INTEGER, PARAMETER ::   jpr_w10m   = 26            ! 10m wind
92   INTEGER, PARAMETER ::   jpr_dqnsdt = 27            ! d(Q non solar)/d(temperature)
93   INTEGER, PARAMETER ::   jpr_rnf    = 28            ! runoffs
94   INTEGER, PARAMETER ::   jpr_cal    = 29            ! calving
95   INTEGER, PARAMETER ::   jpr_taum   = 30            ! wind stress module
96   INTEGER, PARAMETER ::   jpr_co2    = 31
97   INTEGER, PARAMETER ::   jpr_topm   = 32            ! topmeltn
98   INTEGER, PARAMETER ::   jpr_botm   = 33            ! botmeltn
99   INTEGER, PARAMETER ::   jprcv      = 33            ! total number of fields received
100
101   INTEGER, PARAMETER ::   jps_fice   =  1            ! ice fraction
102   INTEGER, PARAMETER ::   jps_toce   =  2            ! ocean temperature
103   INTEGER, PARAMETER ::   jps_tice   =  3            ! ice   temperature
104   INTEGER, PARAMETER ::   jps_tmix   =  4            ! mixed temperature (ocean+ice)
105   INTEGER, PARAMETER ::   jps_albice =  5            ! ice   albedo
106   INTEGER, PARAMETER ::   jps_albmix =  6            ! mixed albedo
107   INTEGER, PARAMETER ::   jps_hice   =  7            ! ice  thickness
108   INTEGER, PARAMETER ::   jps_hsnw   =  8            ! snow thickness
109   INTEGER, PARAMETER ::   jps_ocx1   =  9            ! ocean current on grid 1
110   INTEGER, PARAMETER ::   jps_ocy1   = 10            !
111   INTEGER, PARAMETER ::   jps_ocz1   = 11            !
112   INTEGER, PARAMETER ::   jps_ivx1   = 12            ! ice   current on grid 1
113   INTEGER, PARAMETER ::   jps_ivy1   = 13            !
114   INTEGER, PARAMETER ::   jps_ivz1   = 14            !
115   INTEGER, PARAMETER ::   jps_co2    = 15
116   INTEGER, PARAMETER ::   jpsnd      = 15            ! total number of fields sended
117
118   !                                                         !!** namelist namsbc_cpl **
119   TYPE ::   FLD_C
120      CHARACTER(len = 32) ::   cldes                  ! desciption of the coupling strategy
121      CHARACTER(len = 32) ::   clcat                  ! multiple ice categories strategy
122      CHARACTER(len = 32) ::   clvref                 ! reference of vector ('spherical' or 'cartesian')
123      CHARACTER(len = 32) ::   clvor                  ! orientation of vector fields ('eastward-northward' or 'local grid')
124      CHARACTER(len = 32) ::   clvgrd                 ! grids on which is located the vector fields
125   END TYPE FLD_C
126   ! Send to the atmosphere                           !
127   TYPE(FLD_C) ::   sn_snd_temp, sn_snd_alb, sn_snd_thick, sn_snd_crt, sn_snd_co2                       
128   ! Received from the atmosphere                     !
129   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
130   TYPE(FLD_C) ::   sn_rcv_cal, sn_rcv_iceflx, sn_rcv_co2                       
131
132   TYPE ::   DYNARR     
133      REAL(wp), POINTER, DIMENSION(:,:,:)    ::   z3   
134   END TYPE DYNARR
135
136   TYPE( DYNARR ), SAVE, DIMENSION(jprcv) ::   frcv                      ! all fields recieved from the atmosphere
137
138   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   albedo_oce_mix     ! ocean albedo sent to atmosphere (mix clear/overcast sky)
139
140   INTEGER , ALLOCATABLE, SAVE, DIMENSION(    :) ::   nrcvinfo           ! OASIS info argument
141
142#if ! defined key_lim2   &&   ! defined key_lim3
143   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   u_ice, v_ice,fr1_i0,fr2_i0          ! jpi, jpj
144   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tn_ice, alb_ice, qns_ice, dqns_ice  ! (jpi,jpj,jpl)
145#endif
146
147#if defined key_cice
148   INTEGER, PARAMETER ::   jpl = ncat
149#elif ! defined key_lim2   &&   ! defined key_lim3
150   INTEGER, PARAMETER ::   jpl = 1 
151   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   emp_ice
152   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qsr_ice
153#endif
154
155#if ! defined key_lim3   &&  ! defined key_cice
156   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  a_i
157#endif
158
159#if ! defined key_lim3
160   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  ht_i, ht_s
161#endif
162
163#if ! defined key_cice
164   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  topmelt, botmelt
165#endif
166
167   !! Substitution
168#  include "vectopt_loop_substitute.h90"
169   !!----------------------------------------------------------------------
170   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
171   !! $Id$
172   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
173   !!----------------------------------------------------------------------
174
175CONTAINS
176 
177   INTEGER FUNCTION sbc_cpl_alloc()
178      !!----------------------------------------------------------------------
179      !!             ***  FUNCTION sbc_cpl_alloc  ***
180      !!----------------------------------------------------------------------
181      INTEGER :: ierr(4),jn
182      !!----------------------------------------------------------------------
183      ierr(:) = 0
184      !
185      ALLOCATE( albedo_oce_mix(jpi,jpj), nrcvinfo(jprcv),  STAT=ierr(1) )
186      !
187#if ! defined key_lim2 && ! defined key_lim3
188      ! quick patch to be able to run the coupled model without sea-ice...
189      ALLOCATE( u_ice(jpi,jpj) , fr1_i0(jpi,jpj) , tn_ice (jpi,jpj,1) ,     &
190                v_ice(jpi,jpj) , fr2_i0(jpi,jpj) , alb_ice(jpi,jpj,1),      &
191                emp_ice(jpi,jpj) , qns_ice(jpi,jpj,1) , dqns_ice(jpi,jpj,1) , STAT=ierr(2) )
192#endif
193
194#if ! defined key_lim3 && ! defined key_cice
195      ALLOCATE( a_i(jpi,jpj,jpl) , STAT=ierr(3) )
196#endif
197
198#if defined key_cice || defined key_lim2
199      ALLOCATE( ht_i(jpi,jpj,jpl) , ht_s(jpi,jpj,jpl) , STAT=ierr(4) )
200#endif
201      sbc_cpl_alloc = MAXVAL( ierr )
202      IF( lk_mpp            )   CALL mpp_sum ( sbc_cpl_alloc )
203      IF( sbc_cpl_alloc > 0 )   CALL ctl_warn('sbc_cpl_alloc: allocation of arrays failed')
204      !
205   END FUNCTION sbc_cpl_alloc
206
207
208   SUBROUTINE sbc_cpl_init( k_ice )     
209      !!----------------------------------------------------------------------
210      !!             ***  ROUTINE sbc_cpl_init  ***
211      !!
212      !! ** Purpose :   Initialisation of send and recieved information from
213      !!                the atmospheric component
214      !!
215      !! ** Method  : * Read namsbc_cpl namelist
216      !!              * define the receive interface
217      !!              * define the send    interface
218      !!              * initialise the OASIS coupler
219      !!----------------------------------------------------------------------
220      INTEGER, INTENT(in) ::   k_ice    ! ice management in the sbc (=0/1/2/3)
221      !!
222      INTEGER ::   jn   ! dummy loop index
223      REAL(wp), POINTER, DIMENSION(:,:) ::   zacs, zaos
224      !!
225      NAMELIST/namsbc_cpl/  sn_snd_temp, sn_snd_alb   , sn_snd_thick, sn_snd_crt   , sn_snd_co2,   &
226         &                  sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau  , sn_rcv_dqnsdt, sn_rcv_qsr,   &
227         &                  sn_rcv_qns , sn_rcv_emp   , sn_rcv_rnf  , sn_rcv_cal   , sn_rcv_iceflx  , sn_rcv_co2
228      !!---------------------------------------------------------------------
229      !
230      IF( nn_timing == 1 )  CALL timing_start('sbc_cpl_init')
231      !
232      CALL wrk_alloc( jpi,jpj, zacs, zaos )
233
234      ! ================================ !
235      !      Namelist informations       !
236      ! ================================ !
237
238      ! default definitions
239      !                    !     description       !  multiple  !    vector   !      vector          ! vector !
240      !                    !                       ! categories !  reference  !    orientation       ! grids  !
241      ! send
242      sn_snd_temp   = FLD_C( 'weighted oce and ice',    'no'    ,     ''      ,         ''           ,   ''   ) 
243      sn_snd_alb    = FLD_C( 'weighted ice'        ,    'no'    ,     ''      ,         ''           ,   ''   ) 
244      sn_snd_thick  = FLD_C( 'none'                ,    'no'    ,     ''      ,         ''           ,   ''   ) 
245      sn_snd_crt    = FLD_C( 'none'                ,    'no'    , 'spherical' , 'eastward-northward' ,  'T'   )     
246      sn_snd_co2    = FLD_C( 'none'                ,    'no'    ,     ''      ,         ''           ,   ''   )     
247      ! receive
248      sn_rcv_w10m   = FLD_C( 'none'                ,    'no'    ,     ''      ,         ''          ,   ''    )
249      sn_rcv_taumod = FLD_C( 'coupled'             ,    'no'    ,     ''      ,         ''          ,   ''    )
250      sn_rcv_tau    = FLD_C( 'oce only'            ,    'no'    , 'cartesian' , 'eastward-northward',  'U,V'  ) 
251      sn_rcv_dqnsdt = FLD_C( 'coupled'             ,    'no'    ,     ''      ,         ''          ,   ''    )
252      sn_rcv_qsr    = FLD_C( 'oce and ice'         ,    'no'    ,     ''      ,         ''          ,   ''    )
253      sn_rcv_qns    = FLD_C( 'oce and ice'         ,    'no'    ,     ''      ,         ''          ,   ''    )
254      sn_rcv_emp    = FLD_C( 'conservative'        ,    'no'    ,     ''      ,         ''          ,   ''    )
255      sn_rcv_rnf    = FLD_C( 'coupled'             ,    'no'    ,     ''      ,         ''          ,   ''    )
256      sn_rcv_cal    = FLD_C( 'coupled'             ,    'no'    ,     ''      ,         ''          ,   ''    )
257      sn_rcv_iceflx = FLD_C( 'none'                ,    'no'    ,     ''      ,         ''          ,   ''    )
258      sn_rcv_co2    = FLD_C( 'none'                ,    'no'    ,     ''      ,         ''          ,   ''    )
259
260      REWIND( numnam )                    ! ... read namlist namsbc_cpl
261      READ  ( numnam, namsbc_cpl )
262
263      IF(lwp) THEN                        ! control print
264         WRITE(numout,*)
265         WRITE(numout,*)'sbc_cpl_init : namsbc_cpl namelist '
266         WRITE(numout,*)'~~~~~~~~~~~~'
267         WRITE(numout,*)'  received fields (mutiple ice categogies)'
268         WRITE(numout,*)'      10m wind module                 = ', TRIM(sn_rcv_w10m%cldes  ), ' (', TRIM(sn_rcv_w10m%clcat  ), ')'
269         WRITE(numout,*)'      stress module                   = ', TRIM(sn_rcv_taumod%cldes), ' (', TRIM(sn_rcv_taumod%clcat), ')'
270         WRITE(numout,*)'      surface stress                  = ', TRIM(sn_rcv_tau%cldes   ), ' (', TRIM(sn_rcv_tau%clcat   ), ')'
271         WRITE(numout,*)'                     - referential    = ', sn_rcv_tau%clvref
272         WRITE(numout,*)'                     - orientation    = ', sn_rcv_tau%clvor
273         WRITE(numout,*)'                     - mesh           = ', sn_rcv_tau%clvgrd
274         WRITE(numout,*)'      non-solar heat flux sensitivity = ', TRIM(sn_rcv_dqnsdt%cldes), ' (', TRIM(sn_rcv_dqnsdt%clcat), ')'
275         WRITE(numout,*)'      solar heat flux                 = ', TRIM(sn_rcv_qsr%cldes   ), ' (', TRIM(sn_rcv_qsr%clcat   ), ')'
276         WRITE(numout,*)'      non-solar heat flux             = ', TRIM(sn_rcv_qns%cldes   ), ' (', TRIM(sn_rcv_qns%clcat   ), ')'
277         WRITE(numout,*)'      freshwater budget               = ', TRIM(sn_rcv_emp%cldes   ), ' (', TRIM(sn_rcv_emp%clcat   ), ')'
278         WRITE(numout,*)'      runoffs                         = ', TRIM(sn_rcv_rnf%cldes   ), ' (', TRIM(sn_rcv_rnf%clcat   ), ')'
279         WRITE(numout,*)'      calving                         = ', TRIM(sn_rcv_cal%cldes   ), ' (', TRIM(sn_rcv_cal%clcat   ), ')'
280         WRITE(numout,*)'      sea ice heat fluxes             = ', TRIM(sn_rcv_iceflx%cldes), ' (', TRIM(sn_rcv_iceflx%clcat), ')'
281         WRITE(numout,*)'      atm co2                         = ', TRIM(sn_rcv_co2%cldes   ), ' (', TRIM(sn_rcv_co2%clcat   ), ')'
282         WRITE(numout,*)'  sent fields (multiple ice categories)'
283         WRITE(numout,*)'      surface temperature             = ', TRIM(sn_snd_temp%cldes  ), ' (', TRIM(sn_snd_temp%clcat  ), ')'
284         WRITE(numout,*)'      albedo                          = ', TRIM(sn_snd_alb%cldes   ), ' (', TRIM(sn_snd_alb%clcat   ), ')'
285         WRITE(numout,*)'      ice/snow thickness              = ', TRIM(sn_snd_thick%cldes ), ' (', TRIM(sn_snd_thick%clcat ), ')'
286         WRITE(numout,*)'      surface current                 = ', TRIM(sn_snd_crt%cldes   ), ' (', TRIM(sn_snd_crt%clcat   ), ')'
287         WRITE(numout,*)'                      - referential   = ', sn_snd_crt%clvref 
288         WRITE(numout,*)'                      - orientation   = ', sn_snd_crt%clvor
289         WRITE(numout,*)'                      - mesh          = ', sn_snd_crt%clvgrd
290         WRITE(numout,*)'      oce co2 flux                    = ', TRIM(sn_snd_co2%cldes   ), ' (', TRIM(sn_snd_co2%clcat   ), ')'
291      ENDIF
292
293      !                                   ! allocate sbccpl arrays
294      IF( sbc_cpl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' )
295     
296      ! ================================ !
297      !   Define the receive interface   !
298      ! ================================ !
299      nrcvinfo(:) = OASIS_idle   ! needed by nrcvinfo(jpr_otx1) if we do not receive ocean stress
300
301      ! for each field: define the OASIS name                              (srcv(:)%clname)
302      !                 define receive or not from the namelist parameters (srcv(:)%laction)
303      !                 define the north fold type of lbc                  (srcv(:)%nsgn)
304
305      ! default definitions of srcv
306      srcv(:)%laction = .FALSE.   ;   srcv(:)%clgrid = 'T'   ;   srcv(:)%nsgn = 1.   ;   srcv(:)%nct = 1
307
308      !                                                      ! ------------------------- !
309      !                                                      ! ice and ocean wind stress !   
310      !                                                      ! ------------------------- !
311      !                                                           ! Name
312      srcv(jpr_otx1)%clname = 'O_OTaux1'      ! 1st ocean component on grid ONE (T or U)
313      srcv(jpr_oty1)%clname = 'O_OTauy1'      ! 2nd   -      -         -     -
314      srcv(jpr_otz1)%clname = 'O_OTauz1'      ! 3rd   -      -         -     -
315      srcv(jpr_otx2)%clname = 'O_OTaux2'      ! 1st ocean component on grid TWO (V)
316      srcv(jpr_oty2)%clname = 'O_OTauy2'      ! 2nd   -      -         -     -
317      srcv(jpr_otz2)%clname = 'O_OTauz2'      ! 3rd   -      -         -     -
318      !
319      srcv(jpr_itx1)%clname = 'O_ITaux1'      ! 1st  ice  component on grid ONE (T, F, I or U)
320      srcv(jpr_ity1)%clname = 'O_ITauy1'      ! 2nd   -      -         -     -
321      srcv(jpr_itz1)%clname = 'O_ITauz1'      ! 3rd   -      -         -     -
322      srcv(jpr_itx2)%clname = 'O_ITaux2'      ! 1st  ice  component on grid TWO (V)
323      srcv(jpr_ity2)%clname = 'O_ITauy2'      ! 2nd   -      -         -     -
324      srcv(jpr_itz2)%clname = 'O_ITauz2'      ! 3rd   -      -         -     -
325      !
326      ! Vectors: change of sign at north fold ONLY if on the local grid
327      IF( TRIM( sn_rcv_tau%clvor ) == 'local grid' )   srcv(jpr_otx1:jpr_itz2)%nsgn = -1.
328     
329      !                                                           ! Set grid and action
330      SELECT CASE( TRIM( sn_rcv_tau%clvgrd ) )      !  'T', 'U,V', 'U,V,I', 'U,V,F', 'T,I', 'T,F', or 'T,U,V'
331      CASE( 'T' ) 
332         srcv(jpr_otx1:jpr_itz2)%clgrid  = 'T'        ! oce and ice components given at T-point
333         srcv(jpr_otx1:jpr_otz1)%laction = .TRUE.     ! receive oce components on grid 1
334         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1
335      CASE( 'U,V' ) 
336         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'U'        ! oce components given at U-point
337         srcv(jpr_otx2:jpr_otz2)%clgrid  = 'V'        !           and           V-point
338         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'U'        ! ice components given at U-point
339         srcv(jpr_itx2:jpr_itz2)%clgrid  = 'V'        !           and           V-point
340         srcv(jpr_otx1:jpr_itz2)%laction = .TRUE.     ! receive oce and ice components on both grid 1 & 2
341      CASE( 'U,V,T' )
342         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'U'        ! oce components given at U-point
343         srcv(jpr_otx2:jpr_otz2)%clgrid  = 'V'        !           and           V-point
344         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'T'        ! ice components given at T-point
345         srcv(jpr_otx1:jpr_otz2)%laction = .TRUE.     ! receive oce components on grid 1 & 2
346         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1 only
347      CASE( 'U,V,I' )
348         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'U'        ! oce components given at U-point
349         srcv(jpr_otx2:jpr_otz2)%clgrid  = 'V'        !           and           V-point
350         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'I'        ! ice components given at I-point
351         srcv(jpr_otx1:jpr_otz2)%laction = .TRUE.     ! receive oce components on grid 1 & 2
352         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1 only
353      CASE( 'U,V,F' )
354         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'U'        ! oce components given at U-point
355         srcv(jpr_otx2:jpr_otz2)%clgrid  = 'V'        !           and           V-point
356         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'F'        ! ice components given at F-point
357         srcv(jpr_otx1:jpr_otz2)%laction = .TRUE.     ! receive oce components on grid 1 & 2
358         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1 only
359      CASE( 'T,I' ) 
360         srcv(jpr_otx1:jpr_itz2)%clgrid  = 'T'        ! oce and ice components given at T-point
361         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'I'        ! ice components given at I-point
362         srcv(jpr_otx1:jpr_otz1)%laction = .TRUE.     ! receive oce components on grid 1
363         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1
364      CASE( 'T,F' ) 
365         srcv(jpr_otx1:jpr_itz2)%clgrid  = 'T'        ! oce and ice components given at T-point
366         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'F'        ! ice components given at F-point
367         srcv(jpr_otx1:jpr_otz1)%laction = .TRUE.     ! receive oce components on grid 1
368         srcv(jpr_itx1:jpr_itz1)%laction = .TRUE.     ! receive ice components on grid 1
369      CASE( 'T,U,V' )
370         srcv(jpr_otx1:jpr_otz1)%clgrid  = 'T'        ! oce components given at T-point
371         srcv(jpr_itx1:jpr_itz1)%clgrid  = 'U'        ! ice components given at U-point
372         srcv(jpr_itx2:jpr_itz2)%clgrid  = 'V'        !           and           V-point
373         srcv(jpr_otx1:jpr_otz1)%laction = .TRUE.     ! receive oce components on grid 1 only
374         srcv(jpr_itx1:jpr_itz2)%laction = .TRUE.     ! receive ice components on grid 1 & 2
375      CASE default   
376         CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_tau%clvgrd' )
377      END SELECT
378      !
379      IF( TRIM( sn_rcv_tau%clvref ) == 'spherical' )   &           ! spherical: 3rd component not received
380         &     srcv( (/jpr_otz1, jpr_otz2, jpr_itz1, jpr_itz2/) )%laction = .FALSE. 
381      !
382      IF( TRIM( sn_rcv_tau%clvor  ) == 'local grid' ) THEN        ! already on local grid -> no need of the second grid
383            srcv(jpr_otx2:jpr_otz2)%laction = .FALSE. 
384            srcv(jpr_itx2:jpr_itz2)%laction = .FALSE. 
385            srcv(jpr_oty1)%clgrid = srcv(jpr_oty2)%clgrid   ! not needed but cleaner...
386            srcv(jpr_ity1)%clgrid = srcv(jpr_ity2)%clgrid   ! not needed but cleaner...
387      ENDIF
388      !
389      IF( TRIM( sn_rcv_tau%cldes ) /= 'oce and ice' ) THEN        ! 'oce and ice' case ocean stress on ocean mesh used
390         srcv(jpr_itx1:jpr_itz2)%laction = .FALSE.    ! ice components not received
391         srcv(jpr_itx1)%clgrid = 'U'                  ! ocean stress used after its transformation
392         srcv(jpr_ity1)%clgrid = 'V'                  ! i.e. it is always at U- & V-points for i- & j-comp. resp.
393      ENDIF
394       
395      !                                                      ! ------------------------- !
396      !                                                      !    freshwater budget      !   E-P
397      !                                                      ! ------------------------- !
398      ! we suppose that atmosphere modele do not make the difference between precipiration (liquide or solid)
399      ! over ice of free ocean within the same atmospheric cell.cd
400      srcv(jpr_rain)%clname = 'OTotRain'      ! Rain = liquid precipitation
401      srcv(jpr_snow)%clname = 'OTotSnow'      ! Snow = solid precipitation
402      srcv(jpr_tevp)%clname = 'OTotEvap'      ! total evaporation (over oce + ice sublimation)
403      srcv(jpr_ievp)%clname = 'OIceEvap'      ! evaporation over ice = sublimation
404      srcv(jpr_sbpr)%clname = 'OSubMPre'      ! sublimation - liquid precipitation - solid precipitation
405      srcv(jpr_semp)%clname = 'OISubMSn'      ! ice solid water budget = sublimation - solid precipitation
406      srcv(jpr_oemp)%clname = 'OOEvaMPr'      ! ocean water budget = ocean Evap - ocean precip
407      SELECT CASE( TRIM( sn_rcv_emp%cldes ) )
408      CASE( 'oce only'      )   ;   srcv(                                 jpr_oemp   )%laction = .TRUE. 
409      CASE( 'conservative'  )   ;   srcv( (/jpr_rain, jpr_snow, jpr_ievp, jpr_tevp/) )%laction = .TRUE.
410      CASE( 'oce and ice'   )   ;   srcv( (/jpr_ievp, jpr_sbpr, jpr_semp, jpr_oemp/) )%laction = .TRUE.
411      CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_emp%cldes' )
412      END SELECT
413
414      !                                                      ! ------------------------- !
415      !                                                      !     Runoffs & Calving     !   
416      !                                                      ! ------------------------- !
417      srcv(jpr_rnf   )%clname = 'O_Runoff'   ;   IF( TRIM( sn_rcv_rnf%cldes ) == 'coupled' )   srcv(jpr_rnf)%laction = .TRUE.
418! This isn't right - really just want ln_rnf_emp changed
419!                                                 IF( TRIM( sn_rcv_rnf%cldes ) == 'climato' )   THEN   ;   ln_rnf = .TRUE.
420!                                                 ELSE                                                 ;   ln_rnf = .FALSE.
421!                                                 ENDIF
422      srcv(jpr_cal   )%clname = 'OCalving'   ;   IF( TRIM( sn_rcv_cal%cldes ) == 'coupled' )   srcv(jpr_cal)%laction = .TRUE.
423
424      !                                                      ! ------------------------- !
425      !                                                      !    non solar radiation    !   Qns
426      !                                                      ! ------------------------- !
427      srcv(jpr_qnsoce)%clname = 'O_QnsOce'
428      srcv(jpr_qnsice)%clname = 'O_QnsIce'
429      srcv(jpr_qnsmix)%clname = 'O_QnsMix'
430      SELECT CASE( TRIM( sn_rcv_qns%cldes ) )
431      CASE( 'oce only'      )   ;   srcv(               jpr_qnsoce   )%laction = .TRUE.
432      CASE( 'conservative'  )   ;   srcv( (/jpr_qnsice, jpr_qnsmix/) )%laction = .TRUE.
433      CASE( 'oce and ice'   )   ;   srcv( (/jpr_qnsice, jpr_qnsoce/) )%laction = .TRUE.
434      CASE( 'mixed oce-ice' )   ;   srcv(               jpr_qnsmix   )%laction = .TRUE. 
435      CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_qns%cldes' )
436      END SELECT
437      IF( TRIM( sn_rcv_qns%cldes ) == 'mixed oce-ice' .AND. jpl > 1 ) &
438         CALL ctl_stop( 'sbc_cpl_init: sn_rcv_qns%cldes not currently allowed to be mixed oce-ice for multi-category ice' )
439      !                                                      ! ------------------------- !
440      !                                                      !    solar radiation        !   Qsr
441      !                                                      ! ------------------------- !
442      srcv(jpr_qsroce)%clname = 'O_QsrOce'
443      srcv(jpr_qsrice)%clname = 'O_QsrIce'
444      srcv(jpr_qsrmix)%clname = 'O_QsrMix'
445      SELECT CASE( TRIM( sn_rcv_qsr%cldes ) )
446      CASE( 'oce only'      )   ;   srcv(               jpr_qsroce   )%laction = .TRUE.
447      CASE( 'conservative'  )   ;   srcv( (/jpr_qsrice, jpr_qsrmix/) )%laction = .TRUE.
448      CASE( 'oce and ice'   )   ;   srcv( (/jpr_qsrice, jpr_qsroce/) )%laction = .TRUE.
449      CASE( 'mixed oce-ice' )   ;   srcv(               jpr_qsrmix   )%laction = .TRUE. 
450      CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_qsr%cldes' )
451      END SELECT
452      IF( TRIM( sn_rcv_qsr%cldes ) == 'mixed oce-ice' .AND. jpl > 1 ) &
453         CALL ctl_stop( 'sbc_cpl_init: sn_rcv_qsr%cldes not currently allowed to be mixed oce-ice for multi-category ice' )
454      !                                                      ! ------------------------- !
455      !                                                      !   non solar sensitivity   !   d(Qns)/d(T)
456      !                                                      ! ------------------------- !
457      srcv(jpr_dqnsdt)%clname = 'O_dQnsdT'   
458      IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'coupled' )   srcv(jpr_dqnsdt)%laction = .TRUE.
459      !
460      ! non solar sensitivity mandatory for LIM ice model
461      IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'none' .AND. k_ice /= 0 .AND. k_ice /= 4) &
462         CALL ctl_stop( 'sbc_cpl_init: sn_rcv_dqnsdt%cldes must be coupled in namsbc_cpl namelist' )
463      ! non solar sensitivity mandatory for mixed oce-ice solar radiation coupling technique
464      IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'none' .AND. TRIM( sn_rcv_qns%cldes ) == 'mixed oce-ice' ) &
465         CALL ctl_stop( 'sbc_cpl_init: namsbc_cpl namelist mismatch between sn_rcv_qns%cldes and sn_rcv_dqnsdt%cldes' )
466      !                                                      ! ------------------------- !
467      !                                                      !    Ice Qsr penetration    !   
468      !                                                      ! ------------------------- !
469      ! fraction of net shortwave radiation which is not absorbed in the thin surface layer
470      ! and penetrates inside the ice cover ( Maykut and Untersteiner, 1971 ; Elbert anbd Curry, 1993 )
471      ! Coupled case: since cloud cover is not received from atmosphere
472      !               ===> defined as constant value -> definition done in sbc_cpl_init
473      fr1_i0(:,:) = 0.18
474      fr2_i0(:,:) = 0.82
475      !                                                      ! ------------------------- !
476      !                                                      !      10m wind module      !   
477      !                                                      ! ------------------------- !
478      srcv(jpr_w10m)%clname = 'O_Wind10'   ;   IF( TRIM(sn_rcv_w10m%cldes  ) == 'coupled' )   srcv(jpr_w10m)%laction = .TRUE. 
479      !
480      !                                                      ! ------------------------- !
481      !                                                      !   wind stress module      !   
482      !                                                      ! ------------------------- !
483      srcv(jpr_taum)%clname = 'O_TauMod'   ;   IF( TRIM(sn_rcv_taumod%cldes) == 'coupled' )   srcv(jpr_taum)%laction = .TRUE.
484      lhftau = srcv(jpr_taum)%laction
485
486      !                                                      ! ------------------------- !
487      !                                                      !      Atmospheric CO2      !
488      !                                                      ! ------------------------- !
489      srcv(jpr_co2 )%clname = 'O_AtmCO2'   ;   IF( TRIM(sn_rcv_co2%cldes   ) == 'coupled' )    srcv(jpr_co2 )%laction = .TRUE.
490      !                                                      ! ------------------------- !
491      !                                                      !   topmelt and botmelt     !   
492      !                                                      ! ------------------------- !
493      srcv(jpr_topm )%clname = 'OTopMlt'
494      srcv(jpr_botm )%clname = 'OBotMlt'
495      IF( TRIM(sn_rcv_iceflx%cldes) == 'coupled' ) THEN
496         IF ( TRIM( sn_rcv_iceflx%clcat ) == 'yes' ) THEN
497            srcv(jpr_topm:jpr_botm)%nct = jpl
498         ELSE
499            CALL ctl_stop( 'sbc_cpl_init: sn_rcv_iceflx%clcat should always be set to yes currently' )
500         ENDIF
501         srcv(jpr_topm:jpr_botm)%laction = .TRUE.
502      ENDIF
503
504      ! Allocate all parts of frcv used for received fields
505      DO jn = 1, jprcv
506         IF ( srcv(jn)%laction ) ALLOCATE( frcv(jn)%z3(jpi,jpj,srcv(jn)%nct) )
507      END DO
508      ! Allocate taum part of frcv which is used even when not received as coupling field
509      IF ( .NOT. srcv(jpr_taum)%laction ) ALLOCATE( frcv(jpr_taum)%z3(jpi,jpj,srcv(jn)%nct) )
510
511      ! ================================ !
512      !     Define the send interface    !
513      ! ================================ !
514      ! for each field: define the OASIS name                           (ssnd(:)%clname)
515      !                 define send or not from the namelist parameters (ssnd(:)%laction)
516      !                 define the north fold type of lbc               (ssnd(:)%nsgn)
517     
518      ! default definitions of nsnd
519      ssnd(:)%laction = .FALSE.   ;   ssnd(:)%clgrid = 'T'   ;   ssnd(:)%nsgn = 1.  ; ssnd(:)%nct = 1
520         
521      !                                                      ! ------------------------- !
522      !                                                      !    Surface temperature    !
523      !                                                      ! ------------------------- !
524      ssnd(jps_toce)%clname = 'O_SSTSST'
525      ssnd(jps_tice)%clname = 'O_TepIce'
526      ssnd(jps_tmix)%clname = 'O_TepMix'
527      SELECT CASE( TRIM( sn_snd_temp%cldes ) )
528      CASE( 'none'         )       ! nothing to do
529      CASE( 'oce only'             )   ;   ssnd(   jps_toce             )%laction = .TRUE.
530      CASE( 'weighted oce and ice' )
531         ssnd( (/jps_toce, jps_tice/) )%laction = .TRUE.
532         IF ( TRIM( sn_snd_temp%clcat ) == 'yes' )  ssnd(jps_tice)%nct = jpl
533      CASE( 'mixed oce-ice'        )   ;   ssnd(   jps_tmix             )%laction = .TRUE.
534      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_temp%cldes' )
535      END SELECT
536     
537      !                                                      ! ------------------------- !
538      !                                                      !          Albedo           !
539      !                                                      ! ------------------------- !
540      ssnd(jps_albice)%clname = 'O_AlbIce' 
541      ssnd(jps_albmix)%clname = 'O_AlbMix'
542      SELECT CASE( TRIM( sn_snd_alb%cldes ) )
543      CASE( 'none'          )       ! nothing to do
544      CASE( 'weighted ice'  )   ;   ssnd(jps_albice)%laction = .TRUE.
545      CASE( 'mixed oce-ice' )   ;   ssnd(jps_albmix)%laction = .TRUE.
546      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_alb%cldes' )
547      END SELECT
548      !
549      ! Need to calculate oceanic albedo if
550      !     1. sending mixed oce-ice albedo or
551      !     2. receiving mixed oce-ice solar radiation
552      IF ( TRIM ( sn_snd_alb%cldes ) == 'mixed oce-ice' .OR. TRIM ( sn_rcv_qsr%cldes ) == 'mixed oce-ice' ) THEN
553         CALL albedo_oce( zaos, zacs )
554         ! Due to lack of information on nebulosity : mean clear/overcast sky
555         albedo_oce_mix(:,:) = ( zacs(:,:) + zaos(:,:) ) * 0.5
556      ENDIF
557
558      !                                                      ! ------------------------- !
559      !                                                      !  Ice fraction & Thickness !
560      !                                                      ! ------------------------- !
561      ssnd(jps_fice)%clname = 'OIceFrc'
562      ssnd(jps_hice)%clname = 'OIceTck'
563      ssnd(jps_hsnw)%clname = 'OSnwTck'
564      IF( k_ice /= 0 ) THEN
565         ssnd(jps_fice)%laction = .TRUE.                  ! if ice treated in the ocean (even in climato case)
566! Currently no namelist entry to determine sending of multi-category ice fraction so use the thickness entry for now
567         IF ( TRIM( sn_snd_thick%clcat ) == 'yes' ) ssnd(jps_fice)%nct = jpl
568      ENDIF
569
570      SELECT CASE ( TRIM( sn_snd_thick%cldes ) )
571      CASE( 'none'         )       ! nothing to do
572      CASE( 'ice and snow' ) 
573         ssnd(jps_hice:jps_hsnw)%laction = .TRUE.
574         IF ( TRIM( sn_snd_thick%clcat ) == 'yes' ) THEN
575            ssnd(jps_hice:jps_hsnw)%nct = jpl
576         ELSE
577            IF ( jpl > 1 ) THEN
578CALL ctl_stop( 'sbc_cpl_init: use weighted ice and snow option for sn_snd_thick%cldes if not exchanging category fields' )
579            ENDIF
580         ENDIF
581      CASE ( 'weighted ice and snow' ) 
582         ssnd(jps_hice:jps_hsnw)%laction = .TRUE.
583         IF ( TRIM( sn_snd_thick%clcat ) == 'yes' ) ssnd(jps_hice:jps_hsnw)%nct = jpl
584      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_thick%cldes' )
585      END SELECT
586
587      !                                                      ! ------------------------- !
588      !                                                      !      Surface current      !
589      !                                                      ! ------------------------- !
590      !        ocean currents              !            ice velocities
591      ssnd(jps_ocx1)%clname = 'O_OCurx1'   ;   ssnd(jps_ivx1)%clname = 'O_IVelx1'
592      ssnd(jps_ocy1)%clname = 'O_OCury1'   ;   ssnd(jps_ivy1)%clname = 'O_IVely1'
593      ssnd(jps_ocz1)%clname = 'O_OCurz1'   ;   ssnd(jps_ivz1)%clname = 'O_IVelz1'
594      !
595      ssnd(jps_ocx1:jps_ivz1)%nsgn = -1.   ! vectors: change of the sign at the north fold
596
597      IF( sn_snd_crt%clvgrd == 'U,V' ) THEN
598         ssnd(jps_ocx1)%clgrid = 'U' ; ssnd(jps_ocy1)%clgrid = 'V'
599      ELSE IF( sn_snd_crt%clvgrd /= 'T' ) THEN 
600         CALL ctl_stop( 'sn_snd_crt%clvgrd must be equal to T' )
601         ssnd(jps_ocx1:jps_ivz1)%clgrid  = 'T'      ! all oce and ice components on the same unique grid
602      ENDIF
603      ssnd(jps_ocx1:jps_ivz1)%laction = .TRUE.   ! default: all are send
604      IF( TRIM( sn_snd_crt%clvref ) == 'spherical' )   ssnd( (/jps_ocz1, jps_ivz1/) )%laction = .FALSE. 
605      IF( TRIM( sn_snd_crt%clvor ) == 'eastward-northward' ) ssnd(jps_ocx1:jps_ivz1)%nsgn = 1.
606      SELECT CASE( TRIM( sn_snd_crt%cldes ) )
607      CASE( 'none'                 )   ;   ssnd(jps_ocx1:jps_ivz1)%laction = .FALSE.
608      CASE( 'oce only'             )   ;   ssnd(jps_ivx1:jps_ivz1)%laction = .FALSE.
609      CASE( 'weighted oce and ice' )   !   nothing to do
610      CASE( 'mixed oce-ice'        )   ;   ssnd(jps_ivx1:jps_ivz1)%laction = .FALSE.
611      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_crt%cldes' )
612      END SELECT
613
614      !                                                      ! ------------------------- !
615      !                                                      !          CO2 flux         !
616      !                                                      ! ------------------------- !
617      ssnd(jps_co2)%clname = 'O_CO2FLX' ;  IF( TRIM(sn_snd_co2%cldes) == 'coupled' )    ssnd(jps_co2 )%laction = .TRUE.
618      !
619      ! ================================ !
620      !   initialisation of the coupler  !
621      ! ================================ !
622
623      CALL cpl_prism_define(jprcv, jpsnd)           
624      !
625      IF( ln_dm2dc .AND. ( cpl_prism_freq( jpr_qsroce ) + cpl_prism_freq( jpr_qsrmix ) /= 86400 ) )   &
626         &   CALL ctl_stop( 'sbc_cpl_init: diurnal cycle reconstruction (ln_dm2dc) needs daily couping for solar radiation' )
627
628      CALL wrk_dealloc( jpi,jpj, zacs, zaos )
629      !
630      IF( nn_timing == 1 )  CALL timing_stop('sbc_cpl_init')
631      !
632   END SUBROUTINE sbc_cpl_init
633
634
635   SUBROUTINE sbc_cpl_rcv( kt, k_fsbc, k_ice )     
636      !!----------------------------------------------------------------------
637      !!             ***  ROUTINE sbc_cpl_rcv  ***
638      !!
639      !! ** Purpose :   provide the stress over the ocean and, if no sea-ice,
640      !!                provide the ocean heat and freshwater fluxes.
641      !!
642      !! ** Method  : - Receive all the atmospheric fields (stored in frcv array). called at each time step.
643      !!                OASIS controls if there is something do receive or not. nrcvinfo contains the info
644      !!                to know if the field was really received or not
645      !!
646      !!              --> If ocean stress was really received:
647      !!
648      !!                  - transform the received ocean stress vector from the received
649      !!                 referential and grid into an atmosphere-ocean stress in
650      !!                 the (i,j) ocean referencial and at the ocean velocity point.
651      !!                    The received stress are :
652      !!                     - defined by 3 components (if cartesian coordinate)
653      !!                            or by 2 components (if spherical)
654      !!                     - oriented along geographical   coordinate (if eastward-northward)
655      !!                            or  along the local grid coordinate (if local grid)
656      !!                     - given at U- and V-point, resp.   if received on 2 grids
657      !!                            or at T-point               if received on 1 grid
658      !!                    Therefore and if necessary, they are successively
659      !!                  processed in order to obtain them
660      !!                     first  as  2 components on the sphere
661      !!                     second as  2 components oriented along the local grid
662      !!                     third  as  2 components on the U,V grid
663      !!
664      !!              -->
665      !!
666      !!              - In 'ocean only' case, non solar and solar ocean heat fluxes
667      !!             and total ocean freshwater fluxes 
668      !!
669      !! ** Method  :   receive all fields from the atmosphere and transform
670      !!              them into ocean surface boundary condition fields
671      !!
672      !! ** Action  :   update  utau, vtau   ocean stress at U,V grid
673      !!                        taum, wndm   wind stres and wind speed module at T-point
674      !!                        qns , qsr    non solar and solar ocean heat fluxes   ('ocean only case)
675      !!                        emp = emps   evap. - precip. (- runoffs) (- calving) ('ocean only case)
676      !!----------------------------------------------------------------------
677      INTEGER, INTENT(in) ::   kt       ! ocean model time step index
678      INTEGER, INTENT(in) ::   k_fsbc   ! frequency of sbc (-> ice model) computation
679      INTEGER, INTENT(in) ::   k_ice    ! ice management in the sbc (=0/1/2/3)
680      !!
681      LOGICAL ::    llnewtx, llnewtau      ! update wind stress components and module??
682      INTEGER  ::   ji, jj, jn             ! dummy loop indices
683      INTEGER  ::   isec                   ! number of seconds since nit000 (assuming rdttra did not change since nit000)
684      REAL(wp) ::   zcumulneg, zcumulpos   ! temporary scalars     
685      REAL(wp) ::   zcoef                  ! temporary scalar
686      REAL(wp) ::   zrhoa  = 1.22          ! Air density kg/m3
687      REAL(wp) ::   zcdrag = 1.5e-3        ! drag coefficient
688      REAL(wp) ::   zzx, zzy               ! temporary variables
689      REAL(wp), POINTER, DIMENSION(:,:) ::   ztx, zty 
690      !!----------------------------------------------------------------------
691      !
692      IF( nn_timing == 1 )  CALL timing_start('sbc_cpl_rcv')
693      !
694      CALL wrk_alloc( jpi,jpj, ztx, zty )
695
696      IF( kt == nit000 )   CALL sbc_cpl_init( k_ice )          ! initialisation
697
698      !                                                 ! Receive all the atmos. fields (including ice information)
699      isec = ( kt - nit000 ) * NINT( rdttra(1) )             ! date of exchanges
700      DO jn = 1, jprcv                                       ! received fields sent by the atmosphere
701         IF( srcv(jn)%laction )   CALL cpl_prism_rcv( jn, isec, frcv(jn)%z3, nrcvinfo(jn) )
702      END DO
703
704      !                                                      ! ========================= !
705      IF( srcv(jpr_otx1)%laction ) THEN                      !  ocean stress components  !
706         !                                                   ! ========================= !
707         ! define frcv(jpr_otx1)%z3(:,:,1) and frcv(jpr_oty1)%z3(:,:,1): stress at U/V point along model grid
708         ! => need to be done only when we receive the field
709         IF(  nrcvinfo(jpr_otx1) == OASIS_Rcv ) THEN
710            !
711            IF( TRIM( sn_rcv_tau%clvref ) == 'cartesian' ) THEN            ! 2 components on the sphere
712               !                                                       ! (cartesian to spherical -> 3 to 2 components)
713               !
714               CALL geo2oce( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), frcv(jpr_otz1)%z3(:,:,1),   &
715                  &          srcv(jpr_otx1)%clgrid, ztx, zty )
716               frcv(jpr_otx1)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 1st grid
717               frcv(jpr_oty1)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 1st grid
718               !
719               IF( srcv(jpr_otx2)%laction ) THEN
720                  CALL geo2oce( frcv(jpr_otx2)%z3(:,:,1), frcv(jpr_oty2)%z3(:,:,1), frcv(jpr_otz2)%z3(:,:,1),   &
721                     &          srcv(jpr_otx2)%clgrid, ztx, zty )
722                  frcv(jpr_otx2)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 2nd grid
723                  frcv(jpr_oty2)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 2nd grid
724               ENDIF
725               !
726            ENDIF
727            !
728            IF( TRIM( sn_rcv_tau%clvor ) == 'eastward-northward' ) THEN   ! 2 components oriented along the local grid
729               !                                                       ! (geographical to local grid -> rotate the components)
730               CALL rot_rep( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), srcv(jpr_otx1)%clgrid, 'en->i', ztx )   
731               IF( srcv(jpr_otx2)%laction ) THEN
732                  CALL rot_rep( frcv(jpr_otx2)%z3(:,:,1), frcv(jpr_oty2)%z3(:,:,1), srcv(jpr_otx2)%clgrid, 'en->j', zty )   
733               ELSE 
734                  CALL rot_rep( frcv(jpr_otx1)%z3(:,:,1), frcv(jpr_oty1)%z3(:,:,1), srcv(jpr_otx1)%clgrid, 'en->j', zty ) 
735               ENDIF
736               frcv(jpr_otx1)%z3(:,:,1) = ztx(:,:)      ! overwrite 1st component on the 1st grid
737               frcv(jpr_oty1)%z3(:,:,1) = zty(:,:)      ! overwrite 2nd component on the 2nd grid
738            ENDIF
739            !                             
740            IF( srcv(jpr_otx1)%clgrid == 'T' ) THEN
741               DO jj = 2, jpjm1                                          ! T ==> (U,V)
742                  DO ji = fs_2, fs_jpim1   ! vector opt.
743                     frcv(jpr_otx1)%z3(ji,jj,1) = 0.5 * ( frcv(jpr_otx1)%z3(ji+1,jj  ,1) + frcv(jpr_otx1)%z3(ji,jj,1) )
744                     frcv(jpr_oty1)%z3(ji,jj,1) = 0.5 * ( frcv(jpr_oty1)%z3(ji  ,jj+1,1) + frcv(jpr_oty1)%z3(ji,jj,1) )
745                  END DO
746               END DO
747               CALL lbc_lnk( frcv(jpr_otx1)%z3(:,:,1), 'U',  -1. )   ;   CALL lbc_lnk( frcv(jpr_oty1)%z3(:,:,1), 'V',  -1. )
748            ENDIF
749            llnewtx = .TRUE.
750         ELSE
751            llnewtx = .FALSE.
752         ENDIF
753         !                                                   ! ========================= !
754      ELSE                                                   !   No dynamical coupling   !
755         !                                                   ! ========================= !
756         frcv(jpr_otx1)%z3(:,:,1) = 0.e0                               ! here simply set to zero
757         frcv(jpr_oty1)%z3(:,:,1) = 0.e0                               ! an external read in a file can be added instead
758         llnewtx = .TRUE.
759         !
760      ENDIF
761     
762      !                                                      ! ========================= !
763      !                                                      !    wind stress module     !   (taum)
764      !                                                      ! ========================= !
765      !
766      IF( .NOT. srcv(jpr_taum)%laction ) THEN                    ! compute wind stress module from its components if not received
767         ! => need to be done only when otx1 was changed
768         IF( llnewtx ) THEN
769!CDIR NOVERRCHK
770            DO jj = 2, jpjm1
771!CDIR NOVERRCHK
772               DO ji = fs_2, fs_jpim1   ! vect. opt.
773                  zzx = frcv(jpr_otx1)%z3(ji-1,jj  ,1) + frcv(jpr_otx1)%z3(ji,jj,1)
774                  zzy = frcv(jpr_oty1)%z3(ji  ,jj-1,1) + frcv(jpr_oty1)%z3(ji,jj,1)
775                  frcv(jpr_taum)%z3(ji,jj,1) = 0.5 * SQRT( zzx * zzx + zzy * zzy )
776               END DO
777            END DO
778            CALL lbc_lnk( frcv(jpr_taum)%z3(:,:,1), 'T', 1. )
779            llnewtau = .TRUE.
780         ELSE
781            llnewtau = .FALSE.
782         ENDIF
783      ELSE
784         llnewtau = nrcvinfo(jpr_taum) == OASIS_Rcv
785         ! Stress module can be negative when received (interpolation problem)
786         IF( llnewtau ) THEN
787            frcv(jpr_taum)%z3(:,:,1) = MAX( 0.0e0, frcv(jpr_taum)%z3(:,:,1) )
788         ENDIF
789      ENDIF
790     
791      !                                                      ! ========================= !
792      !                                                      !      10 m wind speed      !   (wndm)
793      !                                                      ! ========================= !
794      !
795      IF( .NOT. srcv(jpr_w10m)%laction ) THEN                    ! compute wind spreed from wind stress module if not received 
796         ! => need to be done only when taumod was changed
797         IF( llnewtau ) THEN
798            zcoef = 1. / ( zrhoa * zcdrag ) 
799!CDIR NOVERRCHK
800            DO jj = 1, jpj
801!CDIR NOVERRCHK
802               DO ji = 1, jpi 
803                  wndm(ji,jj) = SQRT( frcv(jpr_taum)%z3(ji,jj,1) * zcoef )
804               END DO
805            END DO
806         ENDIF
807      ELSE
808         IF ( nrcvinfo(jpr_w10m) == OASIS_Rcv ) wndm(:,:) = frcv(jpr_w10m)%z3(:,:,1)
809      ENDIF
810
811      ! u(v)tau and taum will be modified by ice model
812      ! -> need to be reset before each call of the ice/fsbc     
813      IF( MOD( kt-1, k_fsbc ) == 0 ) THEN
814         !
815         utau(:,:) = frcv(jpr_otx1)%z3(:,:,1)
816         vtau(:,:) = frcv(jpr_oty1)%z3(:,:,1)
817         taum(:,:) = frcv(jpr_taum)%z3(:,:,1)
818         CALL iom_put( "taum_oce", taum )   ! output wind stress module
819         
820      ENDIF
821
822#if defined key_cpl_carbon_cycle
823      !                                                              ! atmosph. CO2 (ppm)
824      IF( srcv(jpr_co2)%laction )   atm_co2(:,:) = frcv(jpr_co2)%z3(:,:,1)
825#endif
826
827      !                                                      ! ========================= !
828      IF( k_ice <= 1 ) THEN                                  !  heat & freshwater fluxes ! (Ocean only case)
829         !                                                   ! ========================= !
830         !
831         !                                                       ! non solar heat flux over the ocean (qns)
832         IF( srcv(jpr_qnsoce)%laction )   qns(:,:) = frcv(jpr_qnsoce)%z3(:,:,1)
833         IF( srcv(jpr_qnsmix)%laction )   qns(:,:) = frcv(jpr_qnsmix)%z3(:,:,1)
834         ! add the latent heat of solid precip. melting
835         IF( srcv(jpr_snow  )%laction )   qns(:,:) = qns(:,:) - frcv(jpr_snow)%z3(:,:,1) * lfus             
836
837         !                                                       ! solar flux over the ocean          (qsr)
838         IF( srcv(jpr_qsroce)%laction )   qsr(:,:) = frcv(jpr_qsroce)%z3(:,:,1)
839         IF( srcv(jpr_qsrmix)%laction )   qsr(:,:) = frcv(jpr_qsrmix)%z3(:,:,1)
840         IF( ln_dm2dc )   qsr(:,:) = sbc_dcy( qsr )                           ! modify qsr to include the diurnal cycle
841         !
842         !                                                       ! total freshwater fluxes over the ocean (emp, emps)
843         SELECT CASE( TRIM( sn_rcv_emp%cldes ) )                                    ! evaporation - precipitation
844         CASE( 'conservative' )
845            emp(:,:) = frcv(jpr_tevp)%z3(:,:,1) - ( frcv(jpr_rain)%z3(:,:,1) + frcv(jpr_snow)%z3(:,:,1) )
846         CASE( 'oce only', 'oce and ice' )
847            emp(:,:) = frcv(jpr_oemp)%z3(:,:,1)
848         CASE default
849            CALL ctl_stop( 'sbc_cpl_rcv: wrong definition of sn_rcv_emp%cldes' )
850         END SELECT
851         !
852         !                                                        ! runoffs and calving (added in emp)
853         IF( srcv(jpr_rnf)%laction )   emp(:,:) = emp(:,:) - frcv(jpr_rnf)%z3(:,:,1)
854         IF( srcv(jpr_cal)%laction )   emp(:,:) = emp(:,:) - frcv(jpr_cal)%z3(:,:,1)
855         !
856!!gm :  this seems to be internal cooking, not sure to need that in a generic interface
857!!gm                                       at least should be optional...
858!!         IF( TRIM( sn_rcv_rnf%cldes ) == 'coupled' ) THEN     ! add to the total freshwater budget
859!!            ! remove negative runoff
860!!            zcumulpos = SUM( MAX( frcv(jpr_rnf)%z3(:,:,1), 0.e0 ) * e1t(:,:) * e2t(:,:) * tmask_i(:,:) )
861!!            zcumulneg = SUM( MIN( frcv(jpr_rnf)%z3(:,:,1), 0.e0 ) * e1t(:,:) * e2t(:,:) * tmask_i(:,:) )
862!!            IF( lk_mpp )   CALL mpp_sum( zcumulpos )   ! sum over the global domain
863!!            IF( lk_mpp )   CALL mpp_sum( zcumulneg )
864!!            IF( zcumulpos /= 0. ) THEN                 ! distribute negative runoff on positive runoff grid points
865!!               zcumulneg = 1.e0 + zcumulneg / zcumulpos
866!!               frcv(jpr_rnf)%z3(:,:,1) = MAX( frcv(jpr_rnf)%z3(:,:,1), 0.e0 ) * zcumulneg
867!!            ENDIF     
868!!            ! add runoff to e-p
869!!            emp(:,:) = emp(:,:) - frcv(jpr_rnf)%z3(:,:,1)
870!!         ENDIF
871!!gm  end of internal cooking
872         !
873         emps(:,:) = emp(:,:)                                        ! concentration/dilution = emp
874 
875      ENDIF
876      !
877      CALL wrk_dealloc( jpi,jpj, ztx, zty )
878      !
879      IF( nn_timing == 1 )  CALL timing_stop('sbc_cpl_rcv')
880      !
881   END SUBROUTINE sbc_cpl_rcv
882   
883
884   SUBROUTINE sbc_cpl_ice_tau( p_taui, p_tauj )     
885      !!----------------------------------------------------------------------
886      !!             ***  ROUTINE sbc_cpl_ice_tau  ***
887      !!
888      !! ** Purpose :   provide the stress over sea-ice in coupled mode
889      !!
890      !! ** Method  :   transform the received stress from the atmosphere into
891      !!             an atmosphere-ice stress in the (i,j) ocean referencial
892      !!             and at the velocity point of the sea-ice model (cp_ice_msh):
893      !!                'C'-grid : i- (j-) components given at U- (V-) point
894      !!                'I'-grid : B-grid lower-left corner: both components given at I-point
895      !!
896      !!                The received stress are :
897      !!                 - defined by 3 components (if cartesian coordinate)
898      !!                        or by 2 components (if spherical)
899      !!                 - oriented along geographical   coordinate (if eastward-northward)
900      !!                        or  along the local grid coordinate (if local grid)
901      !!                 - given at U- and V-point, resp.   if received on 2 grids
902      !!                        or at a same point (T or I) if received on 1 grid
903      !!                Therefore and if necessary, they are successively
904      !!             processed in order to obtain them
905      !!                 first  as  2 components on the sphere
906      !!                 second as  2 components oriented along the local grid
907      !!                 third  as  2 components on the cp_ice_msh point
908      !!
909      !!                In 'oce and ice' case, only one vector stress field
910      !!             is received. It has already been processed in sbc_cpl_rcv
911      !!             so that it is now defined as (i,j) components given at U-
912      !!             and V-points, respectively. Therefore, here only the third
913      !!             transformation is done and only if the ice-grid is a 'I'-grid.
914      !!
915      !! ** Action  :   return ptau_i, ptau_j, the stress over the ice at cp_ice_msh point
916      !!----------------------------------------------------------------------
917      REAL(wp), INTENT(out), DIMENSION(:,:) ::   p_taui   ! i- & j-components of atmos-ice stress [N/m2]
918      REAL(wp), INTENT(out), DIMENSION(:,:) ::   p_tauj   ! at I-point (B-grid) or U & V-point (C-grid)
919      !!
920      INTEGER ::   ji, jj                          ! dummy loop indices
921      INTEGER ::   itx                             ! index of taux over ice
922      REAL(wp), POINTER, DIMENSION(:,:) ::   ztx, zty 
923      !!----------------------------------------------------------------------
924      !
925      IF( nn_timing == 1 )  CALL timing_start('sbc_cpl_ice_tau')
926      !
927      CALL wrk_alloc( jpi,jpj, ztx, zty )
928
929      IF( srcv(jpr_itx1)%laction ) THEN   ;   itx =  jpr_itx1   
930      ELSE                                ;   itx =  jpr_otx1
931      ENDIF
932
933      ! do something only if we just received the stress from atmosphere
934      IF(  nrcvinfo(itx) == OASIS_Rcv ) THEN
935
936         !                                                      ! ======================= !
937         IF( srcv(jpr_itx1)%laction ) THEN                      !   ice stress received   !
938            !                                                   ! ======================= !
939           
940            IF( TRIM( sn_rcv_tau%clvref ) == 'cartesian' ) THEN            ! 2 components on the sphere
941               !                                                       ! (cartesian to spherical -> 3 to 2 components)
942               CALL geo2oce(  frcv(jpr_itx1)%z3(:,:,1), frcv(jpr_ity1)%z3(:,:,1), frcv(jpr_itz1)%z3(:,:,1),   &
943                  &          srcv(jpr_itx1)%clgrid, ztx, zty )
944               frcv(jpr_itx1)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 1st grid
945               frcv(jpr_ity1)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 1st grid
946               !
947               IF( srcv(jpr_itx2)%laction ) THEN
948                  CALL geo2oce( frcv(jpr_itx2)%z3(:,:,1), frcv(jpr_ity2)%z3(:,:,1), frcv(jpr_itz2)%z3(:,:,1),   &
949                     &          srcv(jpr_itx2)%clgrid, ztx, zty )
950                  frcv(jpr_itx2)%z3(:,:,1) = ztx(:,:)   ! overwrite 1st comp. on the 2nd grid
951                  frcv(jpr_ity2)%z3(:,:,1) = zty(:,:)   ! overwrite 2nd comp. on the 2nd grid
952               ENDIF
953               !
954            ENDIF
955            !
956            IF( TRIM( sn_rcv_tau%clvor ) == 'eastward-northward' ) THEN   ! 2 components oriented along the local grid
957               !                                                       ! (geographical to local grid -> rotate the components)
958               CALL rot_rep( frcv(jpr_itx1)%z3(:,:,1), frcv(jpr_ity1)%z3(:,:,1), srcv(jpr_itx1)%clgrid, 'en->i', ztx )   
959               IF( srcv(jpr_itx2)%laction ) THEN
960                  CALL rot_rep( frcv(jpr_itx2)%z3(:,:,1), frcv(jpr_ity2)%z3(:,:,1), srcv(jpr_itx2)%clgrid, 'en->j', zty )   
961               ELSE
962                  CALL rot_rep( frcv(jpr_itx1)%z3(:,:,1), frcv(jpr_ity1)%z3(:,:,1), srcv(jpr_itx1)%clgrid, 'en->j', zty ) 
963               ENDIF
964               frcv(jpr_itx1)%z3(:,:,1) = ztx(:,:)      ! overwrite 1st component on the 1st grid
965               frcv(jpr_ity1)%z3(:,:,1) = zty(:,:)      ! overwrite 2nd component on the 1st grid
966            ENDIF
967            !                                                   ! ======================= !
968         ELSE                                                   !     use ocean stress    !
969            !                                                   ! ======================= !
970            frcv(jpr_itx1)%z3(:,:,1) = frcv(jpr_otx1)%z3(:,:,1)
971            frcv(jpr_ity1)%z3(:,:,1) = frcv(jpr_oty1)%z3(:,:,1)
972            !
973         ENDIF
974
975         !                                                      ! ======================= !
976         !                                                      !     put on ice grid     !
977         !                                                      ! ======================= !
978         !   
979         !                                                  j+1   j     -----V---F
980         ! ice stress on ice velocity point (cp_ice_msh)                 !       |
981         ! (C-grid ==>(U,V) or B-grid ==> I or F)                 j      |   T   U
982         !                                                               |       |
983         !                                                   j    j-1   -I-------|
984         !                                               (for I)         |       |
985         !                                                              i-1  i   i
986         !                                                               i      i+1 (for I)
987         SELECT CASE ( cp_ice_msh )
988            !
989         CASE( 'I' )                                         ! B-grid ==> I
990            SELECT CASE ( srcv(jpr_itx1)%clgrid )
991            CASE( 'U' )
992               DO jj = 2, jpjm1                                   ! (U,V) ==> I
993                  DO ji = 2, jpim1   ! NO vector opt.
994                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji-1,jj  ,1) + frcv(jpr_itx1)%z3(ji-1,jj-1,1) )
995                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji  ,jj-1,1) + frcv(jpr_ity1)%z3(ji-1,jj-1,1) )
996                  END DO
997               END DO
998            CASE( 'F' )
999               DO jj = 2, jpjm1                                   ! F ==> I
1000                  DO ji = 2, jpim1   ! NO vector opt.
1001                     p_taui(ji,jj) = frcv(jpr_itx1)%z3(ji-1,jj-1,1)
1002                     p_tauj(ji,jj) = frcv(jpr_ity1)%z3(ji-1,jj-1,1)
1003                  END DO
1004               END DO
1005            CASE( 'T' )
1006               DO jj = 2, jpjm1                                   ! T ==> I
1007                  DO ji = 2, jpim1   ! NO vector opt.
1008                     p_taui(ji,jj) = 0.25 * ( frcv(jpr_itx1)%z3(ji,jj  ,1) + frcv(jpr_itx1)%z3(ji-1,jj  ,1)   &
1009                        &                   + frcv(jpr_itx1)%z3(ji,jj-1,1) + frcv(jpr_itx1)%z3(ji-1,jj-1,1) ) 
1010                     p_tauj(ji,jj) = 0.25 * ( frcv(jpr_ity1)%z3(ji,jj  ,1) + frcv(jpr_ity1)%z3(ji-1,jj  ,1)   &
1011                        &                   + frcv(jpr_oty1)%z3(ji,jj-1,1) + frcv(jpr_ity1)%z3(ji-1,jj-1,1) )
1012                  END DO
1013               END DO
1014            CASE( 'I' )
1015               p_taui(:,:) = frcv(jpr_itx1)%z3(:,:,1)                   ! I ==> I
1016               p_tauj(:,:) = frcv(jpr_ity1)%z3(:,:,1)
1017            END SELECT
1018            IF( srcv(jpr_itx1)%clgrid /= 'I' ) THEN
1019               CALL lbc_lnk( p_taui, 'I',  -1. )   ;   CALL lbc_lnk( p_tauj, 'I',  -1. )
1020            ENDIF
1021            !
1022         CASE( 'F' )                                         ! B-grid ==> F
1023            SELECT CASE ( srcv(jpr_itx1)%clgrid )
1024            CASE( 'U' )
1025               DO jj = 2, jpjm1                                   ! (U,V) ==> F
1026                  DO ji = fs_2, fs_jpim1   ! vector opt.
1027                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji,jj,1) + frcv(jpr_itx1)%z3(ji  ,jj+1,1) )
1028                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji,jj,1) + frcv(jpr_ity1)%z3(ji+1,jj  ,1) )
1029                  END DO
1030               END DO
1031            CASE( 'I' )
1032               DO jj = 2, jpjm1                                   ! I ==> F
1033                  DO ji = 2, jpim1   ! NO vector opt.
1034                     p_taui(ji,jj) = frcv(jpr_itx1)%z3(ji+1,jj+1,1)
1035                     p_tauj(ji,jj) = frcv(jpr_ity1)%z3(ji+1,jj+1,1)
1036                  END DO
1037               END DO
1038            CASE( 'T' )
1039               DO jj = 2, jpjm1                                   ! T ==> F
1040                  DO ji = 2, jpim1   ! NO vector opt.
1041                     p_taui(ji,jj) = 0.25 * ( frcv(jpr_itx1)%z3(ji,jj  ,1) + frcv(jpr_itx1)%z3(ji+1,jj  ,1)   &
1042                        &                   + frcv(jpr_itx1)%z3(ji,jj+1,1) + frcv(jpr_itx1)%z3(ji+1,jj+1,1) ) 
1043                     p_tauj(ji,jj) = 0.25 * ( frcv(jpr_ity1)%z3(ji,jj  ,1) + frcv(jpr_ity1)%z3(ji+1,jj  ,1)   &
1044                        &                   + frcv(jpr_ity1)%z3(ji,jj+1,1) + frcv(jpr_ity1)%z3(ji+1,jj+1,1) )
1045                  END DO
1046               END DO
1047            CASE( 'F' )
1048               p_taui(:,:) = frcv(jpr_itx1)%z3(:,:,1)                   ! F ==> F
1049               p_tauj(:,:) = frcv(jpr_ity1)%z3(:,:,1)
1050            END SELECT
1051            IF( srcv(jpr_itx1)%clgrid /= 'F' ) THEN
1052               CALL lbc_lnk( p_taui, 'F',  -1. )   ;   CALL lbc_lnk( p_tauj, 'F',  -1. )
1053            ENDIF
1054            !
1055         CASE( 'C' )                                         ! C-grid ==> U,V
1056            SELECT CASE ( srcv(jpr_itx1)%clgrid )
1057            CASE( 'U' )
1058               p_taui(:,:) = frcv(jpr_itx1)%z3(:,:,1)                   ! (U,V) ==> (U,V)
1059               p_tauj(:,:) = frcv(jpr_ity1)%z3(:,:,1)
1060            CASE( 'F' )
1061               DO jj = 2, jpjm1                                   ! F ==> (U,V)
1062                  DO ji = fs_2, fs_jpim1   ! vector opt.
1063                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji,jj,1) + frcv(jpr_itx1)%z3(ji  ,jj-1,1) )
1064                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(jj,jj,1) + frcv(jpr_ity1)%z3(ji-1,jj  ,1) )
1065                  END DO
1066               END DO
1067            CASE( 'T' )
1068               DO jj = 2, jpjm1                                   ! T ==> (U,V)
1069                  DO ji = fs_2, fs_jpim1   ! vector opt.
1070                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji+1,jj  ,1) + frcv(jpr_itx1)%z3(ji,jj,1) )
1071                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji  ,jj+1,1) + frcv(jpr_ity1)%z3(ji,jj,1) )
1072                  END DO
1073               END DO
1074            CASE( 'I' )
1075               DO jj = 2, jpjm1                                   ! I ==> (U,V)
1076                  DO ji = 2, jpim1   ! NO vector opt.
1077                     p_taui(ji,jj) = 0.5 * ( frcv(jpr_itx1)%z3(ji+1,jj+1,1) + frcv(jpr_itx1)%z3(ji+1,jj  ,1) )
1078                     p_tauj(ji,jj) = 0.5 * ( frcv(jpr_ity1)%z3(ji+1,jj+1,1) + frcv(jpr_ity1)%z3(ji  ,jj+1,1) )
1079                  END DO
1080               END DO
1081            END SELECT
1082            IF( srcv(jpr_itx1)%clgrid /= 'U' ) THEN
1083               CALL lbc_lnk( p_taui, 'U',  -1. )   ;   CALL lbc_lnk( p_tauj, 'V',  -1. )
1084            ENDIF
1085         END SELECT
1086
1087      ENDIF
1088      !   
1089      CALL wrk_dealloc( jpi,jpj, ztx, zty )
1090      !
1091      IF( nn_timing == 1 )  CALL timing_stop('sbc_cpl_ice_tau')
1092      !
1093   END SUBROUTINE sbc_cpl_ice_tau
1094   
1095
1096   SUBROUTINE sbc_cpl_ice_flx( p_frld  , palbi   , psst    , pist    )
1097      !!----------------------------------------------------------------------
1098      !!             ***  ROUTINE sbc_cpl_ice_flx  ***
1099      !!
1100      !! ** Purpose :   provide the heat and freshwater fluxes of the
1101      !!              ocean-ice system.
1102      !!
1103      !! ** Method  :   transform the fields received from the atmosphere into
1104      !!             surface heat and fresh water boundary condition for the
1105      !!             ice-ocean system. The following fields are provided:
1106      !!              * total non solar, solar and freshwater fluxes (qns_tot,
1107      !!             qsr_tot and emp_tot) (total means weighted ice-ocean flux)
1108      !!             NB: emp_tot include runoffs and calving.
1109      !!              * fluxes over ice (qns_ice, qsr_ice, emp_ice) where
1110      !!             emp_ice = sublimation - solid precipitation as liquid
1111      !!             precipitation are re-routed directly to the ocean and
1112      !!             runoffs and calving directly enter the ocean.
1113      !!              * solid precipitation (sprecip), used to add to qns_tot
1114      !!             the heat lost associated to melting solid precipitation
1115      !!             over the ocean fraction.
1116      !!       ===>> CAUTION here this changes the net heat flux received from
1117      !!             the atmosphere
1118      !!
1119      !!                  - the fluxes have been separated from the stress as
1120      !!                 (a) they are updated at each ice time step compare to
1121      !!                 an update at each coupled time step for the stress, and
1122      !!                 (b) the conservative computation of the fluxes over the
1123      !!                 sea-ice area requires the knowledge of the ice fraction
1124      !!                 after the ice advection and before the ice thermodynamics,
1125      !!                 so that the stress is updated before the ice dynamics
1126      !!                 while the fluxes are updated after it.
1127      !!
1128      !! ** Action  :   update at each nf_ice time step:
1129      !!                   qns_tot, qsr_tot  non-solar and solar total heat fluxes
1130      !!                   qns_ice, qsr_ice  non-solar and solar heat fluxes over the ice
1131      !!                   emp_tot            total evaporation - precipitation(liquid and solid) (-runoff)(-calving)
1132      !!                   emp_ice            ice sublimation - solid precipitation over the ice
1133      !!                   dqns_ice           d(non-solar heat flux)/d(Temperature) over the ice
1134      !!                   sprecip             solid precipitation over the ocean 
1135      !!----------------------------------------------------------------------
1136      REAL(wp), INTENT(in   ), DIMENSION(:,:)   ::   p_frld     ! lead fraction                [0 to 1]
1137      ! optional arguments, used only in 'mixed oce-ice' case
1138      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   palbi   ! ice albedo
1139      REAL(wp), INTENT(in   ), DIMENSION(:,:  ), OPTIONAL ::   psst    ! sea surface temperature     [Celcius]
1140      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   pist    ! ice surface temperature     [Kelvin]
1141      !
1142      INTEGER ::   jl   ! dummy loop index
1143      REAL(wp), POINTER, DIMENSION(:,:) ::   zcptn, ztmp, zicefr
1144      !!----------------------------------------------------------------------
1145      !
1146      IF( nn_timing == 1 )  CALL timing_start('sbc_cpl_ice_flx')
1147      !
1148      CALL wrk_alloc( jpi,jpj, zcptn, ztmp, zicefr )
1149
1150      zicefr(:,:) = 1.- p_frld(:,:)
1151      IF( lk_diaar5 )   zcptn(:,:) = rcp * tsn(:,:,1,jp_tem)
1152      !
1153      !                                                      ! ========================= !
1154      !                                                      !    freshwater budget      !   (emp)
1155      !                                                      ! ========================= !
1156      !
1157      !                                                           ! total Precipitations - total Evaporation (emp_tot)
1158      !                                                           ! solid precipitation  - sublimation       (emp_ice)
1159      !                                                           ! solid Precipitation                      (sprecip)
1160      SELECT CASE( TRIM( sn_rcv_emp%cldes ) )
1161      CASE( 'conservative'  )   ! received fields: jpr_rain, jpr_snow, jpr_ievp, jpr_tevp
1162         sprecip(:,:) = frcv(jpr_snow)%z3(:,:,1)                 ! May need to ensure positive here
1163         tprecip(:,:) = frcv(jpr_rain)%z3(:,:,1) + sprecip (:,:) ! May need to ensure positive here
1164         emp_tot(:,:) = frcv(jpr_tevp)%z3(:,:,1) - tprecip(:,:)
1165         emp_ice(:,:) = frcv(jpr_ievp)%z3(:,:,1) - frcv(jpr_snow)%z3(:,:,1)
1166                           CALL iom_put( 'rain'         , frcv(jpr_rain)%z3(:,:,1)              )   ! liquid precipitation
1167         IF( lk_diaar5 )   CALL iom_put( 'hflx_rain_cea', frcv(jpr_rain)%z3(:,:,1) * zcptn(:,:) )   ! heat flux from liq. precip.
1168         ztmp(:,:) = frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:)
1169                           CALL iom_put( 'evap_ao_cea'  , ztmp                            )   ! ice-free oce evap (cell average)
1170         IF( lk_diaar5 )   CALL iom_put( 'hflx_evap_cea', ztmp(:,:         ) * zcptn(:,:) )   ! heat flux from from evap (cell ave)
1171      CASE( 'oce and ice'   )   ! received fields: jpr_sbpr, jpr_semp, jpr_oemp, jpr_ievp
1172         emp_tot(:,:) = p_frld(:,:) * frcv(jpr_oemp)%z3(:,:,1) + zicefr(:,:) * frcv(jpr_sbpr)%z3(:,:,1)
1173         emp_ice(:,:) = frcv(jpr_semp)%z3(:,:,1)
1174         sprecip(:,:) = - frcv(jpr_semp)%z3(:,:,1) + frcv(jpr_ievp)%z3(:,:,1)
1175      END SELECT
1176
1177      CALL iom_put( 'snowpre'    , sprecip                                )   ! Snow
1178      CALL iom_put( 'snow_ao_cea', sprecip(:,:         ) * p_frld(:,:)    )   ! Snow        over ice-free ocean  (cell average)
1179      CALL iom_put( 'snow_ai_cea', sprecip(:,:         ) * zicefr(:,:)    )   ! Snow        over sea-ice         (cell average)
1180      CALL iom_put( 'subl_ai_cea', frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) )   ! Sublimation over sea-ice         (cell average)
1181      !   
1182      !                                                           ! runoffs and calving (put in emp_tot)
1183      IF( srcv(jpr_rnf)%laction ) THEN
1184         emp_tot(:,:) = emp_tot(:,:) - frcv(jpr_rnf)%z3(:,:,1)
1185                           CALL iom_put( 'runoffs'      , frcv(jpr_rnf)%z3(:,:,1)              )   ! rivers
1186         IF( lk_diaar5 )   CALL iom_put( 'hflx_rnf_cea' , frcv(jpr_rnf)%z3(:,:,1) * zcptn(:,:) )   ! heat flux from rivers
1187      ENDIF
1188      IF( srcv(jpr_cal)%laction ) THEN
1189         emp_tot(:,:) = emp_tot(:,:) - frcv(jpr_cal)%z3(:,:,1)
1190         CALL iom_put( 'calving', frcv(jpr_cal)%z3(:,:,1) )
1191      ENDIF
1192      !
1193!!gm :  this seems to be internal cooking, not sure to need that in a generic interface
1194!!gm                                       at least should be optional...
1195!!       ! remove negative runoff                            ! sum over the global domain
1196!!       zcumulpos = SUM( MAX( frcv(jpr_rnf)%z3(:,:,1), 0.e0 ) * e1t(:,:) * e2t(:,:) * tmask_i(:,:) )
1197!!       zcumulneg = SUM( MIN( frcv(jpr_rnf)%z3(:,:,1), 0.e0 ) * e1t(:,:) * e2t(:,:) * tmask_i(:,:) )
1198!!       IF( lk_mpp )   CALL mpp_sum( zcumulpos )
1199!!       IF( lk_mpp )   CALL mpp_sum( zcumulneg )
1200!!       IF( zcumulpos /= 0. ) THEN                          ! distribute negative runoff on positive runoff grid points
1201!!          zcumulneg = 1.e0 + zcumulneg / zcumulpos
1202!!          frcv(jpr_rnf)%z3(:,:,1) = MAX( frcv(jpr_rnf)%z3(:,:,1), 0.e0 ) * zcumulneg
1203!!       ENDIF     
1204!!       emp_tot(:,:) = emp_tot(:,:) - frcv(jpr_rnf)%z3(:,:,1)   ! add runoff to e-p
1205!!
1206!!gm  end of internal cooking
1207
1208      !                                                      ! ========================= !
1209      SELECT CASE( TRIM( sn_rcv_qns%cldes ) )                !   non solar heat fluxes   !   (qns)
1210      !                                                      ! ========================= !
1211      CASE( 'oce only' )                                     ! the required field is directly provided
1212         qns_tot(:,:  ) = frcv(jpr_qnsoce)%z3(:,:,1)
1213      CASE( 'conservative' )                                      ! the required fields are directly provided
1214         qns_tot(:,:  ) = frcv(jpr_qnsmix)%z3(:,:,1)
1215         IF ( TRIM(sn_rcv_qns%clcat) == 'yes' ) THEN
1216            qns_ice(:,:,1:jpl) = frcv(jpr_qnsice)%z3(:,:,1:jpl)
1217         ELSE
1218            ! Set all category values equal for the moment
1219            DO jl=1,jpl
1220               qns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,1)
1221            ENDDO
1222         ENDIF
1223      CASE( 'oce and ice' )       ! the total flux is computed from ocean and ice fluxes
1224         qns_tot(:,:  ) =  p_frld(:,:) * frcv(jpr_qnsoce)%z3(:,:,1)
1225         IF ( TRIM(sn_rcv_qns%clcat) == 'yes' ) THEN
1226            DO jl=1,jpl
1227               qns_tot(:,:   ) = qns_tot(:,:) + a_i(:,:,jl) * frcv(jpr_qnsice)%z3(:,:,jl)   
1228               qns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,jl)
1229            ENDDO
1230         ELSE
1231            DO jl=1,jpl
1232               qns_tot(:,:   ) = qns_tot(:,:) + zicefr(:,:) * frcv(jpr_qnsice)%z3(:,:,1)
1233               qns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,1)
1234            ENDDO
1235         ENDIF
1236      CASE( 'mixed oce-ice' )     ! the ice flux is cumputed from the total flux, the SST and ice informations
1237! ** NEED TO SORT OUT HOW THIS SHOULD WORK IN THE MULTI-CATEGORY CASE - CURRENTLY NOT ALLOWED WHEN INTERFACE INITIALISED **
1238         qns_tot(:,:  ) = frcv(jpr_qnsmix)%z3(:,:,1)
1239         qns_ice(:,:,1) = frcv(jpr_qnsmix)%z3(:,:,1)    &
1240            &            + frcv(jpr_dqnsdt)%z3(:,:,1) * ( pist(:,:,1) - ( (rt0 + psst(:,:  ) ) * p_frld(:,:)   &
1241            &                                                   +          pist(:,:,1)   * zicefr(:,:) ) )
1242      END SELECT
1243      ztmp(:,:) = p_frld(:,:) * sprecip(:,:) * lfus               ! add the latent heat of solid precip. melting
1244      qns_tot(:,:) = qns_tot(:,:) - ztmp(:,:)                     ! over free ocean
1245      IF( lk_diaar5 )   CALL iom_put( 'hflx_snow_cea', ztmp + sprecip(:,:) * zcptn(:,:) )   ! heat flux from snow (cell average)
1246!!gm
1247!!    currently it is taken into account in leads budget but not in the qns_tot, and thus not in
1248!!    the flux that enter the ocean....
1249!!    moreover 1 - it is not diagnose anywhere....
1250!!             2 - it is unclear for me whether this heat lost is taken into account in the atmosphere or not...
1251!!
1252!! similar job should be done for snow and precipitation temperature
1253      !                                     
1254      IF( srcv(jpr_cal)%laction ) THEN                            ! Iceberg melting
1255         ztmp(:,:) = frcv(jpr_cal)%z3(:,:,1) * lfus               ! add the latent heat of iceberg melting
1256         qns_tot(:,:) = qns_tot(:,:) - ztmp(:,:)
1257         IF( lk_diaar5 )   CALL iom_put( 'hflx_cal_cea', ztmp + frcv(jpr_cal)%z3(:,:,1) * zcptn(:,:) )   ! heat flux from calving
1258      ENDIF
1259
1260      !                                                      ! ========================= !
1261      SELECT CASE( TRIM( sn_rcv_qsr%cldes ) )                !      solar heat fluxes    !   (qsr)
1262      !                                                      ! ========================= !
1263      CASE( 'oce only' )
1264         qsr_tot(:,:  ) = MAX(0.0,frcv(jpr_qsroce)%z3(:,:,1))
1265      CASE( 'conservative' )
1266         qsr_tot(:,:  ) = frcv(jpr_qsrmix)%z3(:,:,1)
1267         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN
1268            qsr_ice(:,:,1:jpl) = frcv(jpr_qsrice)%z3(:,:,1:jpl)
1269         ELSE
1270            ! Set all category values equal for the moment
1271            DO jl=1,jpl
1272               qsr_ice(:,:,jl) = frcv(jpr_qsrice)%z3(:,:,1)
1273            ENDDO
1274         ENDIF
1275         qsr_tot(:,:  ) = frcv(jpr_qsrmix)%z3(:,:,1)
1276         qsr_ice(:,:,1) = frcv(jpr_qsrice)%z3(:,:,1)
1277      CASE( 'oce and ice' )
1278         qsr_tot(:,:  ) =  p_frld(:,:) * frcv(jpr_qsroce)%z3(:,:,1)
1279         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN
1280            DO jl=1,jpl
1281               qsr_tot(:,:   ) = qsr_tot(:,:) + a_i(:,:,jl) * frcv(jpr_qsrice)%z3(:,:,jl)   
1282               qsr_ice(:,:,jl) = frcv(jpr_qsrice)%z3(:,:,jl)
1283            ENDDO
1284         ELSE
1285            DO jl=1,jpl
1286               qsr_tot(:,:   ) = qsr_tot(:,:) + zicefr(:,:) * frcv(jpr_qsrice)%z3(:,:,1)
1287               qsr_ice(:,:,jl) = frcv(jpr_qsrice)%z3(:,:,1)
1288            ENDDO
1289         ENDIF
1290      CASE( 'mixed oce-ice' )
1291         qsr_tot(:,:  ) = frcv(jpr_qsrmix)%z3(:,:,1)
1292! ** NEED TO SORT OUT HOW THIS SHOULD WORK IN THE MULTI-CATEGORY CASE - CURRENTLY NOT ALLOWED WHEN INTERFACE INITIALISED **
1293!       Create solar heat flux over ice using incoming solar heat flux and albedos
1294!       ( see OASIS3 user guide, 5th edition, p39 )
1295         qsr_ice(:,:,1) = frcv(jpr_qsrmix)%z3(:,:,1) * ( 1.- palbi(:,:,1) )   &
1296            &            / (  1.- ( albedo_oce_mix(:,:  ) * p_frld(:,:)       &
1297            &                     + palbi         (:,:,1) * zicefr(:,:) ) )
1298      END SELECT
1299      IF( ln_dm2dc ) THEN   ! modify qsr to include the diurnal cycle
1300         qsr_tot(:,:  ) = sbc_dcy( qsr_tot(:,:  ) )
1301         DO jl=1,jpl
1302            qsr_ice(:,:,jl) = sbc_dcy( qsr_ice(:,:,jl) )
1303         ENDDO
1304      ENDIF
1305
1306      SELECT CASE( TRIM( sn_rcv_dqnsdt%cldes ) )
1307      CASE ('coupled')
1308         IF ( TRIM(sn_rcv_dqnsdt%clcat) == 'yes' ) THEN
1309            dqns_ice(:,:,1:jpl) = frcv(jpr_dqnsdt)%z3(:,:,1:jpl)
1310         ELSE
1311            ! Set all category values equal for the moment
1312            DO jl=1,jpl
1313               dqns_ice(:,:,jl) = frcv(jpr_dqnsdt)%z3(:,:,1)
1314            ENDDO
1315         ENDIF
1316      END SELECT
1317
1318      SELECT CASE( TRIM( sn_rcv_iceflx%cldes ) )
1319      CASE ('coupled')
1320         topmelt(:,:,:)=frcv(jpr_topm)%z3(:,:,:)
1321         botmelt(:,:,:)=frcv(jpr_botm)%z3(:,:,:)
1322      END SELECT
1323
1324      CALL wrk_dealloc( jpi,jpj, zcptn, ztmp, zicefr )
1325      !
1326      IF( nn_timing == 1 )  CALL timing_stop('sbc_cpl_ice_flx')
1327      !
1328   END SUBROUTINE sbc_cpl_ice_flx
1329   
1330   
1331   SUBROUTINE sbc_cpl_snd( kt )
1332      !!----------------------------------------------------------------------
1333      !!             ***  ROUTINE sbc_cpl_snd  ***
1334      !!
1335      !! ** Purpose :   provide the ocean-ice informations to the atmosphere
1336      !!
1337      !! ** Method  :   send to the atmosphere through a call to cpl_prism_snd
1338      !!              all the needed fields (as defined in sbc_cpl_init)
1339      !!----------------------------------------------------------------------
1340      INTEGER, INTENT(in) ::   kt
1341      !
1342      INTEGER ::   ji, jj, jl   ! dummy loop indices
1343      INTEGER ::   isec, info   ! local integer
1344      REAL(wp), POINTER, DIMENSION(:,:)   ::   zfr_l, ztmp1, ztmp2, zotx1, zoty1, zotz1, zitx1, zity1, zitz1
1345      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztmp3, ztmp4   
1346      !!----------------------------------------------------------------------
1347      !
1348      IF( nn_timing == 1 )  CALL timing_start('sbc_cpl_snd')
1349      !
1350      CALL wrk_alloc( jpi,jpj, zfr_l, ztmp1, ztmp2, zotx1, zoty1, zotz1, zitx1, zity1, zitz1 )
1351      CALL wrk_alloc( jpi,jpj,jpl, ztmp3, ztmp4 )
1352
1353      isec = ( kt - nit000 ) * NINT(rdttra(1))        ! date of exchanges
1354
1355      zfr_l(:,:) = 1.- fr_i(:,:)
1356
1357      !                                                      ! ------------------------- !
1358      !                                                      !    Surface temperature    !   in Kelvin
1359      !                                                      ! ------------------------- !
1360      IF( ssnd(jps_toce)%laction .OR. ssnd(jps_tice)%laction .OR. ssnd(jps_tmix)%laction ) THEN
1361         SELECT CASE( sn_snd_temp%cldes)
1362         CASE( 'oce only'             )   ;   ztmp1(:,:) =   tsn(:,:,1,jp_tem) + rt0
1363         CASE( 'weighted oce and ice' )   ;   ztmp1(:,:) = ( tsn(:,:,1,jp_tem) + rt0 ) * zfr_l(:,:)   
1364            SELECT CASE( sn_snd_temp%clcat )
1365            CASE( 'yes' )   
1366               ztmp3(:,:,1:jpl) = tn_ice(:,:,1:jpl) * a_i(:,:,1:jpl)
1367            CASE( 'no' )
1368               ztmp3(:,:,:) = 0.0
1369               DO jl=1,jpl
1370                  ztmp3(:,:,1) = ztmp3(:,:,1) + tn_ice(:,:,jl) * a_i(:,:,jl)
1371               ENDDO
1372            CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%clcat' )
1373            END SELECT
1374         CASE( 'mixed oce-ice'        )   
1375            ztmp1(:,:) = ( tsn(:,:,1,1) + rt0 ) * zfr_l(:,:) 
1376            DO jl=1,jpl
1377               ztmp1(:,:) = ztmp1(:,:) + tn_ice(:,:,jl) * a_i(:,:,jl)
1378            ENDDO
1379         CASE default                     ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%cldes' )
1380         END SELECT
1381         IF( ssnd(jps_toce)%laction )   CALL cpl_prism_snd( jps_toce, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info )
1382         IF( ssnd(jps_tice)%laction )   CALL cpl_prism_snd( jps_tice, isec, ztmp3, info )
1383         IF( ssnd(jps_tmix)%laction )   CALL cpl_prism_snd( jps_tmix, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info )
1384      ENDIF
1385      !
1386      !                                                      ! ------------------------- !
1387      !                                                      !           Albedo          !
1388      !                                                      ! ------------------------- !
1389      IF( ssnd(jps_albice)%laction ) THEN                         ! ice
1390         ztmp3(:,:,1:jpl) = alb_ice(:,:,1:jpl) * a_i(:,:,1:jpl)
1391         CALL cpl_prism_snd( jps_albice, isec, ztmp3, info )
1392      ENDIF
1393      IF( ssnd(jps_albmix)%laction ) THEN                         ! mixed ice-ocean
1394         ztmp1(:,:) = albedo_oce_mix(:,:) * zfr_l(:,:)
1395         DO jl=1,jpl
1396            ztmp1(:,:) = ztmp1(:,:) + alb_ice(:,:,jl) * a_i(:,:,jl)
1397         ENDDO
1398         CALL cpl_prism_snd( jps_albmix, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info )
1399      ENDIF
1400      !                                                      ! ------------------------- !
1401      !                                                      !  Ice fraction & Thickness !
1402      !                                                      ! ------------------------- !
1403      ! Send ice fraction field
1404      IF( ssnd(jps_fice)%laction ) THEN
1405         SELECT CASE( sn_snd_thick%clcat )
1406         CASE( 'yes' )   ;   ztmp3(:,:,1:jpl) =  a_i(:,:,1:jpl)
1407         CASE( 'no'  )   ;   ztmp3(:,:,1    ) = fr_i(:,:      )
1408         CASE default    ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%clcat' )
1409         END SELECT
1410         CALL cpl_prism_snd( jps_fice, isec, ztmp3, info )
1411      ENDIF
1412
1413      ! Send ice and snow thickness field
1414      IF( ssnd(jps_hice)%laction .OR. ssnd(jps_hsnw)%laction ) THEN
1415         SELECT CASE( sn_snd_thick%cldes)
1416         CASE( 'none'                  )       ! nothing to do
1417         CASE( 'weighted ice and snow' )   
1418            SELECT CASE( sn_snd_thick%clcat )
1419            CASE( 'yes' )   
1420               ztmp3(:,:,1:jpl) =  ht_i(:,:,1:jpl) * a_i(:,:,1:jpl)
1421               ztmp4(:,:,1:jpl) =  ht_s(:,:,1:jpl) * a_i(:,:,1:jpl)
1422            CASE( 'no' )
1423               ztmp3(:,:,:) = 0.0   ;  ztmp4(:,:,:) = 0.0
1424               DO jl=1,jpl
1425                  ztmp3(:,:,1) = ztmp3(:,:,1) + ht_i(:,:,jl) * a_i(:,:,jl)
1426                  ztmp4(:,:,1) = ztmp4(:,:,1) + ht_s(:,:,jl) * a_i(:,:,jl)
1427               ENDDO
1428            CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%clcat' )
1429            END SELECT
1430         CASE( 'ice and snow'         )   
1431            ztmp3(:,:,1:jpl) = ht_i(:,:,1:jpl)
1432            ztmp4(:,:,1:jpl) = ht_s(:,:,1:jpl)
1433         CASE default                     ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%cldes' )
1434         END SELECT
1435         IF( ssnd(jps_hice)%laction )   CALL cpl_prism_snd( jps_hice, isec, ztmp3, info )
1436         IF( ssnd(jps_hsnw)%laction )   CALL cpl_prism_snd( jps_hsnw, isec, ztmp4, info )
1437      ENDIF
1438      !
1439#if defined key_cpl_carbon_cycle
1440      !                                                      ! ------------------------- !
1441      !                                                      !  CO2 flux from PISCES     !
1442      !                                                      ! ------------------------- !
1443      IF( ssnd(jps_co2)%laction )   CALL cpl_prism_snd( jps_co2, isec, RESHAPE ( oce_co2, (/jpi,jpj,1/) ) , info )
1444      !
1445#endif
1446      !                                                      ! ------------------------- !
1447      IF( ssnd(jps_ocx1)%laction ) THEN                      !      Surface current      !
1448         !                                                   ! ------------------------- !
1449         !   
1450         !                                                  j+1   j     -----V---F
1451         ! surface velocity always sent from T point                     !       |
1452         !                                                        j      |   T   U
1453         !                                                               |       |
1454         !                                                   j    j-1   -I-------|
1455         !                                               (for I)         |       |
1456         !                                                              i-1  i   i
1457         !                                                               i      i+1 (for I)
1458         SELECT CASE( TRIM( sn_snd_crt%cldes ) )
1459         CASE( 'oce only'             )      ! C-grid ==> T
1460            DO jj = 2, jpjm1
1461               DO ji = fs_2, fs_jpim1   ! vector opt.
1462                  zotx1(ji,jj) = 0.5 * ( un(ji,jj,1) + un(ji-1,jj  ,1) )
1463                  zoty1(ji,jj) = 0.5 * ( vn(ji,jj,1) + vn(ji  ,jj-1,1) ) 
1464               END DO
1465            END DO
1466         CASE( 'weighted oce and ice' )   
1467            SELECT CASE ( cp_ice_msh )
1468            CASE( 'C' )                      ! Ocean and Ice on C-grid ==> T
1469               DO jj = 2, jpjm1
1470                  DO ji = fs_2, fs_jpim1   ! vector opt.
1471                     zotx1(ji,jj) = 0.5 * ( un   (ji,jj,1) + un   (ji-1,jj  ,1) ) * zfr_l(ji,jj) 
1472                     zoty1(ji,jj) = 0.5 * ( vn   (ji,jj,1) + vn   (ji  ,jj-1,1) ) * zfr_l(ji,jj)
1473                     zitx1(ji,jj) = 0.5 * ( u_ice(ji,jj  ) + u_ice(ji-1,jj    ) ) *  fr_i(ji,jj)
1474                     zity1(ji,jj) = 0.5 * ( v_ice(ji,jj  ) + v_ice(ji  ,jj-1  ) ) *  fr_i(ji,jj)
1475                  END DO
1476               END DO
1477            CASE( 'I' )                      ! Ocean on C grid, Ice on I-point (B-grid) ==> T
1478               DO jj = 2, jpjm1
1479                  DO ji = 2, jpim1   ! NO vector opt.
1480                     zotx1(ji,jj) = 0.5  * ( un(ji,jj,1)      + un(ji-1,jj  ,1) ) * zfr_l(ji,jj) 
1481                     zoty1(ji,jj) = 0.5  * ( vn(ji,jj,1)      + vn(ji  ,jj-1,1) ) * zfr_l(ji,jj) 
1482                     zitx1(ji,jj) = 0.25 * ( u_ice(ji+1,jj+1) + u_ice(ji,jj+1)                     &
1483                        &                  + u_ice(ji+1,jj  ) + u_ice(ji,jj  )  ) *  fr_i(ji,jj)
1484                     zity1(ji,jj) = 0.25 * ( v_ice(ji+1,jj+1) + v_ice(ji,jj+1)                     &
1485                        &                  + v_ice(ji+1,jj  ) + v_ice(ji,jj  )  ) *  fr_i(ji,jj)
1486                  END DO
1487               END DO
1488            CASE( 'F' )                      ! Ocean on C grid, Ice on F-point (B-grid) ==> T
1489               DO jj = 2, jpjm1
1490                  DO ji = 2, jpim1   ! NO vector opt.
1491                     zotx1(ji,jj) = 0.5  * ( un(ji,jj,1)      + un(ji-1,jj  ,1) ) * zfr_l(ji,jj) 
1492                     zoty1(ji,jj) = 0.5  * ( vn(ji,jj,1)      + vn(ji  ,jj-1,1) ) * zfr_l(ji,jj) 
1493                     zitx1(ji,jj) = 0.25 * ( u_ice(ji-1,jj-1) + u_ice(ji,jj-1)                     &
1494                        &                  + u_ice(ji-1,jj  ) + u_ice(ji,jj  )  ) *  fr_i(ji,jj)
1495                     zity1(ji,jj) = 0.25 * ( v_ice(ji-1,jj-1) + v_ice(ji,jj-1)                     &
1496                        &                  + v_ice(ji-1,jj  ) + v_ice(ji,jj  )  ) *  fr_i(ji,jj)
1497                  END DO
1498               END DO
1499            END SELECT
1500            CALL lbc_lnk( zitx1, 'T', -1. )   ;   CALL lbc_lnk( zity1, 'T', -1. )
1501         CASE( 'mixed oce-ice'        )
1502            SELECT CASE ( cp_ice_msh )
1503            CASE( 'C' )                      ! Ocean and Ice on C-grid ==> T
1504               DO jj = 2, jpjm1
1505                  DO ji = fs_2, fs_jpim1   ! vector opt.
1506                     zotx1(ji,jj) = 0.5 * ( un   (ji,jj,1) + un   (ji-1,jj  ,1) ) * zfr_l(ji,jj)   &
1507                        &         + 0.5 * ( u_ice(ji,jj  ) + u_ice(ji-1,jj    ) ) *  fr_i(ji,jj)
1508                     zoty1(ji,jj) = 0.5 * ( vn   (ji,jj,1) + vn   (ji  ,jj-1,1) ) * zfr_l(ji,jj)   &
1509                        &         + 0.5 * ( v_ice(ji,jj  ) + v_ice(ji  ,jj-1  ) ) *  fr_i(ji,jj)
1510                  END DO
1511               END DO
1512            CASE( 'I' )                      ! Ocean on C grid, Ice on I-point (B-grid) ==> T
1513               DO jj = 2, jpjm1
1514                  DO ji = 2, jpim1   ! NO vector opt.
1515                     zotx1(ji,jj) = 0.5  * ( un(ji,jj,1)      + un(ji-1,jj  ,1) ) * zfr_l(ji,jj)   &   
1516                        &         + 0.25 * ( u_ice(ji+1,jj+1) + u_ice(ji,jj+1)                     &
1517                        &                  + u_ice(ji+1,jj  ) + u_ice(ji,jj  )  ) *  fr_i(ji,jj)
1518                     zoty1(ji,jj) = 0.5  * ( vn(ji,jj,1)      + vn(ji  ,jj-1,1) ) * zfr_l(ji,jj)   & 
1519                        &         + 0.25 * ( v_ice(ji+1,jj+1) + v_ice(ji,jj+1)                     &
1520                        &                  + v_ice(ji+1,jj  ) + v_ice(ji,jj  )  ) *  fr_i(ji,jj)
1521                  END DO
1522               END DO
1523            CASE( 'F' )                      ! Ocean on C grid, Ice on F-point (B-grid) ==> T
1524               DO jj = 2, jpjm1
1525                  DO ji = 2, jpim1   ! NO vector opt.
1526                     zotx1(ji,jj) = 0.5  * ( un(ji,jj,1)      + un(ji-1,jj  ,1) ) * zfr_l(ji,jj)   &   
1527                        &         + 0.25 * ( u_ice(ji-1,jj-1) + u_ice(ji,jj-1)                     &
1528                        &                  + u_ice(ji-1,jj  ) + u_ice(ji,jj  )  ) *  fr_i(ji,jj)
1529                     zoty1(ji,jj) = 0.5  * ( vn(ji,jj,1)      + vn(ji  ,jj-1,1) ) * zfr_l(ji,jj)   & 
1530                        &         + 0.25 * ( v_ice(ji-1,jj-1) + v_ice(ji,jj-1)                     &
1531                        &                  + v_ice(ji-1,jj  ) + v_ice(ji,jj  )  ) *  fr_i(ji,jj)
1532                  END DO
1533               END DO
1534            END SELECT
1535         END SELECT
1536         CALL lbc_lnk( zotx1, ssnd(jps_ocx1)%clgrid, -1. )   ;   CALL lbc_lnk( zoty1, ssnd(jps_ocy1)%clgrid, -1. )
1537         !
1538         !
1539         IF( TRIM( sn_snd_crt%clvor ) == 'eastward-northward' ) THEN             ! Rotation of the components
1540            !                                                                     ! Ocean component
1541            CALL rot_rep( zotx1, zoty1, ssnd(jps_ocx1)%clgrid, 'ij->e', ztmp1 )       ! 1st component
1542            CALL rot_rep( zotx1, zoty1, ssnd(jps_ocx1)%clgrid, 'ij->n', ztmp2 )       ! 2nd component
1543            zotx1(:,:) = ztmp1(:,:)                                                   ! overwrite the components
1544            zoty1(:,:) = ztmp2(:,:)
1545            IF( ssnd(jps_ivx1)%laction ) THEN                                     ! Ice component
1546               CALL rot_rep( zitx1, zity1, ssnd(jps_ivx1)%clgrid, 'ij->e', ztmp1 )    ! 1st component
1547               CALL rot_rep( zitx1, zity1, ssnd(jps_ivx1)%clgrid, 'ij->n', ztmp2 )    ! 2nd component
1548               zitx1(:,:) = ztmp1(:,:)                                                ! overwrite the components
1549               zity1(:,:) = ztmp2(:,:)
1550            ENDIF
1551         ENDIF
1552         !
1553         ! spherical coordinates to cartesian -> 2 components to 3 components
1554         IF( TRIM( sn_snd_crt%clvref ) == 'cartesian' ) THEN
1555            ztmp1(:,:) = zotx1(:,:)                     ! ocean currents
1556            ztmp2(:,:) = zoty1(:,:)
1557            CALL oce2geo ( ztmp1, ztmp2, 'T', zotx1, zoty1, zotz1 )
1558            !
1559            IF( ssnd(jps_ivx1)%laction ) THEN           ! ice velocities
1560               ztmp1(:,:) = zitx1(:,:)
1561               ztmp1(:,:) = zity1(:,:)
1562               CALL oce2geo ( ztmp1, ztmp2, 'T', zitx1, zity1, zitz1 )
1563            ENDIF
1564         ENDIF
1565         !
1566         IF( ssnd(jps_ocx1)%laction )   CALL cpl_prism_snd( jps_ocx1, isec, RESHAPE ( zotx1, (/jpi,jpj,1/) ), info )   ! ocean x current 1st grid
1567         IF( ssnd(jps_ocy1)%laction )   CALL cpl_prism_snd( jps_ocy1, isec, RESHAPE ( zoty1, (/jpi,jpj,1/) ), info )   ! ocean y current 1st grid
1568         IF( ssnd(jps_ocz1)%laction )   CALL cpl_prism_snd( jps_ocz1, isec, RESHAPE ( zotz1, (/jpi,jpj,1/) ), info )   ! ocean z current 1st grid
1569         !
1570         IF( ssnd(jps_ivx1)%laction )   CALL cpl_prism_snd( jps_ivx1, isec, RESHAPE ( zitx1, (/jpi,jpj,1/) ), info )   ! ice   x current 1st grid
1571         IF( ssnd(jps_ivy1)%laction )   CALL cpl_prism_snd( jps_ivy1, isec, RESHAPE ( zity1, (/jpi,jpj,1/) ), info )   ! ice   y current 1st grid
1572         IF( ssnd(jps_ivz1)%laction )   CALL cpl_prism_snd( jps_ivz1, isec, RESHAPE ( zitz1, (/jpi,jpj,1/) ), info )   ! ice   z current 1st grid
1573         !
1574      ENDIF
1575      !
1576      CALL wrk_dealloc( jpi,jpj, zfr_l, ztmp1, ztmp2, zotx1, zoty1, zotz1, zitx1, zity1, zitz1 )
1577      CALL wrk_dealloc( jpi,jpj,jpl, ztmp3, ztmp4 )
1578      !
1579      IF( nn_timing == 1 )  CALL timing_stop('sbc_cpl_snd')
1580      !
1581   END SUBROUTINE sbc_cpl_snd
1582   
1583#else
1584   !!----------------------------------------------------------------------
1585   !!   Dummy module                                            NO coupling
1586   !!----------------------------------------------------------------------
1587   USE par_kind        ! kind definition
1588CONTAINS
1589   SUBROUTINE sbc_cpl_snd( kt )
1590      WRITE(*,*) 'sbc_cpl_snd: You should not have seen this print! error?', kt
1591   END SUBROUTINE sbc_cpl_snd
1592   !
1593   SUBROUTINE sbc_cpl_rcv( kt, k_fsbc, k_ice )     
1594      WRITE(*,*) 'sbc_cpl_snd: You should not have seen this print! error?', kt, k_fsbc, k_ice
1595   END SUBROUTINE sbc_cpl_rcv
1596   !
1597   SUBROUTINE sbc_cpl_ice_tau( p_taui, p_tauj )     
1598      REAL(wp), INTENT(out), DIMENSION(:,:) ::   p_taui   ! i- & j-components of atmos-ice stress [N/m2]
1599      REAL(wp), INTENT(out), DIMENSION(:,:) ::   p_tauj   ! at I-point (B-grid) or U & V-point (C-grid)
1600      p_taui(:,:) = 0.   ;   p_tauj(:,:) = 0. ! stupid definition to avoid warning message when compiling...
1601      WRITE(*,*) 'sbc_cpl_snd: You should not have seen this print! error?'
1602   END SUBROUTINE sbc_cpl_ice_tau
1603   !
1604   SUBROUTINE sbc_cpl_ice_flx( p_frld , palbi   , psst    , pist  )
1605      REAL(wp), INTENT(in   ), DIMENSION(:,:  ) ::   p_frld     ! lead fraction                [0 to 1]
1606      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   palbi   ! ice albedo
1607      REAL(wp), INTENT(in   ), DIMENSION(:,:  ), OPTIONAL ::   psst    ! sea surface temperature      [Celcius]
1608      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   pist    ! ice surface temperature      [Kelvin]
1609      WRITE(*,*) 'sbc_cpl_snd: You should not have seen this print! error?', p_frld(1,1), palbi(1,1,1), psst(1,1), pist(1,1,1) 
1610   END SUBROUTINE sbc_cpl_ice_flx
1611   
1612#endif
1613
1614   !!======================================================================
1615END MODULE sbccpl
Note: See TracBrowser for help on using the repository browser.