source: tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_parameters/constantes.f90 @ 2381

Last change on this file since 2381 was 41, checked in by mmaipsl, 14 years ago

MM, MasaK : Group all definitions of R_Earth in the whole ORCHIDEE code : use a global

definition in constantes.f90

MM, NVui, DS: inverse compilation order of src_parallel and src_parameters

directories.
Now src_parallel will compile first.

File size: 3.0 KB
Line 
1!$Header: /home/ssipsl/CVSREP/ORCHIDEE/src_parameters/constantes.f90,v 1.16 2007/08/01 15:19:05 ssipsl Exp $
2!IPSL (2006)
3! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
4!-
5MODULE constantes
6!!--------------------------------------------------------------------
7!! "constantes" module contains some public technical constants
8!!--------------------------------------------------------------------
9  USE defprec
10  USE parallel
11!-
12  IMPLICIT NONE
13!-
14! To set for more printing
15  LOGICAL,SAVE :: long_print = .FALSE.
16!-
17! One of the most frequent problems is a temperature out of range
18! we provide here a way to catch that in the calling procedure. (JP)
19  LOGICAL,PARAMETER :: diag_qsat = .TRUE.
20!-
21! Selects the type of output for the model.
22! Value is read from run.def in intersurf_history.
23  LOGICAL           :: almaoutput
24!-
25! One day in seconds
26  REAL(r_std),SAVE :: one_day
27! One year in seconds
28  REAL(r_std),SAVE :: one_year
29! Earth radius ~= Equatorial radius
30! The Earth's equatorial radius a, or semi-major axis, is the distance from its center to the equator and equals 6,378.1370 km.
31! The equatorial radius is often used to compare Earth with other planets.
32  REAL(r_std), PARAMETER                          :: R_Earth = 6378000.
33!The meridional mean is well approximated by the semicubic mean of the two axe yielding 6367.4491 km
34! or less accurately by the quadratic mean of the two axes about 6,367.454 km
35! or even just the mean of the two axes about 6,367.445 km.
36!-
37! No comment
38  REAL(r_std),PARAMETER :: pi=3.141592653589793238
39!-
40! 0 degre Celsius in degre Kelvin
41  REAL(r_std),PARAMETER :: tp_00=273.15
42!-
43! Specific value if no restart value
44  REAL(r_std),SAVE :: val_exp = 999999.
45!-
46! Epsilon to detect a near zero floating point
47  REAL(r_std),PARAMETER :: min_sechiba = 1.E-8_r_std
48! The undef value used in SECHIBA
49  REAL(r_std),PARAMETER :: undef_sechiba = 1.E+20_r_std
50!-
51! Numerical constant set to 0
52  REAL(r_std),PARAMETER :: zero = 0._r_std
53! Numerical constant set to 1/2
54  REAL(r_std),PARAMETER :: undemi = 0.5_r_std
55! Numerical constant set to 1
56  REAL(r_std),PARAMETER :: un = 1._r_std
57! Numerical constant set to -1
58  REAL(r_std),PARAMETER :: moins_un = -1._r_std
59! Numerical constant set to 2
60  REAL(r_std),PARAMETER :: deux = 2._r_std
61! Numerical constant set to 3
62  REAL(r_std),PARAMETER :: trois = 3._r_std
63! Numerical constant set to 4
64  REAL(r_std),PARAMETER :: quatre = 4._r_std
65! Numerical constant set to 5
66  REAL(r_std),PARAMETER :: cinq = 5._r_std
67! Numerical constant set to 6
68  REAL(r_std),PARAMETER :: six = 6._r_std
69! Numerical constant set to 8
70  REAL(r_std),PARAMETER :: huit = 8._r_std
71! Numerical constant set to 1000
72  REAL(r_std),PARAMETER :: mille = 1000._r_std
73!-
74  TYPE control_type
75    LOGICAL :: river_routing
76    LOGICAL :: hydrol_cwrr
77    LOGICAL :: ok_sechiba
78    LOGICAL :: ok_co2
79    LOGICAL :: ok_stomate
80    LOGICAL :: ok_dgvm
81    LOGICAL :: stomate_watchout
82    LOGICAL :: ok_pheno
83  END TYPE control_type
84!--------------------
85END MODULE constantes
Note: See TracBrowser for help on using the repository browser.