source: codes/icosagcm/trunk/src/base/earth_const.f90

Last change on this file was 899, checked in by adurocher, 5 years ago

trunk : Fixed GCC warnings

Fixed iso c bindings
fixed warnings with -Wall -Wno-aliasing -Wno-unused -Wno-unused-dummy-argument -Wno-maybe-uninitialized -Wno-tabs warnings
Removed all unused variables (-Wunused-variable)
vector%dot_product is now dot_product_3d to avoid compilation warning "dot_product shadows intrinsic" with GCC

File size: 2.4 KB
Line 
1MODULE earth_const
2  USE prec
3  USE math_const
4 
5  REAL(rstd),SAVE :: radius=6.37122E6
6  REAL(rstd),SAVE :: g=9.80616
7  REAL(rstd),PARAMETER :: daysec=86400
8  REAL(rstd),SAVE :: omega=7.292E-5
9  REAL(rstd),SAVE :: kappa=0.2857143
10  REAL(rstd),SAVE :: cpp=1004.70885
11  REAL(rstd),SAVE :: cppv=1860.
12  REAL(rstd),SAVE :: Rv=461.5
13  REAL(rstd),SAVE :: Treff=273.
14  REAL(rstd),SAVE :: preff=101325.
15  REAL(rstd),SAVE :: pa=50000. ! default value set to preff/2 by disvert_std
16  REAL(rstd),SAVE :: scale_height=8000. ! atmospheric scale height (m)
17  REAL(rstd),SAVE :: scale_factor=1.
18  REAL(rstd),SAVE :: gas_constant = 8.3144621 
19  REAL(rstd),SAVE :: mu                 ! molar mass of the atmosphere
20
21  INTEGER, PARAMETER,PUBLIC :: thermo_none=-99, thermo_theta=1, thermo_entropy=2, &
22       thermo_moist=3, thermo_boussinesq=4, thermo_dry=10, thermo_fake_moist=11, thermo_moist_debug=100
23  INTEGER, PUBLIC :: caldyn_thermo, physics_thermo
24  !$OMP THREADPRIVATE(caldyn_thermo)
25  !$OMP THREADPRIVATE(physics_thermo)
26
27  LOGICAL, SAVE :: boussinesq, hydrostatic
28  !$OMP THREADPRIVATE(boussinesq)
29  !$OMP THREADPRIVATE(hydrostatic)
30  LOGICAL :: dysl, dysl_geopot, dysl_pvort_only, dysl_caldyn_fast, dysl_caldyn_coriolis, dysl_slow_hydro
31  !$OMP THREADPRIVATE(dysl, dysl_geopot, dysl_pvort_only, dysl_caldyn_fast, dysl_caldyn_coriolis, dysl_slow_hydro)
32
33CONTAINS
34 
35  SUBROUTINE init_earth_const
36  USE getin_mod
37  IMPLICIT NONE
38 
39    CALL getin("radius",radius)
40    CALL getin("g",g)
41    CALL getin("scale_factor",scale_factor)
42    CALL getin("omega",omega) 
43    CALL getin("kappa",kappa) 
44    CALL getin("cpp",cpp) 
45    CALL getin("cppv",cppv)
46    CALL getin("Rv",Rv)
47    CALL getin("preff",preff) 
48    CALL getin("Treff",Treff) 
49    CALL getin("scale_height",scale_height)
50   
51    boussinesq=.FALSE.
52    CALL getin("boussinesq",boussinesq) 
53    PRINT *, "Note : key boussinesq is deprecated, use thermo=boussinesq instead"
54    IF(boussinesq) STOP
55    hydrostatic=.TRUE.
56    CALL getin("hydrostatic",hydrostatic) 
57    IF(boussinesq .AND. .NOT. hydrostatic) THEN
58       PRINT *, 'boussinesq=.TRUE. and hydrostatic=.FALSE. : Non-hydrostatic boussinesq equations are not supported'
59       STOP
60    END IF
61   
62    mu=kappa/cpp
63    radius=radius/scale_factor
64    omega=omega*scale_factor
65   
66  END SUBROUTINE init_earth_const
67 
68 
69END MODULE earth_const
Note: See TracBrowser for help on using the repository browser.