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.
Changeset 15466 for NEMO/branches/2021 – NEMO

Changeset 15466 for NEMO/branches/2021


Ignore:
Timestamp:
2021-11-02T10:48:56+01:00 (3 years ago)
Author:
cdllod
Message:

updated and simplified zdfiwm routine

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r15388_updated_zdfiwm/src/OCE/ZDF/zdfiwm.F90

    r14882 r15466  
    99   !!            3.6  !  2016-03  (C. de Lavergne)  New param: internal wave-driven mixing  
    1010   !!            4.0  !  2017-04  (G. Madec)  renamed module, remove the old param. and the CPP keys 
     11   !!            4.0  !  2020-12  (C. de Lavergne)  Update param to match published one 
     12   !!            4.0  !  2021-09  (C. de Lavergne)  Add energy from trapped and shallow internal tides 
    1113   !!---------------------------------------------------------------------- 
    1214 
     
    3739 
    3840   !                      !!* Namelist  namzdf_iwm : internal wave-driven mixing * 
    39    INTEGER ::  nn_zpyc     ! pycnocline-intensified mixing energy proportional to N (=1) or N^2 (=2) 
    4041   LOGICAL ::  ln_mevar    ! variable (=T) or constant (=F) mixing efficiency 
    4142   LOGICAL ::  ln_tsdiff   ! account for differential T/S wave-driven mixing (=T) or not (=F) 
    4243 
    4344   REAL(wp)::  r1_6 = 1._wp / 6._wp 
    44  
    45    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ebot_iwm   ! power available from high-mode wave breaking (W/m2) 
    46    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   epyc_iwm   ! power available from low-mode, pycnocline-intensified wave breaking (W/m2) 
    47    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ecri_iwm   ! power available from low-mode, critical slope wave breaking (W/m2) 
    48    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hbot_iwm   ! WKB decay scale for high-mode energy dissipation (m) 
    49    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hcri_iwm   ! decay scale for low-mode critical slope dissipation (m) 
     45   REAL(wp)::  rnu  = 1.4e-6_wp   ! molecular kinematic viscosity 
     46 
     47   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ebot_iwm   ! bottom-intensified dissipation above abyssal hills (W/m2) 
     48   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ecri_iwm   ! bottom-intensified dissipation at topographic slopes (W/m2) 
     49   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ensq_iwm   ! dissipation scaling with squared buoyancy frequency (W/m2) 
     50   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   esho_iwm   ! dissipation due to shoaling internal tides (W/m2) 
     51   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hbot_iwm   ! decay scale for abyssal hill dissipation (m) 
     52   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hcri_iwm   ! inverse decay scale for topographic slope dissipation (m-1) 
    5053 
    5154   !! * Substitutions 
     
    6366      !!                ***  FUNCTION zdf_iwm_alloc  *** 
    6467      !!---------------------------------------------------------------------- 
    65       ALLOCATE( ebot_iwm(jpi,jpj),  epyc_iwm(jpi,jpj),  ecri_iwm(jpi,jpj) ,     & 
    66       &         hbot_iwm(jpi,jpj),  hcri_iwm(jpi,jpj)                    , STAT=zdf_iwm_alloc ) 
     68      ALLOCATE( ebot_iwm(jpi,jpj),  ecri_iwm(jpi,jpj),  ensq_iwm(jpi,jpj) ,     & 
     69      &         esho_iwm(jpi,jpj),  hbot_iwm(jpi,jpj),  hcri_iwm(jpi,jpj) , STAT=zdf_iwm_alloc ) 
    6770      ! 
    6871      CALL mpp_sum ( 'zdfiwm', zdf_iwm_alloc ) 
     
    7982      !! 
    8083      !! ** Method  : - internal wave-driven vertical mixing is given by: 
    81       !!                  Kz_wave = min(  100 cm2/s, f(  Reb = zemx_iwm /( Nu * N^2 )  ) 
     84      !!                  Kz_wave = min( f( Reb = zemx_iwm / (Nu * N^2) ), 100 cm2/s  ) 
    8285      !!              where zemx_iwm is the 3D space distribution of the wave-breaking  
    8386      !!              energy and Nu the molecular kinematic viscosity. 
     
    8790      !!              - Compute zemx_iwm, the 3D power density that allows to compute 
    8891      !!              Reb and therefrom the wave-induced vertical diffusivity. 
    89       !!              This is divided into three components: 
    90       !!                 1. Bottom-intensified low-mode dissipation at critical slopes 
     92      !!              This is divided into four components: 
     93      !!                 1. Bottom-intensified dissipation at topographic slopes, expressed 
     94      !!              as an exponential decay above the bottom. 
    9195      !!                     zemx_iwm(z) = ( ecri_iwm / rho0 ) * EXP( -(H-z)/hcri_iwm ) 
    9296      !!                                   / ( 1. - EXP( - H/hcri_iwm ) ) * hcri_iwm 
    9397      !!              where hcri_iwm is the characteristic length scale of the bottom  
    94       !!              intensification, ecri_iwm a map of available power, and H the ocean depth. 
    95       !!                 2. Pycnocline-intensified low-mode dissipation 
    96       !!                     zemx_iwm(z) = ( epyc_iwm / rho0 ) * ( sqrt(rn2(z))^nn_zpyc ) 
    97       !!                                   / SUM( sqrt(rn2(z))^nn_zpyc * e3w[z) ) 
    98       !!              where epyc_iwm is a map of available power, and nn_zpyc 
    99       !!              is the chosen stratification-dependence of the internal wave 
    100       !!              energy dissipation. 
    101       !!                 3. WKB-height dependent high mode dissipation 
    102       !!                     zemx_iwm(z) = ( ebot_iwm / rho0 ) * rn2(z) * EXP(-z_wkb(z)/hbot_iwm) 
    103       !!                                   / SUM( rn2(z) * EXP(-z_wkb(z)/hbot_iwm) * e3w[z) ) 
    104       !!              where hbot_iwm is the characteristic length scale of the WKB bottom  
    105       !!              intensification, ebot_iwm is a map of available power, and z_wkb is the 
    106       !!              WKB-stretched height above bottom defined as 
    107       !!                    z_wkb(z) = H * SUM( sqrt(rn2(z'>=z)) * e3w[z'>=z) ) 
    108       !!                                 / SUM( sqrt(rn2(z'))    * e3w[z')    ) 
    109       !! 
    110       !!              - update the model vertical eddy viscosity and diffusivity:  
    111       !!                     avt  = avt  +    av_wave 
     98      !!              intensification, ecri_iwm a static 2D map of available power, and  
     99      !!              H the ocean depth. 
     100      !!                 2. Bottom-intensified dissipation above abyssal hills, expressed 
     101      !!              as an algebraic decay above bottom. 
     102      !!                     zemx_iwm(z) = ( ebot_iwm / rho0 ) * ( 1 + hbot_iwm/H )  
     103      !!                                   / ( 1 + (H-z)/hbot_iwm )^2                                 
     104      !!              where hbot_iwm is the characteristic length scale of the bottom  
     105      !!              intensification and ebot_iwm is a static 2D map of available power. 
     106      !!                 3. Dissipation scaling in the vertical with the squared buoyancy  
     107      !!              frequency (N^2). 
     108      !!                     zemx_iwm(z) = ( ensq_iwm / rho0 ) * rn2(z) 
     109      !!                                   / ZSUM( rn2 * e3w ) 
     110      !!              where ensq_iwm is a static 2D map of available power. 
     111      !!                 4. Dissipation due to shoaling internal tides, scaling in the 
     112      !!              vertical with the buoyancy frequency (N). 
     113      !!                     zemx_iwm(z) = ( esho_iwm / rho0 ) * sqrt(rn2(z)) 
     114      !!                                   / ZSUM( sqrt(rn2) * e3w ) 
     115      !!              where esho_iwm is a static 2D map of available power. 
     116      !! 
     117      !!              - update the model vertical eddy viscosity and diffusivity: 
     118      !!                     avt  = avt  +    av_wave  
     119      !!                     avs  = avs  +    av_wave 
    112120      !!                     avm  = avm  +    av_wave 
    113121      !! 
    114122      !!              - if namelist parameter ln_tsdiff = T, account for differential mixing: 
    115       !!                     avs  = avt  +    av_wave * diffusivity_ratio(Reb) 
     123      !!                     avs  = avs  +    av_wave * diffusivity_ratio(Reb) 
    116124      !! 
    117125      !! ** Action  : - avt, avs, avm, increased by tide internal wave-driven mixing     
    118126      !! 
    119       !! References :  de Lavergne et al. 2015, JPO; 2016, in prep. 
     127      !! References :  de Lavergne et al. JAMES 2020, https://doi.org/10.1029/2020MS002065 
     128      !!               de Lavergne et al. JPO 2016, https://doi.org/10.1175/JPO-D-14-0259.1 
    120129      !!---------------------------------------------------------------------- 
    121130      INTEGER                    , INTENT(in   ) ::   kt             ! ocean time step 
    122       INTEGER                    , INTENT(in   ) ::   Kmm            ! time level index 
     131      INTEGER                    , INTENT(in   ) ::   Kmm            ! time level index       
    123132      REAL(wp), DIMENSION(:,:,:) , INTENT(inout) ::   p_avm          ! momentum Kz (w-points) 
    124133      REAL(wp), DIMENSION(:,:,:) , INTENT(inout) ::   p_avt, p_avs   ! tracer   Kz (w-points) 
     
    128137      REAL(wp)       :: ztmp1, ztmp2        ! scalar workspace 
    129138      REAL(wp), DIMENSION(A2D(nn_hls))     ::   zfact       ! Used for vertical structure 
    130       REAL(wp), DIMENSION(A2D(nn_hls))     ::   zhdep       ! Ocean depth 
    131       REAL(wp), DIMENSION(A2D(nn_hls),jpk) ::   zwkb        ! WKB-stretched height above bottom 
    132       REAL(wp), DIMENSION(A2D(nn_hls),jpk) ::   zweight     ! Weight for high mode vertical distribution 
    133       REAL(wp), DIMENSION(A2D(nn_hls),jpk) ::   znu_t       ! Molecular kinematic viscosity (T grid) 
    134       REAL(wp), DIMENSION(A2D(nn_hls),jpk) ::   znu_w       ! Molecular kinematic viscosity (W grid) 
    135139      REAL(wp), DIMENSION(A2D(nn_hls),jpk) ::   zReb        ! Turbulence intensity parameter 
    136140      REAL(wp), DIMENSION(A2D(nn_hls),jpk) ::   zemx_iwm    ! local energy density available for mixing (W/kg) 
     
    141145      !!---------------------------------------------------------------------- 
    142146      ! 
    143       !                        
    144       ! Set to zero the 1st and last vertical levels of appropriate variables 
     147      !                       !* Set to zero the 1st and last vertical levels of appropriate variables 
    145148      IF( iom_use("emix_iwm") ) THEN 
    146149         zemx_iwm(:,:,:) = 0._wp 
     
    157160      !                       ! ----------------------------- ! 
    158161      !                              
    159       !                       !* Critical slope mixing: distribute energy over the time-varying ocean depth, 
    160       !                                                 using an exponential decay from the seafloor. 
    161       DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 )             ! part independent of the level 
    162          zhdep(ji,jj) = gdepw_0(ji,jj,mbkt(ji,jj)+1)       ! depth of the ocean 
    163          zfact(ji,jj) = rho0 * (  1._wp - EXP( -zhdep(ji,jj) / hcri_iwm(ji,jj) )  ) 
     162      !                       !* 'cri' component: distribute energy over the time-varying 
     163      !                       !* ocean depth using an exponential decay from the seafloor. 
     164      DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 )                ! part independent of the level 
     165         zfact(ji,jj) = rho0 * (  1._wp - EXP( -ht(ji,jj) * hcri_iwm(ji,jj) )  ) 
    164166         IF( zfact(ji,jj) /= 0._wp )   zfact(ji,jj) = ecri_iwm(ji,jj) / zfact(ji,jj) 
    165167      END_2D 
    166 !!gm gde3w ==>>>  check for ssh taken into account.... seem OK gde3w_n=gdept(:,:,:,Kmm) - ssh(:,:,Kmm) 
    167       DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )   ! complete with the level-dependent part 
     168 
     169      DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )      ! complete with the level-dependent part 
    168170         IF ( zfact(ji,jj) == 0._wp .OR. wmask(ji,jj,jk) == 0._wp ) THEN   ! optimization 
    169171            zemx_iwm(ji,jj,jk) = 0._wp 
    170172         ELSE 
    171             zemx_iwm(ji,jj,jk) = zfact(ji,jj) * (  EXP( ( gde3w(ji,jj,jk  ) - zhdep(ji,jj) ) / hcri_iwm(ji,jj) )     & 
    172                  &                               - EXP( ( gde3w(ji,jj,jk-1) - zhdep(ji,jj) ) / hcri_iwm(ji,jj) ) )   & 
    173                  &                            / ( gde3w(ji,jj,jk) - gde3w(ji,jj,jk-1) ) 
     173            zemx_iwm(ji,jj,jk) = zfact(ji,jj) * (  EXP( ( gdept(ji,jj,jk  ,Kmm) - ht(ji,jj) ) * hcri_iwm(ji,jj) )     & 
     174                 &                               - EXP( ( gdept(ji,jj,jk-1,Kmm) - ht(ji,jj) ) * hcri_iwm(ji,jj) ) )   & 
     175                 &                            / e3w(ji,jj,jk,Kmm) 
    174176         ENDIF 
    175177      END_3D 
    176 !!gm delta(gde3w) = e3t(:,:,:,Kmm)  !!  Please verify the grid-point position w versus t-point 
    177 !!gm it seems to me that only 1/hcri_iwm  is used ==>  compute it one for all 
    178  
    179  
    180       !                        !* Pycnocline-intensified mixing: distribute energy over the time-varying  
    181       !                        !* ocean depth as proportional to sqrt(rn2)^nn_zpyc 
    182       !                                          ! (NB: N2 is masked, so no use of wmask here) 
    183       SELECT CASE ( nn_zpyc ) 
    184       ! 
    185       CASE ( 1 )               ! Dissipation scales as N (recommended) 
    186          ! 
    187          DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
    188             zfact(ji,jj) = 0._wp 
    189          END_2D 
    190          DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )       ! part independent of the level 
    191             zfact(ji,jj) = zfact(ji,jj) + e3w(ji,jj,jk,Kmm) * SQRT(  MAX( 0._wp, rn2(ji,jj,jk) )  ) * wmask(ji,jj,jk) 
    192          END_3D 
    193          ! 
    194          DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
    195             IF( zfact(ji,jj) /= 0 )   zfact(ji,jj) = epyc_iwm(ji,jj) / ( rho0 * zfact(ji,jj) ) 
    196          END_2D 
    197          ! 
    198          DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )       ! complete with the level-dependent part 
    199             zemx_iwm(ji,jj,jk) = zemx_iwm(ji,jj,jk) + zfact(ji,jj) * SQRT(  MAX( 0._wp, rn2(ji,jj,jk) )  ) * wmask(ji,jj,jk) 
    200          END_3D 
    201          ! 
    202       CASE ( 2 )               ! Dissipation scales as N^2 
    203          ! 
    204          DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
    205             zfact(ji,jj) = 0._wp 
    206          END_2D 
    207          DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )       ! part independent of the level 
    208             zfact(ji,jj) = zfact(ji,jj) + e3w(ji,jj,jk,Kmm) * MAX( 0._wp, rn2(ji,jj,jk) ) * wmask(ji,jj,jk) 
    209          END_3D 
    210          ! 
    211          DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
    212             IF( zfact(ji,jj) /= 0 )   zfact(ji,jj) = epyc_iwm(ji,jj) / ( rho0 * zfact(ji,jj) ) 
    213          END_2D 
    214          ! 
    215          DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 ) 
    216             zemx_iwm(ji,jj,jk) = zemx_iwm(ji,jj,jk) + zfact(ji,jj) * MAX( 0._wp, rn2(ji,jj,jk) ) * wmask(ji,jj,jk) 
    217          END_3D 
    218          ! 
    219       END SELECT 
    220  
    221       !                        !* WKB-height dependent mixing: distribute energy over the time-varying  
    222       !                        !* ocean depth as proportional to rn2 * exp(-z_wkb/rn_hbot) 
    223       ! 
    224       DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
    225          zwkb(ji,jj,1) = 0._wp 
    226       END_2D 
    227       DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 ) 
    228          zwkb(ji,jj,jk) = zwkb(ji,jj,jk-1) + e3w(ji,jj,jk,Kmm) * SQRT(  MAX( 0._wp, rn2(ji,jj,jk) )  ) * wmask(ji,jj,jk) 
    229       END_3D 
    230       DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
    231          zfact(ji,jj) = zwkb(ji,jj,jpkm1) 
    232       END_2D 
    233       ! 
    234       DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 ) 
    235          IF( zfact(ji,jj) /= 0 )   zwkb(ji,jj,jk) = zhdep(ji,jj) * ( zfact(ji,jj) - zwkb(ji,jj,jk) )   & 
    236             &                                     * wmask(ji,jj,jk) / zfact(ji,jj) 
    237       END_3D 
    238       DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
    239          zwkb (ji,jj,1) = zhdep(ji,jj) * wmask(ji,jj,1) 
    240       END_2D 
    241       ! 
    242       DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 ) 
    243          IF ( rn2(ji,jj,jk) <= 0._wp .OR. wmask(ji,jj,jk) == 0._wp ) THEN   ! optimization: EXP coast a lot 
    244             zweight(ji,jj,jk) = 0._wp 
    245          ELSE 
    246             zweight(ji,jj,jk) = rn2(ji,jj,jk) * hbot_iwm(ji,jj)    & 
    247                &   * (  EXP( -zwkb(ji,jj,jk) / hbot_iwm(ji,jj) ) - EXP( -zwkb(ji,jj,jk-1) / hbot_iwm(ji,jj) )  ) 
    248          ENDIF 
    249       END_3D 
    250       ! 
     178 
     179                               !* 'bot' component: distribute energy over the time-varying 
     180                               !* ocean depth using an algebraic decay above the seafloor. 
    251181      DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
    252182         zfact(ji,jj) = 0._wp 
    253183      END_2D 
    254       DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )       ! part independent of the level 
    255          zfact(ji,jj) = zfact(ji,jj) + zweight(ji,jj,jk) 
    256       END_3D 
    257       ! 
     184      DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 )               ! part independent of the level 
     185         IF( ht(ji,jj) /= 0._wp )  zfact(ji,jj) = ebot_iwm(ji,jj) * (  1._wp +  hbot_iwm(ji,jj) / ht(ji,jj)  ) / rho0 
     186      END_2D 
     187 
     188      DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )     ! complete with the level-dependent part 
     189         zemx_iwm(ji,jj,jk) = zemx_iwm(ji,jj,jk) +                                                                                          &  
     190            &         zfact(ji,jj) * (   1._wp / ( 1._wp + ( ht(ji,jj) - gdept(ji,jj,jk  ,Kmm) ) / hbot_iwm(ji,jj) )                        & 
     191            &                         -  1._wp / ( 1._wp + ( ht(ji,jj) - gdept(ji,jj,jk-1,Kmm) ) / hbot_iwm(ji,jj) )   ) * wmask(ji,jj,jk)  & 
     192            &                      / e3w(ji,jj,jk,Kmm) 
     193      END_3D 
     194 
     195                               !* 'nsq' component: distribute energy over the time-varying  
     196                               !* ocean depth as proportional to rn2 
    258197      DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
    259          IF( zfact(ji,jj) /= 0 )   zfact(ji,jj) = ebot_iwm(ji,jj) / ( rho0 * zfact(ji,jj) ) 
    260       END_2D 
    261       ! 
    262       DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )       ! complete with the level-dependent part 
    263          zemx_iwm(ji,jj,jk) = zemx_iwm(ji,jj,jk) + zweight(ji,jj,jk) * zfact(ji,jj) * wmask(ji,jj,jk)   & 
    264             &                                                        / ( gde3w(ji,jj,jk) - gde3w(ji,jj,jk-1) ) 
    265 !!gm  use of e3t(ji,jj,:,Kmm) just above? 
    266       END_3D 
    267       ! 
    268 !!gm  this is to be replaced by just a constant value znu=1.e-6 m2/s 
    269       ! Calculate molecular kinematic viscosity 
    270       DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 1, jpkm1 ) 
    271          znu_t(ji,jj,jk) = 1.e-4_wp * (  17.91_wp - 0.53810_wp * ts(ji,jj,jk,jp_tem,Kmm)   & 
    272             &                                     + 0.00694_wp * ts(ji,jj,jk,jp_tem,Kmm) * ts(ji,jj,jk,jp_tem,Kmm)  & 
    273             &                                     + 0.02305_wp * ts(ji,jj,jk,jp_sal,Kmm)  ) * tmask(ji,jj,jk) * r1_rho0 
    274       END_3D 
    275       DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 ) 
    276          znu_w(ji,jj,jk) = 0.5_wp * ( znu_t(ji,jj,jk-1) + znu_t(ji,jj,jk) ) * wmask(ji,jj,jk) 
    277       END_3D 
    278 !!gm end 
    279       ! 
     198         zfact(ji,jj) = 0._wp 
     199      END_2D 
     200      DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )     ! part independent of the level 
     201         zfact(ji,jj) = zfact(ji,jj) + e3w(ji,jj,jk,Kmm) * MAX( 0._wp, rn2(ji,jj,jk) ) 
     202      END_3D 
     203      ! 
     204      DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
     205         IF( zfact(ji,jj) /= 0._wp )   zfact(ji,jj) = ensq_iwm(ji,jj) / ( rho0 * zfact(ji,jj) ) 
     206      END_2D 
     207      ! 
     208      DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )     ! complete with the level-dependent part 
     209         zemx_iwm(ji,jj,jk) = zemx_iwm(ji,jj,jk) + zfact(ji,jj) * MAX( 0._wp, rn2(ji,jj,jk) ) 
     210      END_3D 
     211 
     212                               !* 'sho' component: distribute energy over the time-varying  
     213                               !* ocean depth as proportional to sqrt(rn2) 
     214      DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
     215         zfact(ji,jj) = 0._wp 
     216      END_2D 
     217      DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )     ! part independent of the level 
     218         zfact(ji,jj) = zfact(ji,jj) + e3w(ji,jj,jk,Kmm) * SQRT(  MAX( 0._wp, rn2(ji,jj,jk) )  ) 
     219      END_3D 
     220      ! 
     221      DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) 
     222         IF( zfact(ji,jj) /= 0._wp )   zfact(ji,jj) = esho_iwm(ji,jj) / ( rho0 * zfact(ji,jj) ) 
     223      END_2D 
     224      ! 
     225      DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )     ! complete with the level-dependent part 
     226         zemx_iwm(ji,jj,jk) = zemx_iwm(ji,jj,jk) + zfact(ji,jj) * SQRT(  MAX( 0._wp, rn2(ji,jj,jk) )  ) 
     227      END_3D 
     228 
    280229      ! Calculate turbulence intensity parameter Reb 
    281230      DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 ) 
    282          zReb(ji,jj,jk) = zemx_iwm(ji,jj,jk) / MAX( 1.e-20_wp, znu_w(ji,jj,jk) * rn2(ji,jj,jk) ) 
     231         zReb(ji,jj,jk) = zemx_iwm(ji,jj,jk) / MAX( 1.e-20_wp, rnu * rn2(ji,jj,jk) ) 
    283232      END_3D 
    284233      ! 
    285234      ! Define internal wave-induced diffusivity 
    286235      DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 ) 
    287          zav_wave(ji,jj,jk) = znu_w(ji,jj,jk) * zReb(ji,jj,jk) * r1_6   ! This corresponds to a constant mixing efficiency of 1/6 
    288       END_3D 
    289       ! 
    290       IF( ln_mevar ) THEN                ! Variable mixing efficiency case : modify zav_wave in the 
    291          DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )   ! energetic (Reb > 480) and buoyancy-controlled (Reb <10.224 ) regimes 
     236         zav_wave(ji,jj,jk) = zReb(ji,jj,jk) * r1_6 * rnu  ! This corresponds to a constant mixing efficiency of 1/6 
     237      END_3D 
     238      ! 
     239      IF( ln_mevar ) THEN                                          ! Variable mixing efficiency case : modify zav_wave in the 
     240         DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 ) ! energetic (Reb > 480) and buoyancy-controlled (Reb <10.224) regimes 
    292241            IF( zReb(ji,jj,jk) > 480.00_wp ) THEN 
    293                zav_wave(ji,jj,jk) = 3.6515_wp * znu_w(ji,jj,jk) * SQRT( zReb(ji,jj,jk) ) 
     242               zav_wave(ji,jj,jk) = 3.6515_wp * rnu * SQRT( zReb(ji,jj,jk) ) 
    294243            ELSEIF( zReb(ji,jj,jk) < 10.224_wp ) THEN 
    295                zav_wave(ji,jj,jk) = 0.052125_wp * znu_w(ji,jj,jk) * zReb(ji,jj,jk) * SQRT( zReb(ji,jj,jk) ) 
     244               zav_wave(ji,jj,jk) = 0.052125_wp * rnu * zReb(ji,jj,jk) * SQRT( zReb(ji,jj,jk) ) 
    296245            ENDIF 
    297246         END_3D 
    298247      ENDIF 
    299248      ! 
    300       DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )      ! Bound diffusivity by molecular value and 100 cm2/s 
     249      DO_3D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )    ! Bound diffusivity by molecular value and 100 cm2/s 
    301250         zav_wave(ji,jj,jk) = MIN(  MAX( 1.4e-7_wp, zav_wave(ji,jj,jk) ), 1.e-2_wp  ) * wmask(ji,jj,jk) 
    302251      END_3D 
     
    304253      IF( kt == nit000 ) THEN        !* Control print at first time-step: diagnose the energy consumed by zav_wave 
    305254         IF( .NOT. l_istiled .OR. ntile == 1 ) zztmp = 0._wp                    ! Do only on the first tile 
    306 !!gm used of glosum 3D.... 
    307255         DO_3D( 0, 0, 0, 0, 2, jpkm1 ) 
    308256            zztmp = zztmp + e3w(ji,jj,jk,Kmm) * e1e2t(ji,jj)   & 
     
    327275      !                          !   Update  mixing coefs  !                           
    328276      !                          ! ----------------------- ! 
    329       !       
     277      ! 
    330278      IF( ln_tsdiff ) THEN                !* Option for differential mixing of salinity and temperature 
    331279         ztmp1 = 0.505_wp + 0.495_wp * TANH( 0.92_wp * ( LOG10( 1.e-20_wp ) - 0.60_wp ) ) 
     
    339287         END_3D 
    340288         CALL iom_put( "av_ratio", zav_ratio ) 
    341          DO_3D_OVR( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 )    !* update momentum & tracer diffusivity with wave-driven mixing 
     289         DO_3D_OVR( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1, 2, jpkm1 ) !* update momentum & tracer diffusivity with wave-driven mixing 
    342290            p_avs(ji,jj,jk) = p_avs(ji,jj,jk) + zav_wave(ji,jj,jk) * zav_ratio(ji,jj,jk) 
    343291            p_avt(ji,jj,jk) = p_avt(ji,jj,jk) + zav_wave(ji,jj,jk) 
     
    352300         END_3D 
    353301      ENDIF 
    354  
    355       !                                   !* output internal wave-driven mixing coefficient 
     302      !                             !* output internal wave-driven mixing coefficient 
    356303      CALL iom_put( "av_wave", zav_wave ) 
    357                                           !* output useful diagnostics: Kz*N^2 ,  
    358 !!gm Kz*N2 should take into account the ratio avs/avt if it is used.... (see diaar5) 
    359                                           !  vertical integral of rho0 * Kz * N^2 , energy density (zemx_iwm) 
     304                                    !* output useful diagnostics: Kz*N^2 ,  
     305                                    !  vertical integral of rho0 * Kz * N^2 , energy density (zemx_iwm) 
    360306      IF( iom_use("bflx_iwm") .OR. iom_use("pcmap_iwm") ) THEN 
    361307         ALLOCATE( z2d(A2D(nn_hls)) , z3d(A2D(nn_hls),jpk) ) 
     
    375321      ENDIF 
    376322      CALL iom_put( "emix_iwm", zemx_iwm ) 
    377        
     323 
    378324      IF(sn_cfctl%l_prtctl)   CALL prt_ctl(tab3d_1=zav_wave , clinfo1=' iwm - av_wave: ', tab3d_2=avt, clinfo2=' avt: ', kdim=jpk) 
    379325      ! 
     
    391337      !! 
    392338      !!              - Read the input data in NetCDF files : 
    393       !!              power available from high-mode wave breaking (mixing_power_bot.nc) 
    394       !!              power available from pycnocline-intensified wave-breaking (mixing_power_pyc.nc) 
    395       !!              power available from critical slope wave-breaking (mixing_power_cri.nc) 
    396       !!              WKB decay scale for high-mode wave-breaking (decay_scale_bot.nc) 
    397       !!              decay scale for critical slope wave-breaking (decay_scale_cri.nc) 
     339      !!              bottom-intensified dissipation above abyssal hills (mixing_power_bot.nc) 
     340      !!              bottom-intensified dissipation at topographic slopes (mixing_power_cri.nc) 
     341      !!              dissipation scaling with squared buoyancy frequency (mixing_power_nsq.nc) 
     342      !!              dissipation due to shoaling internal tides (mixing_power_sho.nc) 
     343      !!              decay scale for abyssal hill dissipation (decay_scale_bot.nc) 
     344      !!              decay scale for topographic-slope dissipation (decay_scale_cri.nc) 
    398345      !! 
    399346      !! ** input   : - Namlist namzdf_iwm 
    400       !!              - NetCDF files : mixing_power_bot.nc, mixing_power_pyc.nc, mixing_power_cri.nc, 
    401       !!              decay_scale_bot.nc decay_scale_cri.nc 
     347      !!              - NetCDF files : mixing_power_bot.nc, mixing_power_cri.nc, mixing_power_nsq.nc, 
     348      !!              mixing_power_sho.nc, decay_scale_bot.nc, decay_scale_cri.nc 
    402349      !! 
    403350      !! ** Action  : - Increase by 1 the nstop flag is setting problem encounter 
    404       !!              - Define ebot_iwm, epyc_iwm, ecri_iwm, hbot_iwm, hcri_iwm 
    405       !! 
    406       !! References : de Lavergne et al. JPO, 2015 ; de Lavergne PhD 2016 
    407       !!              de Lavergne et al. in prep., 2017 
     351      !!              - Define ebot_iwm, ecri_iwm, ensq_iwm, esho_iwm, hbot_iwm, hcri_iwm 
     352      !! 
     353      !! References : de Lavergne et al. JAMES 2020, https://doi.org/10.1029/2020MS002065 
    408354      !!---------------------------------------------------------------------- 
    409355      INTEGER  ::   ifpr               ! dummy loop indices 
    410356      INTEGER  ::   inum               ! local integer 
    411357      INTEGER  ::   ios 
    412       REAL(wp) ::   zbot, zpyc, zcri   ! local scalars 
     358      REAL(wp) ::   zbot, zcri, znsq, zsho   ! local scalars 
    413359      ! 
    414360      CHARACTER(len=256)            ::   cn_dir                 ! Root directory for location of ssr files 
    415       INTEGER, PARAMETER            ::   jpiwm  = 5             ! maximum number of files to read 
     361      INTEGER, PARAMETER            ::   jpiwm  = 6             ! maximum number of files to read 
    416362      INTEGER, PARAMETER            ::   jp_mpb = 1 
    417       INTEGER, PARAMETER            ::   jp_mpp = 2 
    418       INTEGER, PARAMETER            ::   jp_mpc = 3 
    419       INTEGER, PARAMETER            ::   jp_dsb = 4 
    420       INTEGER, PARAMETER            ::   jp_dsc = 5 
    421       ! 
    422       TYPE(FLD_N), DIMENSION(jpiwm) ::   slf_iwm                ! array of namelist informations 
    423       TYPE(FLD_N)                   ::   sn_mpb, sn_mpp, sn_mpc ! informations about Mixing Power field to be read 
    424       TYPE(FLD_N)                   ::   sn_dsb, sn_dsc         ! informations about Decay Scale field to be read 
    425       TYPE(FLD  ), DIMENSION(jpiwm) ::   sf_iwm                 ! structure of input fields (file informations, fields read) 
    426       ! 
    427       NAMELIST/namzdf_iwm/ nn_zpyc, ln_mevar, ln_tsdiff, & 
    428          &                 cn_dir, sn_mpb, sn_mpp, sn_mpc, sn_dsb, sn_dsc 
     363      INTEGER, PARAMETER            ::   jp_mpc = 2 
     364      INTEGER, PARAMETER            ::   jp_mpn = 3 
     365      INTEGER, PARAMETER            ::   jp_mps = 4 
     366      INTEGER, PARAMETER            ::   jp_dsb = 5 
     367      INTEGER, PARAMETER            ::   jp_dsc = 6 
     368      ! 
     369      TYPE(FLD_N), DIMENSION(jpiwm) ::   slf_iwm                        ! array of namelist informations 
     370      TYPE(FLD_N)                   ::   sn_mpb, sn_mpc, sn_mpn, sn_mps ! information about Mixing Power field to be read 
     371      TYPE(FLD_N)                   ::   sn_dsb, sn_dsc                 ! information about Decay Scale field to be read 
     372      TYPE(FLD  ), DIMENSION(jpiwm) ::   sf_iwm                         ! structure of input fields (file informations, fields read) 
     373      ! 
     374      NAMELIST/namzdf_iwm/ ln_mevar, ln_tsdiff, & 
     375          &                cn_dir, sn_mpb, sn_mpc, sn_mpn, sn_mps, sn_dsb, sn_dsc 
    429376      !!---------------------------------------------------------------------- 
    430377      ! 
     
    441388         WRITE(numout,*) '~~~~~~~~~~~~' 
    442389         WRITE(numout,*) '   Namelist namzdf_iwm : set wave-driven mixing parameters' 
    443          WRITE(numout,*) '      Pycnocline-intensified diss. scales as N (=1) or N^2 (=2) = ', nn_zpyc 
    444390         WRITE(numout,*) '      Variable (T) or constant (F) mixing efficiency            = ', ln_mevar 
    445391         WRITE(numout,*) '      Differential internal wave-driven mixing (T) or not (F)   = ', ln_tsdiff 
    446392      ENDIF 
    447393       
    448       ! The new wave-driven mixing parameterization elevates avt and avm in the interior, and 
     394      ! This internal-wave-driven mixing parameterization elevates avt and avm in the interior, and 
    449395      ! ensures that avt remains larger than its molecular value (=1.4e-7). Therefore, avtb should  
    450396      ! be set here to a very small value, and avmb to its (uniform) molecular value (=1.4e-6). 
    451       avmb(:) = 1.4e-6_wp        ! viscous molecular value 
     397      avmb(:) = rnu              ! molecular value 
    452398      avtb(:) = 1.e-10_wp        ! very small diffusive minimum (background avt is specified in zdf_iwm)     
    453       avtb_2d(:,:) = 1.e0_wp     ! uniform  
     399      avtb_2d(:,:) = 1._wp     ! uniform  
    454400      IF(lwp) THEN                  ! Control print 
    455401         WRITE(numout,*) 
     
    462408      ! 
    463409      ! store namelist information in an array 
    464       slf_iwm(jp_mpb) = sn_mpb ; slf_iwm(jp_mpp) = sn_mpp ; slf_iwm(jp_mpc) = sn_mpc 
     410      slf_iwm(jp_mpb) = sn_mpb ; slf_iwm(jp_mpc) = sn_mpc ; slf_iwm(jp_mpn) = sn_mpn ; slf_iwm(jp_mps) = sn_mps 
    465411      slf_iwm(jp_dsb) = sn_dsb ; slf_iwm(jp_dsc) = sn_dsc 
    466412      ! 
     
    473419      CALL fld_fill( sf_iwm, slf_iwm , cn_dir, 'zdfiwm_init', 'iwm input file', 'namiwm' ) 
    474420 
    475       !                             ! hard-coded default definition (to be defined in namelist ?) 
    476       sf_iwm(jp_mpb)%fnow(:,:,1) = 1.e-6 
    477       sf_iwm(jp_mpp)%fnow(:,:,1) = 1.e-6 
    478       sf_iwm(jp_mpc)%fnow(:,:,1) = 1.e-10 
    479       sf_iwm(jp_dsb)%fnow(:,:,1) = 100. 
    480       sf_iwm(jp_dsc)%fnow(:,:,1) = 100. 
     421      !                             ! hard-coded default values 
     422      sf_iwm(jp_mpb)%fnow(:,:,1) = 1.e-10_wp 
     423      sf_iwm(jp_mpc)%fnow(:,:,1) = 1.e-10_wp 
     424      sf_iwm(jp_mpn)%fnow(:,:,1) = 1.e-6_wp 
     425      sf_iwm(jp_mps)%fnow(:,:,1) = 1.e-10_wp 
     426      sf_iwm(jp_dsb)%fnow(:,:,1) = 100._wp 
     427      sf_iwm(jp_dsc)%fnow(:,:,1) = 100._wp 
    481428 
    482429      !                             ! read necessary fields 
    483430      CALL fld_read( nit000, 1, sf_iwm ) 
    484431 
    485       ebot_iwm(:,:) = sf_iwm(1)%fnow(:,:,1) * ssmask(:,:) ! energy flux for high-mode wave breaking [W/m2] 
    486       epyc_iwm(:,:) = sf_iwm(2)%fnow(:,:,1) * ssmask(:,:) ! energy flux for pynocline-intensified wave breaking [W/m2] 
    487       ecri_iwm(:,:) = sf_iwm(3)%fnow(:,:,1) * ssmask(:,:) ! energy flux for critical slope wave breaking [W/m2] 
    488       hbot_iwm(:,:) = sf_iwm(4)%fnow(:,:,1)               ! spatially variable decay scale for high-mode wave breaking [m] 
    489       hcri_iwm(:,:) = sf_iwm(5)%fnow(:,:,1)               ! spatially variable decay scale for critical slope wave breaking [m] 
     432      ebot_iwm(:,:) = sf_iwm(1)%fnow(:,:,1) * ssmask(:,:) ! energy flux for dissipation above abyssal hills [W/m2] 
     433      ecri_iwm(:,:) = sf_iwm(2)%fnow(:,:,1) * ssmask(:,:) ! energy flux for dissipation at topographic slopes [W/m2] 
     434      ensq_iwm(:,:) = sf_iwm(3)%fnow(:,:,1) * ssmask(:,:) ! energy flux for dissipation scaling with N^2 [W/m2] 
     435      esho_iwm(:,:) = sf_iwm(4)%fnow(:,:,1) * ssmask(:,:) ! energy flux for dissipation due to shoaling [W/m2] 
     436      hbot_iwm(:,:) = sf_iwm(5)%fnow(:,:,1)               ! spatially variable decay scale for abyssal hill dissipation [m] 
     437      hcri_iwm(:,:) = sf_iwm(6)%fnow(:,:,1)               ! spatially variable decay scale for topographic-slope [m] 
     438 
     439      hcri_iwm(:,:) = 1._wp / hcri_iwm(:,:) ! only the inverse height is used, hence calculated here once for all 
    490440 
    491441      zbot = glob_sum( 'zdfiwm', e1e2t(:,:) * ebot_iwm(:,:) ) 
    492       zpyc = glob_sum( 'zdfiwm', e1e2t(:,:) * epyc_iwm(:,:) ) 
    493442      zcri = glob_sum( 'zdfiwm', e1e2t(:,:) * ecri_iwm(:,:) ) 
     443      znsq = glob_sum( 'zdfiwm', e1e2t(:,:) * ensq_iwm(:,:) ) 
     444      zsho = glob_sum( 'zdfiwm', e1e2t(:,:) * esho_iwm(:,:) ) 
    494445 
    495446      IF(lwp) THEN 
    496          WRITE(numout,*) '      High-mode wave-breaking energy:             ', zbot * 1.e-12_wp, 'TW' 
    497          WRITE(numout,*) '      Pycnocline-intensifed wave-breaking energy: ', zpyc * 1.e-12_wp, 'TW' 
    498          WRITE(numout,*) '      Critical slope wave-breaking energy:        ', zcri * 1.e-12_wp, 'TW' 
     447         WRITE(numout,*) '      Dissipation above abyssal hills:        ', zbot * 1.e-12_wp, 'TW' 
     448         WRITE(numout,*) '      Dissipation along topographic slopes:   ', zcri * 1.e-12_wp, 'TW' 
     449         WRITE(numout,*) '      Dissipation scaling with N^2:           ', znsq * 1.e-12_wp, 'TW' 
     450         WRITE(numout,*) '      Dissipation due to shoaling:            ', zsho * 1.e-12_wp, 'TW' 
    499451      ENDIF 
    500452      ! 
Note: See TracChangeset for help on using the changeset viewer.