source: branches/publications/ORCHIDEE_GLUC_r6545/src_stomate/stomate_wet_ch4_constantes_var.f90 @ 6737

Last change on this file since 6737 was 4632, checked in by albert.jornet, 7 years ago

Clean: place CH4 wetlands variables to its own modules.

File size: 2.3 KB
Line 
1! =================================================================================================================================
2! MODULE       : stomate_wet_ch4_constantes_var
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF       CH4_calcul main module
10!!
11!!\n DESCRIPTION : None
12!!
13!! RECENT CHANGE(S) : None
14!!
15!! REFERENCE(S) : None
16!!
17!! SVN :
18!! $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/branches/ORCHIDEE-MICT/ORCHIDEE/src_stomate/stomate.f90 $
19!! $Date: 2017-07-28 17:48:13 +0200 (Fri, 28 Jul 2017) $
20!! $Revision: 4542 $
21!! \n
22!_ ================================================================================================================================
23MODULE stomate_wet_ch4_constantes_var
24  ! modules used:
25  USE ioipsl_para
26
27  IMPLICIT NONE
28
29  ! private & public routines
30
31  PUBLIC
32!
33! stomate cste WETLAND
34!
35  ! Nb of vertical layers for CH4 diffussion
36  INTEGER(i_std),SAVE  :: nvert = 171 
37  INTEGER(i_std),SAVE  :: ns = 151
38  INTEGER(i_std),SAVE  :: nday = 24
39  REAL(r_std),SAVE  :: h = 0.1
40  REAL(r_std),SAVE  :: rk = 1
41  REAL(r_std),PARAMETER  :: rkh = 100 !rk/h**2
42  REAL(r_std),SAVE  :: diffair = 7.2
43  REAL(r_std),SAVE  :: pox = 0.5
44  REAL(r_std),SAVE  :: dveg = 0.001
45  REAL(r_std),SAVE  :: rkm = 5.0
46  REAL(r_std),SAVE  :: xvmax = 20.0
47  REAL(r_std),SAVE  :: oxq10 = 2.0
48  REAL(r_std),PARAMETER  :: funit = 3.84 !3.84/rk
49  REAL(r_std),SAVE  :: scmax = 500.
50  REAL(r_std),SAVE  :: sr0pl = 600.
51
52!valeur de WTD pour les routines de calcul de densite de flux de CH4
53  REAL(r_std),SAVE  :: pwater_wet1=-3
54  REAL(r_std),SAVE  :: pwater_wet2=-9
55  REAL(r_std),SAVE  :: pwater_wet3=-15
56  REAL(r_std),SAVE  :: pwater_wet4=-21
57
58  REAL(r_std),SAVE  :: rpv = 0.5
59  REAL(r_std),SAVE  :: iother = -1.0
60
61!!pour l instant je les mets constantes pour toutes les latitudes
62  REAL(r_std),SAVE  :: rq10 = 3.0
63
64  REAL(r_std),SAVE , DIMENSION(3) :: alpha_CH4 = (/0.006,0.004,0.028/)
65
66!FLAG for CH4 from wetland
67  LOGICAL,SAVE                            :: CH4_WTD1, CH4_WTD2, CH4_WTD3, CH4_WTD4
68
69!atmoshpere methane concentration/ near surface methane concentration
70  REAL(r_std), SAVE            :: CH4atmo_CONC
71
72CONTAINS
73
74
75END MODULE stomate_wet_ch4_constantes_var
76
Note: See TracBrowser for help on using the repository browser.