Ignore:
Timestamp:
Sep 16, 2016, 3:05:48 PM (8 years ago)
Author:
mlefevre
Message:

In modif_mars : deleted planet specific modules. Added initialization module_model_constants. Implemented heating rates reading for prescribed planet.

Location:
trunk/MESOSCALE/LMD_MM_MARS/SRC
Files:
6 deleted
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/LESnophys_/modif/module_model_constants.F

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

    r1236 r1607  
    107107   INTEGER :: icm,jcm, ii, im1, jj, jm1, loop, error, fid, nxc, nyc
    108108   REAL    :: u_mean,v_mean, f0, p_surf, p_level, qvf, z_at_v, z_at_u
    109    REAL    :: z_scale, xrad, yrad, zrad, rad, delt, cof1, cof2
     109   REAL    :: xrad, yrad, zrad, rad, delt, cof1, cof2
    110110!   REAL, EXTERNAL :: interp_0
    111111   REAL    :: hm, xa
     
    129129 INTEGER :: ierr
    130130!!MARS
     131 REAL, DIMENSION(nl_max) :: profdustq,profdustn
     132 REAL, DIMENSION(nl_max) :: prescribed_sw,prescribed_lw
    131133
    132134      REAL :: pfu, pfd, phm
     
    134136      !INTEGER :: hypsometric_opt = 2 ! Wee et al. 2012 correction
    135137
    136 
     138character(len=10) :: planet
    137139
    138140#ifdef DM_PARALLEL
     
    140142#endif
    141143
     144   call init_planet_constants
    142145
    143146   SELECT CASE ( model_data_order )
     
    878881  ENDDO
    879882  ENDDO
    880 
     883    IF (planet.eq."prescribed") Then
     884      call read_hr(profdustq,profdustn,nl_in)
     885      open(unit=17,file="prescribed_sw.txt",action="write")
     886      open(unit=18,file="prescribed_lw.txt",action="write")
     887      DO k=1,kte!-1
     888        p_level = grid%em_znu(k)*(pd_surf - grid%p_top) + grid%p_top
     889        prescribed_sw(k) = interp_0( profdustq, pd_in, p_level, nl_in )
     890        prescribed_lw(k) = interp_0( profdustn, pd_in, p_level, nl_in )
     891        write (17,*) prescribed_sw(k)
     892        write (18,*) prescribed_lw(k)
     893      ENDDO
     894      close(unit=17)
     895      close(unit=18)
     896    ENDIF
    881897 END SUBROUTINE init_domain_rk
    882898
     
    955971!      parameter (p1000mb = 1.e+05, r = 287, cp = 1003., cv = cp-r, cvpm = -cv/cp, g=9.81 )
    956972!      parameter (p1000mb = 610., r = 192., cp = 844.6, cv = cp-r, cvpm = -cv/cp, g=3.72)
    957       parameter (p1000mb = 610., r = 191., cp = 744.5, cv = cp-r, cvpm = -cv/cp, g=3.72)
     973!      parameter (p1000mb = 610., r = 191., cp = 744.5, cv = cp-r, cvpm = -cv/cp, g=3.72)
    958974!****Mars
    959975      integer k, it, nl
     
    9991015      qvf = 1. + rvovrd*qv_input(1)
    10001016      rho_surf = 1./((r/p1000mb)*th_surf*qvf*((p_surf/p1000mb)**cvpm))
    1001       pi_surf = (p_surf/p1000mb)**(r/cp)
     1017      pi_surf = (p_surf/p1000mb)**(rcp)
    10021018          !!!!!! rcp variable
    10031019          !rho_surf =  1./((r_input(1)/p1000mb)*th_surf*qvf*((p_surf/p1000mb)**cvpm_input(1)))
     
    10471063                      - dz*(0.75*rho_input(k)+0.25*rho_input(k-1))*g*qvf1
    10481064                      !- 0.5*dz*(rho_input(k)+rho_input(k-1))*g*qvf1
    1049               rho_input(k) = 1./((r/p1000mb)*th_input(k)*qvf*((pm_input(k)/p1000mb)**cvpm))
     1065              rho_input(k) = 1./((r_d/p1000mb)*th_input(k)*qvf*((pm_input(k)/p1000mb)**cvpm))
    10501066!!
    10511067!! marche pas
     
    11641180      end subroutine read_sounding
    11651181
     1182      subroutine read_hr(hr_sw,hr_lw,n)
     1183      implicit none
     1184      integer n
     1185      real hr_sw(n),hr_lw(n)
     1186      logical end_of_file
     1187
     1188      integer k
     1189
     1190! first element is the surface
     1191
     1192      open(unit=11,file='input_hr',form='formatted',status='old')
     1193      rewind(11)
     1194      end_of_file = .false.
     1195      k = 0
     1196      do while (.not. end_of_file)
     1197
     1198        read(11,*,end=102) hr_sw(k+1),hr_lw(k+1)
     1199        write(*,*) k,hr_sw(k+1),hr_lw(k+1)
     1200        k = k+1
     1201        go to 113
     1202 102    end_of_file = .true.
     1203 113    continue
     1204      enddo
     1205
     1206      close(unit=11,status = 'keep')
     1207
     1208      end subroutine read_hr
     1209
    11661210END MODULE module_initialize
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/WRFV2/share/init_modules.F

    r11 r1607  
    5555 CALL init_module_configure
    5656 CALL init_module_driver_constants
    57  CALL init_module_model_constants
     57 CALL init_planet_constants
    5858 CALL init_module_domain
    5959 CALL init_module_machine
Note: See TracChangeset for help on using the changeset viewer.