source: trunk/libf/phyvenus/suphec.F @ 24

Last change on this file since 24 was 3, checked in by slebonnois, 14 years ago

Creation de repertoires:

  • chantiers : pour communiquer sur nos projets de modifs
  • documentation : pour stocker les docs

Ajout de:

  • libf/phytitan : physique de Titan
  • libf/chimtitan: chimie de Titan
  • libf/phyvenus : physique de Venus
File size: 7.3 KB
Line 
1!
2! $Header: /home/cvsroot/LMDZ4/libf/phylmd/suphec.F,v 1.1.1.1 2004/05/19 12:53:08 lmdzadmin Exp $
3!
4      SUBROUTINE suphec
5C
6#include "YOMCST.h"
7#include "YOETHF.h"
8cIM cf. JLD
9       LOGICAL firstcall
10       SAVE firstcall
11       DATA firstcall /.TRUE./
12       IF (firstcall) THEN
13         PRINT*, 'suphec initialise les constantes du GCM'
14         firstcall = .FALSE.
15       ELSE
16         PRINT*, 'suphec DEJA APPELE '
17         RETURN
18       ENDIF
19C      -----------------------------------------------------------------
20C
21C*       1.    DEFINE FUNDAMENTAL CONSTANTS.
22C              -----------------------------
23C
24      WRITE(UNIT=6,FMT='(''0*** Constants of the ICM   ***'')')
25      RPI=2.*ASIN(1.)
26      RCLUM=299792458.
27      RHPLA=6.6260755E-34
28      RKBOL=1.380658E-23
29      RNAVO=6.0221367E+23
30      WRITE(UNIT=6,FMT='('' *** Fundamental constants ***'')')
31      WRITE(UNIT=6,FMT='(''           PI = '',E13.7,'' -'')')RPI
32      WRITE(UNIT=6,FMT='(''            c = '',E13.7,''m s-1'')')
33     S RCLUM
34      WRITE(UNIT=6,FMT='(''            h = '',E13.7,''J s'')')
35     S RHPLA
36      WRITE(UNIT=6,FMT='(''            K = '',E13.7,''J K-1'')')
37     S RKBOL
38      WRITE(UNIT=6,FMT='(''            N = '',E13.7,''mol-1'')')
39     S RNAVO
40C
41C     ----------------------------------------------------------------
42C
43C*       2.    DEFINE ASTRONOMICAL CONSTANTS.
44C              ------------------------------
45C
46c TERRE
47c     RDAY=86400.
48c     REA=149597870000.
49c     REPSM=0.409093
50C
51c     RSIYEA=365.25*RDAY*2.*RPI/6.283076
52c 1/(duree du jour) = 1/(periode rotation) - 1/(periode revolution)
53c     RSIDAY=RDAY/(1.+RDAY/RSIYEA)
54c     ROMEGA=2.*RPI/RSIDAY
55
56c VENUS
57      RSIDAY=20.9961e6   ! 243.01 j
58      RSIYEA=19.4141e6   ! 224.7 j
59      ROMEGA=2.*RPI/RSIDAY
60c 1/(duree du jour) = 1/(periode rotation) + 1/(periode revolution)
61      RDAY=RSIDAY/(1.+RSIDAY/RSIYEA) ! 116.748 j
62      REA=108.15e9
63      REPSM=0.  ! 0. veut dire qu'on commence au point vernal
64c
65cIM on mets R_ecc, R_peri, R_incl dans conf_phys.F90
66
67      WRITE(UNIT=6,FMT='('' *** Astronomical constants ***'')')
68      WRITE(UNIT=6,FMT='(''          day = '',E13.7,'' s'')')RDAY
69      WRITE(UNIT=6,FMT='('' half g. axis = '',E13.7,'' m'')')REA
70      WRITE(UNIT=6,FMT='('' mean anomaly = '',E13.7,'' -'')')REPSM
71      WRITE(UNIT=6,FMT='('' sideral year = '',E13.7,'' s'')')RSIYEA
72      WRITE(UNIT=6,FMT='(''  sideral day = '',E13.7,'' s'')')RSIDAY
73      WRITE(UNIT=6,FMT='(''        omega = '',E13.7,'' s-1'')')
74     S                  ROMEGA
75c     write(unit=6,fmt='('' excentricite = '',e13.7,''-'')')R_ecc
76c     write(unit=6,fmt='(''     equinoxe = '',e13.7,''-'')')R_peri
77c     write(unit=6,fmt='(''  inclinaison = '',e13.7,''-'')')R_incl
78C
79C     ------------------------------------------------------------------
80C
81C*       3.    DEFINE GEOIDE.
82C              --------------
83C
84c TERRE
85c     RG=9.80665
86c     RA=6371229.
87
88c VENUS
89      RG=8.87
90      RA=6051300.
91
92      R1SA=SNGL(1.D0/DBLE(RA))
93      WRITE(UNIT=6,FMT='('' ***         Geoide         ***'')')
94      WRITE(UNIT=6,FMT='(''       Gravity = '',E13.7,'' m s-2'')')
95     S      RG
96      WRITE(UNIT=6,FMT='('' Planet radius = '',E13.7,'' m'')')RA
97      WRITE(UNIT=6,FMT='(''  Inverse P.R. = '',E13.7,'' m-1'')')R1SA
98C
99C     -----------------------------------------------------------------
100C
101C*       4.    DEFINE RADIATION CONSTANTS.
102C              ---------------------------
103C
104c z.x.li      RSIGMA=2. * RPI**5 * RKBOL**4 /(15.* RCLUM**2 * RHPLA**3)
105      rsigma = 2.*rpi**5 * (rkbol/rhpla)**3 * rkbol/rclum/rclum/15.
106cIM init. dans conf_phys.F90   RI0=1365.
107      WRITE(UNIT=6,FMT='('' ***        Radiation       ***'')')
108      WRITE(UNIT=6,FMT='('' Stefan-Bol.  = '',E13.7,'' W m-2 K-4''
109     S )')  RSIGMA
110cIM init. dans conf_phys.F90   WRITE(UNIT=6,FMT='('' Solar const. = '',E13.7,'' W m-2'')')
111cIM init. dans conf_phys.F90  S      RI0
112C
113C     -----------------------------------------------------------------
114C
115C*       5.    DEFINE THERMODYNAMIC CONSTANTS, GAS PHASE.
116C              ------------------------------------------
117C
118      R=RNAVO*RKBOL
119c TERRE
120c     RMD=28.9644
121      RMV=18.0153
122
123c VENUS
124      RMD=43.44
125
126      RD=1000.*R/RMD
127      RV=1000.*R/RMV
128c TERRE
129c     RCPD=3.5*RD
130      RCPV=4. *RV
131c VENUS
132! ADAPTATION GCM POUR CP(T)
133! VENUS: Cp(T) = RCPD*(T/T0)^nu (RCPD phys = cpp dyn)
134! avec RCPD=1000., T0=460. et nu=0.35
135      RCPD=1.0e3
136!     RCPD=9.0e2  ! Version constante
137
138      RCVD=RCPD-RD
139      RCVV=RCPV-RV
140      RKAPPA=RD/RCPD
141      RETV=RV/RD-1.
142      WRITE(UNIT=6,FMT='('' *** Thermodynamic, gas     ***'')')
143      WRITE(UNIT=6,FMT='('' Perfect gas  = '',e13.7)') R
144      WRITE(UNIT=6,FMT='('' Dry air mass = '',e13.7)') RMD
145      WRITE(UNIT=6,FMT='('' Vapour  mass = '',e13.7)') RMV
146      WRITE(UNIT=6,FMT='('' Dry air cst. = '',e13.7)') RD
147      WRITE(UNIT=6,FMT='('' Vapour  cst. = '',e13.7)') RV
148      WRITE(UNIT=6,FMT='(''        Cpd0  = '',e13.7)') RCPD
149      WRITE(UNIT=6,FMT='(''         Cvd  = '',e13.7)') RCVD
150      WRITE(UNIT=6,FMT='(''         Cpv  = '',e13.7)') RCPV
151      WRITE(UNIT=6,FMT='(''         Cvv  = '',e13.7)') RCVV
152      WRITE(UNIT=6,FMT='(''     Rd/Cpd0  = '',e13.7)') RKAPPA
153      WRITE(UNIT=6,FMT='(''     Rv/Rd-1  = '',e13.7)') RETV
154C
155C     ----------------------------------------------------------------
156C
157C*       6.    DEFINE THERMODYNAMIC CONSTANTS, LIQUID PHASE.
158C              ---------------------------------------------
159C
160      RCW=RCPV
161      WRITE(UNIT=6,FMT='('' *** Thermodynamic, liquid  ***'')')
162      WRITE(UNIT=6,FMT='(''         Cw   = '',E13.7)') RCW
163C
164C     ----------------------------------------------------------------
165C
166C*       7.    DEFINE THERMODYNAMIC CONSTANTS, SOLID PHASE.
167C              --------------------------------------------
168C
169      RCS=RCPV
170      WRITE(UNIT=6,FMT='('' *** thermodynamic, solid   ***'')')
171      WRITE(UNIT=6,FMT='(''         Cs   = '',E13.7)') RCS
172C
173C     ----------------------------------------------------------------
174C
175C*       8.    DEFINE THERMODYNAMIC CONSTANTS, TRANSITION OF PHASE.
176C              ----------------------------------------------------
177C
178      RTT=273.16
179      RLVTT=2.5008E+6
180      RLSTT=2.8345E+6
181      RLMLT=RLSTT-RLVTT
182      RATM=100000.
183      WRITE(UNIT=6,FMT='('' *** Thermodynamic, trans.  ***'')')
184      WRITE(UNIT=6,FMT='('' Fusion point  = '',E13.7)') RTT
185      WRITE(UNIT=6,FMT='(''        RLvTt  = '',E13.7)') RLVTT
186      WRITE(UNIT=6,FMT='(''        RLsTt  = '',E13.7)') RLSTT
187      WRITE(UNIT=6,FMT='(''        RLMlt  = '',E13.7)') RLMLT
188      WRITE(UNIT=6,FMT='('' Normal press. = '',E13.7)') RATM
189      WRITE(UNIT=6,FMT='('' Latent heat :  '')')
190C
191C     ----------------------------------------------------------------
192C
193C*       9.    SATURATED VAPOUR PRESSURE.
194C              --------------------------
195C
196      RESTT=611.14
197      RGAMW=(RCW-RCPV)/RV
198      RBETW=RLVTT/RV+RGAMW*RTT
199      RALPW=LOG(RESTT)+RBETW/RTT+RGAMW*LOG(RTT)
200      RGAMS=(RCS-RCPV)/RV
201      RBETS=RLSTT/RV+RGAMS*RTT
202      RALPS=LOG(RESTT)+RBETS/RTT+RGAMS*LOG(RTT)
203      RGAMD=RGAMS-RGAMW
204      RBETD=RBETS-RBETW
205      RALPD=RALPS-RALPW
206C
207C     ------------------------------------------------------------------
208c
209c calculer les constantes pour les fonctions thermodynamiques
210c
211      RVTMP2=RCPV/RCPD-1.
212      RHOH2O=RATM/100.
213      R2ES=RESTT*RD/RV
214      R3LES=17.269
215      R3IES=21.875
216      R4LES=35.86
217      R4IES=7.66
218      R5LES=R3LES*(RTT-R4LES)
219      R5IES=R3IES*(RTT-R4IES)
220C
221      RETURN
222      END
Note: See TracBrowser for help on using the repository browser.