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 13121 for NEMO/branches/2020/dev_r12953_ENHANCE-10_acc_fix_traqsr/src/OCE/ZDF/zdftke.F90 – NEMO

Ignore:
Timestamp:
2020-06-17T13:01:47+02:00 (4 years ago)
Author:
acc
Message:

2020/dev_r12953_ENHANCE-10_acc_fix_traqsr. Merge in trunk changes from 12953 to current HEAD (13115). Fully SETTE tested

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r12953_ENHANCE-10_acc_fix_traqsr/src/OCE/ZDF/zdftke.F90

    r12702 r13121  
    4545   USE zdfdrg         ! vertical physics: top/bottom drag coef. 
    4646   USE zdfmxl         ! vertical physics: mixed layer 
     47#if defined key_si3 
     48   USE ice, ONLY: hm_i, h_i 
     49#endif 
     50#if defined key_cice 
     51   USE sbc_ice, ONLY: h_i 
     52#endif 
    4753   ! 
    4854   USE in_out_manager ! I/O manager 
     
    6470   INTEGER  ::   nn_mxl    ! type of mixing length (=0/1/2/3) 
    6571   REAL(wp) ::   rn_mxl0   ! surface  min value of mixing length (kappa*z_o=0.4*0.1 m)  [m] 
     72   INTEGER  ::      nn_mxlice ! type of scaling under sea-ice 
     73   REAL(wp) ::      rn_mxlice ! max constant ice thickness value when scaling under sea-ice ( nn_mxlice=1) 
    6674   INTEGER  ::   nn_pdl    ! Prandtl number or not (ratio avt/avm) (=0/1) 
    6775   REAL(wp) ::   rn_ediff  ! coefficient for avt: avt=rn_ediff*mxl*sqrt(e) 
     
    422430      REAL(wp) ::   zrn2, zraug, zcoef, zav   ! local scalars 
    423431      REAL(wp) ::   zdku,   zdkv, zsqen       !   -      - 
    424       REAL(wp) ::   zemxl, zemlm, zemlp       !   -      - 
     432      REAL(wp) ::   zemxl, zemlm, zemlp, zmaxice       !   -      - 
    425433      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zmxlm, zmxld   ! 3D workspace 
    426434      !!-------------------------------------------------------------------- 
     
    436444      zmxld(:,:,:)  = rmxl_min 
    437445      ! 
    438       IF( ln_mxl0 ) THEN            ! surface mixing length = F(stress) : l=vkarmn*2.e5*taum/(rho0*g) 
     446     IF( ln_mxl0 ) THEN            ! surface mixing length = F(stress) : l=vkarmn*2.e5*taum/(rho0*g) 
     447         ! 
    439448         zraug = vkarmn * 2.e5_wp / ( rho0 * grav ) 
     449#if ! defined key_si3 && ! defined key_cice 
    440450         DO_2D_00_00 
    441             zmxlm(ji,jj,1) = MAX( rn_mxl0, zraug * taum(ji,jj) * tmask(ji,jj,1) ) 
     451            zmxlm(ji,jj,1) =  zraug * taum(ji,jj) * tmask(ji,jj,1) 
    442452         END_2D 
    443       ELSE  
     453#else 
     454         SELECT CASE( nn_mxlice )             ! Type of scaling under sea-ice 
     455         ! 
     456         CASE( 0 )                      ! No scaling under sea-ice 
     457            DO_2D_00_00 
     458               zmxlm(ji,jj,1) = zraug * taum(ji,jj) * tmask(ji,jj,1) 
     459            END_2D 
     460            ! 
     461         CASE( 1 )                           ! scaling with constant sea-ice thickness 
     462            DO_2D_00_00 
     463               zmxlm(ji,jj,1) =  ( ( 1. - fr_i(ji,jj) ) * zraug * taum(ji,jj) + fr_i(ji,jj) * rn_mxlice ) * tmask(ji,jj,1) 
     464            END_2D 
     465            ! 
     466         CASE( 2 )                                 ! scaling with mean sea-ice thickness 
     467            DO_2D_00_00 
     468#if defined key_si3 
     469               zmxlm(ji,jj,1) = ( ( 1. - fr_i(ji,jj) ) * zraug * taum(ji,jj) + fr_i(ji,jj) * hm_i(ji,jj) * 2. ) * tmask(ji,jj,1) 
     470#elif defined key_cice 
     471               zmaxice = MAXVAL( h_i(ji,jj,:) ) 
     472               zmxlm(ji,jj,1) = ( ( 1. - fr_i(ji,jj) ) * zraug * taum(ji,jj) + fr_i(ji,jj) * zmaxice ) * tmask(ji,jj,1) 
     473#endif 
     474            END_2D 
     475            ! 
     476         CASE( 3 )                                 ! scaling with max sea-ice thickness 
     477            DO_2D_00_00 
     478               zmaxice = MAXVAL( h_i(ji,jj,:) ) 
     479               zmxlm(ji,jj,1) = ( ( 1. - fr_i(ji,jj) ) * zraug * taum(ji,jj) + fr_i(ji,jj) * zmaxice ) * tmask(ji,jj,1) 
     480            END_2D 
     481            ! 
     482         END SELECT 
     483#endif 
     484         ! 
     485         DO_2D_00_00 
     486            zmxlm(ji,jj,1) = MAX( rn_mxl0, zmxlm(ji,jj,1) ) 
     487         END_2D 
     488         ! 
     489      ELSE 
    444490         zmxlm(:,:,1) = rn_mxl0 
    445491      ENDIF 
     492 
    446493      ! 
    447494      DO_3D_00_00( 2, jpkm1 ) 
     
    547594      INTEGER             ::   ios 
    548595      !! 
    549       NAMELIST/namzdf_tke/ rn_ediff, rn_ediss , rn_ebb , rn_emin  ,          & 
    550          &                 rn_emin0, rn_bshear, nn_mxl , ln_mxl0  ,          & 
    551          &                 rn_mxl0 , nn_pdl   , ln_drg , ln_lc    , rn_lc,   & 
    552          &                 nn_etau , nn_htau  , rn_efr , rn_eice   
     596      NAMELIST/namzdf_tke/ rn_ediff, rn_ediss , rn_ebb   , rn_emin  ,  & 
     597         &                 rn_emin0, rn_bshear, nn_mxl   , ln_mxl0  ,  & 
     598         &                 rn_mxl0 , nn_mxlice, rn_mxlice,             & 
     599         &                 nn_pdl  , ln_drg   , ln_lc    , rn_lc,      & 
     600         &                 nn_etau , nn_htau  , rn_efr   , rn_eice   
    553601      !!---------------------------------------------------------------------- 
    554602      ! 
     
    576624         WRITE(numout,*) '      mixing length type                          nn_mxl    = ', nn_mxl 
    577625         WRITE(numout,*) '         surface mixing length = F(stress) or not    ln_mxl0   = ', ln_mxl0 
     626         IF( ln_mxl0 ) THEN 
     627            WRITE(numout,*) '      type of scaling under sea-ice               nn_mxlice = ', nn_mxlice 
     628            IF( nn_mxlice == 1 ) & 
     629            WRITE(numout,*) '      ice thickness when scaling under sea-ice    rn_mxlice = ', rn_mxlice 
     630         ENDIF          
    578631         WRITE(numout,*) '         surface  mixing length minimum value        rn_mxl0   = ', rn_mxl0 
    579632         WRITE(numout,*) '      top/bottom friction forcing flag            ln_drg    = ', ln_drg 
Note: See TracChangeset for help on using the changeset viewer.