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/2020/dev_r13648_ASINTER-04_laurent_bulk_ice/src/OCE/SBC – NEMO

source: NEMO/branches/2020/dev_r13648_ASINTER-04_laurent_bulk_ice/src/OCE/SBC/sbcblk.F90 @ 13981

Last change on this file since 13981 was 13981, checked in by laurent, 3 years ago

Canceled changes in dynatf.F90, NEW "iom_put-able" "[uv]tau_oce" and "[uv]tau_ice" at T-points!

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