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

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

devel : moved thermodynamics from caldyn_vars to earth_const

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