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 13249 for NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/ZDF/zdfgls.F90 – NEMO

Ignore:
Timestamp:
2020-07-04T10:22:08+02:00 (4 years ago)
Author:
clem
Message:

merge with Jerome's branch NEMO_4.03_IODRAG

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/ZDF/zdfgls.F90

    r11536 r13249  
    5353   INTEGER  ::   nn_bc_bot         ! bottom boundary condition (=0/1) 
    5454   INTEGER  ::   nn_z0_met         ! Method for surface roughness computation 
     55   INTEGER  ::   nn_z0_ice         ! Roughness accounting for sea ice 
    5556   INTEGER  ::   nn_stab_func      ! stability functions G88, KC or Canuto (=0/1/2) 
    5657   INTEGER  ::   nn_clos           ! closure 0/1/2/3 MY82/k-eps/k-w/gen 
     
    6162   REAL(wp) ::   rn_crban          ! Craig and Banner constant for surface breaking waves mixing 
    6263   REAL(wp) ::   rn_hsro           ! Minimum surface roughness 
     64   REAL(wp) ::   rn_hsri           ! Ice ocean roughness 
    6365   REAL(wp) ::   rn_frac_hs        ! Fraction of wave height as surface roughness (if nn_z0_met > 1)  
    6466 
     
    150152      REAL(wp), DIMENSION(jpi,jpj)     ::   zflxs       ! Turbulence fluxed induced by internal waves  
    151153      REAL(wp), DIMENSION(jpi,jpj)     ::   zhsro       ! Surface roughness (surface waves) 
     154      REAL(wp), DIMENSION(jpi,jpj)     ::   zice_fra    ! Tapering of wave breaking under sea ice 
    152155      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   eb          ! tke at time before 
    153156      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   hmxl_b      ! mixing length at time before 
     
    165168      ustar2_bot (:,:) = 0._wp 
    166169 
     170      SELECT CASE ( nn_z0_ice ) 
     171      CASE( 0 )   ;   zice_fra(:,:) = 0._wp 
     172      CASE( 1 )   ;   zice_fra(:,:) =        TANH( fr_i(:,:) * 10._wp ) 
     173      CASE( 2 )   ;   zice_fra(:,:) =              fr_i(:,:) 
     174      CASE( 3 )   ;   zice_fra(:,:) = MIN( 4._wp * fr_i(:,:) , 1._wp ) 
     175      END SELECT 
     176       
    167177      ! Compute surface, top and bottom friction at T-points 
    168178      DO jj = 2, jpjm1           
     
    206216      END SELECT 
    207217      ! 
     218      ! adapt roughness where there is sea ice 
     219      zhsro(:,:) = ( (1._wp-zice_fra(:,:)) * zhsro(:,:) + zice_fra(:,:) * rn_hsri )*tmask(:,:,1)  + (1._wp - tmask(:,:,1))*rn_hsro 
     220      ! 
    208221      DO jk = 2, jpkm1              !==  Compute dissipation rate  ==! 
    209222         DO jj = 1, jpjm1 
     
    300313      CASE ( 0 )             ! Dirichlet boundary condition (set e at k=1 & 2)  
    301314      ! First level 
    302       en   (:,:,1) = MAX(  rn_emin , rc02r * ustar2_surf(:,:) * (1._wp + rsbc_tke1)**r2_3  ) 
     315      en   (:,:,1) = MAX(  rn_emin , rc02r * ustar2_surf(:,:) * (1._wp + (1._wp-zice_fra(:,:))*rsbc_tke1)**r2_3  ) 
    303316      zd_lw(:,:,1) = en(:,:,1) 
    304317      zd_up(:,:,1) = 0._wp 
     
    306319      !  
    307320      ! One level below 
    308       en   (:,:,2) =  MAX(  rc02r * ustar2_surf(:,:) * (  1._wp + rsbc_tke1 * ((zhsro(:,:)+gdepw_n(:,:,2))  & 
    309          &                 / zhsro(:,:) )**(1.5_wp*ra_sf)  )**(2._wp/3._wp)                      , rn_emin   ) 
     321      en   (:,:,2) =  MAX(  rc02r * ustar2_surf(:,:) * (  1._wp + (1._wp-zice_fra(:,:))*rsbc_tke1 * ((zhsro(:,:)+gdepw_n(:,:,2)) & 
     322         &                 / zhsro(:,:) )**(1.5_wp*ra_sf)  )**(2._wp/3._wp) , rn_emin   ) 
    310323      zd_lw(:,:,2) = 0._wp  
    311324      zd_up(:,:,2) = 0._wp 
     
    316329      ! 
    317330      ! Dirichlet conditions at k=1 
    318       en   (:,:,1) = MAX(  rc02r * ustar2_surf(:,:) * (1._wp + rsbc_tke1)**r2_3 , rn_emin  ) 
     331      en   (:,:,1) = MAX(  rc02r * ustar2_surf(:,:) * (1._wp + (1._wp-zice_fra(:,:))*rsbc_tke1)**r2_3 , rn_emin  ) 
    319332      zd_lw(:,:,1) = en(:,:,1) 
    320333      zd_up(:,:,1) = 0._wp 
     
    326339      zd_lw(:,:,2) = 0._wp 
    327340      zkar (:,:)   = (rl_sf + (vkarmn-rl_sf)*(1.-EXP(-rtrans*gdept_n(:,:,1)/zhsro(:,:)) )) 
    328       zflxs(:,:)   = rsbc_tke2 * ustar2_surf(:,:)**1.5_wp * zkar(:,:) & 
     341      zflxs(:,:)   = rsbc_tke2 * (1._wp-zice_fra(:,:)) * ustar2_surf(:,:)**1.5_wp * zkar(:,:) & 
    329342          &                    * (  ( zhsro(:,:)+gdept_n(:,:,1) ) / zhsro(:,:)  )**(1.5_wp*ra_sf) 
    330343!!gm why not   :                        * ( 1._wp + gdept_n(:,:,1) / zhsro(:,:) )**(1.5_wp*ra_sf) 
     
    577590         zkar (:,:)   = rl_sf + (vkarmn-rl_sf)*(1._wp-EXP(-rtrans*gdept_n(:,:,1)/zhsro(:,:) )) ! Lengh scale slope 
    578591         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) 
     592         zflxs(:,:)   = (rnn + (1._wp-zice_fra(:,:))*rsbc_tke1 * (rnn + rmm*ra_sf) * zdep(:,:)) & 
     593            &           *(1._wp + (1._wp-zice_fra(:,:))*rsbc_tke1*zdep(:,:))**(2._wp*rmm/3._wp-1_wp) 
    580594         zdep (:,:)   = rsbc_psi1 * (zwall_psi(:,:,1)*p_avm(:,:,1)+zwall_psi(:,:,2)*p_avm(:,:,2)) * & 
    581595            &           ustar2_surf(:,:)**rmm * zkar(:,:)**rnn * (zhsro(:,:) + gdept_n(:,:,1))**(rnn-1.) 
     
    850864      REAL(wp)::   zcr   ! local scalar 
    851865      !! 
    852       NAMELIST/namzdf_gls/rn_emin, rn_epsmin, ln_length_lim, & 
    853          &            rn_clim_galp, ln_sigpsi, rn_hsro,      & 
    854          &            rn_crban, rn_charn, rn_frac_hs,        & 
    855          &            nn_bc_surf, nn_bc_bot, nn_z0_met,     & 
     866      NAMELIST/namzdf_gls/rn_emin, rn_epsmin, ln_length_lim,       & 
     867         &            rn_clim_galp, ln_sigpsi, rn_hsro, rn_hsri,   & 
     868         &            rn_crban, rn_charn, rn_frac_hs,              & 
     869         &            nn_bc_surf, nn_bc_bot, nn_z0_met, nn_z0_ice, & 
    856870         &            nn_stab_func, nn_clos 
    857871      !!---------------------------------------------------------- 
     
    881895         WRITE(numout,*) '      Charnock coefficient                          rn_charn       = ', rn_charn 
    882896         WRITE(numout,*) '      Surface roughness formula                     nn_z0_met      = ', nn_z0_met 
     897         WRITE(numout,*) '      surface wave breaking under ice               nn_z0_ice      = ', nn_z0_ice 
     898         SELECT CASE( nn_z0_ice ) 
     899         CASE( 0 )   ;   WRITE(numout,*) '   ==>>>   no impact of ice cover on surface wave breaking' 
     900         CASE( 1 )   ;   WRITE(numout,*) '   ==>>>   roughness uses rn_hsri and is weigthed by 1-TANH( fr_i(:,:) * 10 )' 
     901         CASE( 2 )   ;   WRITE(numout,*) '   ==>>>   roughness uses rn_hsri and is weighted by 1-fr_i(:,:)' 
     902         CASE( 3 )   ;   WRITE(numout,*) '   ==>>>   roughness uses rn_hsri and is weighted by 1-MIN( 1, 4 * fr_i(:,:) )' 
     903         CASE DEFAULT 
     904            CALL ctl_stop( 'zdf_gls_init: wrong value for nn_z0_ice, should be 0,1,2, or 3') 
     905         END SELECT 
    883906         WRITE(numout,*) '      Wave height frac. (used if nn_z0_met=2)       rn_frac_hs     = ', rn_frac_hs 
    884907         WRITE(numout,*) '      Stability functions                           nn_stab_func   = ', nn_stab_func 
    885908         WRITE(numout,*) '      Type of closure                               nn_clos        = ', nn_clos 
    886909         WRITE(numout,*) '      Surface roughness (m)                         rn_hsro        = ', rn_hsro 
     910         WRITE(numout,*) '      Ice-ocean roughness (used if nn_z0_ice/=0)    rn_hsri        = ', rn_hsri 
    887911         WRITE(numout,*) 
    888912         WRITE(numout,*) '   Namelist namdrg_top/_bot:   used values:' 
Note: See TracChangeset for help on using the changeset viewer.