source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/config/ppsrc/dyn3d_common/conf_planete.f90 @ 224

Last change on this file since 224 was 224, checked in by ymipsl, 10 years ago
File size: 5.3 KB
Line 
1!
2! $Id$
3!
4SUBROUTINE conf_planete
5!
6
7
8
9! if not using IOIPSL, we still need to use (a local version of) getin
10USE ioipsl_getincom
11
12IMPLICIT NONE
13!
14!
15!   Declarations :
16!   --------------
17!-----------------------------------------------------------------------
18!   INCLUDE 'dimensions.h'
19!
20!   dimensions.h contient les dimensions du modele
21!   ndm est tel que iim=2**ndm
22!-----------------------------------------------------------------------
23
24      INTEGER iim,jjm,llm,ndm
25
26      PARAMETER (iim= 128,jjm=96,llm=64,ndm=1)
27
28!-----------------------------------------------------------------------
29!
30! $Id: comconst.h 1437 2010-09-30 08:29:10Z emillour $
31!
32!-----------------------------------------------------------------------
33! INCLUDE comconst.h
34
35      COMMON/comconsti/im,jm,lllm,imp1,jmp1,lllmm1,lllmp1,lcl,          &
36     &                 iflag_top_bound,mode_top_bound
37      COMMON/comconstr/dtvr,daysec,                                     &
38     & pi,dtphys,dtdiss,rad,r,kappa,cotot,unsim,g,omeg                  &
39     & ,dissip_fac_mid,dissip_fac_up,dissip_deltaz,dissip_hdelta        &
40     & ,dissip_pupstart  ,tau_top_bound,                                &
41     & daylen,molmass, ihf
42      COMMON/cpdetvenus/cpp,nu_venus,t0_venus
43
44      INTEGER im,jm,lllm,imp1,jmp1,lllmm1,lllmp1,lcl
45      REAL dtvr ! dynamical time step (in s)
46      REAL daysec !length (in s) of a standard day
47      REAL pi    ! something like 3.14159....
48      REAL dtphys ! (s) time step for the physics
49      REAL dtdiss ! (s) time step for the dissipation
50      REAL rad ! (m) radius of the planet
51      REAL r ! Reduced Gas constant r=R/mu
52             ! with R=8.31.. J.K-1.mol-1, mu: mol mass of atmosphere (kg/mol)
53      REAL cpp   ! Cp
54      REAL kappa ! kappa=R/Cp
55      REAL cotot
56      REAL unsim ! = 1./iim
57      REAL g ! (m/s2) gravity
58      REAL omeg ! (rad/s) rotation rate of the planet
59! Dissipation factors, for Earth model:
60      REAL dissip_factz,dissip_zref !dissip_deltaz
61! Dissipation factors, for other planets:
62      REAL dissip_fac_mid,dissip_fac_up,dissip_deltaz,dissip_hdelta
63      REAL dissip_pupstart
64      INTEGER iflag_top_bound,mode_top_bound
65      REAL tau_top_bound
66      REAL daylen ! length of solar day, in 'standard' day length
67      REAL molmass ! (g/mol) molar mass of the atmosphere
68
69      REAL nu_venus,t0_venus ! coeffs needed for Cp(T), Venus atmosphere
70      REAL ihf  ! (W/m2) intrinsic heat flux for giant planets
71
72
73!-----------------------------------------------------------------------
74!
75! $Id: comvert.h 1654 2012-09-24 15:07:18Z aslmd $
76!
77!-----------------------------------------------------------------------
78!   INCLUDE 'comvert.h'
79
80      COMMON/comvertr/ap(llm+1),bp(llm+1),presnivs(llm),dpres(llm),     &
81     &               pa,preff,nivsigs(llm),nivsig(llm+1),               &
82     &               aps(llm),bps(llm),scaleheight,pseudoalt(llm)
83
84      common/comverti/disvert_type, pressure_exner
85
86      real ap     ! hybrid pressure contribution at interlayers
87      real bp     ! hybrid sigma contribution at interlayer
88      real presnivs ! (reference) pressure at mid-layers
89      real dpres
90      real pa     ! reference pressure (Pa) at which hybrid coordinates
91                  ! become purely pressure
92      real preff  ! reference surface pressure (Pa)
93      real nivsigs
94      real nivsig
95      real aps    ! hybrid pressure contribution at mid-layers
96      real bps    ! hybrid sigma contribution at mid-layers
97      real scaleheight ! atmospheric (reference) scale height (km)
98      real pseudoalt ! pseudo-altitude of model levels (km), based on presnivs(),
99                     ! preff and scaleheight
100
101      integer disvert_type ! type of vertical discretization:
102                           ! 1: Earth (default for planet_type==earth),
103                           !     automatic generation
104                           ! 2: Planets (default for planet_type!=earth),
105                           !     using 'z2sig.def' (or 'esasig.def) file
106
107      logical pressure_exner
108!     compute pressure inside layers using Exner function, else use mean
109!     of pressure values at interfaces
110
111 !-----------------------------------------------------------------------
112!
113!   local:
114!   ------
115
116real :: year_day_dyn
117
118! ---------------------------------------------
119! Initialisations de constantes de la dynamique
120! ---------------------------------------------
121! Pi
122pi=2.*asin(1.)
123
124!Reference surface pressure (Pa)
125preff=101325.
126CALL getin('preff', preff)
127! Reference pressure at which hybrid coord. become purely pressure
128! pa=50000.
129pa=preff/2.
130CALL getin('pa', pa)
131! Gravity
132g=9.80665
133CALL getin('g',g)
134! Molar mass of the atmosphere
135molmass = 28.9644
136CALL getin('molmass',molmass)
137! kappa=R/Cp et Cp     
138kappa = 2./7.
139CALL getin('kappa',kappa)
140cpp=8.3145/molmass/kappa*1000.
141CALL getin('cpp',cpp)
142! Radius of the planet
143rad = 6371229. 
144CALL getin('radius',rad)
145! Length of a standard day (s)
146daysec=86400.
147CALL getin('daysec',daysec)
148! Rotation rate of the planet:
149! Length of a solar day, in standard days
150daylen = 1.
151CALL getin('daylen',daylen)
152! Number of days (standard) per year:
153year_day_dyn = 365.25
154CALL getin('year_day',year_day_dyn)
155! Omega
156! omeg=2.*pi/86400.
157omeg=2.*pi/daysec*(1./daylen+1./year_day_dyn)
158CALL getin('omeg',omeg)
159
160! Intrinsic heat flux [default is none]
161! Aymeric -- for giant planets
162! [matters only if planet_type="giant"]
163ihf = 0.
164CALL getin('ihf',ihf)
165
166
167
168END SUBROUTINE conf_planete
Note: See TracBrowser for help on using the repository browser.