/[lmdze]/trunk/phylmd/suphec.f
ViewVC logotype

Diff of /trunk/phylmd/suphec.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/libf/phylmd/suphec.f90 revision 37 by guez, Tue Dec 21 15:45:48 2010 UTC trunk/Sources/phylmd/suphec.f revision 198 by guez, Tue May 31 16:17:35 2016 UTC
# Line 1  Line 1 
1  module suphec_m  module suphec_m
2    
3      use nr_util, only: pi
4    
5    implicit none    implicit none
6    
7  contains    ! A1.0 Fundamental constants
8      real, parameter:: RCLUM = 299792458. ! speed of light, m s-1
9      real, parameter:: RHPLA = 6.6260755E-34 ! Planck constant, J s
10      real, parameter:: KBOL = 1.380658E-23 ! Boltzmann constant, in J K-1
11      real, parameter:: NAVO = 6.0221367E23 ! Avogadro number, in mol-1
12    
13    SUBROUTINE suphec    ! A1.1 Astronomical constants
14    
15      ! From phylmd/suphec.F,v 1.2 2005/06/06 13:16:33    REAL ROMEGA
16      real, parameter:: RDAY = 86400.
17    
18      ! Initialise certaines constantes et parametres physiques.    REAL, parameter:: RSIYEA = 365.25 * RDAY * 2. * PI / 6.283076
19      ! sideral year, in s
20    
21      use YOMCST, only: rpi, rclum, rhpla, rkbol, rnavo, rday, rea, repsm, &    REAL, parameter:: RSIDAY = RDAY / (1. + RDAY / RSIYEA) ! sideral day, in s
          rsiyea, rsiday,romega, rg, ra, r1sa, rsigma, r, rmd, rmo3, rmv, rd, &  
          rv, rcpd, rcvd, rcpv, rcvv, rkappa, retv, rcw, rcs, rtt, rlvtt, &  
          rlstt, rlmlt, ratm, restt, rgamw, rbetw, ralpw, rgams, rbets, ralps, &  
          rgamd, rbetd, ralpd  
     use yoethf, only: r2es, r3ies, r3les, r4ies, r4les, r5ies, r5les, rhoh2o, &  
          rvtmp2  
22    
23      !------------------------------------------    ! A1.2 Geoide
24      real, parameter:: RG = 9.80665 ! acceleration of gravity, in m s-2
25      real, parameter:: RA = 6371229.
26    
27      PRINT *, 'Call sequence information: suphec'    ! A1.3 Radiation
28      REAL, parameter:: rsigma = 2. * pi**5 * (kbol / rhpla)**3 * kbol / rclum**2 &
29           / 15.
30    
31      ! A1.4 Thermodynamic gas phase
32      REAL, parameter:: R = NAVO * KBOL ! ideal gas constant, in J K-1 mol-1
33      real, parameter:: MV = 18.0153 ! molar mass of water, in g mol-1
34    
35      real, parameter:: RV = 1e3 * R / MV
36      ! specific ideal gas constant for water vapor, in J K-1 kg-1
37      ! (factor 1e3: conversion from g to kg)
38    
39      real, parameter:: MD = 28.9644 ! molar mass of dry air, in g mol-1
40    
41      real, parameter:: RD = 1e3 * R / MD
42      ! specific ideal gas constant for dry air, in J K-1 kg-1
43      ! (factor 1e3: conversion from g to kg)
44    
45      real, parameter:: RCPV = 4. * RV ! Cpv, gas phase
46    
47      real, save:: RCVD, RCVV
48    
49      real, parameter:: RCPD = 7. / 2 * RD
50      ! specific heat capacity for dry air, in J K-1 kg-1
51    
52      real, parameter:: RMO3 = 47.9942
53      REAL, parameter:: RKAPPA = RD/RCPD
54      real, save:: RETV
55    
56      ! A1.5, 6 Thermodynamic liquid, solid phases
57    
58      REAL, parameter:: RCW = RCPV ! LIQUID PHASE Cw
59      real, save:: RCS
60    
61      ! A1.7 Thermodynamic transition of phase
62      REAL, save:: RLMLT
63      real, parameter:: RTT = 273.16
64      real, parameter:: RLVTT = 2.5008E+6
65      real, parameter:: RLSTT = 2.8345E+6
66      real, parameter:: RATM = 1e5
67    
68      ! 1. DEFINE FUNDAMENTAL CONSTANTS    ! A1.8 Curve of saturation
69      REAL, save:: RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS
70      real, parameter:: RESTT = 611.14
71      REAL, save:: RALPD, RBETD, RGAMD
72    
73      print *, 'Constants of the ICM'    private pi
74      RPI=2.*ASIN(1.)  
75      RCLUM=299792458.  contains
76      RHPLA=6.6260755E-34  
77      RKBOL=1.380658E-23    SUBROUTINE suphec
78      RNAVO=6.0221367E+23  
79      print *, 'Fundamental constants '      ! From phylmd/suphec.F, version 1.2 2005/06/06 13:16:33
80      print '(''           PI = '',E13.7,'' -'')', RPI      ! Initialise certaines constantes et certains paramètres physiques.
81      print '(''            c = '',E13.7,''m s-1'')', RCLUM  
82      print '(''            h = '',E13.7,''J s'')', RHPLA      !------------------------------------------
83      print '(''            K = '',E13.7,''J K-1'')', RKBOL  
84      print '(''            N = '',E13.7,''mol-1'')', RNAVO      PRINT *, 'Call sequence information: suphec'
85    
86      ! 2. DEFINE ASTRONOMICAL CONSTANTS      ! 2. DEFINE ASTRONOMICAL CONSTANTS
87    
88      RDAY=86400.      ROMEGA = 2.*PI/RSIDAY
     REA=149597870000.  
     REPSM=0.409093  
   
     RSIYEA=365.25*RDAY*2.*RPI/6.283076  
     RSIDAY=RDAY/(1.+RDAY/RSIYEA)  
     ROMEGA=2.*RPI/RSIDAY  
