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_ASINTER-01-05_merged/src/OCE/SBC – NEMO

source: NEMO/branches/2019/dev_ASINTER-01-05_merged/src/OCE/SBC/sbcblk.F90 @ 12063

Last change on this file since 12063 was 12063, checked in by gsamson, 4 years ago

dev_ASINTER-01-05_merged: update branch with dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk@r12061 and trunk@r12055 + bugfix for agrif compatibility in sbcblk: sette tests with ref configs ok except ABL restartability (under investigation) (tickets #2159 and #2131)

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