mo_constants.f90

      MODULE mo_constants
      
        IMPLICIT NONE
      
   5:   ! ----------------------------------------------------------------
        !
        ! module *mo_constants* basic universal constants  and derived constants.
        !
        ! ----------------------------------------------------------------
  10: 
        REAL :: api     ! 2.*arcsin(1.).
        REAL :: a       ! radius of the earth.
        REAL :: omega   ! solid rotation velocity of the earth.
        REAL :: g       ! gravity acceleration.
  15:   REAL :: cpd     ! specific heat at constant pressure (dry air).
        REAL :: cpv     !            idem               (water vapour).
        REAL :: rd      ! gas constant for dry air.
        REAL :: rv      !    idem      for water vapour.
        REAL :: rcpd    ! rcpd=1./cpd.
  20:   REAL :: vtmpc1  ! vtmpc1=rv/rd-1.
        REAL :: vtmpc2  ! vtmpc2=cpv/cpd-1.
        REAL :: rhoh2o  ! density of liquid water.
        REAL :: alv     ! latent heat for vaporisation.
        REAL :: als     ! latent heat for sublimation.
  25:   REAL :: alf     ! latent heat for fusion.
        REAL :: clw     ! specific heat for liquid water.
        REAL :: tmelt   ! temperature of fusion of ice.
        REAL :: solc    ! solar constant.
        REAL :: stbo    ! stephan boltzmann constant.
  30:   REAL :: dayl    ! length of the day (in seconds).
        REAL :: yearl   ! length of the year (in days).
      
        ! constants used for computation of saturation mixing ratio
        !   over liquid water(*c_les*) or ice(*c_ies*).
  35: 
        REAL :: c1es    ! 610.78
        REAL :: c2es    ! 1es*rd/rv
        REAL :: c3les   ! 17.269
        REAL :: c3ies   ! 21.875
  40:   REAL :: c4les   ! 35.86
        REAL :: c4ies   !  7.66
        REAL :: c5les   ! c3les*(tmelt-c4les)
        REAL :: c5ies   ! c3ies*(tmelt-c4ies)
        REAL :: c5alvcp ! c5les*alv/cpd
  45:   REAL :: c5alscp ! c5ies*als/cpd
        REAL :: alvdcp  ! alv/cpd
        REAL :: alsdcp  ! als/cpd
      
      CONTAINS
  50: 
        SUBROUTINE inicon
      
          ! Description:
          ! Preset constants in mo_constants.
  55:     !
          ! Method:
          !
          ! *inicon* is called from *setdyn*.
          !
  60:     ! Authors:
          !
          ! M. Jarraud, ECMWF, December 1982, original source
          ! L. Kornblueh, MPI, May 1998, f90 rewrite
          ! U. Schulzweida, MPI, May 1998, f90 rewrite
  65:     ! H.-S. Bauer, MPI, Jul 1998, changed
          ! A. Rhodin, MPI, Jan 1999, subroutine inicon put into module mo_constants
          !
          ! for more details see file AUTHORS
          !
  70: 
          USE mo_start_dataset,   ONLY: ly365
      
          IMPLICIT NONE
      
  75:     !  Intrinsic functions 
          INTRINSIC ASIN
      
          !  Executable statements 
      
  80:     !-- 1. Preset constants
      
          api = 2.*ASIN(1.)
          a = 6371000.
          omega = .7292E-4
  85:     g = 9.80665
          cpd = 1005.46
          cpv = 1869.46
          rd = 287.05
          rv = 461.51
  90: 
          rcpd = 1./cpd
          vtmpc1 = rv/rd - 1.
          vtmpc2 = cpv/cpd - 1.
      
  95:     rhoh2o = 1000.
          alv = 2.5008E6
          als = 2.8345E6
          alf = als - alv
      
 100:     clw = 4186.84
          tmelt = 273.16
      
          solc = 1365.
          stbo = 5.67E-8
 105: 
          dayl = 86400.
      
          IF (ly365) THEN
             yearl = 365.2422
 110:     ELSE
             yearl = 360.
          ENDIF
      
          c1es    = 610.78
 115:     c2es    = c1es*rd/rv
          c3les   = 17.269
          c3ies   = 21.875
          c4les   = 35.86
          c4ies   =  7.66
 120:     c5les   = c3les*(tmelt-c4les)
          c5ies   = c3ies*(tmelt-c4ies)
          c5alvcp = c5les*alv/cpd
          c5alscp = c5ies*als/cpd
          alvdcp  = alv/cpd
 125:     alsdcp  = als/cpd
      
        END SUBROUTINE inicon
      
      END MODULE mo_constants


Info Section
uses: mo_start_dataset
back to top
ECHAM 4 vf90 (C) 1998 Max-Planck-Institut für Meteorologie, Hamburg
Wed Nov 24 01:25:21 CST 1999

HTML derived from FORTRAN source by f2html.pl v0.3 (C) 1997,98 Beroud Jean-Marc.