- Timestamp:
- Aug 30, 2023, 9:15:43 AM (15 months ago)
- Location:
- LMDZ6/trunk/libf
- Files:
-
- 7 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/phylmd/atke_exchange_coeff_mod.F90
r4644 r4653 6 6 7 7 subroutine atke_compute_km_kh(ngrid,nlay,dtime, & 8 wind_u,wind_v,temp, play,pinterf,cdrag_uv, &8 wind_u,wind_v,temp,qvap,play,pinterf,cdrag_uv, & 9 9 tke,Km_out,Kh_out) 10 10 … … 26 26 27 27 28 USE atke_turbulence_ini_mod, ONLY : iflag_atke, kappa, l0, ric, cinf, rpi, rcpd, ok_vdiff_tke29 USE atke_turbulence_ini_mod, ONLY : cepsilon, pr_slope, pr_asym, pr_neut, ctkes,rg, rd 28 USE atke_turbulence_ini_mod, ONLY : iflag_atke, kappa, l0, ric, cinf, rpi, rcpd, atke_ok_virtual 29 USE atke_turbulence_ini_mod, ONLY : cepsilon, pr_slope, pr_asym, pr_neut, ctkes,rg, rd, rv, atke_ok_vdiff 30 30 USE atke_turbulence_ini_mod, ONLY : viscom, viscoh, clmix, iflag_atke_lmix, lmin, smmin 31 31 … … 43 43 REAL, DIMENSION(ngrid,nlay), INTENT(IN) :: wind_v ! meridional velocity (m/s) 44 44 REAL, DIMENSION(ngrid,nlay), INTENT(IN) :: temp ! temperature (K) 45 REAL, DIMENSION(ngrid,nlay), INTENT(IN) :: qvap ! specific humidity (kg/kg) 45 46 REAL, DIMENSION(ngrid,nlay), INTENT(IN) :: play ! pressure (Pa) 46 47 REAL, DIMENSION(ngrid,nlay+1), INTENT(IN) :: pinterf ! pressure at interfaces(Pa) … … 81 82 REAL :: netsource ! net source term of tke 82 83 REAL :: ustar ! friction velocity estimation 84 REAL :: invtau 85 REAL :: rvap 83 86 84 87 ! Initializations: … … 90 93 END DO 91 94 92 ! Calculation of potential temperature: (if vapor -> todovirtual potential temperature)95 ! Calculation of potential temperature: (if vapor -> virtual potential temperature) 93 96 !===================================== 94 97 95 98 preff=100000. 96 ! The resultshould not depend on the choice of preff99 ! results should not depend on the choice of preff 97 100 DO ilay=1,nlay 98 101 DO igrid = 1, ngrid … … 101 104 END DO 102 105 106 ! account for water vapor mass for buoyancy calculation 107 IF (atke_ok_virtual) THEN 108 DO ilay=1,nlay 109 DO igrid = 1, ngrid 110 rvap=max(0.,qvap(igrid,ilay)/(1.-qvap(igrid,ilay))) 111 theta(igrid,ilay)=theta(igrid,ilay)*(1.+rvap/(RD/RV))/(1.+rvap) 112 END DO 113 END DO 114 ENDIF 103 115 104 116 … … 287 299 288 300 301 ELSE IF (iflag_atke == 5) THEN 302 ! semi implicit scheme from Arpege (V. Masson methodology with 303 ! Taylor expansion of the dissipation term) 304 ! and implicit resolution when switch num (when we use the mixing length as a function of tke) 305 DO ilay=2,nlay 306 DO igrid=1,ngrid 307 qq=max(sqrt(2.*tke(igrid,ilay)),1.e-10) 308 if (switch_num(igrid,ilay) .and. N2(igrid,ilay)>0.) then 309 invtau=clmix*Sm(igrid,ilay)/sqrt(N2(igrid,ilay))*shear2(igrid,ilay)*(1.-Ri(igrid,ilay)/Prandtl(igrid,ilay)) & 310 -sqrt(N2(igrid,ilay))/(cepsilon*clmix) 311 !qq=qq/(1.-dtime*invtau) 312 !qq=qq*exp(dtime*invtau) 313 tke(igrid,ilay)=tke(igrid,ilay)/(1.-dtime*invtau) 314 tke(igrid,ilay)=max(0.,tke(igrid,ilay)) 315 else 316 qq=(l_exchange(igrid,ilay)*Sm(igrid,ilay)/sqrt(2.)*shear2(igrid,ilay)*(1.-Ri(igrid,ilay)/Prandtl(igrid,ilay)) & 317 +qq*(1.+dtime*qq/(cepsilon*l_exchange(igrid,ilay)*2.*sqrt(2.)))) & 318 /(1.+2.*qq*dtime/(cepsilon*l_exchange(igrid,ilay)*2.*sqrt(2.))) 319 qq=max(0.,qq) 320 tke(igrid,ilay)=0.5*(qq**2) 321 endif 322 ENDDO 323 ENDDO 324 325 289 326 ELSE 290 327 call abort_physic("atke_compute_km_kh", & … … 312 349 ! vertical diffusion of TKE 313 350 !========================== 314 IF ( ok_vdiff_tke) THEN351 IF (atke_ok_vdiff) THEN 315 352 CALL atke_vdiff_tke(ngrid,nlay,dtime,z_lay,z_interf,temp,play,l_exchange,Sm,tke) 316 353 ENDIF … … 338 375 339 376 ! routine that computes the vertical diffusion of TKE by the turbulence 340 ! using an implicit resolution (See note by Dufresne and Ghattas 377 ! using an implicit resolution (See note by Dufresne and Ghattas (2009)) 341 378 ! E Vignon, July 2023 342 379 -
LMDZ6/trunk/libf/phylmd/atke_turbulence_ini_mod.F90
r4644 r4653 13 13 integer :: lunout,prt_level 14 14 !$OMP THREADPRIVATE(lunout,prt_level) 15 real :: rg, rd, rpi, rcpd 16 !$OMP THREADPRIVATE(rg, rd, rpi, rcpd )15 real :: rg, rd, rpi, rcpd, rv 16 !$OMP THREADPRIVATE(rg, rd, rpi, rcpd, rv) 17 17 18 18 real :: viscom, viscoh … … 22 22 !$OMP THREADPRIVATE(lmin) 23 23 24 logical :: ok_vdiff_tke25 !$OMP THREADPRIVATE( ok_vdiff_tke)24 logical :: atke_ok_vdiff, atke_ok_virtual 25 !$OMP THREADPRIVATE(atke_ok_vdiff,atke_ok_virtual) 26 26 27 27 CONTAINS 28 28 29 SUBROUTINE atke_ini(prt_level_in, lunout_in, rg_in, rd_in, rpi_in, rcpd_in )29 SUBROUTINE atke_ini(prt_level_in, lunout_in, rg_in, rd_in, rpi_in, rcpd_in, rv_in) 30 30 31 31 USE ioipsl_getin_p_mod, ONLY : getin_p 32 32 33 33 integer, intent(in) :: lunout_in,prt_level_in 34 real, intent(in) :: rg_in, rd_in, rpi_in, rcpd_in 34 real, intent(in) :: rg_in, rd_in, rpi_in, rcpd_in, rv_in 35 35 36 36 … … 41 41 rpi=rpi_in 42 42 rcpd=rcpd_in 43 rv=rv_in 43 44 44 45 viscom=1.46E-5 … … 59 60 60 61 ! activate vertical diffusion of TKE or not 61 ok_vdiff_tke=.false. 62 CALL getin_p('atke_ok_vdiff_tke',ok_vdiff_tke) 62 atke_ok_vdiff=.false. 63 CALL getin_p('atke_ok_vdiff',atke_ok_vdiff) 64 65 66 ! account for vapor for flottability 67 atke_ok_virtual=.true. 68 CALL getin_p('atke_ok_virtual',atke_ok_virtual) 69 63 70 64 71 ! flag that controls the numerical treatment of diffusion coeffiient calculation … … 82 89 83 90 ! constant for tke dissipation calculation 84 cepsilon= 16.6/2./sqrt(2.)! default value as in yamada491 cepsilon=5.87 ! default value as in yamada4 85 92 CALL getin_p('atke_cepsilon',cepsilon) 93 94 95 ! coefficient for surface TKE 96 ! following Lenderink & Holtslag 2004, ctkes=sqrt(cepsilon) 97 ! (provided by limit condition in neutral conditions) 98 ctkes=sqrt(cepsilon) 99 86 100 87 101 ! slope of Pr=f(Ri) for stable conditions … … 111 125 CALL getin_p('atke_smmin',smmin) 112 126 113 ! coefficient for surface TKE (default value from Arpege, see E. Bazile note)114 ctkes=3.75115 CALL getin_p('atke_ctkes',ctkes)116 127 117 128 ! ratio between the eddy diffusivity coeff for tke wrt that for momentum -
LMDZ6/trunk/libf/phylmd/call_atke_mod.F90
r4644 r4653 9 9 10 10 subroutine call_atke(dtime,ngrid,nlay,cdrag_uv,cdrag_t,u_surf,v_surf,temp_surf, & 11 wind_u,wind_v,temp, play,pinterf, &11 wind_u,wind_v,temp,qvap,play,pinterf, & 12 12 tke,Km_out,Kh_out) 13 13 … … 38 38 REAL, DIMENSION(ngrid,nlay), INTENT(IN) :: wind_v ! meridional velocity (m/s) 39 39 REAL, DIMENSION(ngrid,nlay), INTENT(IN) :: temp ! temperature (K) 40 REAL, DIMENSION(ngrid,nlay), INTENT(IN) :: qvap ! specific humidity (kg/kg) 40 41 REAL, DIMENSION(ngrid,nlay), INTENT(IN) :: play ! pressure (Pa) 41 42 REAL, DIMENSION(ngrid,nlay+1), INTENT(IN) :: pinterf ! pressure at interfaces(Pa) … … 55 56 56 57 call atke_compute_km_kh(ngrid,nlay,dtime,& 57 wind_u,wind_v,temp, play,pinterf,cdrag_uv,&58 wind_u,wind_v,temp,qvap,play,pinterf,cdrag_uv,& 58 59 tke,Km_out,Kh_out) 59 60 … … 74 75 75 76 call atke_compute_km_kh(ngrid,nlay,dtime,& 76 wind_u_predict,wind_v_predict,temp, play,pinterf,cdrag_uv, &77 wind_u_predict,wind_v_predict,temp,qvap,play,pinterf,cdrag_uv, & 77 78 tke,Km_out,Kh_out) 78 79 -
LMDZ6/trunk/libf/phylmd/pbl_surface_mod.F90
r4619 r4653 1704 1704 IF (iflag_pbl>=50) THEN 1705 1705 1706 CALL call_atke(dtime,knon,klev,ycdragm, ycdragh,yus0,yvs0,yts,yu,yv,yt, &1706 CALL call_atke(dtime,knon,klev,ycdragm, ycdragh,yus0,yvs0,yts,yu,yv,yt,yq, & 1707 1707 ypplay,ypaprs,ytke,ycoefm, ycoefh) 1708 1708 … … 1748 1748 IF (iflag_pbl>=50) THEN 1749 1749 1750 CALL call_atke(dtime,knon,klev,ycdragm_x,ycdragh_x,yus0,yvs0,yts_x,yu_x,yv_x,yt_x, &1750 CALL call_atke(dtime,knon,klev,ycdragm_x,ycdragh_x,yus0,yvs0,yts_x,yu_x,yv_x,yt_x,yq_x, & 1751 1751 ypplay,ypaprs,ytke_x,ycoefm_x, ycoefh_x) 1752 1752 … … 1787 1787 IF (iflag_pbl>=50) THEN 1788 1788 1789 CALL call_atke(dtime,knon,klev,ycdragm_w,ycdragh_w,yus0,yvs0,yts_w,yu_w,yv_w,yt_w, &1789 CALL call_atke(dtime,knon,klev,ycdragm_w,ycdragh_w,yus0,yvs0,yts_w,yu_w,yv_w,yt_w,yq_w, & 1790 1790 ypplay,ypaprs,ytke_w,ycoefm_w, ycoefh_w) 1791 1791 -
LMDZ6/trunk/libf/phylmd/physiq_mod.F90
r4651 r4653 1805 1805 CALL wake_ini(rg,rd,rv,prt_level) 1806 1806 CALL yamada_ini(klon,lunout,prt_level) 1807 CALL atke_ini(prt_level, lunout, RG, RD, RPI, RCPD )1807 CALL atke_ini(prt_level, lunout, RG, RD, RPI, RCPD, RV) 1808 1808 CALL thermcell_ini(iflag_thermals,prt_level,tau_thermals,lunout, & 1809 1809 & RG,RD,RCPD,RKAPPA,RLVTT,RETV) -
LMDZ6/trunk/libf/phylmdiso/pbl_surface_mod.F90
r4633 r4653 1981 1981 IF (iflag_pbl>=50) THEN 1982 1982 1983 CALL call_atke(dtime,knon,klev,ycdragm, ycdragh,yus0,yvs0,yts,yu,yv,yt, &1983 CALL call_atke(dtime,knon,klev,ycdragm, ycdragh,yus0,yvs0,yts,yu,yv,yt,yq, & 1984 1984 ypplay,ypaprs,ytke,ycoefm, ycoefh) 1985 1985 … … 2024 2024 IF (iflag_pbl>=50) THEN 2025 2025 2026 CALL call_atke(dtime,knon,klev,ycdragm_x,ycdragh_x,yus0,yvs0,yts_x,yu_x,yv_x,yt_x, &2026 CALL call_atke(dtime,knon,klev,ycdragm_x,ycdragh_x,yus0,yvs0,yts_x,yu_x,yv_x,yt_x,yq_x, & 2027 2027 ypplay,ypaprs,ytke_x,ycoefm_x, ycoefh_x) 2028 2028 … … 2064 2064 IF (iflag_pbl>=50) THEN 2065 2065 2066 CALL call_atke(dtime,knon,klev,ycdragm_w,ycdragh_w,yus0,yvs0,yts_w,yu_w,yv_w,yt_w, &2066 CALL call_atke(dtime,knon,klev,ycdragm_w,ycdragh_w,yus0,yvs0,yts_w,yu_w,yv_w,yt_w,yq_w, & 2067 2067 ypplay,ypaprs,ytke_w,ycoefm_w, ycoefh_w) 2068 2068 -
LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90
r4651 r4653 1917 1917 CALL wake_ini(rg,rd,rv,prt_level) 1918 1918 CALL yamada_ini(klon,lunout,prt_level) 1919 CALL atke_ini(prt_level, lunout, RG, RD, RPI, RCPD )1919 CALL atke_ini(prt_level, lunout, RG, RD, RPI, RCPD, RV) 1920 1920 CALL thermcell_ini(iflag_thermals,prt_level,tau_thermals,lunout, & 1921 1921 & RG,RD,RCPD,RKAPPA,RLVTT,RETV)
Note: See TracChangeset
for help on using the changeset viewer.