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/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/SBC – NEMO

source: NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/SBC/sbcblk.F90 @ 15660

Last change on this file since 15660 was 15540, checked in by sparonuz, 3 years ago

Mixed precision version, tested up to 30 years on ORCA2.

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