89    
90      print *, 'Astronomical constants '      print *, 'Astronomical constants '
91      print '(''          day = '',E13.7,'' s'')', RDAY      print '('' omega = '', E13.7, '' s-1'')', ROMEGA
92      print '('' half g. axis = '',E13.7,'' m'')', REA  
93      print '('' mean anomaly = '',E13.7,'' -'')', REPSM      ! 3. DEFINE GEOIDE.
94      print '('' sideral year = '',E13.7,'' s'')', RSIYEA  
95      print '(''  sideral day = '',E13.7,'' s'')', RSIDAY      print *, ' Geoide '
96      print '(''        omega = '',E13.7,'' s-1'')', ROMEGA      print '('' Gravity = '', E13.7, '' m s-2'')', RG
97        print '('' Earth radius = '', E13.7, '' m'')', RA
98      ! 3.    DEFINE GEOIDE.  
99        ! 4. DEFINE RADIATION CONSTANTS.
100      RG=9.80665  
101      RA=6371229.      print *, ' Radiation '
102      R1SA=SNGL(1.D0/DBLE(RA))      print '('' Stefan-Bol. = '', E13.7, '' W m-2 K-4'')', RSIGMA
103      print *, '        Geoide      '  
104      print '(''      Gravity = '',E13.7,'' m s-2'')', RG      ! 5. DEFINE THERMODYNAMIC CONSTANTS, GAS PHASE.
105      print '('' Earth radius = '',E13.7,'' m'')', RA  
106      print '('' Inverse E.R. = '',E13.7,'' m'')', R1SA      RCVD = RCPD-RD
107        RCVV = RCPV-RV
108      ! 4.    DEFINE RADIATION CONSTANTS.      RETV = RV / RD - 1.
109        print *, 'Thermodynamics, gas'
110      rsigma = 2.*rpi**5 * (rkbol/rhpla)**3 * rkbol/rclum/rclum/15.      print '('' Ozone mass = '', e13.7)', RMO3
111      print *, '       Radiation    '      print *, "rd = ", RD, "J K-1 kg-1"
112      print '('' Stefan-Bol.  = '',E13.7,'' W m-2 K-4'')',   RSIGMA      print *, "rv = ", RV, "J K-1 kg-1"
113        print '('' Cpd = '', e13.7)', RCPD
114      ! 5.    DEFINE THERMODYNAMIC CONSTANTS, GAS PHASE.      print '('' Cvd = '', e13.7)', RCVD
115        print '('' Cvv = '', e13.7)', RCVV
116      R=RNAVO*RKBOL      print '('' Rd/Cpd = '', e13.7)', RKAPPA
117      RMD=28.9644      print '('' Rv / Rd - 1 = '', e13.7)', RETV
     RMO3=47.9942  
     RMV=18.0153  
     RD=1000.*R/RMD  
     RV=1000.*R/RMV  
     RCPD=3.5*RD  
     RCVD=RCPD-RD  
     RCPV=4. *RV  
     RCVV=RCPV-RV  
     RKAPPA=RD/RCPD  
     RETV=RV/RD-1.  
     print *, 'Thermodynamic, gas  '  
     print '('' Perfect gas  = '',e13.7)',  R  
     print '('' Dry air mass = '',e13.7)',  RMD  
     print '('' Ozone   mass = '',e13.7)',  RMO3  
     print '('' Vapour  mass = '',e13.7)',  RMV  
     print '('' Dry air cst. = '',e13.7)',  RD  
     print '('' Vapour  cst. = '',e13.7)',  RV  
     print '(''         Cpd  = '',e13.7)',  RCPD  
     print '(''         Cvd  = '',e13.7)',  RCVD  
     print '(''         Cpv  = '',e13.7)',  RCPV  
     print '(''         Cvv  = '',e13.7)',  RCVV  
     print '(''      Rd/Cpd  = '',e13.7)',  RKAPPA  
     print '(''     Rv/Rd-1  = '',e13.7)',  RETV  
   
     ! 6.    DEFINE THERMODYNAMIC CONSTANTS, LIQUID PHASE.  
   
     RCW=RCPV  
     print *, 'Thermodynamic, liquid  '  
     print '(''         Cw   = '',E13.7)',  RCW  
