Changeset 1598


Ignore:
Timestamp:
Sep 14, 2016, 5:41:37 PM (8 years ago)
Author:
mlefevre
Message:

modified module_model_constants to work on Venus

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/share/module_model_constants.F

    r1585 r1598  
    33!PLANET MARS
    44
    5  MODULE module_model_constants
    6 
    7    !  2. Following are constants for use in defining real number bounds.
    8 
    9    !  A really small number.
    10 
    11    REAL    , PARAMETER :: epsilon         = 1.E-15
    12 
     5MODULE module_model_constants
     6   USE module_configure
     7   !  2. Following are constants for use in defining  REAL number bounds.
     8
     9    IMPLICIT NONE
     10   !character(len=10),save :: planet_type
     11   !integer,save :: planet
    1312   !  4. Following is information related to the physical constants.
    14 
    15    !  These are the physical constants used within the model.
    16 
    17 ! JM NOTE -- can we name this grav instead?
    18    REAL    , PARAMETER :: g = 3.72  ! acceleration due to gravity (m {s}^-2)
    19 
    20 !#if ( NMM_CORE == 1 )
    21 !   REAL    , PARAMETER :: r_d          = 192.  ! gas constant m2 s-2 K-1
    22 !   REAL    , PARAMETER :: cp           = 844.6   ! r= 8.314511E+0 *1000.E+0/mugaz
    23 !#else
    24 !   REAL    , PARAMETER :: r_d          = 192.
    25 !   REAL    , PARAMETER :: cp           = 844.6
    26 !#endif
    27 
    28    REAL    , PARAMETER :: r_d          = 191.
    29    REAL    , PARAMETER :: cp           = 744.5
    30 
    31 
    32    REAL    , PARAMETER :: r_v          = 461.6  ! gas constant for water vapor
    33    REAL    , PARAMETER :: cv           = cp-r_d
    34 !   REAL    , PARAMETER :: cpv          = 4.4*r_v  ! cp / R = 4.4 ?? ! rcp = r/cp  ~0.256793
    35    REAL    , PARAMETER :: cpv          = 3.9*r_v
    36    REAL    , PARAMETER :: cvv          = cpv-r_v
    37    REAL    , PARAMETER :: cvpm         = -cv/cp
    38    REAL    , PARAMETER :: cliq         = 4190.
    39    REAL    , PARAMETER :: cice         = 2106.
    40    REAL    , PARAMETER :: psat         = 610.78
    41    REAL    , PARAMETER :: rcv          = r_d/cv
    42    REAL    , PARAMETER :: rcp          = r_d/cp
    43    REAL    , PARAMETER :: rovg         = r_d/g
    44    REAL    , PARAMETER :: c2           = cp * rcv
    45    !! added in WRFV3
    46    real    , parameter :: mwdry        = 43.49 ! molecular weight of dry air (g/mole)
    47 
    48    REAL    , PARAMETER :: p1000mb      = 610.
    49    REAL    , PARAMETER :: t0           = 220. ! earth : 300 ... à remplacer par 220 ?
    50    REAL    , PARAMETER :: p0           = 610.
    51    REAL    , PARAMETER :: cpovcv       = cp/(cp-r_d)
    52    REAL    , PARAMETER :: cvovcp       = 1./cpovcv
    53    REAL    , PARAMETER :: rvovrd       = r_v/r_d
    54 
    55    REAL    , PARAMETER :: reradius     = 1./3397200.    ! Rayon de mars (m)  ~3397200 m
    56 
    57 !-------------------------------
    58 !****MARS
    59 ! here some LMD stuff
    6013! >> TODO: possible modification with startfi.nc values ?
    61    REAL    , PARAMETER :: wdaysec       = 88800.     ! duree du sol (s)  ~88775 s
    62    REAL    , PARAMETER :: wmugaz        = 43.49      ! Masse molaire de l'atm (g.mol-1) ~43.49
    63    REAL    , PARAMETER :: womeg         = 7.0721E-5  ! omega (rad.s-1)
    64    REAL    , PARAMETER :: wyear_day     = 669        ! Duree de l'annee (sols) ~668.6
    65    REAL    , PARAMETER :: wperiheli     = 206.66     ! Dist.min. soleil-mars (Mkm) ~206.66     
    66    REAL    , PARAMETER :: waphelie      = 249.22     ! Dist.max. soleil-mars (Mkm) ~249.22
    67    REAL    , PARAMETER :: wperi_day     = 485.       ! Date du perihelie (sols depuis printemps)
    68    REAL    , PARAMETER :: wobliquit     = 25.2       ! Obliquite de la planete (deg) ~25.2
    69    REAL    , PARAMETER :: wz0           = 1.e-2      ! surface roughness (m) ~0.01
    70    REAL    , PARAMETER :: wlmixmin      = 30         ! longueur de melange ~100
    71    REAL    , PARAMETER :: wemin_turb    = 1.e-6      ! energie minimale ~1.e-8
    72    REAL    , PARAMETER :: wemissiv      = 0.95       ! Emissivite du sol martien ~.95
    73    REAL    , PARAMETER :: wemissiceN    = 0.95       ! Emissivite calotte nord
    74    REAL    , PARAMETER :: wemissiceS    = 0.95       ! Emissivite calotte sud
    75    REAL    , PARAMETER :: walbediceN    = 0.65        ! Albedo calotte nord !0.5
    76    REAL    , PARAMETER :: walbediceS    = 0.65        ! Albedo calotte sud  !0.5
    77    REAL    , PARAMETER :: wiceradiusN   = 100.e-6    ! mean scat radius of CO2 snow (north)
    78    REAL    , PARAMETER :: wiceradiusS   = 100.e-6    ! mean scat radius of CO2 snow (south)
    79    REAL    , PARAMETER :: wdtemisiceN   = 0.4  ! time scale for snow metamorphism (north) !2 
    80    REAL    , PARAMETER :: wdtemisiceS   = 0.4  ! time scale for snow metamorphism (south) !2
    81 #ifdef NEWPHYS
    82    REAL    , PARAMETER :: wvolcapa      = 1.e6       ! volumetric capacity of soil (new soil model)
    83 #endif
     14
    8415!
    8516!-------------------------------
    86 
    87    REAL    , PARAMETER :: asselin      = .025
    88 !   REAL    , PARAMETER :: asselin      = .0
    89    REAL    , PARAMETER :: cb           = 25.
    90 
    91    REAL    , PARAMETER :: XLV0         = 3.15E6
    92    REAL    , PARAMETER :: XLV1         = 2370.
    93    REAL    , PARAMETER :: XLS0         = 2.905E6
    94    REAL    , PARAMETER :: XLS1         = 259.532
    95 
    96    REAL    , PARAMETER :: XLS          = 2.85E6
    97    REAL    , PARAMETER :: XLV          = 2.5E6
    98    REAL    , PARAMETER :: XLF          = 3.50E5
    99 
    100    REAL    , PARAMETER :: rhowater     = 1000.
    101    REAL    , PARAMETER :: rhosnow      = 100.
    102    REAL    , PARAMETER :: rhoair0      = 0.02   !Earth Surface density: 1.217 kg/m3
     17    REAL    , PARAMETER :: epsilon         = 1.E-15
     18!    REAL    , PARAMETER :: asselin      = .025
     19    REAL    , PARAMETER :: asselin      = .0
     20    REAL    , PARAMETER :: cb           = 25.
     21
     22    REAL    , PARAMETER :: XLV0         = 3.15E6
     23    REAL    , PARAMETER :: XLV1         = 2370.
     24    REAL    , PARAMETER :: XLS0         = 2.905E6
     25    REAL    , PARAMETER :: XLS1         = 259.532
     26
     27    REAL    , PARAMETER :: XLS          = 2.85E6
     28    REAL    , PARAMETER :: XLV          = 2.5E6
     29    REAL    , PARAMETER :: XLF          = 3.50E5
     30
     31    REAL    , PARAMETER :: rhowater     = 1000.
     32    REAL    , PARAMETER :: rhosnow      = 100.
     33    REAL    , PARAMETER :: rhoair0      = 0.02   !Earth Surface density: 1.217 kg/m3
    10334                                                !Mars Surface density: 0.020 kg/m3
    104    REAL    , PARAMETER :: DEGRAD       = 3.1415926/180.
    105    REAL    , PARAMETER :: DPD          = 360./669. ! longitude solaire d'un jour?
    106 
    107    REAL    , PARAMETER ::  SVP1=0.6112
    108    REAL    , PARAMETER ::  SVP2=17.67
    109    REAL    , PARAMETER ::  SVP3=29.65
    110    REAL    , PARAMETER ::  SVPT0=273.15
    111    REAL    , PARAMETER ::  EP_1=R_v/R_d-1.
    112    REAL    , PARAMETER ::  EP_2=R_d/R_v
    113    REAL    , PARAMETER ::  KARMAN=0.4  ! von karman constant
    114    REAL    , PARAMETER ::  EOMEG=7.0721E-5 ! angular rotation rate (rad.s-1)
    115    REAL    , PARAMETER ::  STBOLT=5.67051E-8 ! stefan-boltzmann constant
    116 
    117 
    118 
    119 
    120    !! NB: c_s and c_k in WRFV2 moved to module_diffusion_em.F
    121    !! NB: no need in WRFV3 because set in namelist
    122    REAL    , PARAMETER ::  prandtl = 1./3.0
     35    REAL    , PARAMETER :: DEGRAD       = 3.1415926/180.
     36    REAL    , PARAMETER :: DPD          = 360./669. ! longitude solaire d'un jour?
     37
     38    REAL    , PARAMETER ::  SVP1=0.6112
     39    REAL    , PARAMETER ::  SVP2=17.67
     40    REAL    , PARAMETER ::  SVP3=29.65
     41    REAL    , PARAMETER ::  SVPT0=273.15
     42
     43    REAL    , PARAMETER ::  KARMAN=0.4  ! von karman constant
     44
     45    REAL    , PARAMETER ::  STBOLT=5.67051E-8 ! stefan-boltzmann constant
     46
     47                                      ! proportionality constants for eddy viscosity coefficient calc
     48    REAL    , PARAMETER ::  c_s = .25  ! turbulence parameterization constant, for smagorinsky
     49!    REAL    , PARAMETER ::  c_s = .1  ! turbulence parameterization constant, for smagorinsky
     50    REAL    , PARAMETER ::  c_k = .15  ! turbulence parameterization constant, for TKE
     51    REAL    , PARAMETER ::  prandtl = 1./3.0
    12352                                         ! constants for w-damping option
    124 !   REAL    , PARAMETER ::  w_alpha = 0.3 ! strength m/s/s
    125    REAL    , PARAMETER ::  w_alpha = 2.0 ! strength m/s/s
    126 !   REAL    , PARAMETER ::  w_beta  = 1.0 ! activation cfl number
    127    REAL    , PARAMETER ::  w_beta  = 0.8 ! activation cfl number
    128 
    129 !! in WRFV3
    130 !   REAL    , PARAMETER ::  w_alpha = 0.3 ! strength m/s/s
    131 !   REAL    , PARAMETER ::  w_beta  = 1.0 ! activation cfl number
    132 !!
    133        REAL , PARAMETER ::  pq0=379.90516
    134        REAL , PARAMETER ::  epsq2=0.2
    135 !      REAL , PARAMETER ::  epsq2=0.02
    136        REAL , PARAMETER ::  a2=17.2693882
    137        REAL , PARAMETER ::  a3=273.16
    138        REAL , PARAMETER ::  a4=35.86
    139        REAL , PARAMETER ::  epsq=1.e-12
    140        REAL , PARAMETER ::  p608=rvovrd-1.
     53!    REAL    , PARAMETER ::  w_alpha = 0.3 ! strength m/s/s
     54    REAL    , PARAMETER ::  w_alpha = 2.0 ! strength m/s/s
     55!    REAL    , PARAMETER ::  w_beta  = 1.0 ! activation cfl number
     56    REAL    , PARAMETER ::  w_beta  = 0.8 ! activation cfl number
     57
     58        REAL , PARAMETER ::  pq0=379.90516
     59        REAL , PARAMETER ::  epsq2=0.2
     60!try both ?
     61!        REAL , PARAMETER ::  epsq2=0.02
     62        REAL , PARAMETER ::  a2=17.2693882
     63        REAL , PARAMETER ::  a3=273.16
     64        REAL , PARAMETER ::  a4=35.86
     65        REAL , PARAMETER ::  epsq=1.e-12
     66
    14167!#if ( NMM_CORE == 1 )
    142        REAL , PARAMETER ::  climit=1.e-20
    143        REAL , PARAMETER ::  cm1=2937.4
    144        REAL , PARAMETER ::  cm2=4.9283
    145        REAL , PARAMETER ::  cm3=23.5518
    146 !       REAL , PARAMETER ::  defc=8.0
    147 !       REAL , PARAMETER ::  defm=32.0
    148        REAL , PARAMETER ::  defc=0.0
    149        REAL , PARAMETER ::  defm=99999.0
    150        REAL , PARAMETER ::  epsfc=1./1.05
    151        REAL , PARAMETER ::  epswet=0.0
    152        REAL , PARAMETER ::  fcdif=1./3.
    153 !       REAL , PARAMETER ::  fcm=0.003
    154        REAL , PARAMETER ::  fcm=0.00003
    155 !       REAL , PARAMETER ::  fcm=0.0
    156        REAL , PARAMETER ::  gma=-r_d*(1.-rcp)*0.5
    157        REAL , PARAMETER ::  p400=40000.0
    158        REAL , PARAMETER ::  phitp=15000.0
    159        REAL , PARAMETER ::  pi2=2.*3.1415926
    160        REAL , PARAMETER ::  plbtm=105000.0
    161        REAL , PARAMETER ::  plomd=64200.0
    162        REAL , PARAMETER ::  pmdhi=35000.0
    163        REAL , PARAMETER ::  q2ini=0.50
    164        REAL , PARAMETER ::  rfcp=0.25/cp
    165        REAL , PARAMETER ::  rhcrit_land=0.75
    166        REAL , PARAMETER ::  rhcrit_sea=0.80
    167        REAL , PARAMETER ::  rlag=14.8125
    168        REAL , PARAMETER ::  rlx=0.90
    169        REAL , PARAMETER ::  scq2=50.0
    170        REAL , PARAMETER ::  slopht=0.001
    171        REAL , PARAMETER ::  tlc=2.*0.703972477
    172        REAL , PARAMETER ::  wa=0.15
    173        REAL , PARAMETER ::  wght=0.35
    174        REAL , PARAMETER ::  wpc=0.075
    175        REAL , PARAMETER ::  z0land=0.10
    176 !       REAL , PARAMETER ::  z0max=0.01
    177        REAL , PARAMETER ::  z0max=0.008
    178        REAL , PARAMETER ::  z0sea=0.001
     68        REAL , PARAMETER ::  climit=1.e-20
     69        REAL , PARAMETER ::  cm1=2937.4
     70        REAL , PARAMETER ::  cm2=4.9283
     71        REAL , PARAMETER ::  cm3=23.5518
     72!        REAL , PARAMETER ::  defc=8.0
     73!        REAL , PARAMETER ::  defm=32.0
     74        REAL , PARAMETER ::  defc=0.0
     75        REAL , PARAMETER ::  defm=99999.0
     76        REAL , PARAMETER ::  epsfc=1./1.05
     77        REAL , PARAMETER ::  epswet=0.0
     78        REAL , PARAMETER ::  fcdif=1./3.
     79!        REAL , PARAMETER ::  fcm=0.003
     80        REAL , PARAMETER ::  fcm=0.00003
     81!        REAL , PARAMETER ::  fcm=0.0
     82       
     83        REAL , PARAMETER ::  p400=40000.0
     84        REAL , PARAMETER ::  phitp=15000.0
     85        REAL , PARAMETER ::  pi2=2.*3.1415926
     86        REAL , PARAMETER ::  plbtm=105000.0
     87        REAL , PARAMETER ::  plomd=64200.0
     88        REAL , PARAMETER ::  pmdhi=35000.0
     89        REAL , PARAMETER ::  q2ini=0.50
     90        REAL , PARAMETER ::  rhcrit_land=0.75
     91        REAL , PARAMETER ::  rhcrit_sea=0.80
     92        REAL , PARAMETER ::  rlag=14.8125
     93        REAL , PARAMETER ::  rlx=0.90
     94        REAL , PARAMETER ::  scq2=50.0
     95        REAL , PARAMETER ::  slopht=0.001
     96        REAL , PARAMETER ::  tlc=2.*0.703972477
     97        REAL , PARAMETER ::  wa=0.15
     98        REAL , PARAMETER ::  wght=0.35
     99        REAL , PARAMETER ::  wpc=0.075
     100        REAL , PARAMETER ::  z0land=0.10
     101!        REAL , PARAMETER ::  z0max=0.01
     102        REAL , PARAMETER ::  z0max=0.008
     103        REAL , PARAMETER ::  z0sea=0.001
     104        REAL, PARAMETER :: r_v=461.6 ! gas constant for water vapor
     105
     106     real :: g
     107     REAL :: r_d       
     108     REAL :: cp         
     109     !REAL :: cpp
     110     REAL :: cv               
     111     REAL :: cpv         
     112     REAL :: cvv         
     113     REAL :: cvpm       
     114     REAL :: cliq       
     115     REAL :: cice         
     116     REAL :: psat         
     117     REAL :: rcv         
     118     REAL :: rcp       
     119     REAL :: rovg       
     120     REAL :: c2     
     121     real :: mwdry     !molecular weight of dry air (g/mole)
     122     REAL :: EOMEG ! angular rotation rate (rad.s-1) 
     123
     124     REAL :: p1000mb     
     125     REAL :: t0       
     126     REAL :: p0         
     127     REAL :: cpovcv       
     128     REAL :: cvovcp     
     129     REAL :: rvovrd     
     130     REAL ::  gma
     131     REAL ::  EP_1
     132     REAL ::  EP_2
     133     REAL ::  rfcp
     134     REAL ::  p608
     135     REAL :: rad
     136     REAL :: reradius 
     137     Real :: molmas !Molecular mass
     138
     139    REAL  :: wdaysec        ! duree du sol (s)  ~88775 s
     140    REAL  :: wmugaz         ! Masse molaire de l'atm (g.mol-1) ~43.49
     141    REAL  :: womeg          ! omega (rad.s-1)
     142    REAL  :: wyear_day      ! Duree de l'annee (sols) ~668.6
     143    REAL  :: wperiheli      ! Dist.min. soleil-mars (Mkm) ~206.66     
     144    REAL  :: waphelie       ! Dist.max. soleil-mars (Mkm) ~249.22
     145    REAL  :: wperi_day      ! Date du perihelie (sols depuis printemps)
     146    REAL  :: wobliquit      ! Obliquite de la planete (deg) ~25.2
     147    REAL  :: wz0            ! surface roughness (m) ~0.01
     148    REAL  :: wlmixmin       ! longueur de melange ~100
     149    REAL  :: wemin_turb     ! energie minimale ~1.e-8
     150    REAL  :: wemissiv       ! Emissivite du sol martien ~.95
     151    REAL  :: wemissiceN     !  Emissivite calotte nord
     152    REAL  :: wemissiceS     ! Emissivite calotte sud
     153    REAL  :: walbediceN     ! Albedo calotte nord !0.5
     154    REAL  :: walbediceS     ! Albedo calotte sud  !0.5
     155    REAL  :: wiceradiusN    ! mean scat radius of CO2 snow (north)
     156    REAL  :: wiceradiusS    ! mean scat radius of CO2 snow (south)
     157    REAL  :: wdtemisiceN    ! time scale for snow metamorphism (north) !2 
     158    REAL  :: wdtemisiceS    ! time scale for snow metamorphism (south) !2
     159    REAL  :: wvolcapa       ! volumetric capacity of soil (new soil model)
     160    REAL  :: z_scale        ! scale height
     161 CONTAINS
     162  SUBROUTINE init_planet_constants
     163    IMPLICIT NONE
     164    character(len=15) :: planet
     165    Call initial_config
     166    planet=model_config_rec%planet
     167    !write(*,*) "unknown planet type", planet
     168    !stop
     169   
     170   !  These are the physical constants used within the model
     171   
     172    IF ( planet == "mars" ) then !1=mars
     173! JM NOTE -- can we name this grav instead?
     174     g = 3.72  ! acceleration due to gravity (m {s}^-2)
     175
     176!#if ( NMM_CORE == 1 )
     177!    REAL :: r_d          = 192.  ! gas constant m2 s-2 K-1
     178!    REAL :: cp           = 844.6   ! r= 8.314511E+0 *1000.E+0/mugaz
     179!#else
     180!    REAL :: r_d          = 192.
     181!    REAL :: cp           = 844.6
    179182!#endif
    180183
    181 !!!! needed in WRFV3
    182    !  Earth
    183 
    184    !  The value for P2SI *must* be set to 1.0 for Earth
    185    !  Although, now we may not need this declaration here (see above)
    186    !REAL    , PARAMETER :: P2SI         = 1.0
    187 
    188    !  Orbital constants:
    189 
    190    INTEGER , PARAMETER :: PLANET_YEAR = 365
    191    REAL , PARAMETER :: OBLIQUITY = 23.5
    192    REAL , PARAMETER :: ECCENTRICITY = 0.014
    193    REAL , PARAMETER :: SEMIMAJORAXIS = 1.0 ! In AU
    194    ! Don't know the following values, so we'll fake them for now
    195    REAL , PARAMETER :: zero_date = 0.0   ! Time of perihelion passage
    196    !  Fraction into the year (from perhelion) of the
    197    !  occurrence of the Northern Spring Equinox
    198    REAL , PARAMETER :: EQUINOX_FRACTION= 0.0
    199 !!!! needed in WRFV3
    200 
    201  CONTAINS
    202    SUBROUTINE init_module_model_constants
    203    END SUBROUTINE init_module_model_constants
    204  END MODULE module_model_constants
     184     r_d          = 191.
     185     cp           = 744.5
     186     cliq         = 4190.
     187     cice         = 2106.
     188     psat         = 610.78
     189     t0           = 220. ! earth : 300 ... à remplacer par 220 ?
     190     p0           = 610.
     191     p1000mb      = 610.
     192     mwdry        = 43.49
     193     reradius     = 1./3397200. ! Rayon de mars (m)  ~3397200 m
     194     EOMEG        =7.0721E-5 ! angular rotation rate (rad.s-1)
     195     wdaysec       = 88800.     ! duree du sol (s)  ~88775 s
     196     wmugaz        = 43.49      ! Masse molaire de l'atm (g.mol-1) ~43.49
     197     womeg         = 7.0721E-5  ! omega (rad.s-1)
     198     wyear_day     = 669.       ! Duree de l'annee (sols) ~668.6
     199     wperiheli     = 206.66     ! Dist.min. soleil-mars (Mkm) ~206.66     
     200     waphelie      = 249.22     ! Dist.max. soleil-mars (Mkm) ~249.22
     201     wperi_day     = 485.       ! Date du perihelie (sols depuis printemps)
     202     wobliquit     = 25.2       ! Obliquite de la planete (deg) ~25.2
     203     wz0           = 1.e-2      ! surface roughness (m) ~0.01
     204     wlmixmin      = 30.        ! longueur de melange ~100
     205     wemin_turb    = 1.e-6      ! energie minimale ~1.e-8
     206     wemissiv      = 0.95       ! Emissivite du sol martien ~.95
     207     wemissiceN    = 0.95       ! Emissivite calotte nord
     208     wemissiceS    = 0.95       ! Emissivite calotte sud
     209     walbediceN    = 0.65        ! Albedo calotte nord !0.5
     210     walbediceS    = 0.65        ! Albedo calotte sud  !0.5
     211     wiceradiusN   = 100.e-6    ! mean scat radius of CO2 snow (north)
     212     wiceradiusS   = 100.e-6    ! mean scat radius of CO2 snow (south)
     213     wdtemisiceN   = 0.4  ! time scale for snow metamorphism (north) !2 
     214     wdtemisiceS   = 0.4  ! time scale for snow metamorphism (south) !2
     215#ifdef NEWPHYS
     216     wvolcapa      = 1.e6       ! volumetric capacity of soil (new soil model)
     217#endif
     218!#endif
     219    ELSE if ( planet == "venus") then !2=venus
     220     g            = 8.87
     221     r_d          = 191.84383904727036
     222     !cpp          = 1000.
     223     cp           = 1000.
     224     cliq         = 4190.
     225     psat         = 610.78
     226     t0           = 735. ! earth : 300
     227     p0           = 92.e5
     228     p1000mb      = 92.e5
     229     reradius     = 1./6051800. ! Rayon de mars (m)  ~6051800 m
     230     rad          = 6051800.
     231     wmugaz       = 43.49
     232     womeg        = 0.2992549E-06
     233     wdaysec      = 0.1008707E+08
     234    Else
     235     write(*,*) "unknown planet type:", planet
     236     stop
     237    endif
     238     cv           = cp-r_d
     239     cpv          = 3.9*r_v
     240     cvv          = cpv-r_v
     241     cvpm         = -cv/cp
     242     rcv          = r_d/cv
     243     rcp          = r_d/cp
     244     rovg         = r_d/g
     245     c2           = cp * rcv
     246     cpovcv       = cp/(cp-r_d)
     247     cvovcp       = 1./cpovcv
     248     rvovrd       = r_v/r_d
     249     gma          = -r_d*(1.-rcp)*0.5
     250     EP_1         = r_v/r_d-1.
     251     EP_2         = r_d/r_v
     252     rfcp         =0.25/cp
     253     p608         =rvovrd-1.
     254     z_scale      =r_d*t0/g
     255    write(*,*) "planet : ", planet
     256    write(*,*) "g = ", g
     257    write(*,*) "cp = ", cp
     258    write(*,*) "r_d = ", r_d
     259    write(*,*) "t0 = ", t0
     260    write(*,*) "p0 = ", p0
     261  END SUBROUTINE init_planet_constants
     262END MODULE module_model_constants
Note: See TracChangeset for help on using the changeset viewer.