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 12966 for NEMO/branches/MOI/NEMO_4.03_IODRAG/src/OCE/ZDF/zdfgls.F90 – NEMO

Ignore:
Timestamp:
2020-05-25T12:04:00+02:00 (4 years ago)
Author:
jchanut
Message:

Switch to log-law bcs below ice in tke and gls - hard coded 3cm ice-ocean roughness: #2468

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/MOI/NEMO_4.03_IODRAG/src/OCE/ZDF/zdfgls.F90

    r11536 r12966  
    146146      REAL(wp) ::   gh, gm, shr, dif, zsqen, zavt, zavm !   -      - 
    147147      REAL(wp) ::   zmsku, zmskv                        !   -      - 
     148      REAL(wp) ::   rn_hsri ! ice ocean roughness 
    148149      REAL(wp), DIMENSION(jpi,jpj)     ::   zdep 
    149150      REAL(wp), DIMENSION(jpi,jpj)     ::   zkar 
    150151      REAL(wp), DIMENSION(jpi,jpj)     ::   zflxs       ! Turbulence fluxed induced by internal waves  
    151152      REAL(wp), DIMENSION(jpi,jpj)     ::   zhsro       ! Surface roughness (surface waves) 
     153      REAL(wp), DIMENSION(jpi,jpj)     ::   ziconc      ! Tapering of wave breaking under sea ice 
    152154      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   eb          ! tke at time before 
    153155      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   hmxl_b      ! mixing length at time before 
     
    165167      ustar2_bot (:,:) = 0._wp 
    166168 
     169      ziconc(:,:) = 1._wp - TANH(fr_i(:,:) * 10._wp) 
    167170      ! Compute surface, top and bottom friction at T-points 
    168171      DO jj = 2, jpjm1           
     
    206209      END SELECT 
    207210      ! 
     211      rn_hsri = 0.03_wp  
     212      zhsro(:,:) =  (ziconc(:,:) * zhsro(:,:) + (1._wp - ziconc(:,:)) * rn_hsri)*tmask(:,:,1)  + (1._wp - tmask(:,:,1)) * rn_hsro 
    208213      DO jk = 2, jpkm1              !==  Compute dissipation rate  ==! 
    209214         DO jj = 1, jpjm1 
     
    300305      CASE ( 0 )             ! Dirichlet boundary condition (set e at k=1 & 2)  
    301306      ! First level 
    302       en   (:,:,1) = MAX(  rn_emin , rc02r * ustar2_surf(:,:) * (1._wp + rsbc_tke1)**r2_3  ) 
     307      en   (:,:,1) = MAX(  rn_emin , rc02r * ustar2_surf(:,:) * (1._wp + ziconc(:,:)*rsbc_tke1)**r2_3  ) 
    303308      zd_lw(:,:,1) = en(:,:,1) 
    304309      zd_up(:,:,1) = 0._wp 
     
    306311      !  
    307312      ! One level below 
    308       en   (:,:,2) =  MAX(  rc02r * ustar2_surf(:,:) * (  1._wp + rsbc_tke1 * ((zhsro(:,:)+gdepw_n(:,:,2))   & 
     313      en   (:,:,2) =  MAX(  rc02r * ustar2_surf(:,:) * (  1._wp + ziconc(:,:)*rsbc_tke1 * ((zhsro(:,:)+gdepw_n(:,:,2))   & 
    309314         &                 / zhsro(:,:) )**(1.5_wp*ra_sf)  )**(2._wp/3._wp)                      , rn_emin   ) 
    310315      zd_lw(:,:,2) = 0._wp  
     
    316321      ! 
    317322      ! Dirichlet conditions at k=1 
    318       en   (:,:,1) = MAX(  rc02r * ustar2_surf(:,:) * (1._wp + rsbc_tke1)**r2_3 , rn_emin  ) 
     323      en   (:,:,1) = MAX(  rc02r * ustar2_surf(:,:) * (1._wp + ziconc(:,:)*rsbc_tke1)**r2_3 , rn_emin  ) 
    319324      zd_lw(:,:,1) = en(:,:,1) 
    320325      zd_up(:,:,1) = 0._wp 
     
    326331      zd_lw(:,:,2) = 0._wp 
    327332      zkar (:,:)   = (rl_sf + (vkarmn-rl_sf)*(1.-EXP(-rtrans*gdept_n(:,:,1)/zhsro(:,:)) )) 
    328       zflxs(:,:)   = rsbc_tke2 * ustar2_surf(:,:)**1.5_wp * zkar(:,:) & 
     333      zflxs(:,:)   = rsbc_tke2 * ziconc(:,:) * ustar2_surf(:,:)**1.5_wp * zkar(:,:) & 
    329334          &                    * (  ( zhsro(:,:)+gdept_n(:,:,1) ) / zhsro(:,:)  )**(1.5_wp*ra_sf) 
    330335!!gm why not   :                        * ( 1._wp + gdept_n(:,:,1) / zhsro(:,:) )**(1.5_wp*ra_sf) 
     
    577582         zkar (:,:)   = rl_sf + (vkarmn-rl_sf)*(1._wp-EXP(-rtrans*gdept_n(:,:,1)/zhsro(:,:) )) ! Lengh scale slope 
    578583         zdep (:,:)   = ((zhsro(:,:) + gdept_n(:,:,1)) / zhsro(:,:))**(rmm*ra_sf) 
    579          zflxs(:,:)   = (rnn + rsbc_tke1 * (rnn + rmm*ra_sf) * zdep(:,:))*(1._wp + rsbc_tke1*zdep(:,:))**(2._wp*rmm/3._wp-1_wp) 
     584         zflxs(:,:)   = (rnn + ziconc(:,:)*rsbc_tke1 * (rnn + rmm*ra_sf) * zdep(:,:))*(1._wp + ziconc(:,:)*rsbc_tke1*zdep(:,:))**(2._wp*rmm/3._wp-1_wp) 
    580585         zdep (:,:)   = rsbc_psi1 * (zwall_psi(:,:,1)*p_avm(:,:,1)+zwall_psi(:,:,2)*p_avm(:,:,2)) * & 
    581586            &           ustar2_surf(:,:)**rmm * zkar(:,:)**rnn * (zhsro(:,:) + gdept_n(:,:,1))**(rnn-1.) 
Note: See TracChangeset for help on using the changeset viewer.