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

source: trunk/NEMO/OPA_SRC/SBC/sbccpl.F90 @ 1742

Last change on this file since 1742 was 1742, checked in by smasson, 14 years ago

sbccpl: bugfix of pqsr_ice + energy due to iceberg melting, see ticket:607

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