source: LMDZ6/trunk/libf/dyn3d_common/conf_planete.f90 @ 5424

Last change on this file since 5424 was 5268, checked in by abarral, 8 weeks ago

.f90 <-> .F90 depending on cpp key use

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 1.6 KB
RevLine 
[1437]1!
2! $Id$
3!
4SUBROUTINE conf_planete
5!
6USE IOIPSL
[2597]7USE comconst_mod, ONLY: pi, g, molmass, kappa, cpp, omeg, rad, &
8                        year_day, daylen, daysec, ihf
[2600]9USE comvert_mod, ONLY: preff, pa
[1437]10IMPLICIT NONE
11!
12!
13!   Declarations :
14!   --------------
[2600]15
[1437]16!
17!   local:
18!   ------
19
20! ---------------------------------------------
21! Initialisations de constantes de la dynamique
22! ---------------------------------------------
23! Pi
24pi=2.*asin(1.)
25
26!Reference surface pressure (Pa)
[4379]27! 101080 : specific value for CMIP5 aqua/terra planets
28! "Specify the initial dry mass to be equivalent to
29!  a global mean surface pressure (101325 minus 245) Pa."
30preff=101080.
[1437]31CALL getin('preff', preff)
[4379]32
[1437]33! Reference pressure at which hybrid coord. become purely pressure
34! pa=50000.
35pa=preff/2.
36CALL getin('pa', pa)
[4379]37
[1437]38! Gravity
39g=9.80665
[4379]40
[1437]41CALL getin('g',g)
42! Molar mass of the atmosphere
[4379]43
[1437]44molmass = 28.9644
45CALL getin('molmass',molmass)
46! kappa=R/Cp et Cp     
[4379]47
[1437]48kappa = 2./7.
49CALL getin('kappa',kappa)
[4379]50
[1437]51cpp=8.3145/molmass/kappa*1000.
52CALL getin('cpp',cpp)
53! Radius of the planet
[4379]54
[1437]55rad = 6371229.
56CALL getin('radius',rad)
[4379]57
[1437]58! Length of a standard day (s)
59daysec=86400.
60CALL getin('daysec',daysec)
[4379]61
[1437]62! Rotation rate of the planet:
63! Length of a solar day, in standard days
64daylen = 1.
[4379]65
[1437]66CALL getin('daylen',daylen)
67! Number of days (standard) per year:
[4379]68
[1437]69year_day = 365.25
70CALL getin('year_day',year_day)
71! Omega
72! omeg=2.*pi/86400.
[4379]73
[1437]74omeg=2.*pi/daysec*(1./daylen+1./year_day)
75CALL getin('omeg',omeg)
76
[1505]77! Intrinsic heat flux (default: none) (only used if planet_type="giant")
78ihf = 0.
79call getin('ihf',ihf)
80
[1437]81END SUBROUTINE conf_planete
Note: See TracBrowser for help on using the repository browser.