118    
119      ! 7.    DEFINE THERMODYNAMIC CONSTANTS, SOLID PHASE.      ! 7. DEFINE THERMODYNAMIC CONSTANTS, SOLID PHASE.
120    
121      RCS=RCPV      RCS = RCPV
122      print *, 'thermodynamic, solid'      print *, 'thermodynamic, solid'
123      print '(''         Cs   = '',E13.7)',  RCS      print '('' Cs = '', E13.7)', RCS
124    
125      ! 8.    DEFINE THERMODYNAMIC CONSTANTS, TRANSITION OF PHASE.      ! 8. DEFINE THERMODYNAMIC CONSTANTS, TRANSITION OF PHASE.
126    
127      RTT=273.16      RLMLT = RLSTT-RLVTT
128      RLVTT=2.5008E+6      print *, 'Thermodynamic, transition of phase:'
129      RLSTT=2.8345E+6      print '('' Fusion point = '', E13.7)', RTT
130      RLMLT=RLSTT-RLVTT      print '('' RLvTt = '', E13.7)', RLVTT
131      RATM=100000.      print '('' RLsTt = '', E13.7)', RLSTT
132      print *, 'Thermodynamic, trans.  '      print '('' RLMlt = '', E13.7)', RLMLT
133      print '('' Fusion point  = '',E13.7)',  RTT      print '('' Normal pressure = '', E13.7)', RATM
134      print '(''        RLvTt  = '',E13.7)',  RLVTT  
135      print '(''        RLsTt  = '',E13.7)',  RLSTT      ! 9. SATURATED VAPOUR PRESSURE.
136      print '(''        RLMlt  = '',E13.7)',  RLMLT  
137      print '('' Normal press. = '',E13.7)',  RATM      RGAMW = (RCW-RCPV)/RV
138        RBETW = RLVTT/RV+RGAMW*RTT
139      ! 9.    SATURATED VAPOUR PRESSURE.      RALPW = LOG(RESTT)+RBETW/RTT+RGAMW*LOG(RTT)
140        RGAMS = (RCS-RCPV)/RV
141      RESTT=611.14      RBETS = RLSTT/RV+RGAMS*RTT
142      RGAMW=(RCW-RCPV)/RV      RALPS = LOG(RESTT)+RBETS/RTT+RGAMS*LOG(RTT)
143      RBETW=RLVTT/RV+RGAMW*RTT      RGAMD = RGAMS-RGAMW
144      RALPW=LOG(RESTT)+RBETW/RTT+RGAMW*LOG(RTT)      RBETD = RBETS-RBETW
145      RGAMS=(RCS-RCPV)/RV      RALPD = RALPS-RALPW
     RBETS=RLSTT/RV+RGAMS*RTT  
     RALPS=LOG(RESTT)+RBETS/RTT+RGAMS*LOG(RTT)  
     RGAMD=RGAMS-RGAMW  
     RBETD=RBETS-RBETW  
     RALPD=RALPS-RALPW  
   
     ! calculer les constantes pour les fonctions thermodynamiques  
   
     RVTMP2=RCPV/RCPD-1.  
     RHOH2O=RATM/100.  
     R2ES=RESTT*RD/RV  
     R3LES=17.269  
     R3IES=21.875  
     R4LES=35.86  
     R4IES=7.66  
     R5LES=R3LES*(RTT-R4LES)  
     R5IES=R3IES*(RTT-R4IES)  
146    
147    END SUBROUTINE suphec    END SUBROUTINE suphec
148    

Legend:
Removed from v.37  
changed lines
  Added in v.198

  ViewVC Help
Powered by ViewVC 1.1.21