source: LMDZ.3.3/branches/rel-LF/libf/phylmd/suphec.F @ 489

Last change on this file since 489 was 433, checked in by lmdzadmin, 21 years ago

Convergence avec la version de Ionela dec 2002

YOMCST.? : suppression RI0 (IM)
albedo.F : facteur 1.2 sur le nouveau calcul (IM)
clesphys.h : rajout de différentes ctes (concentration des gaz) (IM)
clmain.F : separation des flux LW, SW (JLD)

remplace qsurf par yqsol (IM)

conf_phys.F90 : rajout de différentes ctes (gaz + orbite) (IM)
convect3.F : DPINV+SIGD*0.5*(EVAP(1)+EVAP(2)) (SBL)
cv3_routines.F:
cvparam3.h : compatibilite avec conema3 TEMPORAIRE (FH)
phyetat0.F : lecture de co2_ppm et solaire pour tests de coherence
phyredem.F : co2_ppm et solaire passé en common
physiq.F : separation flux LW, SW

rajout diagnostiques (slp, w500)
suppression iflag_con = 4
clwcon0=qcondc (FH)
position dU "ENDIF ! ok_cvl"

radlwsw.F : passage des concentrations gaz dans un common (IM)

PEMIS(i) = 1.0 (JLD pour cohérence ORCHIDEE)

stdlevvar.F90 :
suphec.F : suppression init. des ctes orbitales (IM)

