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

source: branches/2011/dev_r2802_UKMO8_sbccpl/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 @ 2817

Last change on this file since 2817 was 2817, checked in by charris, 13 years ago

Fixes to 10m wind and CO2 flux following e-mails from Sebastien and Christian.

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