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

Last change on this file since 714 was 714, checked in by dubos, 6 years ago

devel : backported from trunk commits r607,r648,r649,r667,r668,r669,r706

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