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

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

correction in benchmark version

File size: 6.9 KB
Line 
1! MODULE       : livestock_parameters_var
2!
3! CONTACT      : orchidee-help _at_ listes.ipsl.fr
4!
5! LICENCE      : IPSL (2011)
6! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
7!
8!>BRIEF        This module contains the variables in function of livestock type (livestock).
9!!
10!! DESCRIPTION: This module contains the declarations for the externalized variables in function of the
11!!                livestock type(livestock).
12
13!!                The module is already USE in module livestock_parameters. Therefor no need to USE it seperatly except
14!!                if the subroutines in module livestock_parameters are not needed.
15
16!!
17!! RECENT CHANGE(S): None
18!!
19!! REFERENCE(S) : None
20!!
21!! SVN          :
22!! $HeadURL: $
23!! $Date: $
24!! $Revision: $
25!!
26
27!_ ================================================================================================================================
28
29MODULE livestock_parameters_var
30
31  USE defprec
32
33  IMPLICIT NONE
34 INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: livestock_to_lmtc  !! Table of conversion : we associate one pft to one metaclass
35                                                                 !! (1-13, unitless)
36!$OMP THREADPRIVATE(livestock_to_lmtc)
37
38 LOGICAL, SAVE   :: l_first_livestock_parameters = .TRUE.             !! To keep first call trace of the module (true/false)
39!$OMP THREADPRIVATE(l_first_livestock_parameters)
40
41  INTEGER(i_std), SAVE   ::  nlm = 5    !! Number of MTCS fixed in the code (unitless)
42!$OMP THREADPRIVATE(nlm)
43
44
45  CHARACTER(len=34), ALLOCATABLE, SAVE, DIMENSION(:)   ::  LIVESTOCK_name       !! description of the MTC (unitless)
46                                                                !  1
47                                                                !  2
48                                                                !  3
49                                                                !  4
50                                                                !  5
51!$OMP THREADPRIVATE(LIVESTOCK_name)
52
53  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:)           :: is_ruminant             !! flag for ruminant animal types (true/false)
54  !$OMP THREADPRIVATE(is_ruminant)
55
56  REAL(r_std),ALLOCATABLE, SAVE                      :: max_above             !! Max aboveground biomass fraction that can be extracted (unitless)
57  !$OMP THREADPRIVATE(max_above)
58  !
59  ! ANIMAL CHARACTERISTICS
60  !
61
62  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  weight_euref        !! European weight references  (kg)
63                                                                !! used in case of normalizing litter amount
64!$OMP THREADPRIVATE(weight_euref)
65
66  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)   ::  xexcreted  !! proportion of N excreted calculated from (1-Nretained)
67                                                                !! Nretained : fraction of nitrogen retained by the animal
68!$OMP THREADPRIVATE(xexcreted)
69                                                                         !! for the production of meat, milk, or wood
70
71  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  xurine      !! Proportion of TAN in N excreted
72!$OMP THREADPRIVATE(xurine)
73  !
74  ! ACTIVITIES CHARACTERISTICS
75  !
76
77  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  straw_euref !! European straw used in litter-based manure
78                                                                !! management systems  (kg /Heads/yr)
79!$OMP THREADPRIVATE(straw_euref)
80                                                                        !! used only for Europe region?
81
82  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  n_straw_euref       !! European N added in straw-litter
83                                                                !! (kg N /Heads/yr)
84!$OMP THREADPRIVATE(n_straw_euref)
85
86  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  length_euref        !! European length of housing (days)
87!$OMP THREADPRIVATE(length_euref)
88
89  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  xgrazing    !! Fraction of the year where
90                                                                !! animal graze (European)
91!$OMP THREADPRIVATE(xgrazing)
92
93  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  xyard       !! Fraction of the year where
94                                                                !! animal is at yard (European)
95!$OMP THREADPRIVATE(xyard)
96
97  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  graz_period   !! Period (in days) where
98                                !! animal is at grazing (European)
99!$OMP THREADPRIVATE(graz_period)
100
101
102
103  !
104  ! MANURE INFORMATION
105  !
106
107  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  xmin        !! Fraction of mineralized organic N
108                                                                !! present in manure stored
109!$OMP THREADPRIVATE(xmin)
110
111  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ximm        !! Fraction of TAN that is immobilized in
112                                                                                                        !! organic matter when manure is handled as straw-based solid manure
113!$OMP THREADPRIVATE(ximm)
114  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  ef_hou    !! Emission factor of TAN during
115                                                              !! housing in manure
116!$OMP THREADPRIVATE(ef_hou)
117
118REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ef_hou_s      !! Emission factor of TAN during
119              !! housing in solid manure
120!$OMP THREADPRIVATE(ef_hou_s)
121
122  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ef_hou_l    !! Emission factor of TAN during
123                                                                !! housing in liquid manure
124!$OMP THREADPRIVATE(ef_hou_l)
125
126  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ef_yard     !! Emission factor of TAN when
127                                                                !! animal is at yard
128!$OMP THREADPRIVATE(ef_yard)
129 REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::  ef_sto   !! Emission factor of TAN during
130                                                             !! storage in manure
131!$OMP THREADPRIVATE(ef_sto)
132  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ef_sto_l    !! Emission factor of TAN during
133                                                                !! storage in liquid manure
134!$OMP THREADPRIVATE(ef_sto_l)
135
136  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ef_sto_s    !! Emission factor of TAN during
137                                                                !! storage in solid manure
138!$OMP THREADPRIVATE(ef_sto_s)
139
140  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ef_n2o_sto_l        !! Emission factor of N2O during
141                                                                !! storage in liquid manure
142!$OMP THREADPRIVATE(ef_n2o_sto_l)
143
144  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ef_n2o_sto_s        !! Emission factor of N2O during
145                                                                !! storage in solid manure
146!$OMP THREADPRIVATE(ef_n2o_sto_s)
147
148  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ef_no_sto_l !! Emission factor of NO during
149                                                                !! storage in liquid manure
150!$OMP THREADPRIVATE(ef_no_sto_l)
151
152  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ef_no_sto_s !! Emission factor of NO during
153                                                                !! storage in solid manure
154!$OMP THREADPRIVATE(ef_no_sto_s)
155
156  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ef_n2_sto_l !! Emission factor of N2 during
157                                                                !! storage in liquid manure
158!$OMP THREADPRIVATE(ef_n2_sto_l)
159
160  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ef_n2_sto_s !! Emission factor of N2 during
161                                                                !! storage in solid manure
162!$OMP THREADPRIVATE(ef_n2_sto_s)
163
164  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ef_app_l    !! Emission factor of TAN during
165                                                                !! application of liquid manure
166!$OMP THREADPRIVATE(ef_app_l)
167
168  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ef_app_s    !! Emission factor of TAN during
169                                                                !! application of solid manure
170!$OMP THREADPRIVATE(ef_app_s)
171
172  REAL(r_std),ALLOCATABLE, SAVE, DIMENSION(:)   ::  ef_graz     !! Emission factor of TAN during
173                                                                !! grazing
174!$OMP THREADPRIVATE(ef_graz)
175
176
177
178
179END MODULE livestock_parameters_var
Note: See TracBrowser for help on using the repository browser.