Changeset 3395 for palm/trunk/UTIL/inifor/src/util.f90
- Timestamp:
- Oct 22, 2018 5:32:49 PM (7 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/UTIL/inifor/src/util.f90
r3183 r3395 26 26 ! ----------------- 27 27 ! $Id$ 28 ! New routines for computing potential temperature and moist air density 29 ! Increased number of digits in real-to-str conversion 30 ! 31 ! 3183 2018-07-27 14:25:55Z suehring 28 32 ! Improved real-to-string conversion 29 33 ! … … 48 52 USE defs, & 49 53 ONLY : dp, PI, DATE, SNAME 54 USE types, & 55 ONLY : grid_definition 50 56 51 57 IMPLICIT NONE … … 281 287 282 288 289 !------------------------------------------------------------------------------! 290 ! Description: 291 ! ------------ 292 !> Converts the absolute temperature to the potential temperature in place using 293 !> the identity a^b = e^(b ln(a)). 294 !> 295 !> theta = T * (p_ref/p)^(R/c_p) = T * e^( R/c_p * ln(p_ref/p) ) 296 !------------------------------------------------------------------------------! 297 SUBROUTINE potential_temperature(t, p, p_ref, r, cp) 298 REAL(dp), DIMENSION(:,:,:), INTENT(INOUT) :: t 299 REAL(dp), DIMENSION(:,:,:), INTENT(IN) :: p 300 REAL(dp), INTENT(IN) :: p_ref, r, cp 301 REAL(dp) :: rcp 302 303 rcp = r/cp 304 t(:,:,:) = t(:,:,:) * EXP( rcp * LOG(p_ref / p(:,:,:)) ) 305 306 END SUBROUTINE potential_temperature 307 308 309 !------------------------------------------------------------------------------! 310 ! Description: 311 ! ------------ 312 !> Compute the density in place of the given temperature (t_rho). 313 !------------------------------------------------------------------------------! 314 SUBROUTINE moist_density(t_rho, p, qv, rd, rv) 315 REAL(dp), DIMENSION(:,:,:), INTENT(INOUT) :: t_rho 316 REAL(dp), DIMENSION(:,:,:), INTENT(IN) :: p, qv 317 REAL(dp), INTENT(IN) :: rd, rv 318 319 t_rho(:,:,:) = p(:,:,:) / ( & 320 (rv * qv(:,:,:) + rd * (1.0_dp - qv(:,:,:))) * t_rho(:,:,:) & 321 ) 322 323 END SUBROUTINE moist_density 324 325 283 326 ! Convert a real number to a string in scientific notation 284 327 ! showing four significant digits. … … 298 341 299 342 300 CHARACTER(LEN=1 2) FUNCTION real_to_str_f(val)343 CHARACTER(LEN=16) FUNCTION real_to_str_f(val) 301 344 302 345 REAL(dp), INTENT(IN) :: val 303 346 304 WRITE(real_to_str_f, '(F1 2.4)') val347 WRITE(real_to_str_f, '(F16.8)') val 305 348 real_to_str_f = ADJUSTL(real_to_str_f) 306 349
Note: See TracChangeset
for help on using the changeset viewer.