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/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC – NEMO

source: NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC/sbcblk.F90 @ 11804

Last change on this file since 11804 was 11804, checked in by laurent, 5 years ago

Use of "TURB_FLUXES@…" inside sbcblk.F90, positive latent HF & positive cool-skin temperature now allowed!

  • Property svn:keywords set to Id
File size: 70.7 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   !!----------------------------------------------------------------------
21
22   !!----------------------------------------------------------------------
23   !!   sbc_blk_init  : initialisation of the chosen bulk formulation as ocean surface boundary condition
24   !!   sbc_blk       : bulk formulation as ocean surface boundary condition
25   !!   blk_oce       : computes momentum, heat and freshwater fluxes over ocean
26   !!             sea-ice case only :
27   !!   blk_ice_tau   : provide the air-ice stress
28   !!   blk_ice_flx   : provide the heat and mass fluxes at air-ice interface
29   !!   blk_ice_qcn   : provide ice surface temperature and snow/ice conduction flux (emulating conduction flux)
30   !!   Cdn10_Lupkes2012 : Lupkes et al. (2012) air-ice drag
31   !!   Cdn10_Lupkes2015 : Lupkes et al. (2015) air-ice drag
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 sbc_ice        ! Surface boundary condition: ice fields
42   USE lib_fortran    ! to use key_nosignedzero
43#if defined key_si3
44   USE ice     , ONLY :   u_ice, v_ice, jpl, a_i_b, at_i_b, t_su, rn_cnd_s, hfx_err_dif
45   USE icethd_dh      ! for CALL ice_thd_snwblow
46#endif
47   USE sbcblk_algo_ncar     ! => turb_ncar     : NCAR - CORE (Large & Yeager, 2009)
48   USE sbcblk_algo_coare3p0 ! => turb_coare3p0 : COAREv3.0 (Fairall et al. 2003)
49   USE sbcblk_algo_coare3p6 ! => turb_coare3p6 : COAREv3.6 (Fairall et al. 2018 + Edson et al. 2013)
50   USE sbcblk_algo_ecmwf    ! => turb_ecmwf    : ECMWF (IFS cycle 45r1)
51   !
52   USE iom            ! I/O manager library
53   USE in_out_manager ! I/O manager
54   USE lib_mpp        ! distribued memory computing library
55   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
56   USE prtctl         ! Print control
57
58   USE sbcblk_phy     !LB: all thermodynamics functions in the marine boundary layer, rho_air, q_sat, etc...
59
60
61   IMPLICIT NONE
62   PRIVATE
63
64   PUBLIC   sbc_blk_init  ! called in sbcmod
65   PUBLIC   sbc_blk       ! called in sbcmod
66#if defined key_si3
67   PUBLIC   blk_ice_tau   ! routine called in icesbc
68   PUBLIC   blk_ice_flx   ! routine called in icesbc
69   PUBLIC   blk_ice_qcn   ! routine called in icesbc
70#endif
71
72   INTEGER , PARAMETER ::   jpfld   =10           ! maximum number of files to read
73   INTEGER , PARAMETER ::   jp_wndi = 1           ! index of 10m wind velocity (i-component) (m/s)    at T-point
74   INTEGER , PARAMETER ::   jp_wndj = 2           ! index of 10m wind velocity (j-component) (m/s)    at T-point
75   INTEGER , PARAMETER ::   jp_tair = 3           ! index of 10m air temperature             (Kelvin)
76   INTEGER , PARAMETER ::   jp_humi = 4           ! index of specific humidity               ( % )
77   INTEGER , PARAMETER ::   jp_qsr  = 5           ! index of solar heat                      (W/m2)
78   INTEGER , PARAMETER ::   jp_qlw  = 6           ! index of Long wave                       (W/m2)
79   INTEGER , PARAMETER ::   jp_prec = 7           ! index of total precipitation (rain+snow) (Kg/m2/s)
80   INTEGER , PARAMETER ::   jp_snow = 8           ! index of snow (solid prcipitation)       (kg/m2/s)
81   INTEGER , PARAMETER ::   jp_slp  = 9           ! index of sea level pressure              (Pa)
82   INTEGER , PARAMETER ::   jp_tdif =10           ! index of tau diff associated to HF tau   (N/m2)   at T-point
83
84   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf   ! structure of input fields (file informations, fields read)
85
86   !                           !!* Namelist namsbc_blk : bulk parameters
87   LOGICAL  ::   ln_NCAR        ! "NCAR"      algorithm   (Large and Yeager 2008)
88   LOGICAL  ::   ln_COARE_3p0   ! "COARE 3.0" algorithm   (Fairall et al. 2003)
89   LOGICAL  ::   ln_COARE_3p6   ! "COARE 3.6" algorithm   (Edson et al. 2013)
90   LOGICAL  ::   ln_ECMWF       ! "ECMWF"     algorithm   (IFS cycle 45r1)
91   !
92   LOGICAL  ::   ln_taudif      ! logical flag to use the "mean of stress module - module of mean stress" data
93   REAL(wp) ::   rn_pfac        ! multiplication factor for precipitation
94   REAL(wp) ::   rn_efac        ! multiplication factor for evaporation
95   REAL(wp) ::   rn_vfac        ! multiplication factor for ice/ocean velocity in the calculation of wind stress
96   REAL(wp) ::   rn_zqt         ! z(q,t) : height of humidity and temperature measurements
97   REAL(wp) ::   rn_zu          ! z(u)   : height of wind measurements
98   !!gm ref namelist initialize it so remove the setting to false below
99   LOGICAL  ::   ln_Cd_L12 = .FALSE. !  Modify the drag ice-atm depending on ice concentration (from Lupkes et al. JGR2012)
100   LOGICAL  ::   ln_Cd_L15 = .FALSE. !  Modify the drag ice-atm depending on ice concentration (from Lupkes et al. JGR2015)
101   !
102   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   Cd_atm                    ! transfer coefficient for momentum      (tau)
103   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   Ch_atm                    ! transfer coefficient for sensible heat (Q_sens)
104   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   Ce_atm                    ! tansfert coefficient for evaporation   (Q_lat)
105   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   t_zu                      ! air temperature at wind speed height (needed by Lupkes 2015 bulk scheme)
106   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   q_zu                      ! air spec. hum.  at wind speed height (needed by Lupkes 2015 bulk scheme)
107   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   cdn_oce, chn_oce, cen_oce ! needed by Lupkes 2015 bulk scheme
108
109   !LB:
110   LOGICAL  ::   ln_skin_cs     ! use the cool-skin (only available in ECMWF and COARE algorithms) !LB
111   LOGICAL  ::   ln_skin_wl     ! use the warm-layer parameterization (only available in ECMWF and COARE algorithms) !LB
112   LOGICAL  ::   ln_humi_sph    ! humidity read in files ("sn_humi") is specific humidity [kg/kg] if .true. !LB
113   LOGICAL  ::   ln_humi_dpt    ! humidity read in files ("sn_humi") is dew-point temperature [K] if .true. !LB
114   LOGICAL  ::   ln_humi_rlh    ! humidity read in files ("sn_humi") is relative humidity     [%] if .true. !LB
115   !
116   INTEGER  ::   nhumi          ! choice of the bulk algorithm
117   !                            ! associated indices:
118   INTEGER, PARAMETER :: np_humi_sph = 1
119   INTEGER, PARAMETER :: np_humi_dpt = 2
120   INTEGER, PARAMETER :: np_humi_rlh = 3
121   !LB.
122
123   INTEGER  ::   nblk           ! choice of the bulk algorithm
124   !                            ! associated indices:
125   INTEGER, PARAMETER ::   np_NCAR      = 1   ! "NCAR" algorithm        (Large and Yeager 2008)
126   INTEGER, PARAMETER ::   np_COARE_3p0 = 2   ! "COARE 3.0" algorithm   (Fairall et al. 2003)
127   INTEGER, PARAMETER ::   np_COARE_3p6 = 3   ! "COARE 3.6" algorithm   (Edson et al. 2013)
128   INTEGER, PARAMETER ::   np_ECMWF     = 4   ! "ECMWF" algorithm       (IFS cycle 45r1)
129
130   !! * Substitutions
131#  include "vectopt_loop_substitute.h90"
132   !!----------------------------------------------------------------------
133   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
134   !! $Id$
135   !! Software governed by the CeCILL license (see ./LICENSE)
136   !!----------------------------------------------------------------------
137CONTAINS
138
139   INTEGER FUNCTION sbc_blk_alloc()
140      !!-------------------------------------------------------------------
141      !!             ***  ROUTINE sbc_blk_alloc ***
142      !!-------------------------------------------------------------------
143      ALLOCATE( Cd_atm (jpi,jpj), Ch_atm (jpi,jpj), Ce_atm (jpi,jpj), t_zu(jpi,jpj), q_zu(jpi,jpj), &
144         &      cdn_oce(jpi,jpj), chn_oce(jpi,jpj), cen_oce(jpi,jpj), STAT=sbc_blk_alloc )
145      !
146      CALL mpp_sum ( 'sbcblk', sbc_blk_alloc )
147      IF( sbc_blk_alloc /= 0 )   CALL ctl_stop( 'STOP', 'sbc_blk_alloc: failed to allocate arrays' )
148   END FUNCTION sbc_blk_alloc
149
150   !LB:
151   INTEGER FUNCTION sbc_blk_cswl_alloc()
152      !!-------------------------------------------------------------------
153      !!             ***  ROUTINE sbc_blk_cswl_alloc ***
154      !!-------------------------------------------------------------------
155      !WRITE(numout,*) '*** LB: allocating tsk!'
156      ALLOCATE( tsk(jpi,jpj), STAT=sbc_blk_cswl_alloc )
157      !WRITE(numout,*) '*** LB: done!'
158      CALL mpp_sum ( 'sbcblk', sbc_blk_cswl_alloc )
159      IF( sbc_blk_cswl_alloc /= 0 )   CALL ctl_stop( 'STOP', 'sbc_blk_cswl_alloc: failed to allocate arrays' )
160   END FUNCTION sbc_blk_cswl_alloc
161   !LB.
162
163
164   SUBROUTINE sbc_blk_init
165      !!---------------------------------------------------------------------
166      !!                    ***  ROUTINE sbc_blk_init  ***
167      !!
168      !! ** Purpose :   choose and initialize a bulk formulae formulation
169      !!
170      !! ** Method  :
171      !!
172      !!----------------------------------------------------------------------
173      INTEGER  ::   ifpr, jfld            ! dummy loop indice and argument
174      INTEGER  ::   ios, ierror, ioptio   ! Local integer
175      !!
176      CHARACTER(len=100)            ::   cn_dir                ! Root directory for location of atmospheric forcing files
177      TYPE(FLD_N), DIMENSION(jpfld) ::   slf_i                 ! array of namelist informations on the fields to read
178      TYPE(FLD_N) ::   sn_wndi, sn_wndj, sn_humi, sn_qsr       ! informations about the fields to be read
179      TYPE(FLD_N) ::   sn_qlw , sn_tair, sn_prec, sn_snow      !       "                        "
180      TYPE(FLD_N) ::   sn_slp , sn_tdif                        !       "                        "
181      NAMELIST/namsbc_blk/ sn_wndi, sn_wndj, sn_humi, sn_qsr, sn_qlw ,                &   ! input fields
182         &                 sn_tair, sn_prec, sn_snow, sn_slp, sn_tdif,                &
183         &                 ln_NCAR, ln_COARE_3p0, ln_COARE_3p6, ln_ECMWF,             &   ! bulk algorithm
184         &                 cn_dir , ln_taudif, rn_zqt, rn_zu,                         &
185         &                 rn_pfac, rn_efac, rn_vfac, ln_Cd_L12, ln_Cd_L15,           &
186         &                 ln_skin_cs, ln_skin_wl, ln_humi_sph, ln_humi_dpt, ln_humi_rlh    ! cool-skin / warm-layer !LB
187      !!---------------------------------------------------------------------
188      !
189      !                                      ! allocate sbc_blk_core array
190      IF( sbc_blk_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_blk : unable to allocate standard arrays' )
191      !
192      !                             !** read bulk namelist
193      REWIND( numnam_ref )                !* Namelist namsbc_blk in reference namelist : bulk parameters
194      READ  ( numnam_ref, namsbc_blk, IOSTAT = ios, ERR = 901)
195901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc_blk in reference namelist', lwp )
196      !
197      REWIND( numnam_cfg )                !* Namelist namsbc_blk in configuration namelist : bulk parameters
198      READ  ( numnam_cfg, namsbc_blk, IOSTAT = ios, ERR = 902 )
199902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc_blk in configuration namelist', lwp )
200      !
201      IF(lwm) WRITE( numond, namsbc_blk )
202      !
203      !                             !** initialization of the chosen bulk formulae (+ check)
204      !                                   !* select the bulk chosen in the namelist and check the choice
205      ioptio = 0
206      IF( ln_NCAR      ) THEN
207         nblk =  np_NCAR        ;   ioptio = ioptio + 1
208      ENDIF
209      IF( ln_COARE_3p0 ) THEN
210         nblk =  np_COARE_3p0   ;   ioptio = ioptio + 1
211      ENDIF
212      IF( ln_COARE_3p6 ) THEN
213         nblk =  np_COARE_3p6   ;   ioptio = ioptio + 1
214      ENDIF
215      IF( ln_ECMWF     ) THEN
216         nblk =  np_ECMWF       ;   ioptio = ioptio + 1
217      ENDIF
218      IF( ioptio /= 1 )   CALL ctl_stop( 'sbc_blk_init: Choose one and only one bulk algorithm' )
219
220
221
222      !LB:
223      !                             !** initialization of the cool-skin / warm-layer parametrization
224      IF( ln_skin_cs .OR. ln_skin_wl ) THEN
225         IF ( ln_NCAR ) CALL ctl_stop( 'sbc_blk_init: Cool-skin/warm-layer param. not compatible with NCAR algorithm!' )
226         !                       ! allocate array(s) for cool-skin/warm-layer param.
227         IF( sbc_blk_cswl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_blk : unable to allocate standard arrays' )
228      END IF
229      !
230      ioptio = 0
231      IF( ln_humi_sph ) THEN
232         nhumi =  np_humi_sph    ;   ioptio = ioptio + 1
233      ENDIF
234      IF( ln_humi_dpt ) THEN
235         nhumi =  np_humi_dpt    ;   ioptio = ioptio + 1
236      ENDIF
237      IF( ln_humi_rlh ) THEN
238         nhumi =  np_humi_rlh    ;   ioptio = ioptio + 1
239      ENDIF
240      IF( ioptio /= 1 )   CALL ctl_stop( 'sbc_blk_init: Choose one and only one type of air humidity' )
241      !LB.
242
243      !
244      IF( ln_dm2dc ) THEN                 !* check: diurnal cycle on Qsr
245         IF( sn_qsr%nfreqh /= 24 )   CALL ctl_stop( 'sbc_blk_init: ln_dm2dc=T only with daily short-wave input' )
246         IF( sn_qsr%ln_tint ) THEN
247            CALL ctl_warn( 'sbc_blk_init: ln_dm2dc=T daily qsr time interpolation done by sbcdcy module',   &
248               &           '              ==> We force time interpolation = .false. for qsr' )
249            sn_qsr%ln_tint = .false.
250         ENDIF
251      ENDIF
252      !                                   !* set the bulk structure
253      !                                      !- store namelist information in an array
254      slf_i(jp_wndi) = sn_wndi   ;   slf_i(jp_wndj) = sn_wndj
255      slf_i(jp_qsr ) = sn_qsr    ;   slf_i(jp_qlw ) = sn_qlw
256      slf_i(jp_tair) = sn_tair   ;   slf_i(jp_humi) = sn_humi
257      slf_i(jp_prec) = sn_prec   ;   slf_i(jp_snow) = sn_snow
258      slf_i(jp_slp)  = sn_slp    ;   slf_i(jp_tdif) = sn_tdif
259      !
260      lhftau = ln_taudif                     !- add an extra field if HF stress is used
261      jfld = jpfld - COUNT( (/.NOT.lhftau/) )
262      !
263      !                                      !- allocate the bulk structure
264      ALLOCATE( sf(jfld), STAT=ierror )
265      IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_blk_init: unable to allocate sf structure' )
266      DO ifpr= 1, jfld
267         ALLOCATE( sf(ifpr)%fnow(jpi,jpj,1) )
268         IF( slf_i(ifpr)%ln_tint )   ALLOCATE( sf(ifpr)%fdta(jpi,jpj,1,2) )
269         IF( slf_i(ifpr)%nfreqh > 0. .AND. MOD( 3600. * slf_i(ifpr)%nfreqh , REAL(nn_fsbc) * rdt) /= 0. )   &
270            &  CALL ctl_warn( 'sbc_blk_init: sbcmod timestep rdt*nn_fsbc is NOT a submultiple of atmospheric forcing frequency.',   &
271            &                 '               This is not ideal. You should consider changing either rdt or nn_fsbc value...' )
272
273      END DO
274      !                                      !- fill the bulk structure with namelist informations
275      CALL fld_fill( sf, slf_i, cn_dir, 'sbc_blk_init', 'surface boundary condition -- bulk formulae', 'namsbc_blk' )
276      !
277      IF ( ln_wave ) THEN
278         !Activated wave module but neither drag nor stokes drift activated
279         IF ( .NOT.(ln_cdgw .OR. ln_sdw .OR. ln_tauwoc .OR. ln_stcor ) )   THEN
280            CALL ctl_stop( 'STOP',  'Ask for wave coupling but ln_cdgw=F, ln_sdw=F, ln_tauwoc=F, ln_stcor=F' )
281            !drag coefficient read from wave model definable only with mfs bulk formulae and core
282         ELSEIF (ln_cdgw .AND. .NOT. ln_NCAR )       THEN
283            CALL ctl_stop( 'drag coefficient read from wave model definable only with NCAR and CORE bulk formulae')
284         ELSEIF (ln_stcor .AND. .NOT. ln_sdw)                             THEN
285            CALL ctl_stop( 'Stokes-Coriolis term calculated only if activated Stokes Drift ln_sdw=T')
286         ENDIF
287      ELSE
288         IF ( ln_cdgw .OR. ln_sdw .OR. ln_tauwoc .OR. ln_stcor )                &
289            &   CALL ctl_stop( 'Not Activated Wave Module (ln_wave=F) but asked coupling ',    &
290            &                  'with drag coefficient (ln_cdgw =T) '  ,                        &
291            &                  'or Stokes Drift (ln_sdw=T) ' ,                                 &
292            &                  'or ocean stress modification due to waves (ln_tauwoc=T) ',      &
293            &                  'or Stokes-Coriolis term (ln_stcori=T)'  )
294      ENDIF
295      !
296      !
297      IF(lwp) THEN                     !** Control print
298         !
299         WRITE(numout,*)                  !* namelist
300         WRITE(numout,*) '   Namelist namsbc_blk (other than data information):'
301         WRITE(numout,*) '      "NCAR"      algorithm   (Large and Yeager 2008)     ln_NCAR      = ', ln_NCAR
302         WRITE(numout,*) '      "COARE 3.0" algorithm   (Fairall et al. 2003)       ln_COARE_3p0 = ', ln_COARE_3p0
303         WRITE(numout,*) '      "COARE 3.6" algorithm (Fairall 2018 + Edson al 2013)ln_COARE_3p6 = ', ln_COARE_3p6
304         WRITE(numout,*) '      "ECMWF"     algorithm   (IFS cycle 45r1)            ln_ECMWF     = ', ln_ECMWF
305         WRITE(numout,*) '      add High freq.contribution to the stress module     ln_taudif    = ', ln_taudif
306         WRITE(numout,*) '      Air temperature and humidity reference height (m)   rn_zqt       = ', rn_zqt
307         WRITE(numout,*) '      Wind vector reference height (m)                    rn_zu        = ', rn_zu
308         WRITE(numout,*) '      factor applied on precipitation (total & snow)      rn_pfac      = ', rn_pfac
309         WRITE(numout,*) '      factor applied on evaporation                       rn_efac      = ', rn_efac
310         WRITE(numout,*) '      factor applied on ocean/ice velocity                rn_vfac      = ', rn_vfac
311         WRITE(numout,*) '         (form absolute (=0) to relative winds(=1))'
312         WRITE(numout,*) '      use ice-atm drag from Lupkes2012                    ln_Cd_L12    = ', ln_Cd_L12
313         WRITE(numout,*) '      use ice-atm drag from Lupkes2015                    ln_Cd_L15    = ', ln_Cd_L15
314         !
315         WRITE(numout,*)
316         SELECT CASE( nblk )              !* Print the choice of bulk algorithm
317         CASE( np_NCAR      )   ;   WRITE(numout,*) '   ==>>>   "NCAR" algorithm        (Large and Yeager 2008)'
318         CASE( np_COARE_3p0 )   ;   WRITE(numout,*) '   ==>>>   "COARE 3.0" algorithm   (Fairall et al. 2003)'
319         CASE( np_COARE_3p6 )   ;   WRITE(numout,*) '   ==>>>   "COARE 3.6" algorithm (Fairall 2018+Edson et al. 2013)'
320         CASE( np_ECMWF     )   ;   WRITE(numout,*) '   ==>>>   "ECMWF" algorithm       (IFS cycle 45r1)'
321         END SELECT
322         !
323         WRITE(numout,*)
324         WRITE(numout,*) '      use cool-skin  parameterization (SSST)  ln_skin_cs  = ', ln_skin_cs !LB
325         WRITE(numout,*) '      use warm-layer parameterization (SSST)  ln_skin_wl  = ', ln_skin_wl !LB
326         !
327         !LB:
328         WRITE(numout,*)
329         SELECT CASE( nhumi )              !* Print the choice of air humidity
330         CASE( np_humi_sph )   ;   WRITE(numout,*) '   ==>>>   air humidity is SPECIFIC HUMIDITY     [kg/kg]'
331         CASE( np_humi_dpt )   ;   WRITE(numout,*) '   ==>>>   air humidity is DEW-POINT TEMPERATURE [K]'
332         CASE( np_humi_rlh )   ;   WRITE(numout,*) '   ==>>>   air humidity is RELATIVE HUMIDITY     [%]'
333         END SELECT
334         !LB.
335         !
336      ENDIF
337      !
338   END SUBROUTINE sbc_blk_init
339
340
341   SUBROUTINE sbc_blk( kt )
342      !!---------------------------------------------------------------------
343      !!                    ***  ROUTINE sbc_blk  ***
344      !!
345      !! ** Purpose :   provide at each time step the surface ocean fluxes
346      !!              (momentum, heat, freshwater and runoff)
347      !!
348      !! ** Method  : (1) READ each fluxes in NetCDF files:
349      !!      the 10m wind velocity (i-component) (m/s)    at T-point
350      !!      the 10m wind velocity (j-component) (m/s)    at T-point
351      !!      the 10m or 2m specific humidity     ( % )
352      !!      the solar heat                      (W/m2)
353      !!      the Long wave                       (W/m2)
354      !!      the 10m or 2m air temperature       (Kelvin)
355      !!      the total precipitation (rain+snow) (Kg/m2/s)
356      !!      the snow (solid prcipitation)       (kg/m2/s)
357      !!      the tau diff associated to HF tau   (N/m2)   at T-point   (ln_taudif=T)
358      !!              (2) CALL blk_oce
359      !!
360      !!      C A U T I O N : never mask the surface stress fields
361      !!                      the stress is assumed to be in the (i,j) mesh referential
362      !!
363      !! ** Action  :   defined at each time-step at the air-sea interface
364      !!              - utau, vtau  i- and j-component of the wind stress
365      !!              - taum        wind stress module at T-point
366      !!              - wndm        wind speed  module at T-point over free ocean or leads in presence of sea-ice
367      !!              - qns, qsr    non-solar and solar heat fluxes
368      !!              - emp         upward mass flux (evapo. - precip.)
369      !!              - sfx         salt flux due to freezing/melting (non-zero only if ice is present)
370      !!
371      !! ** References :   Large & Yeager, 2004 / Large & Yeager, 2008
372      !!                   Brodeau et al. Ocean Modelling 2010
373      !!----------------------------------------------------------------------
374      INTEGER, INTENT(in) ::   kt   ! ocean time step
375      !!---------------------------------------------------------------------
376      !
377      CALL fld_read( kt, nn_fsbc, sf )             ! input fields provided at the current time-step
378      !
379      IF( kt == nit000 ) tsk(:,:) = sst_m(:,:)*tmask(:,:,1)  ! no previous estimate of skin temperature => using bulk SST
380      !
381      IF( MOD( kt - 1, nn_fsbc ) == 0 )   CALL blk_oce( kt, sf, sst_m, ssu_m, ssv_m ) !  compute the surface ocean fluxes using bulk formulea
382
383#if defined key_cice
384      IF( MOD( kt - 1, nn_fsbc ) == 0 )   THEN
385         qlw_ice(:,:,1)   = sf(jp_qlw )%fnow(:,:,1)
386         IF( ln_dm2dc ) THEN
387            qsr_ice(:,:,1) = sbc_dcy( sf(jp_qsr)%fnow(:,:,1) )
388         ELSE
389            qsr_ice(:,:,1) =          sf(jp_qsr)%fnow(:,:,1)
390         ENDIF
391         tatm_ice(:,:)    = sf(jp_tair)%fnow(:,:,1)
392         !LB:
393         SELECT CASE( nhumi )
394         CASE( np_humi_sph )
395            qatm_ice(:,:) =           sf(jp_humi)%fnow(:,:,1)
396         CASE( np_humi_dpt )
397            qatm_ice(:,:) = q_sat(    sf(jp_humi)%fnow(:,:,1), sf(jp_slp)%fnow(:,:,1) )
398         CASE( np_humi_rlh )
399            qatm_ice(:,:) = q_air_rh( 0.01_wp*sf(jp_humi)%fnow(:,:,1), sf(jp_tair)%fnow(:,:,1), sf(jp_slp)%fnow(:,:,1)) !LB: 0.01 => RH is % percent in file
400         END SELECT
401         !LB.
402         tprecip(:,:)     = sf(jp_prec)%fnow(:,:,1) * rn_pfac
403         sprecip(:,:)     = sf(jp_snow)%fnow(:,:,1) * rn_pfac
404         wndi_ice(:,:)    = sf(jp_wndi)%fnow(:,:,1)
405         wndj_ice(:,:)    = sf(jp_wndj)%fnow(:,:,1)
406      ENDIF
407#endif
408      !
409   END SUBROUTINE sbc_blk
410
411
412   SUBROUTINE blk_oce( kt, sf, pst, pu, pv )
413      !!---------------------------------------------------------------------
414      !!                     ***  ROUTINE blk_oce  ***
415      !!
416      !! ** Purpose :   provide the momentum, heat and freshwater fluxes at
417      !!      the ocean surface at each time step
418      !!
419      !! ** Method  :   bulk formulea for the ocean using atmospheric
420      !!      fields read in sbc_read
421      !!
422      !! ** Outputs : - utau    : i-component of the stress at U-point  (N/m2)
423      !!              - vtau    : j-component of the stress at V-point  (N/m2)
424      !!              - taum    : Wind stress module at T-point         (N/m2)
425      !!              - wndm    : Wind speed module at T-point          (m/s)
426      !!              - qsr     : Solar heat flux over the ocean        (W/m2)
427      !!              - qns     : Non Solar heat flux over the ocean    (W/m2)
428      !!              - emp     : evaporation minus precipitation       (kg/m2/s)
429      !!
430      !!  ** Nota  :   sf has to be a dummy argument for AGRIF on NEC
431      !!---------------------------------------------------------------------
432      INTEGER  , INTENT(in   )                 ::   kt    ! time step index
433      TYPE(fld), INTENT(inout), DIMENSION(:)   ::   sf    ! input data
434      REAL(wp) , INTENT(in)   , DIMENSION(:,:) ::   pst   ! surface temperature                      [Celcius]
435      REAL(wp) , INTENT(in)   , DIMENSION(:,:) ::   pu    ! surface current at U-point (i-component) [m/s]
436      REAL(wp) , INTENT(in)   , DIMENSION(:,:) ::   pv    ! surface current at V-point (j-component) [m/s]
437      !
438      INTEGER  ::   ji, jj               ! dummy loop indices
439      REAL(wp) ::   zztmp                ! local variable
440      REAL(wp), DIMENSION(jpi,jpj) ::   zwnd_i, zwnd_j    ! wind speed components at T-point
441      REAL(wp), DIMENSION(jpi,jpj) ::   zsq               ! specific humidity at pst  [kg/kg]
442      REAL(wp), DIMENSION(jpi,jpj) ::   zqlw, zqsb        ! long wave and sensible heat fluxes
443      REAL(wp), DIMENSION(jpi,jpj) ::   zqla, zevap       ! latent heat fluxes and evaporation
444      REAL(wp), DIMENSION(jpi,jpj) ::   zst               ! surface temperature in Kelvin
445      REAL(wp), DIMENSION(jpi,jpj) ::   zU_zu             ! bulk wind speed at height zu  [m/s]
446      REAL(wp), DIMENSION(jpi,jpj) ::   ztpot             ! potential temperature of air at z=rn_zqt [K]
447      REAL(wp), DIMENSION(jpi,jpj) ::   zqair             ! specific humidity     of air at z=rn_zqt [kg/kg] !LB
448      !!---------------------------------------------------------------------
449      !
450      ! local scalars ( place there for vector optimisation purposes)
451      zst(:,:) = pst(:,:) + rt0      ! convert SST from Celcius to Kelvin (and set minimum value far above 0 K)
452
453      ! ----------------------------------------------------------------------------- !
454      !      0   Wind components and module at T-point relative to the moving ocean   !
455      ! ----------------------------------------------------------------------------- !
456
457      ! ... components ( U10m - U_oce ) at T-point (unmasked)
458      !!gm    move zwnd_i (_j) set to zero  inside the key_cyclone ???
459      zwnd_i(:,:) = 0._wp
460      zwnd_j(:,:) = 0._wp
461#if defined key_cyclone
462      CALL wnd_cyc( kt, zwnd_i, zwnd_j )    ! add analytical tropical cyclone (Vincent et al. JGR 2012)
463      DO jj = 2, jpjm1
464         DO ji = fs_2, fs_jpim1   ! vect. opt.
465            sf(jp_wndi)%fnow(ji,jj,1) = sf(jp_wndi)%fnow(ji,jj,1) + zwnd_i(ji,jj)
466            sf(jp_wndj)%fnow(ji,jj,1) = sf(jp_wndj)%fnow(ji,jj,1) + zwnd_j(ji,jj)
467         END DO
468      END DO
469#endif
470      DO jj = 2, jpjm1
471         DO ji = fs_2, fs_jpim1   ! vect. opt.
472            zwnd_i(ji,jj) = (  sf(jp_wndi)%fnow(ji,jj,1) - rn_vfac * 0.5 * ( pu(ji-1,jj  ) + pu(ji,jj) )  )
473            zwnd_j(ji,jj) = (  sf(jp_wndj)%fnow(ji,jj,1) - rn_vfac * 0.5 * ( pv(ji  ,jj-1) + pv(ji,jj) )  )
474         END DO
475      END DO
476      CALL lbc_lnk_multi( 'sbcblk', zwnd_i, 'T', -1., zwnd_j, 'T', -1. )
477      ! ... scalar wind ( = | U10m - U_oce | ) at T-point (masked)
478      wndm(:,:) = SQRT(  zwnd_i(:,:) * zwnd_i(:,:)   &
479         &             + zwnd_j(:,:) * zwnd_j(:,:)  ) * tmask(:,:,1)
480
481      ! ----------------------------------------------------------------------------- !
482      !      I   Solar FLUX                                                           !
483      ! ----------------------------------------------------------------------------- !
484
485      ! ocean albedo assumed to be constant + modify now Qsr to include the diurnal cycle                    ! Short Wave
486      zztmp = 1. - albo
487      IF( ln_dm2dc ) THEN
488         qsr(:,:) = zztmp * sbc_dcy( sf(jp_qsr)%fnow(:,:,1) ) * tmask(:,:,1)
489      ELSE
490         qsr(:,:) = zztmp *          sf(jp_qsr)%fnow(:,:,1)   * tmask(:,:,1)
491      ENDIF
492
493
494      ! ----------------------------------------------------------------------------- !
495      !     II    Turbulent FLUXES                                                    !
496      ! ----------------------------------------------------------------------------- !
497
498      ! ... specific humidity at SST and IST tmask(
499      zsq(:,:) = rdct_qsat_salt * q_sat( zst(:,:), sf(jp_slp)%fnow(:,:,1) )
500
501      IF ( ln_skin_cs .OR. ln_skin_wl ) THEN
502         zqsb(:,:) = zst(:,:) !LB: using array zqsb to backup original zst before skin action
503         zqla(:,:) = zsq(:,:) !LB: using array zqla to backup original zsq before skin action
504      END IF
505
506      !LB:
507      ! zqair = specific humidity of air at "rn_zqt" m above thes sea:
508      SELECT CASE( nhumi )
509      CASE( np_humi_sph )
510         zqair(:,:) =        sf(jp_humi)%fnow(:,:,1)      ! what we read in file is already a spec. humidity!
511      CASE( np_humi_dpt )
512         IF (lwp) WRITE(numout,*) ' *** blk_oce => computing q_air out of d_air and slp !' !LBrm
513         zqair(:,:) = q_sat( sf(jp_humi)%fnow(:,:,1), sf(jp_slp)%fnow(:,:,1) )
514      CASE( np_humi_rlh )
515         IF (lwp) WRITE(numout,*) ' *** blk_oce => computing q_air out of RH, t_air and slp !' !LBrm
516         zqair(:,:) = q_air_rh( 0.01_wp*sf(jp_humi)%fnow(:,:,1), sf(jp_tair)%fnow(:,:,1), sf(jp_slp)%fnow(:,:,1) ) !LB: 0.01 => RH is % percent in file
517      END SELECT
518      !LB.
519
520      !! Estimate of potential temperature at z=rn_zqt, based on adiabatic lapse-rate
521      !!    (see Josey, Gulev & Yu, 2013) / doi=10.1016/B978-0-12-391851-2.00005-2
522      !!    (since reanalysis products provide absolute temperature "T" at z, not theta !)
523      ztpot = sf(jp_tair)%fnow(:,:,1) + gamma_moist( sf(jp_tair)%fnow(:,:,1), zqair(:,:) ) * rn_zqt
524
525
526      IF ( ln_skin_cs .OR. ln_skin_wl ) THEN
527
528         SELECT CASE( nblk )        !==  transfer coefficients  ==!   Cd, Ch, Ce at T-point
529
530         CASE( np_COARE_3p0 )
531            IF (lwp) WRITE(numout,*) ' *** blk_oce => calling "turb_coare3p0" WITH CSWL options!!!, gdept_1d(1)=', gdept_1d(1) !LBrm
532            CALL turb_coare3p0 ( kt, rn_zqt, rn_zu, zst, ztpot, zsq, zqair, wndm, ln_skin_cs, ln_skin_wl,&  ! COARE v3.0
533               &                Cd_atm, Ch_atm, Ce_atm, t_zu, q_zu, zU_zu, cdn_oce, chn_oce, cen_oce,    &
534               &                Qsw=qsr(:,:), rad_lw=sf(jp_qlw)%fnow(:,:,1), slp=sf(jp_slp)%fnow(:,:,1) )
535
536         CASE( np_COARE_3p6 )
537            IF (lwp) WRITE(numout,*) ' *** blk_oce => calling "turb_coare3p6" WITH CSWL options!!!, gdept_1d(1)=', gdept_1d(1) !LBrm
538            CALL turb_coare3p6 ( kt, rn_zqt, rn_zu, zst, ztpot, zsq, zqair, wndm, ln_skin_cs, ln_skin_wl,&  ! COARE v3.6
539               &                Cd_atm, Ch_atm, Ce_atm, t_zu, q_zu, zU_zu, cdn_oce, chn_oce, cen_oce,    &
540               &                Qsw=qsr(:,:), rad_lw=sf(jp_qlw)%fnow(:,:,1), slp=sf(jp_slp)%fnow(:,:,1) )
541
542         CASE( np_ECMWF     )
543            IF (lwp) WRITE(numout,*) ' *** blk_oce => calling "turb_ecmwf" WITH CSWL options!!!, gdept_1d(1)=', gdept_1d(1) !LBrm
544            CALL turb_ecmwf   ( kt, rn_zqt, rn_zu, zst, ztpot, zsq, zqair, wndm, ln_skin_cs, ln_skin_wl,    &  ! ECMWF
545               &                Cd_atm, Ch_atm, Ce_atm, t_zu, q_zu, zU_zu, cdn_oce, chn_oce, cen_oce,   &
546               &                Qsw=qsr(:,:), rad_lw=sf(jp_qlw)%fnow(:,:,1), slp=sf(jp_slp)%fnow(:,:,1) )
547
548         CASE DEFAULT
549            CALL ctl_stop( 'STOP', 'sbc_oce: unsuported bulk formula selection for "ln_skin_*==.true."' )
550         END SELECT
551
552         !! In the presence of sea-ice we forget about the cool-skin/warm-layer update of zst and zsq:
553         WHERE ( fr_i < 0.001_wp )
554            ! zst and zsq have been updated by cool-skin/warm-layer scheme and we keep it!!!
555            zst(:,:) = zst(:,:)*tmask(:,:,1)
556            zsq(:,:) = zsq(:,:)*tmask(:,:,1)
557         ELSEWHERE
558            ! we forget about the update...
559            zst(:,:) = zqsb(:,:) !LB: using what we backed up before skin-algo
560            zsq(:,:) = zqla(:,:) !LB:  "   "   "
561         END WHERE
562
563         !LB: Update of tsk, the "official" array for skin temperature
564         tsk(:,:) = zst(:,:)
565
566      ELSE !IF ( ln_skin_cs .OR. ln_skin_wl )
567
568
569         SELECT CASE( nblk )        !==  transfer coefficients  ==!   Cd, Ch, Ce at T-point
570            !
571         CASE( np_NCAR      )
572            CALL turb_ncar    ( rn_zqt, rn_zu, zst, ztpot, zsq, zqair, wndm,   &  ! NCAR-COREv2
573               &                Cd_atm, Ch_atm, Ce_atm, t_zu, q_zu, zU_zu, cdn_oce, chn_oce, cen_oce )
574
575         CASE( np_COARE_3p0 )
576            IF (lwp) WRITE(numout,*) ' *** blk_oce => calling "turb_coare3p0" WITHOUT CSWL optional arrays!!!' !LBrm
577            CALL turb_coare3p0 ( kt, rn_zqt, rn_zu, zst, ztpot, zsq, zqair, wndm, ln_skin_cs, ln_skin_wl,&  ! COARE v3.0
578               &                Cd_atm, Ch_atm, Ce_atm, t_zu, q_zu, zU_zu, cdn_oce, chn_oce, cen_oce )
579
580         CASE( np_COARE_3p6 )
581            IF (lwp) WRITE(numout,*) ' *** blk_oce => calling "turb_coare3p6" WITHOUT CSWL optional arrays!!!' !LBrm
582            CALL turb_coare3p6 ( kt, rn_zqt, rn_zu, zst, ztpot, zsq, zqair, wndm, ln_skin_cs, ln_skin_wl,&  ! COARE v3.6
583               &                Cd_atm, Ch_atm, Ce_atm, t_zu, q_zu, zU_zu, cdn_oce, chn_oce, cen_oce )
584
585         CASE( np_ECMWF     )
586            IF (lwp) WRITE(numout,*) ' *** blk_oce => calling "turb_ecmwf" WITHOUT CSWL optional arrays!!!' !LBrm
587            CALL turb_ecmwf   ( kt, rn_zqt, rn_zu, zst, ztpot, zsq, zqair, wndm, ln_skin_cs, ln_skin_wl,    &  ! ECMWF
588               &                Cd_atm, Ch_atm, Ce_atm, t_zu, q_zu, zU_zu, cdn_oce, chn_oce, cen_oce )
589
590         CASE DEFAULT
591            CALL ctl_stop( 'STOP', 'sbc_oce: non-existing bulk formula selected' )
592         END SELECT
593
594      END IF ! IF ( ln_skin_cs .OR. ln_skin_wl )
595
596      !!      CALL iom_put( "Cd_oce", Cd_atm)  ! output value of pure ocean-atm. transfer coef.
597      !!      CALL iom_put( "Ch_oce", Ch_atm)  ! output value of pure ocean-atm. transfer coef.
598     
599      IF( ABS(rn_zu - rn_zqt) < 0.1_wp ) THEN
600         !! If zu == zt, then ensuring once for all that:
601         t_zu(:,:) = ztpot(:,:)
602         q_zu(:,:) = zqair(:,:)
603      END IF
604     
605
606      !  Turbulent fluxes over ocean  => TURB_FLUXES @ sbcblk_phy.F90
607      ! -------------------------------------------------------------
608     
609      CALL TURB_FLUXES( rn_zu, zst(:,:), zsq(:,:), t_zu(:,:), q_zu(:,:), Cd_atm(:,:), Ch_atm(:,:), Ce_atm(:,:), &
610         &                 wndm(:,:), zU_zu(:,:), sf(jp_slp)%fnow(:,:,1), &
611         &                 taum(:,:), zqsb(:,:), zqla(:,:),               &
612         &                 pEvap=zevap(:,:), prhoa=rhoa(:,:) )
613     
614      zqla(:,:)  =  zqla(:,:) * tmask(:,:,1)
615      zqsb(:,:)  =  zqsb(:,:) * tmask(:,:,1)
616      taum(:,:)  =  taum(:,:) * tmask(:,:,1)
617      zevap(:,:) = zevap(:,:) * tmask(:,:,1)
618     
619      DO jj = 1, jpj             ! tau i and j component on T-grid points
620         DO ji = 1, jpi
621            zztmp = taum(ji,jj) / wndm(ji,jj)
622            zwnd_i(ji,jj) = zztmp * zwnd_i(ji,jj)
623            zwnd_j(ji,jj) = zztmp * zwnd_j(ji,jj)
624         END DO
625      END DO
626      !                          ! add the HF tau contribution to the wind stress module
627      IF( lhftau )   taum(:,:) = taum(:,:) + sf(jp_tdif)%fnow(:,:,1)
628
629      CALL iom_put( "taum_oce", taum )   ! output wind stress module
630
631      ! ... utau, vtau at U- and V_points, resp.
632      !     Note the use of 0.5*(2-umask) in order to unmask the stress along coastlines
633      !     Note the use of MAX(tmask(i,j),tmask(i+1,j) is to mask tau over ice shelves
634      DO jj = 1, jpjm1
635         DO ji = 1, fs_jpim1
636            utau(ji,jj) = 0.5 * ( 2. - umask(ji,jj,1) ) * ( zwnd_i(ji,jj) + zwnd_i(ji+1,jj  ) ) &
637               &          * MAX(tmask(ji,jj,1),tmask(ji+1,jj,1))
638            vtau(ji,jj) = 0.5 * ( 2. - vmask(ji,jj,1) ) * ( zwnd_j(ji,jj) + zwnd_j(ji  ,jj+1) ) &
639               &          * MAX(tmask(ji,jj,1),tmask(ji,jj+1,1))
640         END DO
641      END DO
642      CALL lbc_lnk_multi( 'sbcblk', utau, 'U', -1., vtau, 'V', -1. )
643
644
645      ! ----------------------------------------------------------------------------- !
646      !     III    Net longwave radiative FLUX                                        !
647      ! ----------------------------------------------------------------------------- !
648
649      !! LB: now moved after Turbulent fluxes because must use the skin temperature rather that the SST ! (zst is skin temperature if ln_skin_cs==.TRUE. .OR. ln_skin_wl==.TRUE.)
650      zqlw(:,:) = emiss_w * ( sf(jp_qlw)%fnow(:,:,1) - stefan*zst(:,:)*zst(:,:)*zst(:,:)*zst(:,:) ) * tmask(:,:,1)   ! Net radiative longwave flux
651
652
653      IF(ln_ctl) THEN
654         CALL prt_ctl( tab2d_1=zevap , clinfo1=' blk_oce: zevap  : ') !LB
655         CALL prt_ctl( tab2d_1=zqla  , clinfo1=' blk_oce: zqla   : ', tab2d_2=Ce_atm , clinfo2=' Ce_oce  : ' )
656         CALL prt_ctl( tab2d_1=zqsb  , clinfo1=' blk_oce: zqsb   : ', tab2d_2=Ch_atm , clinfo2=' Ch_oce  : ' )
657         CALL prt_ctl( tab2d_1=zqlw  , clinfo1=' blk_oce: zqlw   : ', tab2d_2=qsr, clinfo2=' qsr : ' )
658         CALL prt_ctl( tab2d_1=zsq   , clinfo1=' blk_oce: zsq    : ', tab2d_2=zst, clinfo2=' zst : ' )
659         CALL prt_ctl( tab2d_1=utau  , clinfo1=' blk_oce: utau   : ', mask1=umask,   &
660            &          tab2d_2=vtau  , clinfo2=           ' vtau : ', mask2=vmask )
661         CALL prt_ctl( tab2d_1=wndm  , clinfo1=' blk_oce: wndm   : ')
662         CALL prt_ctl( tab2d_1=zst   , clinfo1=' blk_oce: zst    : ')
663      ENDIF
664
665      ! ----------------------------------------------------------------------------- !
666      !     IV    Total FLUXES                                                       !
667      ! ----------------------------------------------------------------------------- !
668      !
669      emp (:,:) = (  zevap(:,:)                                          &   ! mass flux (evap. - precip.)
670         &         - sf(jp_prec)%fnow(:,:,1) * rn_pfac  ) * tmask(:,:,1)
671      !
672      qns(:,:) = zqlw(:,:) + zqsb(:,:) + zqla(:,:)                                &   ! Downward Non Solar
673         &     - sf(jp_snow)%fnow(:,:,1) * rn_pfac * rLfus                        &   ! remove latent melting heat for solid precip
674         &     - zevap(:,:) * pst(:,:) * rcp                                      &   ! remove evap heat content at SST !LB??? pst is Celsius !?
675         &     + ( sf(jp_prec)%fnow(:,:,1) - sf(jp_snow)%fnow(:,:,1) ) * rn_pfac  &   ! add liquid precip heat content at Tair
676         &     * ( sf(jp_tair)%fnow(:,:,1) - rt0 ) * rcp                          &
677         &     + sf(jp_snow)%fnow(:,:,1) * rn_pfac                                &   ! add solid  precip heat content at min(Tair,Tsnow)
678         &     * ( MIN( sf(jp_tair)%fnow(:,:,1), rt0 ) - rt0 ) * rcpi
679      qns(:,:) = qns(:,:) * tmask(:,:,1)
680      !
681#if defined key_si3
682      qns_oce(:,:) = zqlw(:,:) + zqsb(:,:) + zqla(:,:)                                ! non solar without emp (only needed by SI3)
683      qsr_oce(:,:) = qsr(:,:)
684#endif
685      !
686      !!#LB: NO WHY???? IF ( nn_ice == 0 ) THEN
687      CALL iom_put( "rho_air"  ,   rhoa )                 ! output air density (kg/m^3) !#LB
688      CALL iom_put( "qlw_oce"  ,   zqlw )                 ! output downward longwave heat over the ocean
689      CALL iom_put( "qsb_oce"  ,   zqsb )                 ! output downward sensible heat over the ocean
690      CALL iom_put( "qla_oce"  ,   zqla )                 ! output downward latent   heat over the ocean
691      CALL iom_put( "evap_oce" ,  zevap )                 ! evaporation
692      CALL iom_put( "qemp_oce" ,   qns-zqlw-zqsb-zqla )   ! output downward heat content of E-P over the ocean
693      CALL iom_put( "qns_oce"  ,   qns  )                 ! output downward non solar heat over the ocean
694      CALL iom_put( "qsr_oce"  ,   qsr  )                 ! output downward solar heat over the ocean
695      CALL iom_put( "qt_oce"   ,   qns+qsr )              ! output total downward heat over the ocean
696      tprecip(:,:) = sf(jp_prec)%fnow(:,:,1) * rn_pfac * tmask(:,:,1) ! output total precipitation [kg/m2/s]
697      sprecip(:,:) = sf(jp_snow)%fnow(:,:,1) * rn_pfac * tmask(:,:,1) ! output solid precipitation [kg/m2/s]
698      CALL iom_put( 'snowpre', sprecip )                 ! Snow
699      CALL iom_put( 'precip' , tprecip )                 ! Total precipitation
700      IF ( ln_skin_cs .OR. ln_skin_wl ) THEN
701         CALL iom_put( "t_skin" ,  (zst - rt0) * tmask(:,:,1) )           ! T_skin in Celsius
702         CALL iom_put( "dt_skin" , (zst - pst - rt0) * tmask(:,:,1) )     ! T_skin - SST temperature difference...
703      END IF
704      !!#LB. ENDIF
705      !
706      IF(ln_ctl) THEN
707         CALL prt_ctl(tab2d_1=zqsb , clinfo1=' blk_oce: zqsb   : ', tab2d_2=zqlw , clinfo2=' zqlw  : ')
708         CALL prt_ctl(tab2d_1=zqla , clinfo1=' blk_oce: zqla   : ', tab2d_2=qsr  , clinfo2=' qsr   : ')
709         CALL prt_ctl(tab2d_1=pst  , clinfo1=' blk_oce: pst    : ', tab2d_2=emp  , clinfo2=' emp   : ')
710         CALL prt_ctl(tab2d_1=utau , clinfo1=' blk_oce: utau   : ', mask1=umask,   &
711            &         tab2d_2=vtau , clinfo2=              ' vtau  : ' , mask2=vmask )
712      ENDIF
713      !
714   END SUBROUTINE blk_oce
715
716
717
718#if defined key_si3
719   !!----------------------------------------------------------------------
720   !!   'key_si3'                                       SI3 sea-ice model
721   !!----------------------------------------------------------------------
722   !!   blk_ice_tau : provide the air-ice stress
723   !!   blk_ice_flx : provide the heat and mass fluxes at air-ice interface
724   !!   blk_ice_qcn : provide ice surface temperature and snow/ice conduction flux (emulating conduction flux)
725   !!   Cdn10_Lupkes2012 : Lupkes et al. (2012) air-ice drag
726   !!   Cdn10_Lupkes2015 : Lupkes et al. (2015) air-ice drag
727   !!----------------------------------------------------------------------
728
729   SUBROUTINE blk_ice_tau
730      !!---------------------------------------------------------------------
731      !!                     ***  ROUTINE blk_ice_tau  ***
732      !!
733      !! ** Purpose :   provide the surface boundary condition over sea-ice
734      !!
735      !! ** Method  :   compute momentum using bulk formulation
736      !!                formulea, ice variables and read atmospheric fields.
737      !!                NB: ice drag coefficient is assumed to be a constant
738      !!---------------------------------------------------------------------
739      INTEGER  ::   ji, jj    ! dummy loop indices
740      REAL(wp) ::   zwndi_f , zwndj_f, zwnorm_f   ! relative wind module and components at F-point
741      REAL(wp) ::   zwndi_t , zwndj_t             ! relative wind components at T-point
742      !!---------------------------------------------------------------------
743      !
744      ! set transfer coefficients to default sea-ice values
745      Cd_atm(:,:) = rCd_ice
746      Ch_atm(:,:) = rCd_ice
747      Ce_atm(:,:) = rCd_ice
748
749      wndm_ice(:,:) = 0._wp      !!gm brutal....
750
751      ! ------------------------------------------------------------ !
752      !    Wind module relative to the moving ice ( U10m - U_ice )   !
753      ! ------------------------------------------------------------ !
754      ! C-grid ice dynamics :   U & V-points (same as ocean)
755      DO jj = 2, jpjm1
756         DO ji = fs_2, fs_jpim1   ! vect. opt.
757            zwndi_t = (  sf(jp_wndi)%fnow(ji,jj,1) - rn_vfac * 0.5 * ( u_ice(ji-1,jj  ) + u_ice(ji,jj) )  )
758            zwndj_t = (  sf(jp_wndj)%fnow(ji,jj,1) - rn_vfac * 0.5 * ( v_ice(ji  ,jj-1) + v_ice(ji,jj) )  )
759            wndm_ice(ji,jj) = SQRT( zwndi_t * zwndi_t + zwndj_t * zwndj_t ) * tmask(ji,jj,1)
760         END DO
761      END DO
762      CALL lbc_lnk( 'sbcblk', wndm_ice, 'T',  1. )
763      !
764      ! Make ice-atm. drag dependent on ice concentration
765      IF    ( ln_Cd_L12 ) THEN   ! calculate new drag from Lupkes(2012) equations
766         CALL Cdn10_Lupkes2012( Cd_atm )
767         Ch_atm(:,:) = Cd_atm(:,:)       ! momentum and heat transfer coef. are considered identical
768      ELSEIF( ln_Cd_L15 ) THEN   ! calculate new drag from Lupkes(2015) equations
769         CALL Cdn10_Lupkes2015( Cd_atm, Ch_atm )
770      ENDIF
771
772      !!      CALL iom_put( "rCd_ice", Cd_atm)  ! output value of pure ice-atm. transfer coef.
773      !!      CALL iom_put( "Ch_ice", Ch_atm)  ! output value of pure ice-atm. transfer coef.
774
775      ! local scalars ( place there for vector optimisation purposes)
776
777      !!gm brutal....
778      utau_ice  (:,:) = 0._wp
779      vtau_ice  (:,:) = 0._wp
780      !!gm end
781
782      ! ------------------------------------------------------------ !
783      !    Wind stress relative to the moving ice ( U10m - U_ice )   !
784      ! ------------------------------------------------------------ !
785      ! C-grid ice dynamics :   U & V-points (same as ocean)
786      DO jj = 2, jpjm1
787         DO ji = fs_2, fs_jpim1   ! vect. opt.
788            utau_ice(ji,jj) = 0.5 * rhoa(ji,jj) * Cd_atm(ji,jj) * ( wndm_ice(ji+1,jj  ) + wndm_ice(ji,jj) )            &
789               &          * ( 0.5 * (sf(jp_wndi)%fnow(ji+1,jj,1) + sf(jp_wndi)%fnow(ji,jj,1) ) - rn_vfac * u_ice(ji,jj) )
790            vtau_ice(ji,jj) = 0.5 * rhoa(ji,jj) * Cd_atm(ji,jj) * ( wndm_ice(ji,jj+1  ) + wndm_ice(ji,jj) )            &
791               &          * ( 0.5 * (sf(jp_wndj)%fnow(ji,jj+1,1) + sf(jp_wndj)%fnow(ji,jj,1) ) - rn_vfac * v_ice(ji,jj) )
792         END DO
793      END DO
794      CALL lbc_lnk_multi( 'sbcblk', utau_ice, 'U', -1., vtau_ice, 'V', -1. )
795      !
796      !
797      IF(ln_ctl) THEN
798         CALL prt_ctl(tab2d_1=utau_ice  , clinfo1=' blk_ice: utau_ice : ', tab2d_2=vtau_ice  , clinfo2=' vtau_ice : ')
799         CALL prt_ctl(tab2d_1=wndm_ice  , clinfo1=' blk_ice: wndm_ice : ')
800      ENDIF
801      !
802   END SUBROUTINE blk_ice_tau
803
804
805   SUBROUTINE blk_ice_flx( ptsu, phs, phi, palb )
806      !!---------------------------------------------------------------------
807      !!                     ***  ROUTINE blk_ice_flx  ***
808      !!
809      !! ** Purpose :   provide the heat and mass fluxes at air-ice interface
810      !!
811      !! ** Method  :   compute heat and freshwater exchanged
812      !!                between atmosphere and sea-ice using bulk formulation
813      !!                formulea, ice variables and read atmmospheric fields.
814      !!
815      !! caution : the net upward water flux has with mm/day unit
816      !!---------------------------------------------------------------------
817      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   ptsu   ! sea ice surface temperature
818      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   phs    ! snow thickness
819      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   phi    ! ice thickness
820      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   palb   ! ice albedo (all skies)
821      !!
822      INTEGER  ::   ji, jj, jl               ! dummy loop indices
823      REAL(wp) ::   zst3                     ! local variable
824      REAL(wp) ::   zcoef_dqlw, zcoef_dqla   !   -      -
825      REAL(wp) ::   zztmp, z1_rLsub          !   -      -
826      REAL(wp) ::   zfr1, zfr2               ! local variables
827      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z1_st         ! inverse of surface temperature
828      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z_qlw         ! long wave heat flux over ice
829      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z_qsb         ! sensible  heat flux over ice
830      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z_dqlw        ! long wave heat sensitivity over ice
831      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z_dqsb        ! sensible  heat sensitivity over ice
832      REAL(wp), DIMENSION(jpi,jpj)     ::   zevap, zsnw   ! evaporation and snw distribution after wind blowing (SI3)
833      REAL(wp), DIMENSION(jpi,jpj)     ::   zqair         ! specific humidity of air at z=rn_zqt [kg/kg] !LB
834      !!---------------------------------------------------------------------
835      !
836      zcoef_dqlw = 4._wp * 0.95_wp * stefan             ! local scalars
837      zcoef_dqla = -rLsub * 11637800._wp * (-5897.8_wp) !LB: BAD!
838      !
839
840      !LB:
841      SELECT CASE( nhumi )
842      CASE( np_humi_sph )
843         zqair(:,:) =        sf(jp_humi)%fnow(:,:,1)      ! what we read in file is already a spec. humidity!
844      CASE( np_humi_dpt )
845         IF (lwp) WRITE(numout,*) ' *** blk_ice_flx => computing q_air out of d_air and slp !' !LBrm
846         zqair(:,:) = q_sat( sf(jp_humi)%fnow(:,:,1), sf(jp_slp)%fnow(:,:,1) )
847      CASE( np_humi_rlh )
848         IF (lwp) WRITE(numout,*) ' *** blk_ice_flx => computing q_air out of RH, t_air and slp !' !LBrm
849         zqair(:,:) = q_air_rh( 0.01_wp*sf(jp_humi)%fnow(:,:,1), sf(jp_tair)%fnow(:,:,1), sf(jp_slp)%fnow(:,:,1) ) !LB: 0.01 => RH is % percent in file
850      END SELECT
851      !LB.
852
853      zztmp = 1. / ( 1. - albo )
854      WHERE( ptsu(:,:,:) /= 0._wp )
855         z1_st(:,:,:) = 1._wp / ptsu(:,:,:)
856      ELSEWHERE
857         z1_st(:,:,:) = 0._wp
858      END WHERE
859      !                                     ! ========================== !
860      DO jl = 1, jpl                        !  Loop over ice categories  !
861         !                                  ! ========================== !
862         DO jj = 1 , jpj
863            DO ji = 1, jpi
864               ! ----------------------------!
865               !      I   Radiative FLUXES   !
866               ! ----------------------------!
867               zst3 = ptsu(ji,jj,jl) * ptsu(ji,jj,jl) * ptsu(ji,jj,jl)
868               ! Short Wave (sw)
869               qsr_ice(ji,jj,jl) = zztmp * ( 1. - palb(ji,jj,jl) ) * qsr(ji,jj)
870               ! Long  Wave (lw)
871               z_qlw(ji,jj,jl) = 0.95 * ( sf(jp_qlw)%fnow(ji,jj,1) - stefan * ptsu(ji,jj,jl) * zst3 ) * tmask(ji,jj,1)
872               ! lw sensitivity
873               z_dqlw(ji,jj,jl) = zcoef_dqlw * zst3
874
875               ! ----------------------------!
876               !     II    Turbulent FLUXES  !
877               ! ----------------------------!
878
879               ! ... turbulent heat fluxes with Ch_atm recalculated in blk_ice_tau
880               ! Sensible Heat
881               z_qsb(ji,jj,jl) = rhoa(ji,jj) * rCp_air * Ch_atm(ji,jj) * wndm_ice(ji,jj) * (ptsu(ji,jj,jl) - sf(jp_tair)%fnow(ji,jj,1))
882               ! Latent Heat
883               qla_ice(ji,jj,jl) = rn_efac * MAX( 0.e0, rhoa(ji,jj) * rLsub  * Ch_atm(ji,jj) * wndm_ice(ji,jj) *  &
884                  &                ( 11637800. * EXP( -5897.8 * z1_st(ji,jj,jl) ) / rhoa(ji,jj) - zqair(ji,jj) ) )
885               ! Latent heat sensitivity for ice (Dqla/Dt)
886               IF( qla_ice(ji,jj,jl) > 0._wp ) THEN
887                  dqla_ice(ji,jj,jl) = rn_efac * zcoef_dqla * Ch_atm(ji,jj) * wndm_ice(ji,jj) *  &
888                     &                 z1_st(ji,jj,jl)*z1_st(ji,jj,jl) * EXP(-5897.8 * z1_st(ji,jj,jl))
889               ELSE
890                  dqla_ice(ji,jj,jl) = 0._wp
891               ENDIF
892
893               ! Sensible heat sensitivity (Dqsb_ice/Dtn_ice)
894               z_dqsb(ji,jj,jl) = rhoa(ji,jj) * rCp_air * Ch_atm(ji,jj) * wndm_ice(ji,jj)
895
896               ! ----------------------------!
897               !     III    Total FLUXES     !
898               ! ----------------------------!
899               ! Downward Non Solar flux
900               qns_ice (ji,jj,jl) =     z_qlw (ji,jj,jl) - z_qsb (ji,jj,jl) - qla_ice (ji,jj,jl)
901               ! Total non solar heat flux sensitivity for ice
902               dqns_ice(ji,jj,jl) = - ( z_dqlw(ji,jj,jl) + z_dqsb(ji,jj,jl) + dqla_ice(ji,jj,jl) )
903            END DO
904            !
905         END DO
906         !
907      END DO
908      !
909      tprecip(:,:) = sf(jp_prec)%fnow(:,:,1) * rn_pfac * tmask(:,:,1)  ! total precipitation [kg/m2/s]
910      sprecip(:,:) = sf(jp_snow)%fnow(:,:,1) * rn_pfac * tmask(:,:,1)  ! solid precipitation [kg/m2/s]
911      CALL iom_put( 'snowpre', sprecip )                    ! Snow precipitation
912      CALL iom_put( 'precip' , tprecip )                    ! Total precipitation
913
914      ! --- evaporation --- !
915      z1_rLsub = 1._wp / rLsub
916      evap_ice (:,:,:) = rn_efac * qla_ice (:,:,:) * z1_rLsub    ! sublimation
917      devap_ice(:,:,:) = rn_efac * dqla_ice(:,:,:) * z1_rLsub    ! d(sublimation)/dT
918      zevap    (:,:)   = rn_efac * ( emp(:,:) + tprecip(:,:) )   ! evaporation over ocean
919
920      ! --- evaporation minus precipitation --- !
921      zsnw(:,:) = 0._wp
922      CALL ice_thd_snwblow( (1.-at_i_b(:,:)), zsnw )  ! snow distribution over ice after wind blowing
923      emp_oce(:,:) = ( 1._wp - at_i_b(:,:) ) * zevap(:,:) - ( tprecip(:,:) - sprecip(:,:) ) - sprecip(:,:) * (1._wp - zsnw )
924      emp_ice(:,:) = SUM( a_i_b(:,:,:) * evap_ice(:,:,:), dim=3 ) - sprecip(:,:) * zsnw
925      emp_tot(:,:) = emp_oce(:,:) + emp_ice(:,:)
926
927      ! --- heat flux associated with emp --- !
928      qemp_oce(:,:) = - ( 1._wp - at_i_b(:,:) ) * zevap(:,:) * sst_m(:,:) * rcp                  & ! evap at sst
929         &          + ( tprecip(:,:) - sprecip(:,:) ) * ( sf(jp_tair)%fnow(:,:,1) - rt0 ) * rcp  & ! liquid precip at Tair
930         &          +   sprecip(:,:) * ( 1._wp - zsnw ) *                                        & ! solid precip at min(Tair,Tsnow)
931         &              ( ( MIN( sf(jp_tair)%fnow(:,:,1), rt0 ) - rt0 ) * rcpi * tmask(:,:,1) - rLfus )
932      qemp_ice(:,:) =   sprecip(:,:) * zsnw *                                                    & ! solid precip (only)
933         &              ( ( MIN( sf(jp_tair)%fnow(:,:,1), rt0 ) - rt0 ) * rcpi * tmask(:,:,1) - rLfus )
934
935      ! --- total solar and non solar fluxes --- !
936      qns_tot(:,:) = ( 1._wp - at_i_b(:,:) ) * qns_oce(:,:) + SUM( a_i_b(:,:,:) * qns_ice(:,:,:), dim=3 )  &
937         &           + qemp_ice(:,:) + qemp_oce(:,:)
938      qsr_tot(:,:) = ( 1._wp - at_i_b(:,:) ) * qsr_oce(:,:) + SUM( a_i_b(:,:,:) * qsr_ice(:,:,:), dim=3 )
939
940      ! --- heat content of precip over ice in J/m3 (to be used in 1D-thermo) --- !
941      qprec_ice(:,:) = rhos * ( ( MIN( sf(jp_tair)%fnow(:,:,1), rt0 ) - rt0 ) * rcpi * tmask(:,:,1) - rLfus )
942
943      ! --- heat content of evap over ice in W/m2 (to be used in 1D-thermo) ---
944      DO jl = 1, jpl
945         qevap_ice(:,:,jl) = 0._wp ! should be -evap_ice(:,:,jl)*( ( Tice - rt0 ) * rcpi * tmask(:,:,1) )
946         !                         ! But we do not have Tice => consider it at 0degC => evap=0
947      END DO
948
949      ! --- shortwave radiation transmitted below the surface (W/m2, see Grenfell Maykut 77) --- !
950      zfr1 = ( 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice )            ! transmission when hi>10cm
951      zfr2 = ( 0.82 * ( 1.0 - cldf_ice ) + 0.65 * cldf_ice )            ! zfr2 such that zfr1 + zfr2 to equal 1
952      !
953      WHERE    ( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) <  0.1_wp )       ! linear decrease from hi=0 to 10cm
954         qtr_ice_top(:,:,:) = qsr_ice(:,:,:) * ( zfr1 + zfr2 * ( 1._wp - phi(:,:,:) * 10._wp ) )
955      ELSEWHERE( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) >= 0.1_wp )       ! constant (zfr1) when hi>10cm
956         qtr_ice_top(:,:,:) = qsr_ice(:,:,:) * zfr1
957      ELSEWHERE                                                         ! zero when hs>0
958         qtr_ice_top(:,:,:) = 0._wp
959      END WHERE
960      !
961      IF(ln_ctl) THEN
962         CALL prt_ctl(tab3d_1=qla_ice , clinfo1=' blk_ice: qla_ice  : ', tab3d_2=z_qsb   , clinfo2=' z_qsb    : ', kdim=jpl)
963         CALL prt_ctl(tab3d_1=z_qlw   , clinfo1=' blk_ice: z_qlw    : ', tab3d_2=dqla_ice, clinfo2=' dqla_ice : ', kdim=jpl)
964         CALL prt_ctl(tab3d_1=z_dqsb  , clinfo1=' blk_ice: z_dqsb   : ', tab3d_2=z_dqlw  , clinfo2=' z_dqlw   : ', kdim=jpl)
965         CALL prt_ctl(tab3d_1=dqns_ice, clinfo1=' blk_ice: dqns_ice : ', tab3d_2=qsr_ice , clinfo2=' qsr_ice  : ', kdim=jpl)
966         CALL prt_ctl(tab3d_1=ptsu    , clinfo1=' blk_ice: ptsu     : ', tab3d_2=qns_ice , clinfo2=' qns_ice  : ', kdim=jpl)
967         CALL prt_ctl(tab2d_1=tprecip , clinfo1=' blk_ice: tprecip  : ', tab2d_2=sprecip , clinfo2=' sprecip  : ')
968      ENDIF
969      !
970   END SUBROUTINE blk_ice_flx
971
972
973   SUBROUTINE blk_ice_qcn( ld_virtual_itd, ptsu, ptb, phs, phi )
974      !!---------------------------------------------------------------------
975      !!                     ***  ROUTINE blk_ice_qcn  ***
976      !!
977      !! ** Purpose :   Compute surface temperature and snow/ice conduction flux
978      !!                to force sea ice / snow thermodynamics
979      !!                in the case conduction flux is emulated
980      !!
981      !! ** Method  :   compute surface energy balance assuming neglecting heat storage
982      !!                following the 0-layer Semtner (1976) approach
983      !!
984      !! ** Outputs : - ptsu    : sea-ice / snow surface temperature (K)
985      !!              - qcn_ice : surface inner conduction flux (W/m2)
986      !!
987      !!---------------------------------------------------------------------
988      LOGICAL                   , INTENT(in   ) ::   ld_virtual_itd  ! single-category option
989      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptsu            ! sea ice / snow surface temperature
990      REAL(wp), DIMENSION(:,:)  , INTENT(in   ) ::   ptb             ! sea ice base temperature
991      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   phs             ! snow thickness
992      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   phi             ! sea ice thickness
993      !
994      INTEGER , PARAMETER ::   nit = 10                  ! number of iterations
995      REAL(wp), PARAMETER ::   zepsilon = 0.1_wp         ! characteristic thickness for enhanced conduction
996      !
997      INTEGER  ::   ji, jj, jl           ! dummy loop indices
998      INTEGER  ::   iter                 ! local integer
999      REAL(wp) ::   zfac, zfac2, zfac3   ! local scalars
1000      REAL(wp) ::   zkeff_h, ztsu, ztsu0 !
1001      REAL(wp) ::   zqc, zqnet           !
1002      REAL(wp) ::   zhe, zqa0            !
1003      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zgfac   ! enhanced conduction factor
1004      !!---------------------------------------------------------------------
1005
1006      ! -------------------------------------!
1007      !      I   Enhanced conduction factor  !
1008      ! -------------------------------------!
1009      ! Emulates the enhancement of conduction by unresolved thin ice (ld_virtual_itd = T)
1010      ! Fichefet and Morales Maqueda, JGR 1997
1011      !
1012      zgfac(:,:,:) = 1._wp
1013
1014      IF( ld_virtual_itd ) THEN
1015         !
1016         zfac  = 1._wp /  ( rn_cnd_s + rcnd_i )
1017         zfac2 = EXP(1._wp) * 0.5_wp * zepsilon
1018         zfac3 = 2._wp / zepsilon
1019         !
1020         DO jl = 1, jpl
1021            DO jj = 1 , jpj
1022               DO ji = 1, jpi
1023                  zhe = ( rn_cnd_s * phi(ji,jj,jl) + rcnd_i * phs(ji,jj,jl) ) * zfac                            ! Effective thickness
1024                  IF( zhe >=  zfac2 )   zgfac(ji,jj,jl) = MIN( 2._wp, 0.5_wp * ( 1._wp + LOG( zhe * zfac3 ) ) ) ! Enhanced conduction factor
1025               END DO
1026            END DO
1027         END DO
1028         !
1029      ENDIF
1030
1031      ! -------------------------------------------------------------!
1032      !      II   Surface temperature and conduction flux            !
1033      ! -------------------------------------------------------------!
1034      !
1035      zfac = rcnd_i * rn_cnd_s
1036      !
1037      DO jl = 1, jpl
1038         DO jj = 1 , jpj
1039            DO ji = 1, jpi
1040               !
1041               zkeff_h = zfac * zgfac(ji,jj,jl) / &                                    ! Effective conductivity of the snow-ice system divided by thickness
1042                  &      ( rcnd_i * phs(ji,jj,jl) + rn_cnd_s * MAX( 0.01, phi(ji,jj,jl) ) )
1043               ztsu    = ptsu(ji,jj,jl)                                                ! Store current iteration temperature
1044               ztsu0   = ptsu(ji,jj,jl)                                                ! Store initial surface temperature
1045               zqa0    = qsr_ice(ji,jj,jl) - qtr_ice_top(ji,jj,jl) + qns_ice(ji,jj,jl) ! Net initial atmospheric heat flux
1046               !
1047               DO iter = 1, nit     ! --- Iterative loop
1048                  zqc   = zkeff_h * ( ztsu - ptb(ji,jj) )                              ! Conduction heat flux through snow-ice system (>0 downwards)
1049                  zqnet = zqa0 + dqns_ice(ji,jj,jl) * ( ztsu - ptsu(ji,jj,jl) ) - zqc  ! Surface energy budget
1050                  ztsu  = ztsu - zqnet / ( dqns_ice(ji,jj,jl) - zkeff_h )              ! Temperature update
1051               END DO
1052               !
1053               ptsu   (ji,jj,jl) = MIN( rt0, ztsu )
1054               qcn_ice(ji,jj,jl) = zkeff_h * ( ptsu(ji,jj,jl) - ptb(ji,jj) )
1055               qns_ice(ji,jj,jl) = qns_ice(ji,jj,jl) + dqns_ice(ji,jj,jl) * ( ptsu(ji,jj,jl) - ztsu0 )
1056               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) )  &
1057                  &   * MAX( 0._wp , SIGN( 1._wp, ptsu(ji,jj,jl) - rt0 ) )
1058
1059               ! --- Diagnose the heat loss due to changing non-solar flux (as in icethd_zdf_bl99) --- !
1060               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)
1061
1062            END DO
1063         END DO
1064         !
1065      END DO
1066      !
1067   END SUBROUTINE blk_ice_qcn
1068
1069
1070   SUBROUTINE Cdn10_Lupkes2012( Cd )
1071      !!----------------------------------------------------------------------
1072      !!                      ***  ROUTINE  Cdn10_Lupkes2012  ***
1073      !!
1074      !! ** Purpose :    Recompute the neutral air-ice drag referenced at 10m
1075      !!                 to make it dependent on edges at leads, melt ponds and flows.
1076      !!                 After some approximations, this can be resumed to a dependency
1077      !!                 on ice concentration.
1078      !!
1079      !! ** Method :     The parameterization is taken from Lupkes et al. (2012) eq.(50)
1080      !!                 with the highest level of approximation: level4, eq.(59)
1081      !!                 The generic drag over a cell partly covered by ice can be re-written as follows:
1082      !!
1083      !!                 Cd = Cdw * (1-A) + Cdi * A + Ce * (1-A)**(nu+1/(10*beta)) * A**mu
1084      !!
1085      !!                    Ce = 2.23e-3       , as suggested by Lupkes (eq. 59)
1086      !!                    nu = mu = beta = 1 , as suggested by Lupkes (eq. 59)
1087      !!                    A is the concentration of ice minus melt ponds (if any)
1088      !!
1089      !!                 This new drag has a parabolic shape (as a function of A) starting at
1090      !!                 Cdw(say 1.5e-3) for A=0, reaching 1.97e-3 for A~0.5
1091      !!                 and going down to Cdi(say 1.4e-3) for A=1
1092      !!
1093      !!                 It is theoretically applicable to all ice conditions (not only MIZ)
1094      !!                 => see Lupkes et al (2013)
1095      !!
1096      !! ** References : Lupkes et al. JGR 2012 (theory)
1097      !!                 Lupkes et al. GRL 2013 (application to GCM)
1098      !!
1099      !!----------------------------------------------------------------------
1100      REAL(wp), DIMENSION(:,:), INTENT(inout) ::   Cd
1101      REAL(wp), PARAMETER ::   zCe   = 2.23e-03_wp
1102      REAL(wp), PARAMETER ::   znu   = 1._wp
1103      REAL(wp), PARAMETER ::   zmu   = 1._wp
1104      REAL(wp), PARAMETER ::   zbeta = 1._wp
1105      REAL(wp)            ::   zcoef
1106      !!----------------------------------------------------------------------
1107      zcoef = znu + 1._wp / ( 10._wp * zbeta )
1108
1109      ! generic drag over a cell partly covered by ice
1110      !!Cd(:,:) = Cd_oce(:,:) * ( 1._wp - at_i_b(:,:) ) +  &                        ! pure ocean drag
1111      !!   &      rCd_ice      *           at_i_b(:,:)   +  &                        ! pure ice drag
1112      !!   &      zCe         * ( 1._wp - at_i_b(:,:) )**zcoef * at_i_b(:,:)**zmu   ! change due to sea-ice morphology
1113
1114      ! ice-atm drag
1115      Cd(:,:) = rCd_ice +  &                                                         ! pure ice drag
1116         &      zCe    * ( 1._wp - at_i_b(:,:) )**zcoef * at_i_b(:,:)**(zmu-1._wp)  ! change due to sea-ice morphology
1117
1118   END SUBROUTINE Cdn10_Lupkes2012
1119
1120
1121   SUBROUTINE Cdn10_Lupkes2015( Cd, Ch )
1122      !!----------------------------------------------------------------------
1123      !!                      ***  ROUTINE  Cdn10_Lupkes2015  ***
1124      !!
1125      !! ** pUrpose :    Alternative turbulent transfert coefficients formulation
1126      !!                 between sea-ice and atmosphere with distinct momentum
1127      !!                 and heat coefficients depending on sea-ice concentration
1128      !!                 and atmospheric stability (no meltponds effect for now).
1129      !!
1130      !! ** Method :     The parameterization is adapted from Lupkes et al. (2015)
1131      !!                 and ECHAM6 atmospheric model. Compared to Lupkes2012 scheme,
1132      !!                 it considers specific skin and form drags (Andreas et al. 2010)
1133      !!                 to compute neutral transfert coefficients for both heat and
1134      !!                 momemtum fluxes. Atmospheric stability effect on transfert
1135      !!                 coefficient is also taken into account following Louis (1979).
1136      !!
1137      !! ** References : Lupkes et al. JGR 2015 (theory)
1138      !!                 Lupkes et al. ECHAM6 documentation 2015 (implementation)
1139      !!
1140      !!----------------------------------------------------------------------
1141      !
1142      REAL(wp), DIMENSION(:,:), INTENT(inout) ::   Cd
1143      REAL(wp), DIMENSION(:,:), INTENT(inout) ::   Ch
1144      REAL(wp), DIMENSION(jpi,jpj)            ::   ztm_su, zst, zqo_sat, zqi_sat
1145      !
1146      ! ECHAM6 constants
1147      REAL(wp), PARAMETER ::   z0_skin_ice  = 0.69e-3_wp  ! Eq. 43 [m]
1148      REAL(wp), PARAMETER ::   z0_form_ice  = 0.57e-3_wp  ! Eq. 42 [m]
1149      REAL(wp), PARAMETER ::   z0_ice       = 1.00e-3_wp  ! Eq. 15 [m]
1150      REAL(wp), PARAMETER ::   zce10        = 2.80e-3_wp  ! Eq. 41
1151      REAL(wp), PARAMETER ::   zbeta        = 1.1_wp      ! Eq. 41
1152      REAL(wp), PARAMETER ::   zc           = 5._wp       ! Eq. 13
1153      REAL(wp), PARAMETER ::   zc2          = zc * zc
1154      REAL(wp), PARAMETER ::   zam          = 2. * zc     ! Eq. 14
1155      REAL(wp), PARAMETER ::   zah          = 3. * zc     ! Eq. 30
1156      REAL(wp), PARAMETER ::   z1_alpha     = 1._wp / 0.2_wp  ! Eq. 51
1157      REAL(wp), PARAMETER ::   z1_alphaf    = z1_alpha    ! Eq. 56
1158      REAL(wp), PARAMETER ::   zbetah       = 1.e-3_wp    ! Eq. 26
1159      REAL(wp), PARAMETER ::   zgamma       = 1.25_wp     ! Eq. 26
1160      REAL(wp), PARAMETER ::   z1_gamma     = 1._wp / zgamma
1161      REAL(wp), PARAMETER ::   r1_3         = 1._wp / 3._wp
1162      !
1163      INTEGER  ::   ji, jj         ! dummy loop indices
1164      REAL(wp) ::   zthetav_os, zthetav_is, zthetav_zu
1165      REAL(wp) ::   zrib_o, zrib_i
1166      REAL(wp) ::   zCdn_skin_ice, zCdn_form_ice, zCdn_ice
1167      REAL(wp) ::   zChn_skin_ice, zChn_form_ice
1168      REAL(wp) ::   z0w, z0i, zfmi, zfmw, zfhi, zfhw
1169      REAL(wp) ::   zCdn_form_tmp
1170      !!----------------------------------------------------------------------
1171
1172      ! mean temperature
1173      WHERE( at_i_b(:,:) > 1.e-20 )
1174         ztm_su(:,:) = SUM( t_su(:,:,:) * a_i_b(:,:,:) , dim=3 ) / at_i_b(:,:)
1175      ELSEWHERE
1176         ztm_su(:,:) = rt0
1177      ENDWHERE
1178
1179      ! Momentum Neutral Transfert Coefficients (should be a constant)
1180      zCdn_form_tmp = zce10 * ( LOG( 10._wp / z0_form_ice + 1._wp ) / LOG( rn_zu / z0_form_ice + 1._wp ) )**2   ! Eq. 40
1181      zCdn_skin_ice = ( vkarmn                                      / LOG( rn_zu / z0_skin_ice + 1._wp ) )**2   ! Eq. 7
1182      zCdn_ice      = zCdn_skin_ice   ! Eq. 7 (cf Lupkes email for details)
1183      !zCdn_ice     = 1.89e-3         ! old ECHAM5 value (cf Eq. 32)
1184
1185      ! Heat Neutral Transfert Coefficients
1186      zChn_skin_ice = vkarmn**2 / ( LOG( rn_zu / z0_ice + 1._wp ) * LOG( rn_zu * z1_alpha / z0_skin_ice + 1._wp ) )   ! Eq. 50 + Eq. 52 (cf Lupkes email for details)
1187
1188      ! Atmospheric and Surface Variables
1189      zst(:,:)     = sst_m(:,:) + rt0                                        ! convert SST from Celcius to Kelvin
1190      zqo_sat(:,:) = rdct_qsat_salt * q_sat( zst(:,:)   , sf(jp_slp)%fnow(:,:,1) )  ! saturation humidity over ocean [kg/kg]
1191      zqi_sat(:,:) =                  q_sat( ztm_su(:,:), sf(jp_slp)%fnow(:,:,1) )  ! saturation humidity over ice   [kg/kg] !LB: no 0.98 !!(rdct_qsat_salt)
1192      !
1193      DO jj = 2, jpjm1           ! reduced loop is necessary for reproducibility
1194         DO ji = fs_2, fs_jpim1
1195            ! Virtual potential temperature [K]
1196            zthetav_os = zst(ji,jj)    * ( 1._wp + rctv0 * zqo_sat(ji,jj) )   ! over ocean
1197            zthetav_is = ztm_su(ji,jj) * ( 1._wp + rctv0 * zqi_sat(ji,jj) )   ! ocean ice
1198            zthetav_zu = t_zu (ji,jj)  * ( 1._wp + rctv0 * q_zu(ji,jj)    )   ! at zu
1199
1200            ! Bulk Richardson Number (could use Ri_bulk function from aerobulk instead)
1201            zrib_o = grav / zthetav_os * ( zthetav_zu - zthetav_os ) * rn_zu / MAX( 0.5, wndm(ji,jj)     )**2   ! over ocean
1202            zrib_i = grav / zthetav_is * ( zthetav_zu - zthetav_is ) * rn_zu / MAX( 0.5, wndm_ice(ji,jj) )**2   ! over ice
1203
1204            ! Momentum and Heat Neutral Transfert Coefficients
1205            zCdn_form_ice = zCdn_form_tmp * at_i_b(ji,jj) * ( 1._wp - at_i_b(ji,jj) )**zbeta  ! Eq. 40
1206            zChn_form_ice = zCdn_form_ice / ( 1._wp + ( LOG( z1_alphaf ) / vkarmn ) * SQRT( zCdn_form_ice ) )               ! Eq. 53
1207
1208            ! Momentum and Heat Stability functions (possibility to use psi_m_ecmwf instead)
1209            z0w = rn_zu * EXP( -1._wp * vkarmn / SQRT( Cdn_oce(ji,jj) ) ) ! over water
1210            z0i = z0_skin_ice                                             ! over ice (cf Lupkes email for details)
1211            IF( zrib_o <= 0._wp ) THEN
1212               zfmw = 1._wp - zam * zrib_o / ( 1._wp + 3._wp * zc2 * Cdn_oce(ji,jj) * SQRT( -zrib_o * ( rn_zu / z0w + 1._wp ) ) )  ! Eq. 10
1213               zfhw = ( 1._wp + ( zbetah * ( zthetav_os - zthetav_zu )**r1_3 / ( Chn_oce(ji,jj) * MAX(0.01, wndm(ji,jj)) )   &     ! Eq. 26
1214                  &             )**zgamma )**z1_gamma
1215            ELSE
1216               zfmw = 1._wp / ( 1._wp + zam * zrib_o / SQRT( 1._wp + zrib_o ) )   ! Eq. 12
1217               zfhw = 1._wp / ( 1._wp + zah * zrib_o / SQRT( 1._wp + zrib_o ) )   ! Eq. 28
1218            ENDIF
1219
1220            IF( zrib_i <= 0._wp ) THEN
1221               zfmi = 1._wp - zam * zrib_i / (1._wp + 3._wp * zc2 * zCdn_ice * SQRT( -zrib_i * ( rn_zu / z0i + 1._wp)))   ! Eq.  9
1222               zfhi = 1._wp - zah * zrib_i / (1._wp + 3._wp * zc2 * zCdn_ice * SQRT( -zrib_i * ( rn_zu / z0i + 1._wp)))   ! Eq. 25
1223            ELSE
1224               zfmi = 1._wp / ( 1._wp + zam * zrib_i / SQRT( 1._wp + zrib_i ) )   ! Eq. 11
1225               zfhi = 1._wp / ( 1._wp + zah * zrib_i / SQRT( 1._wp + zrib_i ) )   ! Eq. 27
1226            ENDIF
1227
1228            ! Momentum Transfert Coefficients (Eq. 38)
1229            Cd(ji,jj) = zCdn_skin_ice *   zfmi +  &
1230               &        zCdn_form_ice * ( zfmi * at_i_b(ji,jj) + zfmw * ( 1._wp - at_i_b(ji,jj) ) ) / MAX( 1.e-06, at_i_b(ji,jj) )
1231
1232            ! Heat Transfert Coefficients (Eq. 49)
1233            Ch(ji,jj) = zChn_skin_ice *   zfhi +  &
1234               &        zChn_form_ice * ( zfhi * at_i_b(ji,jj) + zfhw * ( 1._wp - at_i_b(ji,jj) ) ) / MAX( 1.e-06, at_i_b(ji,jj) )
1235            !
1236         END DO
1237      END DO
1238      CALL lbc_lnk_multi( 'sbcblk', Cd, 'T',  1., Ch, 'T', 1. )
1239      !
1240   END SUBROUTINE Cdn10_Lupkes2015
1241
1242#endif
1243
1244   !!======================================================================
1245END MODULE sbcblk
Note: See TracBrowser for help on using the repository browser.