source: codes/icosagcm/trunk/src/earth_const.f90 @ 401

Last change on this file since 401 was 401, checked in by dubos, 8 years ago

Introduced entropy as prognostic variable - tested with JW06

File size: 1.8 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=1004.70885 ! FIXME
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.
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_theta=1, thermo_entropy=2, thermo_moist=3
22  INTEGER, PUBLIC :: caldyn_thermo
23  !$OMP THREADPRIVATE(caldyn_thermo)
24
25  LOGICAL, SAVE :: boussinesq, hydrostatic
26  !$OMP THREADPRIVATE(boussinesq, hydrostatic)
27
28CONTAINS
29 
30  SUBROUTINE init_earth_const
31  USE getin_mod
32  IMPLICIT NONE
33  REAL(rstd) :: X=1
34 
35    CALL getin("radius",radius)
36    CALL getin("g",g)
37    CALL getin("scale_factor",scale_factor)
38    CALL getin("omega",omega) 
39    CALL getin("kappa",kappa) 
40    CALL getin("cpp",cpp) 
41    CALL getin("preff",preff) 
42    CALL getin("Treff",Treff) 
43    CALL getin("scale_height",scale_height)
44   
45    boussinesq=.FALSE.
46    CALL getin("boussinesq",boussinesq) 
47    hydrostatic=.TRUE.
48    CALL getin("hydrostatic",hydrostatic) 
49    IF(boussinesq .AND. .NOT. hydrostatic) THEN
50       PRINT *, 'boussinesq=.TRUE. and hydrostatic=.FALSE. : Non-hydrostatic boussinesq equations are not supported'
51       STOP
52    END IF
53   
54    mu=kappa/cpp
55    radius=radius/scale_factor
56    omega=omega*scale_factor
57   
58  END SUBROUTINE init_earth_const
59 
60 
61END MODULE earth_const
Note: See TracBrowser for help on using the repository browser.