Ignore:
Timestamp:
Oct 22, 2018 5:32:49 PM (7 years ago)
Author:
eckhard
Message:

inifor: Added computation of geostrophic winds from COSMO input

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/UTIL/inifor/src/util.f90

    r3183 r3395  
    2626! -----------------
    2727! $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
    2832! Improved real-to-string conversion
    2933!
     
    4852    USE defs,                                                                  &
    4953        ONLY :  dp, PI, DATE, SNAME
     54    USE types,                                                                 &
     55        ONLY :  grid_definition
    5056
    5157    IMPLICIT NONE
     
    281287
    282288
     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
    283326    ! Convert a real number to a string in scientific notation
    284327    ! showing four significant digits.
     
    298341
    299342
    300     CHARACTER(LEN=12) FUNCTION real_to_str_f(val)
     343    CHARACTER(LEN=16) FUNCTION real_to_str_f(val)
    301344
    302345        REAL(dp), INTENT(IN) ::  val
    303346
    304         WRITE(real_to_str_f, '(F12.4)') val
     347        WRITE(real_to_str_f, '(F16.8)') val
    305348        real_to_str_f = ADJUSTL(real_to_str_f)
    306349
Note: See TracChangeset for help on using the changeset viewer.