source: branches/publications/ORCHIDEE_CAMEO_gmd_2022/src_parameters/constantes_lmtc.f90

Last change on this file was 7063, checked in by maureen.beaudor, 3 years ago

CN fixed values + all undef param converted into 0

File size: 6.9 KB
Line 
1! =================================================================================================================================
2! MODULE       : constantes_lmtc
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2011)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF         This module contains the standard values of the parameters for the 5 metaclasses of livestock used by ORCHIDEE.
10!!
11!!\n DESCRIPTION: None
12!!
13!! RECENT CHANGE(S):
14!!
15!! REFERENCE(S) :
16!! - EMEP/EEA, 2019
17!! - Sommer et al., 2019
18!! - Paustian et al., 2006
19!! - FAO, 2018
20!! SVN          :
21!! $HeadURL: $
22!! $Date: 2020-08-21 16:22:29 +0200 (ven. 21 août 2020) $
23!! $Revision: 6863 $
24!! \n
25!_ ================================================================================================================================
26
27MODULE constantes_lmtc
28
29  USE defprec
30  USE constantes
31
32  IMPLICIT NONE
33
34  !
35  ! METACLASSES CHARACTERISTICS
36  !
37
38  INTEGER(i_std), PARAMETER :: nlmc = 5                         !! Number of MTCS fixed in the code (unitless)
39
40
41
42
43  CHARACTER(len=34), PARAMETER, DIMENSION(nlmc) :: LMTC_name = &  !! description of the MTC (unitless)
44  & (/ 'Non dairy cattle                  ', &          !  1
45  &    'Dairy cattle                      ', &          !  2
46  &    'Pig                               ', &          !  3
47  &    'Small ruminants                   ', &          !  4
48  &    'Chicken                           '  /)         !  5
49
50  LOGICAL, PARAMETER, DIMENSION(nlmc) :: is_ruminant_lmtc  =  &          !! flag for ruminant animal types (true/false)
51  & (/ .TRUE.,   .TRUE.,   .FALSE.,   .TRUE.,   .FALSE.  /)
52
53  REAL(r_std),PARAMETER               :: max_above_lmtc  =  0.7               !! Max aboveground biomass fraction that can be extracted (unitless)
54
55  !
56  ! ANIMAL CHARACTERISTICS
57  !
58  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: weight_euref_lmtc  =  &      !! European weight references  (kg)
59  & (/  340.0,   600.0,   100.0,   50.0,   1.6 /)                        !! used in case of normalizing litter amount
60
61  REAL(r_std), PARAMETER, DIMENSION(nlmc) :: xexcreted_lmtc  =  &        !! proportion of N excreted calculated from (1-Nretained)
62  & (/  0.93,  0.80,  0.70,  0.90, 0.70 /)                               !! Nretained : fraction of nitrogen retained by the animal
63                                                                         !! for the production of meat, milk, or wood
64
65  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: xurine_lmtc  =  &           !! Proportion of TAN in N excreted
66  & (/  0.6,  0.6,  0.7,  0.5, 0.7 /)
67
68
69  !
70  ! ACTIVITIES CHARACTERISTICS
71  !
72  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: straw_euref_lmtc  =  &      !! European straw used in litter-based manure
73  & (/  500.0,  1500.0,  400.0,   20.0,   0.0 /)                      !! management systems  (kg /Heads/yr)
74                                                                        !! used only for Europe region?
75
76  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: n_straw_euref_lmtc  =  &     !! European N added in straw-litter
77  & (/  2.0,  6.0,  1.6,   0.08,   0.0 /)                              !! (kg N /Heads/yr)
78
79  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: length_euref_lmtc  =  &     !! European length of housing (days)
80  & (/  180,   180,   365, 30,  365 /)
81
82  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: xgrazing_lmtc  =  &         !! Fraction of the year where
83  & (/  0.5,  0.5,  0.0,  0.92, 0.0 /)                                  !! animal graze (European)
84
85  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: xyard_lmtc  =  &            !! Fraction of the year where
86  & (/  0.1, 0.25,  0.0,  0.02, 0.0/)                              !! animal is at yard (European)
87
88
89  !
90  ! MANURE INFORMATION
91  !
92
93
94  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ef_hou_s_lmtc  =  &      !! Emission factor of TAN during
95  & (/  0.08,  0.08,  0.23,  0.22, 0.21 /)                           !! housing in solid manure
96
97  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ef_hou_l_lmtc  =  &      !! Emission factor of TAN during
98  & (/  0.19,  0.19,  0.27,  0.0, 0.0/)                        !! housing in liquid manure
99
100  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ef_sto_l_lmtc  =  &      !! Emission factor of TAN during
101  & (/  0.25,  0.25,  0.11,  0.0, 0.0/)                         !! storage in liquid manure
102
103  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ef_sto_s_lmtc  =  &      !! Emission factor of TAN during
104  & (/  0.32,  0.32,  0.29,  0.30, 0.19 /)                           !! storage in solid manure
105
106  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ef_n2o_sto_l_lmtc  =  &   !! Emission factor of N2O during
107  & (/  0.0,  0.0,  0.0,  0.0, 0.0 /)                                 !! storage in liquid manure
108
109  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ef_n2o_sto_s_lmtc  =  &   !! Emission factor of N2O during
110  & (/  0.02,  0.02,  0.01,  0.02, 0.02 /)                            !! storage in solid manure
111
112  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ef_no_sto_l_lmtc  =  &   !! Emission factor of NO during
113  & (/  0.0001,  0.0001,  0.0001,  0.0, 0.0/)                   !! storage in liquid manure
114
115  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ef_no_sto_s_lmtc  =  &   !! Emission factor of NO during
116  & (/  0.01,  0.01,  0.01,  0.01, 0.1 /)                            !! storage in solid manure
117
118  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ef_n2_sto_l_lmtc  =  &   !! Emission factor of N2 during
119  & (/  0.003,  0.003,  0.003,  0.0, 0.0/)                      !! storage in liquid manure
120
121  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ef_n2_sto_s_lmtc  =  &   !! Emission factor of N2 during
122  & (/  0.30,  0.30,  0.30,  0.30, 0.30 /)                           !! storage in solid manure
123
124  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ef_app_l_lmtc  =  &       !! Emission factor of TAN during
125  & (/  0.27,  0.27,  0.20,  0.0, 0.0/)                          !! application of liquid manure
126
127  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ef_app_s_lmtc  =  &       !! Emission factor of TAN during
128  & (/  0.68,  0.68,  0.45,  0.90, 0.41/)                              !! application of solid manure
129
130
131
132  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: xmin_lmtc  =  &            !! Fraction of mineralized organic N
133  & (/  0.1,  0.1,  0.1,  0.1, 0.1 /)                                  !! present in manure stored
134
135  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ximm_lmtc  =  &            !! Fraction of TAN that is immobilized in
136  & (/  0.0067,  0.0067, 0.0067,  0.0067, 0.0067 /)                    !! organic matter when manure is handled
137                                                                       !! as straw-based solid manure
138
139
140
141  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ef_yard_lmtc  =  &       !! Emission factor of TAN when
142  & (/  0.53,  0.30,  0.0,  0.75, 0.0 /)                         !! animal is at yard
143
144
145  REAL(r_std),PARAMETER, DIMENSION(nlmc) :: ef_graz_lmtc  =  &       !! Emission factor of TAN during
146  & (/  0.14,  0.14,  0.31,  0.09, 0.0/)                           !! grazing
147
148
149END MODULE constantes_lmtc
Note: See TracBrowser for help on using the repository browser.