source: codes/icosagcm/devel/src/base/earth_const.f90 @ 836

Last change on this file since 836 was 836, checked in by dubos, 5 years ago

devel : Cp(T) thermodynamics (TBC)

File size: 4.0 KB
Line 
1MODULE earth_const
2  USE prec, ONLY : rstd
3  IMPLICIT NONE
4  SAVE
5
6! init_earth_const is called from icosa_init outside of an OMP PARALLEL section
7! hence the variables set here are not THREADPRIVATE
8
9! Some variable are BIND(C) to be accessible from Python
10
11  REAL(rstd), BIND(C) :: g=9.80616    ! acceleration of gravity assumed constant
12  REAL(rstd):: radius=6.37122E6
13  REAL(rstd) :: omega=7.292E-5
14  REAL(rstd) :: scale_factor=1.
15  REAL(rstd),PARAMETER :: daysec=86400
16
17  REAL(rstd), BIND(C) ::   Treff=273.,     &   ! reference temperature, used in definition of entropy
18                           preff=101325.,  &   ! reference pressure, used in definition of entropy and theta
19                           cpp=1004.70885, &   ! specific heat at constant pressure at t=Treff for dry air
20                           cppv=1860.,     &   ! specific heat at constant pressure at t=Treff for water vapor
21                           Rd,             &   ! specific perfect gas constant for dry air
22                           Rv=461.5            ! specific perfect gas constant for water vapor
23
24  REAL(rstd) :: nu=0.35     ! exponent in variable-Cp law Cp=cpp*(T/Treff)^nu
25  REAL(rstd) :: pa=50000.   ! default value set to preff/2 by disvert_std
26  REAL(rstd) :: scale_height=8000. ! atmospheric scale height (m)
27  REAL(rstd) :: gas_constant = 8.3144621 
28  REAL(rstd) :: mu             ! molar mass (?)
29
30  REAL(rstd) :: kappa=0.2857143
31
32  INTEGER, PARAMETER :: thermo_none=-99, thermo_theta=1, thermo_entropy=2, thermo_variable_Cp=3, &
33       thermo_moist=4, thermo_boussinesq=5, thermo_dry=10, thermo_fake_moist=11, thermo_moist_debug=100
34  LOGICAL :: boussinesq
35  INTEGER, BIND(C) :: caldyn_thermo, physics_thermo
36
37CONTAINS
38 
39  SUBROUTINE init_earth_const
40    USE getin_mod, ONLY : getin
41    USE grid_param, ONLY : nqdyn
42    USE omp_para, ONLY : is_master
43    USE mpipara, ONLY : is_mpi_root
44    CHARACTER(len=255) :: def
45
46    CALL getin("g",g)
47    CALL getin("radius",radius)
48    CALL getin("omega",omega) 
49    CALL getin("scale_factor",scale_factor)
50    radius=radius/scale_factor
51    omega=omega*scale_factor
52
53    CALL getin("kappa",kappa)
54    CALL getin("cpp",cpp)
55    CALL getin("cppv",cppv)
56    CALL getin("Rv",Rv)
57    CALL getin("preff",preff)
58    CALL getin("Treff",Treff)
59    CALL getin("scale_height",scale_height)
60    Rd = kappa*cpp ! kappa = Rd/Cp
61    mu = kappa/cpp ! FIXME ??
62
63    nqdyn=1
64    physics_thermo = thermo_none
65
66    def='theta'
67    CALL getin('thermo',def)
68    SELECT CASE(TRIM(def))
69    CASE('boussinesq')
70       boussinesq=.TRUE.
71       caldyn_thermo=thermo_boussinesq
72    CASE('theta')
73       caldyn_thermo=thermo_theta
74       physics_thermo=thermo_dry
75    CASE('entropy')
76       caldyn_thermo=thermo_entropy
77       physics_thermo=thermo_dry
78    CASE('variable_Cp')
79       caldyn_thermo=thermo_variable_Cp
80       physics_thermo=thermo_variable_Cp
81       CALL getin("nu",nu)
82    CASE('theta_fake_moist')
83       caldyn_thermo=thermo_theta
84       physics_thermo=thermo_fake_moist
85    CASE('entropy_fake_moist')
86       caldyn_thermo=thermo_entropy
87       physics_thermo=thermo_fake_moist
88    CASE('moist')
89       caldyn_thermo=thermo_moist_debug
90       physics_thermo=thermo_moist
91       nqdyn = 2
92    CASE DEFAULT
93       IF (is_mpi_root) PRINT *,'Bad selector for variable caldyn_thermo : <', &
94            TRIM(def),'> options are <theta>, <entropy>'
95       STOP
96    END SELECT
97
98    IF(is_master) THEN
99       SELECT CASE(caldyn_thermo)
100       CASE(thermo_theta)
101          PRINT *, 'caldyn_thermo = thermo_theta'
102       CASE(thermo_entropy)
103          PRINT *, 'caldyn_thermo = thermo_entropy'
104       CASE(thermo_moist_debug)
105          PRINT *, 'caldyn_thermo = thermo_moist_debug'
106       CASE DEFAULT
107          STOP
108       END SELECT
109
110       SELECT CASE(physics_thermo)
111       CASE(thermo_dry)
112          PRINT *, 'physics_thermo = thermo_dry'
113       CASE(thermo_fake_moist)
114          PRINT *, 'physics_thermo = thermo_fake_moist'
115       CASE(thermo_moist)
116          PRINT *, 'physics_thermo = thermo_moist'
117       END SELECT
118
119    END IF
120
121  END SUBROUTINE init_earth_const
122
123END MODULE earth_const
Note: See TracBrowser for help on using the repository browser.