source: tags/ORCHIDEE_1_9_5/ORCHIDEE/src_parameters/constantes.f90 @ 3853

Last change on this file since 3853 was 8, checked in by orchidee, 14 years ago

import first tag equivalent to CVS orchidee_1_9_5 + OOL_1_9_5

File size: 2.5 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!-
11  IMPLICIT NONE
12!-
13! Unit for output messages
14  INTEGER(i_std), SAVE :: numout = 6
15!-
16! To set for more printing
17  LOGICAL,SAVE :: long_print = .FALSE.
18!-
19! One of the most frequent problems is a temperature out of range
20! we provide here a way to catch that in the calling procedure. (JP)
21  LOGICAL,PARAMETER :: diag_qsat = .TRUE.
22!-
23! Selects the type of output for the model.
24! Value is read from run.def in intersurf_history.
25  LOGICAL           :: almaoutput
26!-
27! One day in seconds
28  REAL(r_std),SAVE :: one_day
29! One year in seconds
30  REAL(r_std),SAVE :: one_year
31!-
32! No comment
33  REAL(r_std),PARAMETER :: pi=3.141592653589793238
34!-
35! 0 degre Celsius in degre Kelvin
36  REAL(r_std),PARAMETER :: tp_00=273.15
37!-
38! Specific value if no restart value
39  REAL(r_std),SAVE :: val_exp = 999999.
40!-
41! Epsilon to detect a near zero floating point
42  REAL(r_std),PARAMETER :: min_sechiba = 1.E-8_r_std
43! The undef value used in SECHIBA
44  REAL(r_std),PARAMETER :: undef_sechiba = 1.E+20_r_std
45!-
46! Numerical constant set to 0
47  REAL(r_std),PARAMETER :: zero = 0._r_std
48! Numerical constant set to 1/2
49  REAL(r_std),PARAMETER :: undemi = 0.5_r_std
50! Numerical constant set to 1
51  REAL(r_std),PARAMETER :: un = 1._r_std
52! Numerical constant set to -1
53  REAL(r_std),PARAMETER :: moins_un = -1._r_std
54! Numerical constant set to 2
55  REAL(r_std),PARAMETER :: deux = 2._r_std
56! Numerical constant set to 3
57  REAL(r_std),PARAMETER :: trois = 3._r_std
58! Numerical constant set to 4
59  REAL(r_std),PARAMETER :: quatre = 4._r_std
60! Numerical constant set to 5
61  REAL(r_std),PARAMETER :: cinq = 5._r_std
62! Numerical constant set to 6
63  REAL(r_std),PARAMETER :: six = 6._r_std
64! Numerical constant set to 8
65  REAL(r_std),PARAMETER :: huit = 8._r_std
66! Numerical constant set to 1000
67  REAL(r_std),PARAMETER :: mille = 1000._r_std
68!-
69  TYPE control_type
70    LOGICAL :: river_routing
71    LOGICAL :: hydrol_cwrr
72    LOGICAL :: ok_sechiba
73    LOGICAL :: ok_co2
74    LOGICAL :: ok_stomate
75    LOGICAL :: ok_dgvm
76    LOGICAL :: stomate_watchout
77    LOGICAL :: ok_pheno
78  END TYPE control_type
79!--------------------
80END MODULE constantes
Note: See TracBrowser for help on using the repository browser.