module constants_mod
!
! Bruce Wyman
!
!
!
! Defines useful constants for Earth.
!
!
! Constants are defined as real parameters,
! except for PI and RADIAN, which are calculated in constants_init to promote
! consistency and accuracy among various compilers.
!
! Constants are accessed through the "use" statement.
!
implicit none
private
character(len=128) :: version='$Id: constants.f90,v 1.3 2004/12/10 19:35:17 gtn Exp $'
character(len=128) :: tagname='$Name: mom4p0d $'
!dummy variable to use in HUGE initializations
real :: realnumber
!------------ physical constants ---------------
!
! radius of the earth
!
!
! rotation rate of the planet (earth)
!
!
! acceleration due to gravity
!
!
! gas constant for dry air
!
!
! RDGAS / CP_AIR
!
!
! specific heat capacity of dry air at constant pressure
!
!
! specific heat capacity taken from McDougall (2002) "Potential Enthalpy ..."
!
!
! average density of sea water
!
!
! reciprocal of average density of sea water
!
!
! (kg/m^3)*(cal/kg/deg C)(joules/cal) = (joules/m^3/deg C)
!
real, public, parameter :: RADIUS = 6371.0e3
real, public, parameter :: OMEGA = 7.292e-5
real, public, parameter :: GRAV = 9.80
real, public, parameter :: RDGAS = 287.04
real, public, parameter :: KAPPA = 2./7.
real, public, parameter :: CP_AIR = RDGAS/KAPPA
real, public, parameter :: CP_OCEAN = 3989.24495292815
real, public, parameter :: RHO0 = 1.035e3
real, public, parameter :: RHO0R = 1.0/RHO0
real, public, parameter :: RHO_CP = RHO0*CP_OCEAN
!------------ water vapor constants ---------------
!
! gas constant for water vapor
!
!
! density of liquid water
!
!
! latent heat of evaporation
!
!
! latent heat of fusion
!
!
! latent heat of sublimation
!
!
! temp where fresh water freezes
!
real, public, parameter :: RVGAS = 461.50
real, public, parameter :: DENS_H2O = 1000.
real, public, parameter :: HLV = 2.500e6
real, public, parameter :: HLF = 3.34e5
real, public, parameter :: HLS = 2.834e6
real, public, parameter :: TFREEZE = 273.16
!-------------- radiation constants -----------------
!
! molecular weight of air
!
!
! molecular weight of water
!
!
! molecular weight of ozone
!
!
! diffusivity factor
!
!
! seconds in a day
!
!
! Avogadro's number
!
!
! mean sea level pressure
!
!
! mean sea level pressure
!
!
! radius of the earth
!
real, public, parameter :: WTMAIR = 2.896440E+01
real, public, parameter :: WTMH2O = 1.801534E+01
real, public, parameter :: WTMO3 = 47.99820E+01
real, public, parameter :: DIFFAC = 1.660000E+00
real, public, parameter :: SECONDS_PER_DAY = 8.640000E+04
real, public, parameter :: AVOGNO = 6.023000E+23
real, public, parameter :: PSTD = 1.013250E+06
real, public, parameter :: PSTD_MKS = 101325.0
real, public, parameter :: REARTH = 6.356766E+08
!
! factor used to convert flux divergence to heating rate in degrees per day
!
!
! factor used to convert flux divergence to heating rate in degrees per day
!
!
! mixing ratio of molecular oxygen in air
!
!
! reference atmospheric density
!
!
! minimum value allowed as argument to log function
!
!
! melting point of water
!
real, public, parameter :: RADCON = ((1.0E+02*GRAV)/(1.0E+04*CP_AIR))*SECONDS_PER_DAY
real, public, parameter :: RADCON_MKS = (GRAV/CP_AIR)*SECONDS_PER_DAY
real, public, parameter :: O2MIXRAT = 2.0953E-01
real, public, parameter :: RHOAIR = 1.292269
real, public, parameter :: ALOGMIN = -50.0
real, public, parameter :: FREZDK = 273.16
!------------ miscellaneous constants ---------------
!
! Stefan-Boltzmann constant
!
!
! Von Karman constant
!
!
! ratio of circle circumference to diameter
!
!
! degrees per radian
!
!
! converts rho*g*z (in mks) to dbars: 1dbar = 10^4 (kg/m^3)(m/s^2)m
!
!
! degrees Kelvin at zero Celsius
!
!
! a small number to prevent divide by zero exceptions
!
real, public, parameter :: STEFAN = 5.6734e-8
real, public, parameter :: VONKARM = 0.40
real, public :: PI = HUGE(realnumber)
real, public :: RADIAN = HUGE(realnumber)
real, public, parameter :: C2DBARS = 1.e-4
real, public, parameter :: KELVIN = 273.15
real, public, parameter :: EPSLN = 1.0e-40
!-----------------------------------------------------------------------
! version and tagname published
! so that write_version_number can be called for constants_mod by fms_init
public :: version, tagname
!-----------------------------------------------------------------------
public :: constants_init
contains
subroutine constants_init
! dummy routine. Initialization of PI and RADIAN is done by fms_init.
end subroutine constants_init
end module constants_mod
!
!
! 1. Renaming of constants.
!
!
! 2. Additional constants.
!
!
! Constants have been declared as type REAL, PARAMETER.
!
! The value a constant can not be changed in a users program.
! New constants can be defined in terms of values from the
! constants module using a parameter statement.
!
! The name given to a particular constant may be changed.
!
! Constants can be used on the right side on an assignment statement
! (their value can not be reassigned).
!
! As PI is calculated, it cannot be a parameter variable.
! Do not assign a new value to PI.
!
!
!