Changeset 3430 for palm/trunk/SOURCE/turbulence_closure_mod.f90
- Timestamp:
- Oct 25, 2018 1:36:23 PM (6 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/turbulence_closure_mod.f90
r3398 r3430 25 25 ! ----------------- 26 26 ! $Id$ 27 ! Added support for buildings in the dynamic SGS model 28 ! 29 ! 3398 2018-10-22 19:30:24Z knoop 27 30 ! Refactored production_e and production_e_ij (removed code redundancy) 28 31 ! … … 186 189 simulated_time,timestep_scheme, turbulence_closure, & 187 190 turbulent_inflow, use_upstream_for_tke, vpt_reference, & 188 ws_scheme_sca 191 ws_scheme_sca, current_timestep_number 189 192 190 193 USE advec_ws, & … … 4687 4690 !> 4688 4691 !> @author Hauke Wurps 4692 !> @author Björn Maronga 4689 4693 !------------------------------------------------------------------------------! 4690 4694 SUBROUTINE tcm_diffusivities_dynamic … … 4714 4718 REAL(wp) :: dwdz !< Gradient of w-component in z-direction 4715 4719 4720 REAL(wp) :: flag !< topography flag 4721 4716 4722 REAL(wp) :: uc(-1:1,-1:1) !< u on grid center 4717 4723 REAL(wp) :: vc(-1:1,-1:1) !< v on grid center 4718 4724 REAL(wp) :: wc(-1:1,-1:1) !< w on grid center 4719 ! REAL(wp) :: u2(-1:1,-1:1) !< u2 on grid center4720 ! REAL(wp) :: v2(-1:1,-1:1) !< v2 on grid center4721 ! REAL(wp) :: w2(-1:1,-1:1) !< w2 on grid center4722 ! REAL(wp) :: uv(-1:1,-1:1) !< u*v on grid center4723 ! REAL(wp) :: uw(-1:1,-1:1) !< u*w on grid center4724 ! REAL(wp) :: vw(-1:1,-1:1) !< v*w on grid center4725 4725 4726 4726 REAL(wp) :: ut(nzb:nzt+1,nysg:nyng,nxlg:nxrg) !< test filtered u … … 4740 4740 REAL(wp) :: sd11 !< deviatoric shear tensor 4741 4741 REAL(wp) :: sd22 !< deviatoric shear tensor 4742 REAL(wp) :: sd33 !< deviatoric shear tensor4742 REAL(wp) :: sd33 !<f deviatoric shear tensor 4743 4743 REAL(wp) :: sd12 !< deviatoric shear tensor 4744 4744 REAL(wp) :: sd13 !< deviatoric shear tensor … … 4782 4782 DO j = nys, nyn 4783 4783 DO k = nzb+1, nzt 4784 4785 flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) ) 4786 4784 4787 ! 4785 4788 !-- Compute the deviatoric shear tensor s_ij on grid centers: … … 4885 4888 ! 4886 4889 !-- c* nu*^T is SGS viscosity on test filter level: 4887 cstnust_t = -ldsd / sdt24890 cstnust_t = -ldsd / ( sdt2 + 1.0E-20_wp ) 4888 4891 ! 4889 4892 !-- The model was only tested for an isotropic grid. The following 4890 4893 !-- expression was a recommendation of Stefan Heinz. 4891 4894 delta = MAX( dx, dy, dzw(k) ) 4892 cst = cstnust_t / ( 4.0_wp * delta * SQRT( lnn / 2.0_wp ) ) 4895 4896 IF ( lnn <= 0.0_wp ) THEN 4897 cst = 0.0_wp 4898 ELSE 4899 cst = cstnust_t / & 4900 ( 4.0_wp * delta * SQRT( lnn / 2.0_wp ) + 1.0E-20_wp ) 4901 ENDIF 4902 4893 4903 ! 4894 4904 !-- Calculate border according to Mokhtarpoor and Heinz (2017) 4895 cst_max = fac_cmax * SQRT( e(k,j,i) ) / ( delta * SQRT( 2.0_wp * sd2 ) ) 4896 4905 cst_max = fac_cmax * SQRT( e(k,j,i) ) / & 4906 ( delta * SQRT( 2.0_wp * sd2 ) + 1.0E-20_wp ) 4907 4897 4908 IF ( ABS( cst ) > cst_max ) THEN 4898 4909 cst = cst_max * cst / ABS( cst ) 4899 4910 ENDIF 4900 4911 4901 km(k,j,i) = cst * delta * SQRT( e(k,j,i) ) 4902 4912 km(k,j,i) = cst * delta * SQRT( e(k,j,i) ) * flag 4913 4903 4914 ENDDO 4904 4915 ENDDO
Note: See TracChangeset
for help on using the changeset viewer.