Changeset 3157 for palm/trunk/SOURCE/surface_layer_fluxes_mod.f90
- Timestamp:
- Jul 19, 2018 9:08:49 PM (7 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/surface_layer_fluxes_mod.f90
r3152 r3157 26 26 ! ----------------- 27 27 ! $Id$ 28 ! Added local free convection velocity scale w_lfc in calculation of uvw_abs. 29 ! This can be switche on/off by the user via the flag namelist parameter 30 ! use_free_convection_scaling 31 ! 32 ! 3152 2018-07-19 13:26:52Z suehring 28 33 ! q_surface is now part of surface structure 29 34 ! … … 246 251 most_method, neutral, passive_scalar, pt_surface, q_surface, & 247 252 run_coupled, surface_pressure, simulated_time, terminate_run, & 248 time_since_reference_point, urban_surface, zeta_max, zeta_min 253 time_since_reference_point, urban_surface, & 254 use_free_convection_scaling, zeta_max, zeta_min 249 255 250 256 USE grid_variables, & … … 952 958 !------------------------------------------------------------------------------! 953 959 SUBROUTINE calc_uvw_abs 954 960 955 961 IMPLICIT NONE 956 962 … … 961 967 INTEGER(iwp) :: m !< running index surface elements 962 968 969 REAL(wp) :: w_lfc !< local free convection velocity scale 963 970 ! 964 971 !-- ibit is 1 for upward-facing surfaces, zero for downward-facing surfaces. … … 970 977 j = surf%j(m) 971 978 k = surf%k(m) 979 980 ! 981 !-- Calculate free convection velocity scale w_lfc is 982 !-- use_free_convection_scaling = .T.. This will maintain a horizontal 983 !-- velocity even for very weak wind convective conditions. SIGN is used 984 !-- to set w_lfc to zero under stable conditions. 985 IF ( use_free_convection_scaling ) THEN 986 w_lfc = ABS(g / surf%pt1(m) * surf%z_mo(m) * surf%shf(m)) 987 w_lfc = ( 0.5_wp * ( w_lfc + SIGN(w_lfc,surf%shf(m)) ) )**(0.33333_wp) 988 ELSE 989 w_lfc = 0.0_wp 990 ENDIF 991 972 992 ! 973 993 !-- Compute the absolute value of the horizontal velocity. … … 991 1011 ) * ibit & 992 1012 ) & 993 )**2 1013 )**2 + w_lfc**2 & 994 1014 ) 995 1015
Note: See TracChangeset
for help on using the changeset viewer.