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.
sbcblk.F90 in NEMO/branches/2021/ticket2632_r14588_theta_sbcblk/src/OCE/SBC – NEMO

source: NEMO/branches/2021/ticket2632_r14588_theta_sbcblk/src/OCE/SBC/sbcblk.F90 @ 15551

Last change on this file since 15551 was 15551, checked in by gsamson, 3 years ago

last changes on branch; ticket #2632

  • Property svn:keywords set to Id
File size: 81.9 KB
Line 
1MODULE sbcblk
2   !!======================================================================
3   !!                       ***  MODULE  sbcblk  ***
4   !! Ocean forcing:  momentum, heat and freshwater flux formulation
5   !!                         Aerodynamic Bulk Formulas
6   !!                        SUCCESSOR OF "sbcblk_core"
7   !!=====================================================================
8   !! History :  1.0  !  2004-08  (U. Schweckendiek)  Original CORE code
9   !!            2.0  !  2005-04  (L. Brodeau, A.M. Treguier)  improved CORE bulk and its user interface
10   !!            3.0  !  2006-06  (G. Madec)  sbc rewritting
11   !!             -   !  2006-12  (L. Brodeau)  Original code for turb_core
12   !!            3.2  !  2009-04  (B. Lemaire)  Introduce iom_put
13   !!            3.3  !  2010-10  (S. Masson)  add diurnal cycle
14   !!            3.4  !  2011-11  (C. Harris)  Fill arrays required by CICE
15   !!            3.7  !  2014-06  (L. Brodeau)  simplification and optimization of CORE bulk
16   !!            4.0  !  2016-06  (L. Brodeau)  sbcblk_core becomes sbcblk and is not restricted to the CORE algorithm anymore
17   !!                 !                        ==> based on AeroBulk (https://github.com/brodeau/aerobulk/)
18   !!            4.0  !  2016-10  (G. Madec)  introduce a sbc_blk_init routine
19   !!            4.0  !  2016-10  (M. Vancoppenolle)  Introduce conduction flux emulator (M. Vancoppenolle)
20   !!            4.0  !  2019-03  (F. Lemarié & G. Samson)  add ABL compatibility (ln_abl=TRUE)
21   !!            4.2  !  2020-12  (L. Brodeau) Introduction of various air-ice bulk parameterizations + improvements
22   !!----------------------------------------------------------------------
23
24   !!----------------------------------------------------------------------
25   !!   sbc_blk_init  : initialisation of the chosen bulk formulation as ocean surface boundary condition
26   !!   sbc_blk       : bulk formulation as ocean surface boundary condition
27   !!   blk_oce_1     : computes pieces of momentum, heat and freshwater fluxes over ocean for ABL model  (ln_abl=TRUE)
28   !!   blk_oce_2     : finalizes momentum, heat and freshwater fluxes computation over ocean after the ABL step  (ln_abl=TRUE)
29   !!             sea-ice case only :
30   !!   blk_ice_1   : provide the air-ice stress
31   !!   blk_ice_2   : provide the heat and mass fluxes at air-ice interface
32   !!   blk_ice_qcn   : provide ice surface temperature and snow/ice conduction flux (emulating conduction flux)
33   !!----------------------------------------------------------------------
34   USE oce            ! ocean dynamics and tracers
35   USE dom_oce        ! ocean space and time domain
36   USE phycst         ! physical constants
37   USE fldread        ! read input fields
38   USE sbc_oce        ! Surface boundary condition: ocean fields
39   USE cyclone        ! Cyclone 10m wind form trac of cyclone centres
40   USE sbcdcy         ! surface boundary condition: diurnal cycle
41   USE sbcwave , ONLY :   cdn_wave ! wave module
42   USE lib_fortran    ! to use key_nosignedzero and glob_sum
43   !
44#if defined key_si3
45   USE sbc_ice        ! Surface boundary condition: ice fields #LB? ok to be in 'key_si3' ???
46   USE ice     , ONLY :   u_ice, v_ice, jpl, a_i_b, at_i_b, t_su, rn_cnd_s, hfx_err_dif, nn_qtrice
47   USE icevar         ! for CALL ice_var_snwblow
48   USE sbcblk_algo_ice_an05
49   USE sbcblk_algo_ice_lu12
50   USE sbcblk_algo_ice_lg15
51#endif
52   USE sbcblk_algo_ncar     ! => turb_ncar     : NCAR - (formerly known as CORE, Large & Yeager, 2009)
53   USE sbcblk_algo_coare3p0 ! => turb_coare3p0 : COAREv3.0 (Fairall et al. 2003)
54   USE sbcblk_algo_coare3p6 ! => turb_coare3p6 : COAREv3.6 (Fairall et al. 2018 + Edson et al. 2013)
55   USE sbcblk_algo_ecmwf    ! => turb_ecmwf    : ECMWF (IFS cycle 45r1)
56   USE sbcblk_algo_andreas  ! => turb_andreas  : Andreas et al. 2015
57   !
58   USE iom            ! I/O manager library
59   USE in_out_manager ! I/O manager
60   USE lib_mpp        ! distribued memory computing library
61   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
62   USE prtctl         ! Print control
63
64   USE sbc_phy        ! Catalog of functions for physical/meteorological parameters in the marine boundary layer
65
66   IMPLICIT NONE
67   PRIVATE
68
69   PUBLIC   sbc_blk_init  ! called in sbcmod
70   PUBLIC   sbc_blk       ! called in sbcmod
71   PUBLIC   blk_oce_1     ! called in sbcabl
72   PUBLIC   blk_oce_2     ! called in sbcabl
73#if defined key_si3
74   PUBLIC   blk_ice_1     ! routine called in icesbc
75   PUBLIC   blk_ice_2     ! routine called in icesbc
76   PUBLIC   blk_ice_qcn   ! routine called in icesbc
77#endif
78
79   INTEGER , PUBLIC, PARAMETER ::   jp_wndi  =  1   ! index of 10m wind velocity (i-component) (m/s)    at T-point
80   INTEGER , PUBLIC, PARAMETER ::   jp_wndj  =  2   ! index of 10m wind velocity (j-component) (m/s)    at T-point
81   INTEGER , PUBLIC, PARAMETER ::   jp_tair  =  3   ! index of 10m air temperature             (Kelvin)
82   INTEGER , PUBLIC, PARAMETER ::   jp_humi  =  4   ! index of specific humidity               (kg/kg)
83   INTEGER , PUBLIC, PARAMETER ::   jp_qsr   =  5   ! index of solar heat                      (W/m2)
84   INTEGER , PUBLIC, PARAMETER ::   jp_qlw   =  6   ! index of Long wave                       (W/m2)
85   INTEGER , PUBLIC, PARAMETER ::   jp_prec  =  7   ! index of total precipitation (rain+snow) (Kg/m2/s)
86   INTEGER , PUBLIC, PARAMETER ::   jp_snow  =  8   ! index of snow (solid prcipitation)       (kg/m2/s)
87   INTEGER , PUBLIC, PARAMETER ::   jp_slp   =  9   ! index of sea level pressure              (Pa)
88   INTEGER , PUBLIC, PARAMETER ::   jp_uoatm = 10   ! index of surface current (i-component)
89   !                                                !          seen by the atmospheric forcing (m/s) at T-point
90   INTEGER , PUBLIC, PARAMETER ::   jp_voatm = 11   ! index of surface current (j-component)
91   !                                                !          seen by the atmospheric forcing (m/s) at T-point
92   INTEGER , PUBLIC, PARAMETER ::   jp_cc    = 12   ! index of cloud cover                     (-)      range:0-1
93   INTEGER , PUBLIC, PARAMETER ::   jp_hpgi  = 13   ! index of ABL geostrophic wind or hpg (i-component) (m/s) at T-point
94   INTEGER , PUBLIC, PARAMETER ::   jp_hpgj  = 14   ! index of ABL geostrophic wind or hpg (j-component) (m/s) at T-point
95   INTEGER , PUBLIC, PARAMETER ::   jpfld    = 14   ! maximum number of files to read
96
97   ! Warning: keep this structure allocatable for Agrif...
98   TYPE(FLD), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   sf   ! structure of input atmospheric fields (file informations, fields read)
99
100   !                           !!* Namelist namsbc_blk : bulk parameters
101   LOGICAL  ::   ln_NCAR        ! "NCAR"      algorithm   (Large and Yeager 2008)
102   LOGICAL  ::   ln_COARE_3p0   ! "COARE 3.0" algorithm   (Fairall et al. 2003)
103   LOGICAL  ::   ln_COARE_3p6   ! "COARE 3.6" algorithm   (Edson et al. 2013)
104   LOGICAL  ::   ln_ECMWF       ! "ECMWF"     algorithm   (IFS cycle 45r1)
105   LOGICAL  ::   ln_ANDREAS     ! "ANDREAS"   algorithm   (Andreas et al. 2015)
106   !
107   !#LB:
108   LOGICAL  ::   ln_Cx_ice_cst             ! use constant air-ice bulk transfer coefficients (value given in namelist's rn_Cd_i, rn_Ce_i & rn_Ch_i)
109   REAL(wp) ::   rn_Cd_i, rn_Ce_i, rn_Ch_i ! values for  "    "
110   LOGICAL  ::   ln_Cx_ice_AN05            ! air-ice bulk transfer coefficients based on Andreas et al., 2005
111   LOGICAL  ::   ln_Cx_ice_LU12            ! air-ice bulk transfer coefficients based on Lupkes et al., 2012
112   LOGICAL  ::   ln_Cx_ice_LG15            ! air-ice bulk transfer coefficients based on Lupkes & Gryanik, 2015
113   !#LB.
114   !
115   LOGICAL  ::   ln_crt_fbk     ! Add surface current feedback to the wind stress computation  (Renault et al. 2020)
116   REAL(wp) ::   rn_stau_a      ! Alpha and Beta coefficients of Renault et al. 2020, eq. 10: Stau = Alpha * Wnd + Beta
117   REAL(wp) ::   rn_stau_b      !
118   !
119   REAL(wp)         ::   rn_pfac   ! multiplication factor for precipitation
120   REAL(wp), PUBLIC ::   rn_efac   ! multiplication factor for evaporation
121   REAL(wp)         ::   rn_zqt    ! z(q,t) : height of humidity and temperature measurements
122   REAL(wp)         ::   rn_zu     ! z(u)   : height of wind measurements
123   !
124   INTEGER          :: nn_iter_algo   !  Number of iterations in bulk param. algo ("stable ABL + weak wind" requires more)
125
126   REAL(wp),         ALLOCATABLE, DIMENSION(:,:) ::   theta_zu, q_zu                 ! air temp. and spec. hum. at wind speed height (L15 bulk scheme)
127
128#if defined key_si3
129   REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: Cd_ice , Ch_ice , Ce_ice   !#LB transfert coefficients over ice
130   REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: theta_zu_i, q_zu_i         !#LB fixme ! air temp. and spec. hum. over ice at wind speed height (L15 bulk scheme)
131#endif
132
133
134   LOGICAL  ::   ln_skin_cs     ! use the cool-skin (only available in ECMWF and COARE algorithms) !LB
135   LOGICAL  ::   ln_skin_wl     ! use the warm-layer parameterization (only available in ECMWF and COARE algorithms) !LB
136   LOGICAL  ::   ln_humi_sph    ! humidity read in files ("sn_humi") is specific humidity [kg/kg] if .true. !LB
137   LOGICAL  ::   ln_humi_dpt    ! humidity read in files ("sn_humi") is dew-point temperature [K] if .true. !LB
138   LOGICAL  ::   ln_humi_rlh    ! humidity read in files ("sn_humi") is relative humidity     [%] if .true. !LB
139   LOGICAL  ::   ln_tair_pot    ! temperature read in files ("sn_tair") is already potential temperature (not absolute)
140   !
141   INTEGER  ::   nhumi          ! choice of the bulk algorithm
142   !                            ! associated indices:
143   INTEGER, PARAMETER :: np_humi_sph = 1
144   INTEGER, PARAMETER :: np_humi_dpt = 2
145   INTEGER, PARAMETER :: np_humi_rlh = 3
146
147   INTEGER  ::   nblk           ! choice of the bulk algorithm
148   !                            ! associated indices:
149   INTEGER, PARAMETER ::   np_NCAR      = 1   ! "NCAR" algorithm        (Large and Yeager 2008)
150   INTEGER, PARAMETER ::   np_COARE_3p0 = 2   ! "COARE 3.0" algorithm   (Fairall et al. 2003)
151   INTEGER, PARAMETER ::   np_COARE_3p6 = 3   ! "COARE 3.6" algorithm   (Edson et al. 2013)
152   INTEGER, PARAMETER ::   np_ECMWF     = 4   ! "ECMWF" algorithm       (IFS cycle 45r1)
153   INTEGER, PARAMETER ::   np_ANDREAS   = 5   ! "ANDREAS" algorithm       (Andreas et al. 2015)
154
155   !#LB:
156#if defined key_si3
157   ! Same, over sea-ice:
158   INTEGER  ::   nblk_ice           ! choice of the bulk algorithm
159   !                            ! associated indices:
160   INTEGER, PARAMETER ::   np_ice_cst  = 1   ! constant transfer coefficients
161   INTEGER, PARAMETER ::   np_ice_an05 = 2   ! Andreas et al., 2005
162   INTEGER, PARAMETER ::   np_ice_lu12 = 3   ! Lupkes el al., 2012
163   INTEGER, PARAMETER ::   np_ice_lg15 = 4   ! Lupkes & Gryanik, 2015
164#endif
165   !LB.
166
167
168
169   !! * Substitutions
170#  include "do_loop_substitute.h90"
171   !!----------------------------------------------------------------------
172   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
173   !! $Id$
174   !! Software governed by the CeCILL license (see ./LICENSE)
175   !!----------------------------------------------------------------------
176CONTAINS
177
178   INTEGER FUNCTION sbc_blk_alloc()
179      !!-------------------------------------------------------------------
180      !!             ***  ROUTINE sbc_blk_alloc ***
181      !!-------------------------------------------------------------------
182      ALLOCATE( theta_zu(jpi,jpj), q_zu(jpi,jpj),  STAT=sbc_blk_alloc )
183      CALL mpp_sum ( 'sbcblk', sbc_blk_alloc )
184      IF( sbc_blk_alloc /= 0 )   CALL ctl_stop( 'STOP', 'sbc_blk_alloc: failed to allocate arrays' )
185   END FUNCTION sbc_blk_alloc
186
187#if defined key_si3
188   INTEGER FUNCTION sbc_blk_ice_alloc()
189      !!-------------------------------------------------------------------
190      !!             ***  ROUTINE sbc_blk_ice_alloc ***
191      !!-------------------------------------------------------------------
192      ALLOCATE( Cd_ice (jpi,jpj), Ch_ice (jpi,jpj), Ce_ice (jpi,jpj),         &
193         &      theta_zu_i(jpi,jpj), q_zu_i(jpi,jpj),  STAT=sbc_blk_ice_alloc )
194      CALL mpp_sum ( 'sbcblk', sbc_blk_ice_alloc )
195      IF( sbc_blk_ice_alloc /= 0 )   CALL ctl_stop( 'STOP', 'sbc_blk_ice_alloc: failed to allocate arrays' )
196   END FUNCTION sbc_blk_ice_alloc
197#endif
198
199
200   SUBROUTINE sbc_blk_init
201      !!---------------------------------------------------------------------
202      !!                    ***  ROUTINE sbc_blk_init  ***
203      !!
204      !! ** Purpose :   choose and initialize a bulk formulae formulation
205      !!
206      !! ** Method  :
207      !!
208      !!----------------------------------------------------------------------
209      INTEGER  ::   jfpr                  ! dummy loop indice and argument
210      INTEGER  ::   ios, ierror, ioptio   ! Local integer
211      !!
212      CHARACTER(len=100)            ::   cn_dir                ! Root directory for location of atmospheric forcing files
213      TYPE(FLD_N), DIMENSION(jpfld) ::   slf_i                 ! array of namelist informations on the fields to read
214      TYPE(FLD_N) ::   sn_wndi, sn_wndj , sn_humi, sn_qsr      ! informations about the fields to be read
215      TYPE(FLD_N) ::   sn_qlw , sn_tair , sn_prec, sn_snow     !       "                        "
216      TYPE(FLD_N) ::   sn_slp , sn_uoatm, sn_voatm             !       "                        "
217      TYPE(FLD_N) ::   sn_cc, sn_hpgi, sn_hpgj                 !       "                        "
218      INTEGER     ::   ipka                                    ! number of levels in the atmospheric variable
219      NAMELIST/namsbc_blk/ ln_NCAR, ln_COARE_3p0, ln_COARE_3p6, ln_ECMWF, ln_ANDREAS, &   ! bulk algorithm
220         &                 rn_zqt, rn_zu, nn_iter_algo, ln_skin_cs, ln_skin_wl,       &
221         &                 rn_pfac, rn_efac,                                          &
222         &                 ln_crt_fbk, rn_stau_a, rn_stau_b,                          &   ! current feedback
223         &                 ln_humi_sph, ln_humi_dpt, ln_humi_rlh, ln_tair_pot,        &
224         &                 ln_Cx_ice_cst, rn_Cd_i, rn_Ce_i, rn_Ch_i,                  &
225         &                 ln_Cx_ice_AN05, ln_Cx_ice_LU12, ln_Cx_ice_LG15,            &
226         &                 cn_dir,                                                    &
227         &                 sn_wndi, sn_wndj, sn_qsr, sn_qlw ,                         &   ! input fields
228         &                 sn_tair, sn_humi, sn_prec, sn_snow, sn_slp,                &
229         &                 sn_uoatm, sn_voatm, sn_cc, sn_hpgi, sn_hpgj
230
231      ! cool-skin / warm-layer !LB
232      !!---------------------------------------------------------------------
233      !
234      !                                      ! allocate sbc_blk_core array
235      IF( sbc_blk_alloc()     /= 0 )   CALL ctl_stop( 'STOP', 'sbc_blk : unable to allocate standard arrays' )
236      !
237#if defined key_si3
238      IF( sbc_blk_ice_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_blk : unable to allocate standard ice arrays' )
239#endif
240      !
241      !                             !** read bulk namelist
242      READ  ( numnam_ref, namsbc_blk, IOSTAT = ios, ERR = 901)
243901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc_blk in reference namelist' )
244      !
245      READ  ( numnam_cfg, namsbc_blk, IOSTAT = ios, ERR = 902 )
246902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc_blk in configuration namelist' )
247      !
248      IF(lwm) WRITE( numond, namsbc_blk )
249      !
250      !                             !** initialization of the chosen bulk formulae (+ check)
251      !                                   !* select the bulk chosen in the namelist and check the choice
252      ioptio = 0
253      IF( ln_NCAR      ) THEN
254         nblk =  np_NCAR        ;   ioptio = ioptio + 1
255      ENDIF
256      IF( ln_COARE_3p0 ) THEN
257         nblk =  np_COARE_3p0   ;   ioptio = ioptio + 1
258      ENDIF
259      IF( ln_COARE_3p6 ) THEN
260         nblk =  np_COARE_3p6   ;   ioptio = ioptio + 1
261      ENDIF
262      IF( ln_ECMWF     ) THEN
263         nblk =  np_ECMWF       ;   ioptio = ioptio + 1
264      ENDIF
265      IF( ln_ANDREAS     ) THEN
266         nblk =  np_ANDREAS       ;   ioptio = ioptio + 1
267      ENDIF
268      IF( ioptio /= 1 )   CALL ctl_stop( 'sbc_blk_init: Choose one and only one bulk algorithm' )
269
270      !                             !** initialization of the cool-skin / warm-layer parametrization
271      IF( ln_skin_cs .OR. ln_skin_wl ) THEN
272         !! Some namelist sanity tests:
273         IF( ln_NCAR )      &
274            & CALL ctl_stop( 'sbc_blk_init: Cool-skin/warm-layer param. not compatible with NCAR algorithm' )
275         IF( ln_ANDREAS )      &
276            & CALL ctl_stop( 'sbc_blk_init: Cool-skin/warm-layer param. not compatible with ANDREAS algorithm' )
277         !IF( nn_fsbc /= 1 ) &
278         !   & CALL ctl_stop( 'sbc_blk_init: Please set "nn_fsbc" to 1 when using cool-skin/warm-layer param.')
279      END IF
280
281      IF( ln_skin_wl ) THEN
282         !! Check if the frequency of downwelling solar flux input makes sense and if ln_dm2dc=T if it is daily!
283         IF( (sn_qsr%freqh  < 0.).OR.(sn_qsr%freqh  > 24.) ) &
284            & CALL ctl_stop( 'sbc_blk_init: Warm-layer param. (ln_skin_wl) not compatible with freq. of solar flux > daily' )
285         IF( (sn_qsr%freqh == 24.).AND.(.NOT. ln_dm2dc) ) &
286            & CALL ctl_stop( 'sbc_blk_init: Please set ln_dm2dc=T for warm-layer param. (ln_skin_wl) to work properly' )
287      END IF
288
289      ioptio = 0
290      IF( ln_humi_sph ) THEN
291         nhumi =  np_humi_sph    ;   ioptio = ioptio + 1
292      ENDIF
293      IF( ln_humi_dpt ) THEN
294         nhumi =  np_humi_dpt    ;   ioptio = ioptio + 1
295      ENDIF
296      IF( ln_humi_rlh ) THEN
297         nhumi =  np_humi_rlh    ;   ioptio = ioptio + 1
298      ENDIF
299      IF( ioptio /= 1 )   CALL ctl_stop( 'sbc_blk_init: Choose one and only one type of air humidity' )
300      !
301      IF( ln_dm2dc ) THEN                 !* check: diurnal cycle on Qsr
302         IF( sn_qsr%freqh /= 24. )   CALL ctl_stop( 'sbc_blk_init: ln_dm2dc=T only with daily short-wave input' )
303         IF( sn_qsr%ln_tint ) THEN
304            CALL ctl_warn( 'sbc_blk_init: ln_dm2dc=T daily qsr time interpolation done by sbcdcy module',   &
305               &           '              ==> We force time interpolation = .false. for qsr' )
306            sn_qsr%ln_tint = .false.
307         ENDIF
308      ENDIF
309
310#if defined key_si3
311      ioptio = 0
312      IF( ln_Cx_ice_cst ) THEN
313         nblk_ice =  np_ice_cst     ;   ioptio = ioptio + 1
314      ENDIF
315      IF( ln_Cx_ice_AN05 ) THEN
316         nblk_ice =  np_ice_an05   ;   ioptio = ioptio + 1
317      ENDIF
318      IF( ln_Cx_ice_LU12 ) THEN
319         nblk_ice =  np_ice_lu12    ;   ioptio = ioptio + 1
320      ENDIF
321      IF( ln_Cx_ice_LG15 ) THEN
322         nblk_ice =  np_ice_lg15   ;   ioptio = ioptio + 1
323      ENDIF
324      IF( ioptio /= 1 )   CALL ctl_stop( 'sbc_blk_init: Choose one and only one ice-atm bulk algorithm' )
325#endif
326
327
328      !                                   !* set the bulk structure
329      !                                      !- store namelist information in an array
330      !
331      slf_i(jp_wndi ) = sn_wndi    ;   slf_i(jp_wndj ) = sn_wndj
332      slf_i(jp_qsr  ) = sn_qsr     ;   slf_i(jp_qlw  ) = sn_qlw
333      slf_i(jp_tair ) = sn_tair    ;   slf_i(jp_humi ) = sn_humi
334      slf_i(jp_prec ) = sn_prec    ;   slf_i(jp_snow ) = sn_snow
335      slf_i(jp_slp  ) = sn_slp     ;   slf_i(jp_cc   ) = sn_cc
336      slf_i(jp_uoatm) = sn_uoatm   ;   slf_i(jp_voatm) = sn_voatm
337      slf_i(jp_hpgi ) = sn_hpgi    ;   slf_i(jp_hpgj ) = sn_hpgj
338      !
339      IF( .NOT. ln_abl ) THEN   ! force to not use jp_hpgi and jp_hpgj, should already be done in namelist_* but we never know...
340         slf_i(jp_hpgi)%clname = 'NOT USED'
341         slf_i(jp_hpgj)%clname = 'NOT USED'
342      ENDIF
343      !
344      !                                      !- allocate the bulk structure
345      ALLOCATE( sf(jpfld), STAT=ierror )
346      IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_blk_init: unable to allocate sf structure' )
347      !
348      !                                      !- fill the bulk structure with namelist informations
349      CALL fld_fill( sf, slf_i, cn_dir, 'sbc_blk_init', 'surface boundary condition -- bulk formulae', 'namsbc_blk' )
350      sf(jp_wndi )%zsgn = -1._wp   ;   sf(jp_wndj )%zsgn = -1._wp   ! vector field at T point: overwrite default definition of zsgn
351      sf(jp_uoatm)%zsgn = -1._wp   ;   sf(jp_voatm)%zsgn = -1._wp   ! vector field at T point: overwrite default definition of zsgn
352      sf(jp_hpgi )%zsgn = -1._wp   ;   sf(jp_hpgj )%zsgn = -1._wp   ! vector field at T point: overwrite default definition of zsgn
353      !
354      DO jfpr= 1, jpfld
355         !
356         IF(   ln_abl    .AND.                                                      &
357            &    ( jfpr == jp_wndi .OR. jfpr == jp_wndj .OR. jfpr == jp_humi .OR.   &
358            &      jfpr == jp_hpgi .OR. jfpr == jp_hpgj .OR. jfpr == jp_tair     )  ) THEN
359            ipka = jpka   ! ABL: some fields are 3D input
360         ELSE
361            ipka = 1
362         ENDIF
363         !
364         ALLOCATE( sf(jfpr)%fnow(jpi,jpj,ipka) )
365         !
366         IF( TRIM(sf(jfpr)%clrootname) == 'NOT USED' ) THEN    !--  not used field  --!   (only now allocated and set to default)
367            IF(     jfpr == jp_slp ) THEN
368               sf(jfpr)%fnow(:,:,1:ipka) = 101325._wp   ! use standard pressure in Pa
369            ELSEIF( jfpr == jp_prec .OR. jfpr == jp_snow .OR. jfpr == jp_uoatm .OR. jfpr == jp_voatm ) THEN
370               sf(jfpr)%fnow(:,:,1:ipka) = 0._wp        ! no precip or no snow or no surface currents
371            ELSEIF( jfpr == jp_hpgi .OR. jfpr == jp_hpgj ) THEN
372               IF( .NOT. ln_abl ) THEN
373                  DEALLOCATE( sf(jfpr)%fnow )   ! deallocate as not used in this case
374               ELSE
375                  sf(jfpr)%fnow(:,:,1:ipka) = 0._wp
376               ENDIF
377            ELSEIF( jfpr == jp_cc  ) THEN
378               sf(jp_cc)%fnow(:,:,1:ipka) = pp_cldf
379            ELSE
380               WRITE(ctmp1,*) 'sbc_blk_init: no default value defined for field number', jfpr
381               CALL ctl_stop( ctmp1 )
382            ENDIF
383         ELSE                                                  !-- used field  --!
384            IF( sf(jfpr)%ln_tint )   ALLOCATE( sf(jfpr)%fdta(jpi,jpj,ipka,2) )   ! allocate array for temporal interpolation
385            !
386            IF( sf(jfpr)%freqh > 0. .AND. MOD( NINT(3600. * sf(jfpr)%freqh), nn_fsbc * NINT(rn_Dt) ) /= 0 )   &
387         &  CALL ctl_warn( 'sbc_blk_init: sbcmod timestep rn_Dt*nn_fsbc is NOT a submultiple of atmospheric forcing frequency.',   &
388         &                 '               This is not ideal. You should consider changing either rn_Dt or nn_fsbc value...' )
389         ENDIF
390      END DO
391      !
392      IF( ln_abl ) THEN       ! ABL: read 3D fields for wind, temperature, humidity and pressure gradient
393         rn_zqt = ght_abl(2)          ! set the bulk altitude to ABL first level
394         rn_zu  = ght_abl(2)
395         IF(lwp) WRITE(numout,*)
396         IF(lwp) WRITE(numout,*) '   ABL formulation: overwrite rn_zqt & rn_zu with ABL first level altitude'
397      ENDIF
398      !
399      !
400      IF(lwp) THEN                     !** Control print
401         !
402         WRITE(numout,*)                  !* namelist
403         WRITE(numout,*) '   Namelist namsbc_blk (other than data information):'
404         WRITE(numout,*) '      "NCAR"      algorithm   (Large and Yeager 2008)      ln_NCAR      = ', ln_NCAR
405         WRITE(numout,*) '      "COARE 3.0" algorithm   (Fairall et al. 2003)       ln_COARE_3p0 = ', ln_COARE_3p0
406         WRITE(numout,*) '      "COARE 3.6" algorithm (Fairall 2018 + Edson al 2013) ln_COARE_3p6 = ', ln_COARE_3p6
407         WRITE(numout,*) '      "ECMWF"     algorithm   (IFS cycle 45r1)             ln_ECMWF     = ', ln_ECMWF
408         WRITE(numout,*) '      "ANDREAS"   algorithm   (Andreas et al. 2015)       ln_ANDREAS   = ', ln_ANDREAS
409         WRITE(numout,*) '      Air temperature and humidity reference height (m)   rn_zqt       = ', rn_zqt
410         WRITE(numout,*) '      Wind vector reference height (m)                    rn_zu        = ', rn_zu
411         WRITE(numout,*) '      factor applied on precipitation (total & snow)      rn_pfac      = ', rn_pfac
412         WRITE(numout,*) '      factor applied on evaporation                       rn_efac      = ', rn_efac
413         WRITE(numout,*) '         (form absolute (=0) to relative winds(=1))'
414         WRITE(numout,*) '      use surface current feedback on wind stress         ln_crt_fbk   = ', ln_crt_fbk
415         IF(ln_crt_fbk) THEN
416         WRITE(numout,*) '         Renault et al. 2020, eq. 10: Stau = Alpha * Wnd + Beta'
417         WRITE(numout,*) '            Alpha                                         rn_stau_a    = ', rn_stau_a
418         WRITE(numout,*) '            Beta                                          rn_stau_b    = ', rn_stau_b
419         ENDIF
420         !
421         WRITE(numout,*)
422         SELECT CASE( nblk )              !* Print the choice of bulk algorithm
423         CASE( np_NCAR      )   ;   WRITE(numout,*) '   ==>>>   "NCAR" algorithm        (Large and Yeager 2008)'
424         CASE( np_COARE_3p0 )   ;   WRITE(numout,*) '   ==>>>   "COARE 3.0" algorithm   (Fairall et al. 2003)'
425         CASE( np_COARE_3p6 )   ;   WRITE(numout,*) '   ==>>>   "COARE 3.6" algorithm (Fairall 2018+Edson et al. 2013)'
426         CASE( np_ECMWF     )   ;   WRITE(numout,*) '   ==>>>   "ECMWF" algorithm       (IFS cycle 45r1)'
427         CASE( np_ANDREAS   )   ;   WRITE(numout,*) '   ==>>>   "ANDREAS" algorithm (Andreas et al. 2015)'
428         END SELECT
429         !
430         WRITE(numout,*)
431         WRITE(numout,*) '      use cool-skin  parameterization (SSST)  ln_skin_cs  = ', ln_skin_cs
432         WRITE(numout,*) '      use warm-layer parameterization (SSST)  ln_skin_wl  = ', ln_skin_wl
433         !
434         WRITE(numout,*)
435         SELECT CASE( nhumi )              !* Print the choice of air humidity
436         CASE( np_humi_sph )   ;   WRITE(numout,*) '   ==>>>   air humidity is SPECIFIC HUMIDITY     [kg/kg]'
437         CASE( np_humi_dpt )   ;   WRITE(numout,*) '   ==>>>   air humidity is DEW-POINT TEMPERATURE [K]'
438         CASE( np_humi_rlh )   ;   WRITE(numout,*) '   ==>>>   air humidity is RELATIVE HUMIDITY     [%]'
439         END SELECT
440         !
441         !#LB:
442#if defined key_si3
443         IF( nn_ice > 0 ) THEN
444            WRITE(numout,*)
445            WRITE(numout,*) '      use constant ice-atm bulk transfer coeff.           ln_Cx_ice_cst  = ', ln_Cx_ice_cst
446            WRITE(numout,*) '      use ice-atm bulk coeff. from Andreas et al., 2005   ln_Cx_ice_AN05 = ', ln_Cx_ice_AN05
447            WRITE(numout,*) '      use ice-atm bulk coeff. from Lupkes et al., 2012    ln_Cx_ice_LU12 = ', ln_Cx_ice_LU12
448            WRITE(numout,*) '      use ice-atm bulk coeff. from Lupkes & Gryanik, 2015 ln_Cx_ice_LG15 = ', ln_Cx_ice_LG15
449         ENDIF
450         WRITE(numout,*)
451         SELECT CASE( nblk_ice )              !* Print the choice of bulk algorithm
452         CASE( np_ice_cst  )
453            WRITE(numout,*) '   ==>>>   Constant bulk transfer coefficients over sea-ice:'
454            WRITE(numout,*) '      => Cd_ice, Ce_ice, Ch_ice =', REAL(rn_Cd_i,4), REAL(rn_Ce_i,4), REAL(rn_Ch_i,4)
455            IF( (rn_Cd_i<0._wp).OR.(rn_Cd_i>1.E-2_wp).OR.(rn_Ce_i<0._wp).OR.(rn_Ce_i>1.E-2_wp).OR.(rn_Ch_i<0._wp).OR.(rn_Ch_i>1.E-2_wp) ) &
456               & CALL ctl_stop( 'Be realistic in your pick of Cd_ice, Ce_ice & Ch_ice ! (0 < Cx < 1.E-2)')
457         CASE( np_ice_an05 )   ;   WRITE(numout,*) '   ==>>> bulk algo over ice: Andreas et al, 2005'
458         CASE( np_ice_lu12 )   ;   WRITE(numout,*) '   ==>>> bulk algo over ice: Lupkes et al, 2012'
459         CASE( np_ice_lg15 )   ;   WRITE(numout,*) '   ==>>> bulk algo over ice: Lupkes & Gryanik, 2015'
460         END SELECT
461#endif
462         !#LB.
463         !
464      ENDIF
465      !
466   END SUBROUTINE sbc_blk_init
467
468
469   SUBROUTINE sbc_blk( kt )
470      !!---------------------------------------------------------------------
471      !!                    ***  ROUTINE sbc_blk  ***
472      !!
473      !! ** Purpose :   provide at each time step the surface ocean fluxes
474      !!              (momentum, heat, freshwater and runoff)
475      !!
476      !! ** Method  :
477      !!              (1) READ each fluxes in NetCDF files:
478      !!      the wind velocity (i-component) at z=rn_zu  (m/s) at T-point
479      !!      the wind velocity (j-component) at z=rn_zu  (m/s) at T-point
480      !!      the specific humidity           at z=rn_zqt (kg/kg)
481      !!      the air temperature             at z=rn_zqt (Kelvin)
482      !!      the solar heat                              (W/m2)
483      !!      the Long wave                               (W/m2)
484      !!      the total precipitation (rain+snow)         (Kg/m2/s)
485      !!      the snow (solid precipitation)              (kg/m2/s)
486      !!      ABL dynamical forcing (i/j-components of either hpg or geostrophic winds)
487      !!              (2) CALL blk_oce_1 and blk_oce_2
488      !!
489      !!      C A U T I O N : never mask the surface stress fields
490      !!                      the stress is assumed to be in the (i,j) mesh referential
491      !!
492      !! ** Action  :   defined at each time-step at the air-sea interface
493      !!              - utau, vtau  i- and j-component of the wind stress
494      !!              - taum        wind stress module at T-point
495      !!              - wndm        wind speed  module at T-point over free ocean or leads in presence of sea-ice
496      !!              - qns, qsr    non-solar and solar heat fluxes
497      !!              - emp         upward mass flux (evapo. - precip.)
498      !!              - sfx         salt flux due to freezing/melting (non-zero only if ice is present)
499      !!
500      !! ** References :   Large & Yeager, 2004 / Large & Yeager, 2008
501      !!                   Brodeau et al. Ocean Modelling 2010
502      !!----------------------------------------------------------------------
503      INTEGER, INTENT(in) ::   kt   ! ocean time step
504      !!----------------------------------------------------------------------
505      REAL(wp), DIMENSION(jpi,jpj) ::   zssq, zcd_du, zsen, zlat, zevp, zpre, ztheta
506      REAL(wp) :: ztst
507      LOGICAL  :: llerr
508      !!----------------------------------------------------------------------
509      !
510      CALL fld_read( kt, nn_fsbc, sf )             ! input fields provided at the current time-step
511
512      ! Sanity/consistence test on humidity at first time step to detect potential screw-up:
513      IF( kt == nit000 ) THEN
514         ! mean humidity over ocean on proc
515         ztst = glob_sum( 'sbcblk', sf(jp_humi)%fnow(:,:,1) * e1e2t(:,:) * tmask(:,:,1) ) / glob_sum( 'sbcblk', e1e2t(:,:) * tmask(:,:,1) )
516         llerr = .FALSE.
517         SELECT CASE( nhumi )
518         CASE( np_humi_sph ) ! specific humidity => expect: 0. <= something < 0.065 [kg/kg] (0.061 is saturation at 45degC !!!)
519            IF( (ztst <   0._wp) .OR. (ztst > 0.065_wp) )   llerr = .TRUE.
520         CASE( np_humi_dpt ) ! dew-point temperature => expect: 110. <= something < 320. [K]
521            IF( (ztst < 110._wp) .OR. (ztst >  320._wp) )   llerr = .TRUE.
522         CASE( np_humi_rlh ) ! relative humidity => expect: 0. <= something < 100. [%]
523            IF( (ztst <   0._wp) .OR. (ztst >  100._wp) )   llerr = .TRUE.
524         END SELECT
525         IF(llerr) THEN
526            WRITE(ctmp1,'("   Error on mean humidity value: ",f10.5)') ztst
527            CALL ctl_stop( 'STOP', ctmp1, 'Something is wrong with air humidity!!!', &
528               &   ' ==> check the unit in your input files'       , &
529               &   ' ==> check consistence of namelist choice: specific? relative? dew-point?', &
530               &   ' ==> ln_humi_sph -> [kg/kg] | ln_humi_rlh -> [%] | ln_humi_dpt -> [K] !!!' )
531         ENDIF
532         IF(lwp) THEN
533            WRITE(numout,*) ''
534            WRITE(numout,*) ' Global mean humidity at kt = nit000: ', ztst
535            WRITE(numout,*) ' === Sanity/consistence test on air humidity sucessfuly passed! ==='
536            WRITE(numout,*) ''
537         ENDIF
538      ENDIF   !IF( kt == nit000 )
539      !                                            ! compute the surface ocean fluxes using bulk formulea
540      IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN
541
542         ! Specific humidity of air at z=rn_zqt
543         SELECT CASE( nhumi )
544         CASE( np_humi_sph )
545            q_air_zt(:,:) = sf(jp_humi )%fnow(:,:,1)      ! what we read in file is already a spec. humidity!
546         CASE( np_humi_dpt )
547            IF((kt==nit000).AND.lwp) WRITE(numout,*) ' *** sbc_blk() => computing q_air out of dew-point and P !'
548            q_air_zt(:,:) = q_sat( sf(jp_humi )%fnow(:,:,1), sf(jp_slp  )%fnow(:,:,1) )
549         CASE( np_humi_rlh )
550            IF((kt==nit000).AND.lwp) WRITE(numout,*) ' *** sbc_blk() => computing q_air out of RH, t_air and slp !' !LBrm
551            q_air_zt(:,:) = q_air_rh( 0.01_wp*sf(jp_humi )%fnow(:,:,1), &
552               &                      sf(jp_tair )%fnow(:,:,1), sf(jp_slp  )%fnow(:,:,1) ) !#LB: 0.01 => RH is % percent in file
553         END SELECT
554
555         ! Potential temperature of air at z=rn_zqt (most reanalysis products provide absolute temp., not potential temp.)
556         IF( ln_tair_pot ) THEN
557            ! temperature read into file is already potential temperature, do nothing...
558            theta_air_zt(:,:) = sf(jp_tair )%fnow(:,:,1)
559         ELSE
560            ! temperature read into file is ABSOLUTE temperature (that's the case for ECMWF products for example...)
561            IF((kt==nit000).AND.lwp) WRITE(numout,*) ' *** sbc_blk() => air temperature converted from ABSOLUTE to POTENTIAL!'
562            zpre(:,:)         = pres_temp( q_air_zt(:,:), sf(jp_slp)%fnow(:,:,1), rn_zu, pta=sf(jp_tair)%fnow(:,:,1) )
563            theta_air_zt(:,:) = theta_exner( sf(jp_tair)%fnow(:,:,1), zpre(:,:) )
564         ENDIF
565         !
566         CALL blk_oce_1( kt, sf(jp_wndi )%fnow(:,:,1), sf(jp_wndj )%fnow(:,:,1),   &   !   <<= in
567            &                theta_air_zt(:,:), q_air_zt(:,:),                     &   !   <<= in
568            &                sf(jp_slp  )%fnow(:,:,1), sst_m, ssu_m, ssv_m,        &   !   <<= in
569            &                sf(jp_uoatm)%fnow(:,:,1), sf(jp_voatm)%fnow(:,:,1),   &   !   <<= in
570            &                sf(jp_qsr  )%fnow(:,:,1), sf(jp_qlw  )%fnow(:,:,1),   &   !   <<= in (wl/cs)
571            &                tsk_m, zssq, zcd_du, zsen, zlat, zevp )                   !   =>> out
572
573         CALL blk_oce_2(     theta_air_zt(:,:),                                    &   !   <<= in
574            &                sf(jp_qlw  )%fnow(:,:,1), sf(jp_prec )%fnow(:,:,1),   &   !   <<= in
575            &                sf(jp_snow )%fnow(:,:,1), tsk_m,                      &   !   <<= in
576            &                zsen, zlat, zevp )                                        !   <=> in out
577      ENDIF
578      !
579#if defined key_cice
580      IF( MOD( kt - 1, nn_fsbc ) == 0 )   THEN
581         qlw_ice(:,:,1)   = sf(jp_qlw )%fnow(:,:,1)
582         IF( ln_dm2dc ) THEN
583            qsr_ice(:,:,1) = sbc_dcy( sf(jp_qsr)%fnow(:,:,1) )
584         ELSE
585            qsr_ice(:,:,1) =          sf(jp_qsr)%fnow(:,:,1)
586         ENDIF
587         tatm_ice(:,:) = sf(jp_tair)%fnow(:,:,1)    !#LB: should it be POTENTIAL temperature (theta_air_zt) instead ????
588         qatm_ice(:,:) = q_air_zt(:,:)
589         tprecip(:,:)  = sf(jp_prec)%fnow(:,:,1) * rn_pfac
590         sprecip(:,:)  = sf(jp_snow)%fnow(:,:,1) * rn_pfac
591         wndi_ice(:,:) = sf(jp_wndi)%fnow(:,:,1)
592         wndj_ice(:,:) = sf(jp_wndj)%fnow(:,:,1)
593      ENDIF
594#endif
595      !
596   END SUBROUTINE sbc_blk
597
598
599   SUBROUTINE blk_oce_1( kt, pwndi, pwndj, ptair, pqair,         &  ! inp
600      &                      pslp , pst  , pu   , pv,            &  ! inp
601      &                      puatm, pvatm, pdqsr , pdqlw ,       &  ! inp
602      &                      ptsk , pssq , pcd_du, psen, plat, pevp ) ! out
603      !!---------------------------------------------------------------------
604      !!                     ***  ROUTINE blk_oce_1  ***
605      !!
606      !! ** Purpose :   if ln_blk=T, computes surface momentum, heat and freshwater fluxes
607      !!                if ln_abl=T, computes Cd x |U|, Ch x |U|, Ce x |U| for ABL integration
608      !!
609      !! ** Method  :   bulk formulae using atmospheric fields from :
610      !!                if ln_blk=T, atmospheric fields read in sbc_read
611      !!                if ln_abl=T, the ABL model at previous time-step
612      !!
613      !! ** Outputs : - pssq    : surface humidity used to compute latent heat flux (kg/kg)
614      !!              - pcd_du  : Cd x |dU| at T-points  (m/s)
615      !!              - psen    : sensible heat flux (W/m^2)
616      !!              - plat    : latent heat flux   (W/m^2)
617      !!              - pevp    : evaporation        (mm/s) #lolo
618      !!---------------------------------------------------------------------
619      INTEGER , INTENT(in   )                 ::   kt     ! time step index
620      REAL(wp), INTENT(in   ), DIMENSION(:,:) ::   pwndi  ! atmospheric wind at T-point              [m/s]
621      REAL(wp), INTENT(in   ), DIMENSION(:,:) ::   pwndj  ! atmospheric wind at T-point              [m/s]
622      REAL(wp), INTENT(in   ), DIMENSION(:,:) ::   pqair  ! specific humidity at T-points            [kg/kg]
623      REAL(wp), INTENT(in   ), DIMENSION(:,:) ::   ptair  ! potential temperature at T-points        [Kelvin]
624      REAL(wp), INTENT(in   ), DIMENSION(:,:) ::   pslp   ! sea-level pressure                       [Pa]
625      REAL(wp), INTENT(in   ), DIMENSION(:,:) ::   pst    ! surface temperature                      [Celsius]
626      REAL(wp), INTENT(in   ), DIMENSION(:,:) ::   pu     ! surface current at U-point (i-component) [m/s]
627      REAL(wp), INTENT(in   ), DIMENSION(:,:) ::   pv     ! surface current at V-point (j-component) [m/s]
628      REAL(wp), INTENT(in   ), DIMENSION(:,:) ::   puatm  ! surface current seen by the atm at T-point (i-component) [m/s]
629      REAL(wp), INTENT(in   ), DIMENSION(:,:) ::   pvatm  ! surface current seen by the atm at T-point (j-component) [m/s]
630      REAL(wp), INTENT(in   ), DIMENSION(:,:) ::   pdqsr  ! downwelling solar (shortwave) radiation at surface [W/m^2]
631      REAL(wp), INTENT(in   ), DIMENSION(:,:) ::   pdqlw  ! downwelling longwave radiation at surface [W/m^2]
632      REAL(wp), INTENT(  out), DIMENSION(:,:) ::   ptsk   ! skin temp. (or SST if CS & WL not used)  [Celsius]
633      REAL(wp), INTENT(  out), DIMENSION(:,:) ::   pssq   ! specific humidity at pst                 [kg/kg]
634      REAL(wp), INTENT(  out), DIMENSION(:,:) ::   pcd_du
635      REAL(wp), INTENT(  out), DIMENSION(:,:) ::   psen
636      REAL(wp), INTENT(  out), DIMENSION(:,:) ::   plat
637      REAL(wp), INTENT(  out), DIMENSION(:,:) ::   pevp
638      !
639      INTEGER  ::   ji, jj               ! dummy loop indices
640      REAL(wp) ::   zztmp                ! local variable
641      REAL(wp) ::   zstmax, zstau
642#if defined key_cyclone
643      REAL(wp), DIMENSION(jpi,jpj) ::   zwnd_i, zwnd_j    ! wind speed components at T-point
644#endif
645      REAL(wp), DIMENSION(jpi,jpj) ::   ztau_i, ztau_j    ! wind stress components at T-point
646      REAL(wp), DIMENSION(jpi,jpj) ::   zU_zu             ! bulk wind speed at height zu  [m/s]
647      REAL(wp), DIMENSION(jpi,jpj) ::   zcd_oce           ! momentum transfert coefficient over ocean
648      REAL(wp), DIMENSION(jpi,jpj) ::   zch_oce           ! sensible heat transfert coefficient over ocean
649      REAL(wp), DIMENSION(jpi,jpj) ::   zce_oce           ! latent   heat transfert coefficient over ocean
650      REAL(wp), DIMENSION(jpi,jpj) ::   zsspt             ! potential sea-surface temperature [K]
651      REAL(wp), DIMENSION(jpi,jpj) ::   zpre, ztabs       ! air pressure [Pa] & absolute temperature [K]
652      REAL(wp), DIMENSION(jpi,jpj) ::   zztmp1, zztmp2
653      !!---------------------------------------------------------------------
654      !
655      ! local scalars ( place there for vector optimisation purposes)
656      !                           ! Temporary conversion from Celcius to Kelvin (and set minimum value far above 0 K)
657      ptsk(:,:) = pst(:,:) + rt0  ! by default: skin temperature = "bulk SST" (will remain this way if NCAR algorithm used!)
658
659      ! sea surface potential temperature [K]
660      zsspt(:,:) = theta_exner( ptsk(:,:), pslp(:,:) )
661
662      ! --- cloud cover --- !
663      cloud_fra(:,:) = sf(jp_cc)%fnow(:,:,1)
664
665      ! ----------------------------------------------------------------------------- !
666      !      0   Wind components and module at T-point relative to the moving ocean   !
667      ! ----------------------------------------------------------------------------- !
668
669      ! ... components ( U10m - U_oce ) at T-point (unmasked)
670#if defined key_cyclone
671      zwnd_i(:,:) = 0._wp
672      zwnd_j(:,:) = 0._wp
673      CALL wnd_cyc( kt, zwnd_i, zwnd_j )    ! add analytical tropical cyclone (Vincent et al. JGR 2012)
674      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
675         zwnd_i(ji,jj) = pwndi(ji,jj) + zwnd_i(ji,jj)
676         zwnd_j(ji,jj) = pwndj(ji,jj) + zwnd_j(ji,jj)
677         ! ... scalar wind at T-point (not masked)
678         wndm(ji,jj) = SQRT( zwnd_i(ji,jj) * zwnd_i(ji,jj) + zwnd_j(ji,jj) * zwnd_j(ji,jj) )
679      END_2D
680#else
681      ! ... scalar wind module at T-point (not masked)
682      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
683         wndm(ji,jj) = SQRT(  pwndi(ji,jj) * pwndi(ji,jj) + pwndj(ji,jj) * pwndj(ji,jj)  )
684      END_2D
685#endif
686      ! ----------------------------------------------------------------------------- !
687      !      I   Solar FLUX                                                           !
688      ! ----------------------------------------------------------------------------- !
689
690      ! ocean albedo assumed to be constant + modify now Qsr to include the diurnal cycle                    ! Short Wave
691      zztmp = 1. - albo
692      IF( ln_dm2dc ) THEN
693         qsr(:,:) = zztmp * sbc_dcy( pdqsr(:,:) ) * tmask(:,:,1)
694      ELSE
695         qsr(:,:) = zztmp *          pdqsr(:,:)   * tmask(:,:,1)
696      ENDIF
697
698
699      ! ----------------------------------------------------------------------------- !
700      !     II   Turbulent FLUXES                                                     !
701      ! ----------------------------------------------------------------------------- !
702
703      ! specific humidity at SST
704      pssq(:,:) = rdct_qsat_salt * q_sat( ptsk(:,:), pslp(:,:) )
705
706      IF( ln_skin_cs .OR. ln_skin_wl ) THEN
707         !! Backup "bulk SST" and associated spec. hum.
708         zztmp1(:,:) = zsspt(:,:)
709         zztmp2(:,:) = pssq(:,:)
710      ENDIF
711
712      !! Time to call the user-selected bulk parameterization for
713      !!  ==  transfer coefficients  ==!   Cd, Ch, Ce at T-point, and more...
714      SELECT CASE( nblk )
715
716      CASE( np_NCAR      )
717         CALL turb_ncar    (     rn_zqt, rn_zu, zsspt, ptair, pssq, pqair, wndm, &
718            &                zcd_oce, zch_oce, zce_oce, theta_zu, q_zu, zU_zu , &
719            &                nb_iter=nn_iter_algo )
720         !
721      CASE( np_COARE_3p0 )
722         CALL turb_coare3p0( kt, rn_zqt, rn_zu, zsspt, ptair, pssq, pqair, wndm, &
723            &                ln_skin_cs, ln_skin_wl,                            &
724            &                zcd_oce, zch_oce, zce_oce, theta_zu, q_zu, zU_zu,  &
725            &                nb_iter=nn_iter_algo,                              &
726            &                Qsw=qsr(:,:), rad_lw=pdqlw(:,:), slp=pslp(:,:) )
727         !
728      CASE( np_COARE_3p6 )
729         CALL turb_coare3p6( kt, rn_zqt, rn_zu, zsspt, ptair, pssq, pqair, wndm, &
730            &                ln_skin_cs, ln_skin_wl,                            &
731            &                zcd_oce, zch_oce, zce_oce, theta_zu, q_zu, zU_zu,  &
732            &                nb_iter=nn_iter_algo,                              &
733            &                Qsw=qsr(:,:), rad_lw=pdqlw(:,:), slp=pslp(:,:) )
734         !
735      CASE( np_ECMWF     )
736         CALL turb_ecmwf   ( kt, rn_zqt, rn_zu, zsspt, ptair, pssq, pqair, wndm, &
737            &                ln_skin_cs, ln_skin_wl,                            &
738            &                zcd_oce, zch_oce, zce_oce, theta_zu, q_zu, zU_zu,  &
739            &                nb_iter=nn_iter_algo,                              &
740            &                Qsw=qsr(:,:), rad_lw=pdqlw(:,:), slp=pslp(:,:) )
741         !
742      CASE( np_ANDREAS   )
743         CALL turb_andreas (     rn_zqt, rn_zu, zsspt, ptair, pssq, pqair, wndm, &
744            &                zcd_oce, zch_oce, zce_oce, theta_zu, q_zu, zU_zu , &
745            &                nb_iter=nn_iter_algo   )
746         !
747      CASE DEFAULT
748         CALL ctl_stop( 'STOP', 'sbc_oce: non-existing bulk parameterizaton selected' )
749         !
750      END SELECT
751
752      IF( iom_use('Cd_oce') )   CALL iom_put("Cd_oce",   zcd_oce * tmask(:,:,1))
753      IF( iom_use('Ce_oce') )   CALL iom_put("Ce_oce",   zce_oce * tmask(:,:,1))
754      IF( iom_use('Ch_oce') )   CALL iom_put("Ch_oce",   zch_oce * tmask(:,:,1))
755      !! LB: mainly here for debugging purpose:
756      IF( iom_use('theta_zt') ) CALL iom_put("theta_zt", (ptair-rt0) * tmask(:,:,1)) ! potential temperature at z=zt
757      IF( iom_use('q_zt') )     CALL iom_put("q_zt",     pqair       * tmask(:,:,1)) ! specific humidity       "
758      IF( iom_use('theta_zu') ) CALL iom_put("theta_zu", (theta_zu -rt0) * tmask(:,:,1)) ! potential temperature at z=zu
759      IF( iom_use('q_zu') )     CALL iom_put("q_zu",     q_zu        * tmask(:,:,1)) ! specific humidity       "
760      IF( iom_use('ssq') )      CALL iom_put("ssq",      pssq        * tmask(:,:,1)) ! saturation specific humidity at z=0
761      IF( iom_use('wspd_blk') ) CALL iom_put("wspd_blk", zU_zu       * tmask(:,:,1)) ! bulk wind speed at z=zu
762
763      IF( ln_skin_cs .OR. ln_skin_wl ) THEN
764         !! In the presence of sea-ice we forget about the cool-skin/warm-layer update of zsspt, pssq & ptsk:
765         WHERE ( fr_i(:,:) > 0.001_wp )
766            ! sea-ice present, we forget about the update, using what we backed up before call to turb_*()
767            zsspt(:,:) = zztmp1(:,:)
768            pssq(:,:)  = zztmp2(:,:)
769         END WHERE
770         ! apply potential temperature increment to abolute SST
771         ptsk(:,:) = ptsk(:,:) + ( zsspt(:,:) - zztmp1(:,:) )
772      END IF
773
774      !  Turbulent fluxes over ocean  => BULK_FORMULA @ sbc_phy.F90
775      ! -------------------------------------------------------------
776
777      IF( ln_abl ) THEN         !==  ABL formulation  ==!   multiplication by rho_air and turbulent fluxes computation done in ablstp
778
779         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
780            zztmp = zU_zu(ji,jj)
781            wndm(ji,jj)   = zztmp                   ! Store zU_zu in wndm to compute ustar2 in ablmod
782            pcd_du(ji,jj) = zztmp * zcd_oce(ji,jj)
783            psen(ji,jj)   = zztmp * zch_oce(ji,jj)
784            pevp(ji,jj)   = zztmp * zce_oce(ji,jj)
785            zpre(ji,jj)   = pres_temp( pqair(ji,jj), pslp(ji,jj), rn_zu, ptpot=ptair(ji,jj), pta=ztabs(ji,jj) )
786            rhoa(ji,jj)   = rho_air( ztabs(ji,jj), pqair(ji,jj), zpre(ji,jj) )
787         END_2D
788
789      ELSE                      !==  BLK formulation  ==!   turbulent fluxes computation
790
791         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
792            zpre(ji,jj) = pres_temp( q_zu(ji,jj), pslp(ji,jj), rn_zu, ptpot=theta_zu(ji,jj), pta=ztabs(ji,jj) )
793            rhoa(ji,jj) = rho_air( ztabs(ji,jj), q_zu(ji,jj), zpre(ji,jj) )
794         END_2D
795
796         CALL BULK_FORMULA( rn_zu, zsspt(:,:), pssq(:,:), theta_zu(:,:), q_zu(:,:), &
797            &               zcd_oce(:,:), zch_oce(:,:), zce_oce(:,:),          &
798            &               wndm(:,:), zU_zu(:,:), pslp(:,:), rhoa(:,:),       &
799            &               taum(:,:), psen(:,:), plat(:,:),                   &
800            &               pEvap=pevp(:,:), pfact_evap=rn_efac )
801
802         psen(:,:) = psen(:,:) * tmask(:,:,1)
803         plat(:,:) = plat(:,:) * tmask(:,:,1)
804         taum(:,:) = taum(:,:) * tmask(:,:,1)
805         pevp(:,:) = pevp(:,:) * tmask(:,:,1)
806
807         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
808            IF( wndm(ji,jj) > 0._wp ) THEN
809              zztmp = taum(ji,jj) / wndm(ji,jj)
810#if defined key_cyclone
811               ztau_i(ji,jj) = zztmp * zwnd_i(ji,jj)
812               ztau_j(ji,jj) = zztmp * zwnd_j(ji,jj)
813#else
814               ztau_i(ji,jj) = zztmp * pwndi(ji,jj)
815               ztau_j(ji,jj) = zztmp * pwndj(ji,jj)
816#endif
817            ELSE
818               ztau_i(ji,jj) = 0._wp
819               ztau_j(ji,jj) = 0._wp
820            ENDIF
821         END_2D
822
823         IF( ln_crt_fbk ) THEN   ! aply eq. 10 and 11 of Renault et al. 2020 (doi: 10.1029/2019MS001715)
824            zstmax = MIN( rn_stau_a * 3._wp + rn_stau_b, 0._wp )   ! set the max value of Stau corresponding to a wind of 3 m/s (<0)
825            DO_2D( 0, 1, 0, 1 )   ! end at jpj and jpi, as ztau_j(ji,jj+1) ztau_i(ji+1,jj) used in the next loop
826               zstau = MIN( rn_stau_a * wndm(ji,jj) + rn_stau_b, zstmax )   ! stau (<0) must be smaller than zstmax
827               ztau_i(ji,jj) = ztau_i(ji,jj) + zstau * ( 0.5_wp * ( pu(ji-1,jj  ) + pu(ji,jj) ) - puatm(ji,jj) )
828               ztau_j(ji,jj) = ztau_j(ji,jj) + zstau * ( 0.5_wp * ( pv(ji  ,jj-1) + pv(ji,jj) ) - pvatm(ji,jj) )
829               taum(ji,jj) = SQRT( ztau_i(ji,jj) * ztau_i(ji,jj) + ztau_j(ji,jj) * ztau_j(ji,jj) )
830            END_2D
831         ENDIF
832
833         ! ... utau, vtau at U- and V_points, resp.
834         !     Note the use of 0.5*(2-umask) in order to unmask the stress along coastlines
835         !     Note that coastal wind stress is not used in the code... so this extra care has no effect
836         DO_2D( 0, 0, 0, 0 )              ! start loop at 2, in case ln_crt_fbk = T
837            utau(ji,jj) = 0.5 * ( 2. - umask(ji,jj,1) ) * ( ztau_i(ji,jj) + ztau_i(ji+1,jj  ) ) &
838               &              * MAX(tmask(ji,jj,1),tmask(ji+1,jj,1))
839            vtau(ji,jj) = 0.5 * ( 2. - vmask(ji,jj,1) ) * ( ztau_j(ji,jj) + ztau_j(ji  ,jj+1) ) &
840               &              * MAX(tmask(ji,jj,1),tmask(ji,jj+1,1))
841         END_2D
842
843         IF( ln_crt_fbk ) THEN
844            CALL lbc_lnk( 'sbcblk', utau, 'U', -1._wp, vtau, 'V', -1._wp, taum, 'T', 1._wp )
845         ELSE
846            CALL lbc_lnk( 'sbcblk', utau, 'U', -1._wp, vtau, 'V', -1._wp )
847         ENDIF
848
849         ! Saving open-ocean wind-stress (module and components) on T-points:
850         CALL iom_put( "taum_oce",   taum(:,:)*tmask(:,:,1) )   ! output wind stress module
851         !#LB: These 2 lines below mostly here for 'STATION_ASF' test-case, otherwize "utau" (U-grid) and vtau" (V-grid) does the job in: [DYN/dynatf.F90])
852         CALL iom_put( "utau_oce", ztau_i(:,:)*tmask(:,:,1) )  ! utau at T-points!
853         CALL iom_put( "vtau_oce", ztau_j(:,:)*tmask(:,:,1) )  ! vtau at T-points!
854
855         IF(sn_cfctl%l_prtctl) THEN
856            CALL prt_ctl( tab2d_1=pssq   , clinfo1=' blk_oce_1: pssq   : ')
857            CALL prt_ctl( tab2d_1=wndm   , clinfo1=' blk_oce_1: wndm   : ')
858            CALL prt_ctl( tab2d_1=utau   , clinfo1=' blk_oce_1: utau   : ', mask1=umask,   &
859               &          tab2d_2=vtau   , clinfo2='            vtau   : ', mask2=vmask )
860            CALL prt_ctl( tab2d_1=zcd_oce, clinfo1=' blk_oce_1: Cd     : ')
861         ENDIF
862         !
863      ENDIF ! ln_blk / ln_abl
864
865      ptsk(:,:) = ( ptsk(:,:) - rt0 ) * tmask(:,:,1)  ! Back to Celsius
866
867      IF( ln_skin_cs .OR. ln_skin_wl ) THEN
868         CALL iom_put( "t_skin" ,  ptsk        )  ! T_skin in Celsius
869         CALL iom_put( "dt_skin" , ptsk - pst  )  ! T_skin - SST temperature difference
870      ENDIF
871      !
872   END SUBROUTINE blk_oce_1
873
874
875   SUBROUTINE blk_oce_2( ptair, pdqlw, pprec, psnow, &   ! <<= in
876      &                   ptsk, psen, plat, pevp     )   ! <<= in
877      !!---------------------------------------------------------------------
878      !!                     ***  ROUTINE blk_oce_2  ***
879      !!
880      !! ** Purpose :   finalize the momentum, heat and freshwater fluxes computation
881      !!                at the ocean surface at each time step knowing Cd, Ch, Ce and
882      !!                atmospheric variables (from ABL or external data)
883      !!
884      !! ** Outputs : - utau    : i-component of the stress at U-point  (N/m2)
885      !!              - vtau    : j-component of the stress at V-point  (N/m2)
886      !!              - taum    : Wind stress module at T-point         (N/m2)
887      !!              - wndm    : Wind speed module at T-point          (m/s)
888      !!              - qsr     : Solar heat flux over the ocean        (W/m2)
889      !!              - qns     : Non Solar heat flux over the ocean    (W/m2)
890      !!              - emp     : evaporation minus precipitation       (kg/m2/s)
891      !!---------------------------------------------------------------------
892      REAL(wp), INTENT(in), DIMENSION(:,:) ::   ptair   ! potential temperature of air #LB: confirm!
893      REAL(wp), INTENT(in), DIMENSION(:,:) ::   pdqlw   ! downwelling longwave radiation at surface [W/m^2]
894      REAL(wp), INTENT(in), DIMENSION(:,:) ::   pprec
895      REAL(wp), INTENT(in), DIMENSION(:,:) ::   psnow
896      REAL(wp), INTENT(in), DIMENSION(:,:) ::   ptsk   ! SKIN surface temperature   [Celsius]
897      REAL(wp), INTENT(in), DIMENSION(:,:) ::   psen
898      REAL(wp), INTENT(in), DIMENSION(:,:) ::   plat
899      REAL(wp), INTENT(in), DIMENSION(:,:) ::   pevp
900      !
901      INTEGER  ::   ji, jj               ! dummy loop indices
902      REAL(wp) ::   zztmp,zz1,zz2,zz3    ! local variable
903      REAL(wp), DIMENSION(jpi,jpj) ::   zqlw              ! net long wave radiative heat flux
904      REAL(wp), DIMENSION(jpi,jpj) ::   zcptrain, zcptsnw, zcptn ! Heat content per unit mass (J/kg)
905      !!---------------------------------------------------------------------
906      !
907      ! Heat content per unit mass (J/kg)
908      zcptrain(:,:) = (      ptair        - rt0 ) * rcp  * tmask(:,:,1)
909      zcptsnw (:,:) = ( MIN( ptair, rt0 ) - rt0 ) * rcpi * tmask(:,:,1)
910      zcptn   (:,:) =        ptsk                 * rcp  * tmask(:,:,1)
911      !
912      ! ----------------------------------------------------------------------------- !
913      !     III    Net longwave radiative FLUX                                        !
914      ! ----------------------------------------------------------------------------- !
915      !! #LB: now moved after Turbulent fluxes because must use the skin temperature rather than bulk SST
916      !! (ptsk is skin temperature if ln_skin_cs==.TRUE. .OR. ln_skin_wl==.TRUE.)
917      zqlw(:,:) = qlw_net( pdqlw(:,:), ptsk(:,:)+rt0 )
918
919      ! ----------------------------------------------------------------------------- !
920      !     IV    Total FLUXES                                                       !
921      ! ----------------------------------------------------------------------------- !
922      !
923      emp (:,:) = ( pevp(:,:) - pprec(:,:) * rn_pfac ) * tmask(:,:,1)      ! mass flux (evap. - precip.)
924      !
925      qns(:,:) = zqlw(:,:) + psen(:,:) + plat(:,:)                     &   ! Downward Non Solar
926         &     - psnow(:,:) * rn_pfac * rLfus                          &   ! remove latent melting heat for solid precip
927         &     - pevp(:,:) * zcptn(:,:)                                &   ! remove evap heat content at SST
928         &     + ( pprec(:,:) - psnow(:,:) ) * rn_pfac * zcptrain(:,:) &   ! add liquid precip heat content at Tair
929         &     + psnow(:,:) * rn_pfac * zcptsnw(:,:)                       ! add solid  precip heat content at min(Tair,Tsnow)
930      qns(:,:) = qns(:,:) * tmask(:,:,1)
931      !
932#if defined key_si3
933      qns_oce(:,:) = zqlw(:,:) + psen(:,:) + plat(:,:)                             ! non solar without emp (only needed by SI3)
934      qsr_oce(:,:) = qsr(:,:)
935#endif
936      !
937      CALL iom_put( "rho_air"  , rhoa*tmask(:,:,1) )       ! output air density [kg/m^3]
938      CALL iom_put( "evap_oce" , pevp )                    ! evaporation
939      CALL iom_put( "qlw_oce"  , zqlw )                    ! output downward longwave heat over the ocean
940      CALL iom_put( "qsb_oce"  , psen )                    ! output downward sensible heat over the ocean
941      CALL iom_put( "qla_oce"  , plat )                    ! output downward latent   heat over the ocean
942      tprecip(:,:) = pprec(:,:) * rn_pfac * tmask(:,:,1)   ! output total precipitation [kg/m2/s]
943      sprecip(:,:) = psnow(:,:) * rn_pfac * tmask(:,:,1)   ! output solid precipitation [kg/m2/s]
944      CALL iom_put( 'snowpre', sprecip )                   ! Snow
945      CALL iom_put( 'precip' , tprecip )                   ! Total precipitation
946      !
947      IF ( nn_ice == 0 ) THEN
948         CALL iom_put( "qemp_oce" , qns-zqlw-psen-plat )   ! output downward heat content of E-P over the ocean
949         CALL iom_put( "qns_oce"  ,   qns  )               ! output downward non solar heat over the ocean
950         CALL iom_put( "qsr_oce"  ,   qsr  )               ! output downward solar heat over the ocean
951         CALL iom_put( "qt_oce"   ,   qns+qsr )            ! output total downward heat over the ocean
952      ENDIF
953      !
954      IF(sn_cfctl%l_prtctl) THEN
955         CALL prt_ctl(tab2d_1=zqlw , clinfo1=' blk_oce_2: zqlw  : ')
956         CALL prt_ctl(tab2d_1=psen , clinfo1=' blk_oce_2: psen  : ' )
957         CALL prt_ctl(tab2d_1=plat , clinfo1=' blk_oce_2: plat  : ' )
958         CALL prt_ctl(tab2d_1=qns  , clinfo1=' blk_oce_2: qns   : ' )
959         CALL prt_ctl(tab2d_1=emp  , clinfo1=' blk_oce_2: emp   : ')
960      ENDIF
961      !
962   END SUBROUTINE blk_oce_2
963
964
965#if defined key_si3
966   !!----------------------------------------------------------------------
967   !!   'key_si3'                                       SI3 sea-ice model
968   !!----------------------------------------------------------------------
969   !!   blk_ice_1   : provide the air-ice stress
970   !!   blk_ice_2   : provide the heat and mass fluxes at air-ice interface
971   !!   blk_ice_qcn : provide ice surface temperature and snow/ice conduction flux (emulating conduction flux)
972   !!----------------------------------------------------------------------
973
974   SUBROUTINE blk_ice_1( pwndi, pwndj, ptair, pqair, pslp , puice, pvice, ptsui,  &   ! inputs
975      &                  putaui, pvtaui, pseni, pevpi, pssqi, pcd_dui             )   ! optional outputs
976      !!---------------------------------------------------------------------
977      !!                     ***  ROUTINE blk_ice_1  ***
978      !!
979      !! ** Purpose :   provide the surface boundary condition over sea-ice
980      !!
981      !! ** Method  :   compute momentum using bulk formulation
982      !!                formulea, ice variables and read atmospheric fields.
983      !!                NB: ice drag coefficient is assumed to be a constant
984      !!---------------------------------------------------------------------
985      REAL(wp) , INTENT(in   ), DIMENSION(:,:  ) ::   pslp    ! sea-level pressure [Pa]
986      REAL(wp) , INTENT(in   ), DIMENSION(:,:  ) ::   pwndi   ! atmospheric wind at T-point [m/s]
987      REAL(wp) , INTENT(in   ), DIMENSION(:,:  ) ::   pwndj   ! atmospheric wind at T-point [m/s]
988      REAL(wp) , INTENT(in   ), DIMENSION(:,:  ) ::   ptair   ! atmospheric potential temperature at T-point [K]
989      REAL(wp) , INTENT(in   ), DIMENSION(:,:  ) ::   pqair   ! atmospheric specific humidity at T-point [kg/kg]
990      REAL(wp) , INTENT(in   ), DIMENSION(:,:  ) ::   puice   ! sea-ice velocity on I or C grid [m/s]
991      REAL(wp) , INTENT(in   ), DIMENSION(:,:  ) ::   pvice   ! "
992      REAL(wp) , INTENT(in   ), DIMENSION(:,:  ) ::   ptsui   ! sea-ice surface temperature [K]
993      REAL(wp) , INTENT(  out), DIMENSION(:,:  ), OPTIONAL ::   putaui  ! if ln_blk
994      REAL(wp) , INTENT(  out), DIMENSION(:,:  ), OPTIONAL ::   pvtaui  ! if ln_blk
995      REAL(wp) , INTENT(  out), DIMENSION(:,:  ), OPTIONAL ::   pseni   ! if ln_abl
996      REAL(wp) , INTENT(  out), DIMENSION(:,:  ), OPTIONAL ::   pevpi   ! if ln_abl
997      REAL(wp) , INTENT(  out), DIMENSION(:,:  ), OPTIONAL ::   pssqi   ! if ln_abl
998      REAL(wp) , INTENT(  out), DIMENSION(:,:  ), OPTIONAL ::   pcd_dui ! if ln_abl
999      !
1000      INTEGER  ::   ji, jj    ! dummy loop indices
1001      REAL(wp) ::   zootm_su                      ! sea-ice surface mean temperature
1002      REAL(wp) ::   zztmp1, zztmp2                ! temporary scalars
1003      REAL(wp), DIMENSION(jpi,jpj) :: ztmp, zsipt ! temporary array
1004      !!---------------------------------------------------------------------
1005      !
1006      ! ------------------------------------------------------------ !
1007      !    Wind module relative to the moving ice ( U10m - U_ice )   !
1008      ! ------------------------------------------------------------ !
1009      ! C-grid ice dynamics :   U & V-points (same as ocean)
1010      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
1011         wndm_ice(ji,jj) = SQRT( pwndi(ji,jj) * pwndi(ji,jj) + pwndj(ji,jj) * pwndj(ji,jj) )
1012      END_2D
1013      !
1014      ! potential sea-ice surface temperature [K]
1015      zsipt(:,:) = theta_exner( ptsui(:,:), pslp(:,:) )
1016
1017      ! sea-ice <-> atmosphere bulk transfer coefficients
1018      SELECT CASE( nblk_ice )
1019
1020      CASE( np_ice_cst      )
1021         ! Constant bulk transfer coefficients over sea-ice:
1022         Cd_ice(:,:) = rn_Cd_i
1023         Ch_ice(:,:) = rn_Ch_i
1024         Ce_ice(:,:) = rn_Ce_i
1025         ! no height adjustment, keeping zt values:
1026         theta_zu_i(:,:) = ptair(:,:)
1027         q_zu_i(:,:)     = pqair(:,:)
1028
1029      CASE( np_ice_an05 )  ! calculate new drag from Lupkes(2015) equations
1030         ztmp(:,:) = q_sat( ptsui(:,:), pslp(:,:), l_ice=.TRUE. ) ! temporary array for SSQ
1031         CALL turb_ice_an05( rn_zqt, rn_zu, zsipt, ptair, ztmp, pqair, wndm_ice,       &
1032            &                      Cd_ice, Ch_ice, Ce_ice, theta_zu_i, q_zu_i )
1033         !!
1034      CASE( np_ice_lu12 )
1035         ztmp(:,:) = q_sat( ptsui(:,:), pslp(:,:), l_ice=.TRUE. ) ! temporary array for SSQ
1036         CALL turb_ice_lu12( rn_zqt, rn_zu, zsipt, ptair, ztmp, pqair, wndm_ice, fr_i, &
1037            &                      Cd_ice, Ch_ice, Ce_ice, theta_zu_i, q_zu_i )
1038         !!
1039      CASE( np_ice_lg15 )  ! calculate new drag from Lupkes(2015) equations
1040         ztmp(:,:) = q_sat( ptsui(:,:), pslp(:,:), l_ice=.TRUE. ) ! temporary array for SSQ
1041         CALL turb_ice_lg15( rn_zqt, rn_zu, zsipt, ptair, ztmp, pqair, wndm_ice, fr_i, &
1042            &                      Cd_ice, Ch_ice, Ce_ice, theta_zu_i, q_zu_i )
1043         !!
1044      END SELECT
1045
1046      IF( iom_use('Cd_ice').OR.iom_use('Ce_ice').OR.iom_use('Ch_ice').OR.iom_use('taum_ice').OR.iom_use('utau_ice').OR.iom_use('vtau_ice') ) &
1047         & ztmp(:,:) = ( 1._wp - MAX(0._wp, SIGN( 1._wp, 1.E-6_wp - fr_i )) )*tmask(:,:,1) ! mask for presence of ice !
1048
1049      IF( iom_use('Cd_ice') ) CALL iom_put("Cd_ice", Cd_ice*ztmp)
1050      IF( iom_use('Ce_ice') ) CALL iom_put("Ce_ice", Ce_ice*ztmp)
1051      IF( iom_use('Ch_ice') ) CALL iom_put("Ch_ice", Ch_ice*ztmp)
1052
1053
1054      IF( ln_blk ) THEN
1055         ! ---------------------------------------------------- !
1056         !    Wind stress relative to nonmoving ice ( U10m )    !
1057         ! ---------------------------------------------------- !
1058         ! supress moving ice in wind stress computation as we don't know how to do it properly...
1059         DO_2D( 0, 1, 0, 1 )    ! at T point
1060            zztmp1        = rhoa(ji,jj) * Cd_ice(ji,jj) * wndm_ice(ji,jj)
1061            putaui(ji,jj) = zztmp1 * pwndi(ji,jj)
1062            pvtaui(ji,jj) = zztmp1 * pwndj(ji,jj)
1063         END_2D
1064
1065         !#LB: saving the module, and x-y components, of the ai wind-stress at T-points: NOT weighted by the ice concentration !!!
1066         IF(iom_use('taum_ice')) CALL iom_put('taum_ice', SQRT( putaui*putaui + pvtaui*pvtaui )*ztmp )
1067         !#LB: These 2 lines below mostly here for 'STATION_ASF' test-case, otherwize "utau_oi" (U-grid) and vtau_oi" (V-grid) does the job in: [ICE/icedyn_rhg_evp.F90])
1068         IF(iom_use('utau_ice')) CALL iom_put("utau_ice", putaui*ztmp)  ! utau at T-points!
1069         IF(iom_use('vtau_ice')) CALL iom_put("vtau_ice", pvtaui*ztmp)  ! vtau at T-points!
1070
1071         !
1072         DO_2D( 0, 0, 0, 0 )    ! U & V-points (same as ocean).
1073            !#LB: QUESTION?? so SI3 expects wind stress vector to be provided at U & V points? Not at T-points ?
1074            ! take care of the land-sea mask to avoid "pollution" of coastal stress. p[uv]taui used in frazil and  rheology
1075            zztmp1 = 0.5_wp * ( 2. - umask(ji,jj,1) ) * MAX( tmask(ji,jj,1),tmask(ji+1,jj  ,1) )
1076            zztmp2 = 0.5_wp * ( 2. - vmask(ji,jj,1) ) * MAX( tmask(ji,jj,1),tmask(ji  ,jj+1,1) )
1077            putaui(ji,jj) = zztmp1 * ( putaui(ji,jj) + putaui(ji+1,jj  ) )
1078            pvtaui(ji,jj) = zztmp2 * ( pvtaui(ji,jj) + pvtaui(ji  ,jj+1) )
1079         END_2D
1080         CALL lbc_lnk( 'sbcblk', putaui, 'U', -1._wp, pvtaui, 'V', -1._wp )
1081         !
1082         IF(sn_cfctl%l_prtctl)  CALL prt_ctl( tab2d_1=putaui  , clinfo1=' blk_ice: putaui : '   &
1083            &                               , tab2d_2=pvtaui  , clinfo2='          pvtaui : ' )
1084      ELSE ! ln_abl
1085
1086         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
1087            pcd_dui(ji,jj) = wndm_ice(ji,jj) * Cd_ice(ji,jj)
1088            pseni  (ji,jj) = wndm_ice(ji,jj) * Ch_ice(ji,jj)
1089            pevpi  (ji,jj) = wndm_ice(ji,jj) * Ce_ice(ji,jj)
1090         END_2D
1091         pssqi(:,:) = q_sat( ptsui(:,:), pslp(:,:), l_ice=.TRUE. ) ; ! more accurate way to obtain ssq !
1092
1093      ENDIF ! ln_blk  / ln_abl
1094      !
1095      IF(sn_cfctl%l_prtctl)  CALL prt_ctl(tab2d_1=wndm_ice  , clinfo1=' blk_ice: wndm_ice : ')
1096      !
1097   END SUBROUTINE blk_ice_1
1098
1099
1100   SUBROUTINE blk_ice_2( ptsu, phs, phi, palb, ptair, pqair, pslp, pdqlw, pprec, psnow  )
1101      !!---------------------------------------------------------------------
1102      !!                     ***  ROUTINE blk_ice_2  ***
1103      !!
1104      !! ** Purpose :   provide the heat and mass fluxes at air-ice interface
1105      !!
1106      !! ** Method  :   compute heat and freshwater exchanged
1107      !!                between atmosphere and sea-ice using bulk formulation
1108      !!                formulea, ice variables and read atmmospheric fields.
1109      !!
1110      !! caution : the net upward water flux has with mm/day unit
1111      !!---------------------------------------------------------------------
1112      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   ptsu   ! sea ice surface temperature [K]
1113      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   phs    ! snow thickness
1114      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   phi    ! ice thickness
1115      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   palb   ! ice albedo (all skies)
1116      REAL(wp), DIMENSION(:,:  ), INTENT(in)  ::   ptair  ! potential temperature of air #LB: okay ???
1117      REAL(wp), DIMENSION(:,:  ), INTENT(in)  ::   pqair  ! specific humidity of air
1118      REAL(wp), DIMENSION(:,:  ), INTENT(in)  ::   pslp
1119      REAL(wp), DIMENSION(:,:  ), INTENT(in)  ::   pdqlw
1120      REAL(wp), DIMENSION(:,:  ), INTENT(in)  ::   pprec
1121      REAL(wp), DIMENSION(:,:  ), INTENT(in)  ::   psnow
1122      !!
1123      INTEGER  ::   ji, jj, jl               ! dummy loop indices
1124      REAL(wp) ::   zst, zst3, zsq, zsipt    ! local variable
1125      REAL(wp) ::   zcoef_dqlw, zcoef_dqla   !   -      -
1126      REAL(wp) ::   zztmp, zzblk, zztmp1, z1_rLsub   !   -      -
1127      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z_qlw         ! long wave heat flux over ice
1128      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z_qsb         ! sensible  heat flux over ice
1129      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z_dqlw        ! long wave heat sensitivity over ice
1130      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z_dqsb        ! sensible  heat sensitivity over ice
1131      REAL(wp), DIMENSION(jpi,jpj)     ::   zevap, zsnw   ! evaporation and snw distribution after wind blowing (SI3)
1132      REAL(wp), DIMENSION(jpi,jpj)     ::   ztmp, ztmp2
1133      REAL(wp), DIMENSION(jpi,jpj)     ::   ztri
1134      REAL(wp), DIMENSION(jpi,jpj)     ::   zcptrain, zcptsnw, zcptn ! Heat content per unit mass (J/kg)
1135      !!---------------------------------------------------------------------
1136      !
1137      zcoef_dqlw = 4._wp * emiss_i * stefan             ! local scalars
1138      zztmp = 1. / ( 1. - albo )
1139      dqla_ice(:,:,:) = 0._wp
1140
1141      ! Heat content per unit mass (J/kg)
1142      zcptrain(:,:) = (      ptair        - rt0 ) * rcp  * tmask(:,:,1)
1143      zcptsnw (:,:) = ( MIN( ptair, rt0 ) - rt0 ) * rcpi * tmask(:,:,1)
1144      zcptn   (:,:) =        sst_m                * rcp  * tmask(:,:,1)
1145      !
1146      !                                     ! ========================== !
1147      DO jl = 1, jpl                        !  Loop over ice categories  !
1148         !                                  ! ========================== !
1149         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
1150
1151            zst   = ptsu(ji,jj,jl)                                ! surface temperature of sea-ice [K]
1152            zsq   = q_sat( zst, pslp(ji,jj), l_ice=.TRUE. )       ! surface saturation specific humidity when ice present
1153            zsipt = theta_exner( zst, pslp(ji,jj) )               ! potential sea-ice surface temperature [K] 
1154
1155            ! ----------------------------!
1156            !      I   Radiative FLUXES   !
1157            ! ----------------------------!
1158            ! Short Wave (sw)
1159            qsr_ice(ji,jj,jl) = zztmp * ( 1. - palb(ji,jj,jl) ) * qsr(ji,jj)
1160
1161            ! Long  Wave (lw)
1162            zst3 = zst * zst * zst
1163            z_qlw(ji,jj,jl)   = emiss_i * ( pdqlw(ji,jj) - stefan * zst * zst3 ) * tmask(ji,jj,1)
1164            ! lw sensitivity
1165            z_dqlw(ji,jj,jl)  = zcoef_dqlw * zst3
1166
1167            ! ----------------------------!
1168            !     II    Turbulent FLUXES  !
1169            ! ----------------------------!
1170
1171            ! ... turbulent heat fluxes with Ch_ice recalculated in blk_ice_1
1172
1173            ! Common term in bulk F. equations...
1174            zzblk = rhoa(ji,jj) * wndm_ice(ji,jj)
1175
1176            ! Sensible Heat
1177            zztmp1 = zzblk * rCp_air * Ch_ice(ji,jj)
1178            z_qsb (ji,jj,jl) = zztmp1 * (zsipt - theta_zu_i(ji,jj))
1179            z_dqsb(ji,jj,jl) = zztmp1                        ! ==> Qsens sensitivity (Dqsb_ice/Dtn_ice)
1180
1181            ! Latent Heat
1182            zztmp1 = zzblk * rLsub * Ce_ice(ji,jj)
1183            qla_ice(ji,jj,jl) = MAX( zztmp1 * (zsq - q_zu_i(ji,jj)) , 0._wp )   ! #LB: only sublimation (and not condensation) ???
1184            IF(qla_ice(ji,jj,jl)>0._wp) dqla_ice(ji,jj,jl) = zztmp1*dq_sat_dt_ice(zst, pslp(ji,jj)) ! ==> Qlat sensitivity  (dQlat/dT)
1185            !                                                                                       !#LB: dq_sat_dt_ice() in "sbc_phy.F90"
1186            !#LB: without this unjustified "condensation sensure":
1187            !qla_ice( ji,jj,jl) = zztmp1 * (zsq - q_zu_i(ji,jj))
1188            !dqla_ice(ji,jj,jl) = zztmp1 * dq_sat_dt_ice(zst, pslp(ji,jj)) ! ==> Qlat sensitivity  (dQlat/dT)
1189
1190
1191            ! ----------------------------!
1192            !     III    Total FLUXES     !
1193            ! ----------------------------!
1194            ! Downward Non Solar flux
1195            qns_ice (ji,jj,jl) =     z_qlw (ji,jj,jl) - z_qsb (ji,jj,jl) - qla_ice (ji,jj,jl)
1196            ! Total non solar heat flux sensitivity for ice
1197            dqns_ice(ji,jj,jl) = - ( z_dqlw(ji,jj,jl) + z_dqsb(ji,jj,jl) + dqla_ice(ji,jj,jl) ) !#LB: correct signs ????
1198
1199         END_2D
1200         !
1201      END DO
1202      !
1203      tprecip(:,:) = pprec(:,:) * rn_pfac * tmask(:,:,1)  ! total precipitation [kg/m2/s]
1204      sprecip(:,:) = psnow(:,:) * rn_pfac * tmask(:,:,1)  ! solid precipitation [kg/m2/s]
1205      CALL iom_put( 'snowpre', sprecip )                  ! Snow precipitation
1206      CALL iom_put( 'precip' , tprecip )                  ! Total precipitation
1207
1208      ! --- evaporation --- !
1209      z1_rLsub = 1._wp / rLsub
1210      evap_ice (:,:,:) = rn_efac * qla_ice (:,:,:) * z1_rLsub    ! sublimation
1211      devap_ice(:,:,:) = rn_efac * dqla_ice(:,:,:) * z1_rLsub    ! d(sublimation)/dT
1212      zevap    (:,:)   = emp(:,:) + tprecip(:,:)   ! evaporation over ocean  !LB: removed rn_efac here, correct???
1213
1214      ! --- evaporation minus precipitation --- !
1215      zsnw(:,:) = 0._wp
1216      CALL ice_var_snwblow( (1.-at_i_b(:,:)), zsnw )  ! snow distribution over ice after wind blowing
1217      emp_oce(:,:) = ( 1._wp - at_i_b(:,:) ) * zevap(:,:) - ( tprecip(:,:) - sprecip(:,:) ) - sprecip(:,:) * (1._wp - zsnw )
1218      emp_ice(:,:) = SUM( a_i_b(:,:,:) * evap_ice(:,:,:), dim=3 ) - sprecip(:,:) * zsnw
1219      emp_tot(:,:) = emp_oce(:,:) + emp_ice(:,:)
1220
1221      ! --- heat flux associated with emp --- !
1222      qemp_oce(:,:) = - ( 1._wp - at_i_b(:,:) ) * zevap(:,:) * zcptn(:,:)         & ! evap at sst
1223         &          + ( tprecip(:,:) - sprecip(:,:) )   *   zcptrain(:,:)         & ! liquid precip at Tair
1224         &          +   sprecip(:,:) * ( 1._wp - zsnw ) * ( zcptsnw (:,:) - rLfus ) ! solid precip at min(Tair,Tsnow)
1225      qemp_ice(:,:) =   sprecip(:,:) *           zsnw   * ( zcptsnw (:,:) - rLfus ) ! solid precip (only)
1226
1227      ! --- total solar and non solar fluxes --- !
1228      qns_tot(:,:) = ( 1._wp - at_i_b(:,:) ) * qns_oce(:,:) + SUM( a_i_b(:,:,:) * qns_ice(:,:,:), dim=3 )  &
1229         &           + qemp_ice(:,:) + qemp_oce(:,:)
1230      qsr_tot(:,:) = ( 1._wp - at_i_b(:,:) ) * qsr_oce(:,:) + SUM( a_i_b(:,:,:) * qsr_ice(:,:,:), dim=3 )
1231
1232      ! --- heat content of precip over ice in J/m3 (to be used in 1D-thermo) --- !
1233      qprec_ice(:,:) = rhos * ( zcptsnw(:,:) - rLfus )
1234
1235      ! --- heat content of evap over ice in W/m2 (to be used in 1D-thermo) ---
1236      DO jl = 1, jpl
1237         qevap_ice(:,:,jl) = 0._wp ! should be -evap_ice(:,:,jl)*( ( Tice - rt0 ) * rcpi * tmask(:,:,1) )
1238         !                         ! But we do not have Tice => consider it at 0degC => evap=0
1239      END DO
1240
1241      ! --- shortwave radiation transmitted thru the surface scattering layer (W/m2) --- !
1242      IF( nn_qtrice == 0 ) THEN
1243         ! formulation derived from Grenfell and Maykut (1977), where transmission rate
1244         !    1) depends on cloudiness
1245         !    2) is 0 when there is any snow
1246         !    3) tends to 1 for thin ice
1247         ztri(:,:) = 0.18 * ( 1.0 - cloud_fra(:,:) ) + 0.35 * cloud_fra(:,:)  ! surface transmission when hi>10cm
1248         DO jl = 1, jpl
1249            WHERE    ( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) <  0.1_wp )     ! linear decrease from hi=0 to 10cm
1250               qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ( ztri(:,:) + ( 1._wp - ztri(:,:) ) * ( 1._wp - phi(:,:,jl) * 10._wp ) )
1251            ELSEWHERE( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) >= 0.1_wp )     ! constant (ztri) when hi>10cm
1252               qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ztri(:,:)
1253            ELSEWHERE                                                         ! zero when hs>0
1254               qtr_ice_top(:,:,jl) = 0._wp
1255            END WHERE
1256         ENDDO
1257      ELSEIF( nn_qtrice == 1 ) THEN
1258         ! formulation is derived from the thesis of M. Lebrun (2019).
1259         !    It represents the best fit using several sets of observations
1260         !    It comes with snow conductivities adapted to freezing/melting conditions (see icethd_zdf_bl99.F90)
1261         qtr_ice_top(:,:,:) = 0.3_wp * qsr_ice(:,:,:)
1262      ENDIF
1263      !
1264      IF( iom_use('evap_ao_cea') .OR. iom_use('hflx_evap_cea') ) THEN
1265         CALL iom_put( 'evap_ao_cea'  , zevap(:,:) * ( 1._wp - at_i_b(:,:) ) * tmask(:,:,1)              )   ! ice-free oce evap (cell average)
1266         CALL iom_put( 'hflx_evap_cea', zevap(:,:) * ( 1._wp - at_i_b(:,:) ) * tmask(:,:,1) * zcptn(:,:) )   ! heat flux from evap (cell average)
1267      ENDIF
1268      IF( iom_use('rain') .OR. iom_use('rain_ao_cea') .OR. iom_use('hflx_rain_cea') ) THEN
1269         CALL iom_put( 'rain'         ,   tprecip(:,:) - sprecip(:,:)                             )          ! liquid precipitation
1270         CALL iom_put( 'rain_ao_cea'  , ( tprecip(:,:) - sprecip(:,:) ) * ( 1._wp - at_i_b(:,:) ) )          ! liquid precipitation over ocean (cell average)
1271         CALL iom_put( 'hflx_rain_cea', ( tprecip(:,:) - sprecip(:,:) ) * zcptrain(:,:) )                    ! heat flux from rain (cell average)
1272      ENDIF
1273      IF(  iom_use('snow_ao_cea')   .OR. iom_use('snow_ai_cea')      .OR. &
1274         & iom_use('hflx_snow_cea') .OR. iom_use('hflx_snow_ao_cea') .OR. iom_use('hflx_snow_ai_cea')  )  THEN
1275         CALL iom_put( 'snow_ao_cea'     , sprecip(:,:)                            * ( 1._wp - zsnw(:,:) ) ) ! Snow over ice-free ocean  (cell average)
1276         CALL iom_put( 'snow_ai_cea'     , sprecip(:,:)                            *           zsnw(:,:)   ) ! Snow over sea-ice         (cell average)
1277         CALL iom_put( 'hflx_snow_cea'   , sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) )                         ! heat flux from snow (cell average)
1278         CALL iom_put( 'hflx_snow_ao_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) * ( 1._wp - zsnw(:,:) ) ) ! heat flux from snow (over ocean)
1279         CALL iom_put( 'hflx_snow_ai_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) *           zsnw(:,:)   ) ! heat flux from snow (over ice)
1280      ENDIF
1281      IF( iom_use('hflx_prec_cea') ) THEN                                                                    ! heat flux from precip (cell average)
1282         CALL iom_put('hflx_prec_cea' ,    sprecip(:,:)                  * ( zcptsnw (:,:) - rLfus )  &
1283            &                          + ( tprecip(:,:) - sprecip(:,:) ) *   zcptrain(:,:) )
1284      ENDIF
1285      IF( iom_use('subl_ai_cea') .OR. iom_use('hflx_subl_cea') ) THEN
1286         CALL iom_put( 'subl_ai_cea'  , SUM( a_i_b(:,:,:) *  evap_ice(:,:,:), dim=3 ) * tmask(:,:,1) ) ! Sublimation over sea-ice (cell average)
1287         CALL iom_put( 'hflx_subl_cea', SUM( a_i_b(:,:,:) * qevap_ice(:,:,:), dim=3 ) * tmask(:,:,1) ) ! Heat flux from sublimation (cell average)
1288      ENDIF
1289      !
1290      IF(sn_cfctl%l_prtctl) THEN
1291         CALL prt_ctl(tab3d_1=qla_ice , clinfo1=' blk_ice: qla_ice  : ', tab3d_2=z_qsb   , clinfo2=' z_qsb    : ', kdim=jpl)
1292         CALL prt_ctl(tab3d_1=z_qlw   , clinfo1=' blk_ice: z_qlw    : ', tab3d_2=dqla_ice, clinfo2=' dqla_ice : ', kdim=jpl)
1293         CALL prt_ctl(tab3d_1=z_dqsb  , clinfo1=' blk_ice: z_dqsb   : ', tab3d_2=z_dqlw  , clinfo2=' z_dqlw   : ', kdim=jpl)
1294         CALL prt_ctl(tab3d_1=dqns_ice, clinfo1=' blk_ice: dqns_ice : ', tab3d_2=qsr_ice , clinfo2=' qsr_ice  : ', kdim=jpl)
1295         CALL prt_ctl(tab3d_1=ptsu    , clinfo1=' blk_ice: ptsu     : ', tab3d_2=qns_ice , clinfo2=' qns_ice  : ', kdim=jpl)
1296         CALL prt_ctl(tab2d_1=tprecip , clinfo1=' blk_ice: tprecip  : ', tab2d_2=sprecip , clinfo2=' sprecip  : ')
1297      ENDIF
1298
1299      !#LB:
1300      ! air-ice heat flux components that are not written from ice_stp()@icestp.F90:
1301      IF( iom_use('qla_ice') )  CALL iom_put( 'qla_ice', SUM( - qla_ice * a_i_b, dim=3 ) ) !#LB: sign consistent with what's done for ocean
1302      IF( iom_use('qsb_ice') )  CALL iom_put( 'qsb_ice', SUM( -   z_qsb * a_i_b, dim=3 ) ) !#LB:     ==> negative => loss of heat for sea-ice
1303      IF( iom_use('qlw_ice') )  CALL iom_put( 'qlw_ice', SUM(     z_qlw * a_i_b, dim=3 ) )
1304      !#LB.
1305
1306   END SUBROUTINE blk_ice_2
1307
1308
1309   SUBROUTINE blk_ice_qcn( ld_virtual_itd, ptsu, ptb, phs, phi )
1310      !!---------------------------------------------------------------------
1311      !!                     ***  ROUTINE blk_ice_qcn  ***
1312      !!
1313      !! ** Purpose :   Compute surface temperature and snow/ice conduction flux
1314      !!                to force sea ice / snow thermodynamics
1315      !!                in the case conduction flux is emulated
1316      !!
1317      !! ** Method  :   compute surface energy balance assuming neglecting heat storage
1318      !!                following the 0-layer Semtner (1976) approach
1319      !!
1320      !! ** Outputs : - ptsu    : sea-ice / snow surface temperature (K)
1321      !!              - qcn_ice : surface inner conduction flux (W/m2)
1322      !!
1323      !!---------------------------------------------------------------------
1324      LOGICAL                   , INTENT(in   ) ::   ld_virtual_itd  ! single-category option
1325      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptsu            ! sea ice / snow surface temperature
1326      REAL(wp), DIMENSION(:,:)  , INTENT(in   ) ::   ptb             ! sea ice base temperature
1327      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   phs             ! snow thickness
1328      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   phi             ! sea ice thickness
1329      !
1330      INTEGER , PARAMETER ::   nit = 10                  ! number of iterations
1331      REAL(wp), PARAMETER ::   zepsilon = 0.1_wp         ! characteristic thickness for enhanced conduction
1332      !
1333      INTEGER  ::   ji, jj, jl           ! dummy loop indices
1334      INTEGER  ::   iter                 ! local integer
1335      REAL(wp) ::   zfac, zfac2, zfac3   ! local scalars
1336      REAL(wp) ::   zkeff_h, ztsu, ztsu0 !
1337      REAL(wp) ::   zqc, zqnet           !
1338      REAL(wp) ::   zhe, zqa0            !
1339      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zgfac   ! enhanced conduction factor
1340      !!---------------------------------------------------------------------
1341
1342      ! -------------------------------------!
1343      !      I   Enhanced conduction factor  !
1344      ! -------------------------------------!
1345      ! Emulates the enhancement of conduction by unresolved thin ice (ld_virtual_itd = T)
1346      ! Fichefet and Morales Maqueda, JGR 1997
1347      !
1348      zgfac(:,:,:) = 1._wp
1349
1350      IF( ld_virtual_itd ) THEN
1351         !
1352         zfac  = 1._wp /  ( rn_cnd_s + rcnd_i )
1353         zfac2 = EXP(1._wp) * 0.5_wp * zepsilon
1354         zfac3 = 2._wp / zepsilon
1355         !
1356         DO jl = 1, jpl
1357            DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
1358               zhe = ( rn_cnd_s * phi(ji,jj,jl) + rcnd_i * phs(ji,jj,jl) ) * zfac                            ! Effective thickness
1359               IF( zhe >=  zfac2 )   zgfac(ji,jj,jl) = MIN( 2._wp, 0.5_wp * ( 1._wp + LOG( zhe * zfac3 ) ) ) ! Enhanced conduction factor
1360            END_2D
1361         END DO
1362         !
1363      ENDIF
1364
1365      ! -------------------------------------------------------------!
1366      !      II   Surface temperature and conduction flux            !
1367      ! -------------------------------------------------------------!
1368      !
1369      zfac = rcnd_i * rn_cnd_s
1370      !
1371      DO jl = 1, jpl
1372         DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
1373            !
1374            zkeff_h = zfac * zgfac(ji,jj,jl) / &                                    ! Effective conductivity of the snow-ice system divided by thickness
1375               &      ( rcnd_i * phs(ji,jj,jl) + rn_cnd_s * MAX( 0.01, phi(ji,jj,jl) ) )
1376            ztsu    = ptsu(ji,jj,jl)                                                ! Store current iteration temperature
1377            ztsu0   = ptsu(ji,jj,jl)                                                ! Store initial surface temperature
1378            zqa0    = qsr_ice(ji,jj,jl) - qtr_ice_top(ji,jj,jl) + qns_ice(ji,jj,jl) ! Net initial atmospheric heat flux
1379            !
1380            DO iter = 1, nit     ! --- Iterative loop
1381               zqc   = zkeff_h * ( ztsu - ptb(ji,jj) )                              ! Conduction heat flux through snow-ice system (>0 downwards)
1382               zqnet = zqa0 + dqns_ice(ji,jj,jl) * ( ztsu - ptsu(ji,jj,jl) ) - zqc  ! Surface energy budget
1383               ztsu  = ztsu - zqnet / ( dqns_ice(ji,jj,jl) - zkeff_h )              ! Temperature update
1384            END DO
1385            !
1386            ptsu   (ji,jj,jl) = MIN( rt0, ztsu )
1387            qcn_ice(ji,jj,jl) = zkeff_h * ( ptsu(ji,jj,jl) - ptb(ji,jj) )
1388            qns_ice(ji,jj,jl) = qns_ice(ji,jj,jl) + dqns_ice(ji,jj,jl) * ( ptsu(ji,jj,jl) - ztsu0 )
1389            qml_ice(ji,jj,jl) = ( qsr_ice(ji,jj,jl) - qtr_ice_top(ji,jj,jl) + qns_ice(ji,jj,jl) - qcn_ice(ji,jj,jl) )  &
1390               &   * MAX( 0._wp , SIGN( 1._wp, ptsu(ji,jj,jl) - rt0 ) )
1391
1392            ! --- Diagnose the heat loss due to changing non-solar flux (as in icethd_zdf_bl99) --- !
1393            hfx_err_dif(ji,jj) = hfx_err_dif(ji,jj) - ( dqns_ice(ji,jj,jl) * ( ptsu(ji,jj,jl) - ztsu0 ) ) * a_i_b(ji,jj,jl)
1394
1395         END_2D
1396         !
1397      END DO
1398      !
1399   END SUBROUTINE blk_ice_qcn
1400
1401#endif
1402
1403   !!======================================================================
1404END MODULE sbcblk
Note: See TracBrowser for help on using the repository browser.