Ignore:
Timestamp:
Oct 29, 2018 7:36:56 PM (5 years ago)
Author:
suehring
Message:

Branch resler -r 3439 re-integrated into current trunk: RTM 3.0, transpiration of plant canopy, output fixes in USM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/basic_constants_and_equations_mod.f90

    r3361 r3449  
    2525! -----------------
    2626! $Id$
     27! +degc_to_k
     28!
     29! 3361 2018-10-16 20:39:37Z knoop
    2730! New module (introduced with modularization of bulk cloud physics model)
    2831!
     
    4346    IMPLICIT NONE
    4447
    45     REAL(wp), PARAMETER ::  pi = 3.141592654_wp  !< PI
    46 
    4748    REAL(wp), PARAMETER ::  c_p = 1005.0_wp                           !< heat capacity of dry air (J kg-1 K-1)
     49    REAL(wp), PARAMETER ::  degc_to_k = 273.15_wp                     !< temperature (in K) of 0 deg C (K)
    4850    REAL(wp), PARAMETER ::  g = 9.81_wp                               !< gravitational acceleration (m s-2)
    4951    REAL(wp), PARAMETER ::  kappa = 0.4_wp                            !< von Karman constant
     
    5557    REAL(wp), PARAMETER ::  molecular_weight_of_nh4no3 = 0.08004_wp   !< mol. m. ammonium sulfate (kg mol-1)
    5658    REAL(wp), PARAMETER ::  molecular_weight_of_water = 0.01801528_wp !< mol. m. H2O (kg mol-1)
     59    REAL(wp), PARAMETER ::  pi = 3.141592654_wp                       !< PI
    5760    REAL(wp), PARAMETER ::  rho_l = 1.0E3_wp                          !< density of water (kg m-3)
    5861    REAL(wp), PARAMETER ::  rho_nacl = 2165.0_wp                      !< density of NaCl (kg m-3)
     
    6164    REAL(wp), PARAMETER ::  r_d = 287.0_wp                            !< sp. gas const. dry air (J kg-1 K-1)
    6265    REAL(wp), PARAMETER ::  r_v = 461.51_wp                           !< sp. gas const. water vapor (J kg-1 K-1)
    63     REAL(wp), PARAMETER ::  sigma_sb = 5.67E-08_wp                    !< Stefan-Boltzmann constant
     66    REAL(wp), PARAMETER ::  sigma_sb = 5.67037E-08_wp                 !< Stefan-Boltzmann constant
    6467    REAL(wp), PARAMETER ::  solar_constant = 1368.0_wp                !< solar constant at top of atmosphere
    6568    REAL(wp), PARAMETER ::  vanthoff_nacl = 2.0_wp                    !< van't Hoff factor for NaCl
     
    143146!
    144147!--    Saturation vapor pressure for a specific temperature:
    145        magnus_0d =  611.2_wp * EXP( 17.62_wp * ( t - 273.15_wp ) /             &
     148       magnus_0d =  611.2_wp * EXP( 17.62_wp * ( t - degc_to_k ) /             &
    146149                                                   ( t - 29.65_wp  ) )
    147150
     
    163166!
    164167!--    Saturation vapor pressure for a specific temperature:
    165        magnus_1d =  611.2_wp * EXP( 17.62_wp * ( t - 273.15_wp ) /             &
     168       magnus_1d =  611.2_wp * EXP( 17.62_wp * ( t - degc_to_k ) /             &
    166169                                               ( t - 29.65_wp  ) )
    167170
Note: See TracChangeset for help on using the changeset viewer.