nouvelles E/S (ini_hist..., write_hist...)

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 6.9 KB
Line 
1      SUBROUTINE suphec
2C
3#include "YOMCST.h"
4#include "YOETHF.h"
5cIM cf. JLD
6       LOGICAL firstcall
7       SAVE firstcall
8       DATA firstcall /.TRUE./
9       IF (firstcall) THEN
10         PRINT*, 'suphec initialise les constantes du GCM'
11         firstcall = .FALSE.
12       ELSE
13         PRINT*, 'suphec DEJA APPELE '
14         RETURN
15       ENDIF
16C      -----------------------------------------------------------------
17C
18C*       1.    DEFINE FUNDAMENTAL CONSTANTS.
19C              -----------------------------
20C
21      WRITE(UNIT=6,FMT='(''0*** Constants of the ICM   ***'')')
22      RPI=2.*ASIN(1.)
23      RCLUM=299792458.
24      RHPLA=6.6260755E-34
25      RKBOL=1.380658E-23
26      RNAVO=6.0221367E+23
27      WRITE(UNIT=6,FMT='('' *** Fundamental constants ***'')')
28      WRITE(UNIT=6,FMT='(''           PI = '',E13.7,'' -'')')RPI
29      WRITE(UNIT=6,FMT='(''            c = '',E13.7,''m s-1'')')
30     S RCLUM
31      WRITE(UNIT=6,FMT='(''            h = '',E13.7,''J s'')')
32     S RHPLA
33      WRITE(UNIT=6,FMT='(''            K = '',E13.7,''J K-1'')')
34     S RKBOL
35      WRITE(UNIT=6,FMT='(''            N = '',E13.7,''mol-1'')')
36     S RNAVO
37C
38C     ----------------------------------------------------------------
39C
40C*       2.    DEFINE ASTRONOMICAL CONSTANTS.
41C              ------------------------------
42C
43      RDAY=86400.
44      REA=149597870000.
45      REPSM=0.409093
46C
47      RSIYEA=365.25*RDAY*2.*RPI/6.283076
48      RSIDAY=RDAY/(1.+RDAY/RSIYEA)
49      ROMEGA=2.*RPI/RSIDAY
50c
51c exp1      R_ecc = 0.05
52c exp1      R_peri = 102.04
53c exp1      R_incl = 22.5
54c exp1      print*, 'Parametres orbitaux modifies'
55c ref      R_ecc = 0.016724
56c ref      R_peri = 102.04
57c ref      R_incl = 23.5
58c
59cIM 161002 : pour avoir les ctes AMIP II
60cIM 161002   R_ecc = 0.016724
61cIM 161002   R_peri = 102.04
62cIM 161002   R_incl = 23.5
63cIM on mets R_ecc, R_peri, R_incl dans conf_phys.F90
64c     R_ecc = 0.016715
65c     R_peri = 102.7
66c     R_incl = 23.441
67c
68      WRITE(UNIT=6,FMT='('' *** Astronomical constants ***'')')
69      WRITE(UNIT=6,FMT='(''          day = '',E13.7,'' s'')')RDAY
70      WRITE(UNIT=6,FMT='('' half g. axis = '',E13.7,'' m'')')REA
71      WRITE(UNIT=6,FMT='('' mean anomaly = '',E13.7,'' -'')')REPSM
72      WRITE(UNIT=6,FMT='('' sideral year = '',E13.7,'' s'')')RSIYEA
73      WRITE(UNIT=6,FMT='(''  sideral day = '',E13.7,'' s'')')RSIDAY
74      WRITE(UNIT=6,FMT='(''        omega = '',E13.7,'' s-1'')')
75     S                  ROMEGA
76c     write(unit=6,fmt='('' excentricite = '',e13.7,''-'')')R_ecc
77c     write(unit=6,fmt='(''     equinoxe = '',e13.7,''-'')')R_peri
78c     write(unit=6,fmt='(''  inclinaison = '',e13.7,''-'')')R_incl
79C
80C     ------------------------------------------------------------------
81C
82C*       3.    DEFINE GEOIDE.
83C              --------------
84C
85      RG=9.80665
86      RA=6371229.
87      R1SA=SNGL(1.D0/DBLE(RA))
88      WRITE(UNIT=6,FMT='('' ***         Geoide         ***'')')
89      WRITE(UNIT=6,FMT='(''      Gravity = '',E13.7,'' m s-2'')')
90     S      RG
91      WRITE(UNIT=6,FMT='('' Earth radius = '',E13.7,'' m'')')RA
92      WRITE(UNIT=6,FMT='('' Inverse E.R. = '',E13.7,'' m'')')R1SA
93C
94C     -----------------------------------------------------------------
95C
96C*       4.    DEFINE RADIATION CONSTANTS.
97C              ---------------------------
98C
99c z.x.li      RSIGMA=2. * RPI**5 * RKBOL**4 /(15.* RCLUM**2 * RHPLA**3)
100      rsigma = 2.*rpi**5 * (rkbol/rhpla)**3 * rkbol/rclum/rclum/15.
101cIM init. dans conf_phys.F90   RI0=1365.
102      WRITE(UNIT=6,FMT='('' ***        Radiation       ***'')')
103      WRITE(UNIT=6,FMT='('' Stefan-Bol.  = '',E13.7,'' W m-2 K-4''
104     S )')  RSIGMA
105cIM init. dans conf_phys.F90   WRITE(UNIT=6,FMT='('' Solar const. = '',E13.7,'' W m-2'')')
106cIM init. dans conf_phys.F90  S      RI0
107C
108C     -----------------------------------------------------------------
109C
110C*       5.    DEFINE THERMODYNAMIC CONSTANTS, GAS PHASE.
111C              ------------------------------------------
112C
113      R=RNAVO*RKBOL
114      RMD=28.9644
115      RMV=18.0153
116      RD=1000.*R/RMD
117      RV=1000.*R/RMV
118      RCPD=3.5*RD
119      RCVD=RCPD-RD
120      RCPV=4. *RV
121      RCVV=RCPV-RV
122      RKAPPA=RD/RCPD
123      RETV=RV/RD-1.
124      WRITE(UNIT=6,FMT='('' *** Thermodynamic, gas     ***'')')
125      WRITE(UNIT=6,FMT='('' Perfect gas  = '',e13.7)') R
126      WRITE(UNIT=6,FMT='('' Dry air mass = '',e13.7)') RMD
127      WRITE(UNIT=6,FMT='('' Vapour  mass = '',e13.7)') RMV
128      WRITE(UNIT=6,FMT='('' Dry air cst. = '',e13.7)') RD
129      WRITE(UNIT=6,FMT='('' Vapour  cst. = '',e13.7)') RV
130      WRITE(UNIT=6,FMT='(''         Cpd  = '',e13.7)') RCPD
131      WRITE(UNIT=6,FMT='(''         Cvd  = '',e13.7)') RCVD
132      WRITE(UNIT=6,FMT='(''         Cpv  = '',e13.7)') RCPV
133      WRITE(UNIT=6,FMT='(''         Cvv  = '',e13.7)') RCVV
134      WRITE(UNIT=6,FMT='(''      Rd/Cpd  = '',e13.7)') RKAPPA
135      WRITE(UNIT=6,FMT='(''     Rv/Rd-1  = '',e13.7)') RETV
136C
137C     ----------------------------------------------------------------
138C
139C*       6.    DEFINE THERMODYNAMIC CONSTANTS, LIQUID PHASE.
140C              ---------------------------------------------
141C
142      RCW=RCPV
143      WRITE(UNIT=6,FMT='('' *** Thermodynamic, liquid  ***'')')
144      WRITE(UNIT=6,FMT='(''         Cw   = '',E13.7)') RCW
145C
146C     ----------------------------------------------------------------
147C
148C*       7.    DEFINE THERMODYNAMIC CONSTANTS, SOLID PHASE.
149C              --------------------------------------------
150C
151      RCS=RCPV
152      WRITE(UNIT=6,FMT='('' *** thermodynamic, solid   ***'')')
153      WRITE(UNIT=6,FMT='(''         Cs   = '',E13.7)') RCS
154C
155C     ----------------------------------------------------------------
156C
157C*       8.    DEFINE THERMODYNAMIC CONSTANTS, TRANSITION OF PHASE.
158C              ----------------------------------------------------
159C
160      RTT=273.16
161      RLVTT=2.5008E+6
162      RLSTT=2.8345E+6
163      RLMLT=RLSTT-RLVTT
164      RATM=100000.
165      WRITE(UNIT=6,FMT='('' *** Thermodynamic, trans.  ***'')')
166      WRITE(UNIT=6,FMT='('' Fusion point  = '',E13.7)') RTT
167      WRITE(UNIT=6,FMT='(''        RLvTt  = '',E13.7)') RLVTT
168      WRITE(UNIT=6,FMT='(''        RLsTt  = '',E13.7)') RLSTT
169      WRITE(UNIT=6,FMT='(''        RLMlt  = '',E13.7)') RLMLT
170      WRITE(UNIT=6,FMT='('' Normal press. = '',E13.7)') RATM
171      WRITE(UNIT=6,FMT='('' Latent heat :  '')')
172C
173C     ----------------------------------------------------------------
174C
175C*       9.    SATURATED VAPOUR PRESSURE.
176C              --------------------------
177C
178      RESTT=611.14
179      RGAMW=(RCW-RCPV)/RV
180      RBETW=RLVTT/RV+RGAMW*RTT
181      RALPW=LOG(RESTT)+RBETW/RTT+RGAMW*LOG(RTT)
182      RGAMS=(RCS-RCPV)/RV
183      RBETS=RLSTT/RV+RGAMS*RTT
184      RALPS=LOG(RESTT)+RBETS/RTT+RGAMS*LOG(RTT)
185      RGAMD=RGAMS-RGAMW
186      RBETD=RBETS-RBETW
187      RALPD=RALPS-RALPW
188C
189C     ------------------------------------------------------------------
190c
191c calculer les constantes pour les fonctions thermodynamiques
192c
193      RVTMP2=RCPV/RCPD-1.
194      RHOH2O=RATM/100.
195      R2ES=RESTT*RD/RV
196      R3LES=17.269
197      R3IES=21.875
198      R4LES=35.86
199      R4IES=7.66
200      R5LES=R3LES*(RTT-R4LES)
201      R5IES=R3IES*(RTT-R4IES)
202C
203      RETURN
204      END
Note: See TracBrowser for help on using the repository browser.