1 | |
---|
2 | ! ================================================================================================================================= |
---|
3 | ! MODULE : stomate_io |
---|
4 | ! |
---|
5 | ! CONTACT : orchidee-help _at_ listes.ipsl.fr |
---|
6 | ! |
---|
7 | ! LICENCE : IPSL (2006) |
---|
8 | ! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC |
---|
9 | ! |
---|
10 | !>\BRIEF Module for read and write of restart files for all stomate modules. |
---|
11 | !! |
---|
12 | !!\n DESCRIPTION : This module contains the subroutines readstart and writerestart. All variables that will be read or written |
---|
13 | !! are passed as argument to the subroutines. The subroutine readstart is called from stomate_initialize and |
---|
14 | !! writerestart is called from stomate_finalize. |
---|
15 | !! Note: Not all variables saved in the start files are absolutely necessary. However, Sechiba's and Stomate's |
---|
16 | !! PFTs are not necessarily identical, and for that case this information needs to be saved. |
---|
17 | !! |
---|
18 | !! |
---|
19 | !! RECENT CHANGE(S) : None |
---|
20 | !! |
---|
21 | !! REFERENCE(S) : None |
---|
22 | !! |
---|
23 | !! SVN : |
---|
24 | !! $HeadURL$ |
---|
25 | !! $Date$ |
---|
26 | !! $Revision$ |
---|
27 | !! \n |
---|
28 | !_ ================================================================================================================================ |
---|
29 | MODULE stomate_io |
---|
30 | USE stomate_data |
---|
31 | USE constantes |
---|
32 | USE constantes_soil |
---|
33 | USE mod_orchidee_para |
---|
34 | USE ioipsl_para |
---|
35 | !- |
---|
36 | IMPLICIT NONE |
---|
37 | !- |
---|
38 | PRIVATE |
---|
39 | PUBLIC readstart, writerestart |
---|
40 | !- |
---|
41 | ! reference temperature (K) |
---|
42 | !- |
---|
43 | REAL(r_std),ALLOCATABLE,DIMENSION(:),SAVE :: trefe |
---|
44 | !$OMP THREADPRIVATE(trefe) |
---|
45 | !- |
---|
46 | CONTAINS |
---|
47 | |
---|
48 | !! ================================================================================================================================ |
---|
49 | !! SUBROUTINE : readstart |
---|
50 | !! |
---|
51 | !>\BRIEF Read all variables for stomate from restart file. |
---|
52 | !! |
---|
53 | !! DESCRIPTION : Read all variables for stomate from restart file. |
---|
54 | !! Initialize the variables if they were not found in the restart file or if there was no restart file. |
---|
55 | !! |
---|
56 | !! \n |
---|
57 | !_ ================================================================================================================================ |
---|
58 | |
---|
59 | SUBROUTINE readstart & |
---|
60 | & (npts, index, lalo, resolution, temp_air, dt_days, date_loc, & |
---|
61 | & ind, adapted, regenerate, moiavail_daily, gdd_init_date, litterhum_daily, & |
---|
62 | & t2m_daily, t2m_min_daily, tsurf_daily, tsoil_daily, & |
---|
63 | & soilhum_daily, precip_daily, & |
---|
64 | & gpp_daily, npp_daily, turnover_daily, & |
---|
65 | & moiavail_month, moiavail_week, t2m_longterm, tau_longterm, & |
---|
66 | & t2m_month, t2m_week, tsoil_month, soilhum_month, & |
---|
67 | & fireindex, firelitter, & |
---|
68 | & maxmoiavail_lastyear, maxmoiavail_thisyear, & |
---|
69 | & minmoiavail_lastyear, minmoiavail_thisyear, & |
---|
70 | & maxgppweek_lastyear, maxgppweek_thisyear, & |
---|
71 | & gdd0_lastyear, gdd0_thisyear, precip_lastyear, precip_thisyear, & |
---|
72 | & gdd_m5_dormance, gdd_from_growthinit, gdd_midwinter, ncd_dormance, ngd_minus5, & |
---|
73 | & PFTpresent, npp_longterm, lm_lastyearmax, lm_thisyearmax, & |
---|
74 | & maxfpc_lastyear, maxfpc_thisyear, & |
---|
75 | & turnover_longterm, gpp_week, biomass, resp_maint_part, & |
---|
76 | & leaf_age, leaf_frac, senescence, when_growthinit, age, & |
---|
77 | & resp_hetero, resp_maint, resp_growth, co2_fire, co2_to_bm_dgvm, co2_to_bm_radia, & |
---|
78 | & veget_lastlight, everywhere, need_adjacent, RIP_time, & |
---|
79 | & time_hum_min, hum_min_dormance, & |
---|
80 | & litterpart, litter, dead_leaves, & |
---|
81 | & carbon, lignin_struc,turnover_time, & |
---|
82 | & co2_flux, fco2_lu, fco2_wh, fco2_ha, & |
---|
83 | & prod10,prod100,flux10, flux100, & |
---|
84 | & convflux, cflux_prod10, cflux_prod100, & |
---|
85 | & prod10_harvest,prod100_harvest,flux10_harvest, flux100_harvest, & |
---|
86 | & convflux_harvest, cflux_prod10_harvest, cflux_prod100_harvest, & |
---|
87 | & convfluxpft, fDeforestToProduct, fLulccResidue, fHarvestToProduct, & |
---|
88 | & woodharvestpft, bm_to_litter, carb_mass_total, & |
---|
89 | & Tseason, Tseason_length, Tseason_tmp, & |
---|
90 | & Tmin_spring_time, begin_leaves, onset_date, & |
---|
91 | & global_years, ok_equilibrium, nbp_accu, nbp_flux, & |
---|
92 | & MatrixV, VectorU, previous_stock, current_stock, assim_param) |
---|
93 | |
---|
94 | !--------------------------------------------------------------------- |
---|
95 | !- read start file |
---|
96 | !--------------------------------------------------------------------- |
---|
97 | !- |
---|
98 | ! 0 declarations |
---|
99 | !- |
---|
100 | ! 0.1 input |
---|
101 | !- |
---|
102 | ! Domain size |
---|
103 | INTEGER(i_std),INTENT(in) :: npts |
---|
104 | ! Indices of the points on the map |
---|
105 | INTEGER(i_std),DIMENSION(npts),INTENT(in) :: index |
---|
106 | ! Geogr. coordinates (latitude,longitude) (degrees) |
---|
107 | REAL(r_std),DIMENSION(npts,2),INTENT(in) :: lalo |
---|
108 | ! size in x an y of the grid (m) |
---|
109 | REAL(r_std),DIMENSION(npts,2),INTENT(in) :: resolution |
---|
110 | REAL(r_std),DIMENSION(npts),INTENT(in) :: temp_air !! Air temperature from forcing file or coupled model (K) |
---|
111 | !- |
---|
112 | ! 0.2 output |
---|
113 | !- |
---|
114 | ! time step of STOMATE in days |
---|
115 | REAL(r_std),INTENT(out) :: dt_days |
---|
116 | ! date_loc (d) |
---|
117 | INTEGER(i_std),INTENT(out) :: date_loc |
---|
118 | ! density of individuals (1/m**2) |
---|
119 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: ind |
---|
120 | ! Winter too cold? between 0 and 1 |
---|
121 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: adapted |
---|
122 | ! Winter sufficiently cold? between 0 and 1 |
---|
123 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: regenerate |
---|
124 | ! daily moisture availability |
---|
125 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: moiavail_daily |
---|
126 | ! date for beginning of gdd count |
---|
127 | REAL(r_std),DIMENSION(npts,2),INTENT(out) :: gdd_init_date |
---|
128 | ! daily litter humidity |
---|
129 | REAL(r_std),DIMENSION(npts),INTENT(out) :: litterhum_daily |
---|
130 | ! daily 2 meter temperatures (K) |
---|
131 | REAL(r_std),DIMENSION(npts),INTENT(out) :: t2m_daily |
---|
132 | ! daily minimum 2 meter temperatures (K) |
---|
133 | REAL(r_std),DIMENSION(npts),INTENT(out) :: t2m_min_daily |
---|
134 | ! daily surface temperatures (K) |
---|
135 | REAL(r_std),DIMENSION(npts),INTENT(out) :: tsurf_daily |
---|
136 | ! daily soil temperatures (K) |
---|
137 | REAL(r_std),DIMENSION(npts,nslm),INTENT(out) :: tsoil_daily |
---|
138 | ! daily soil humidity |
---|
139 | REAL(r_std),DIMENSION(npts,nslm),INTENT(out) :: soilhum_daily |
---|
140 | ! daily precipitations (mm/day) (for phenology) |
---|
141 | REAL(r_std),DIMENSION(npts),INTENT(out) :: precip_daily |
---|
142 | ! daily gross primary productivity (gC/m**2/day) |
---|
143 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: gpp_daily |
---|
144 | ! daily net primary productivity (gC/m**2/day) |
---|
145 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: npp_daily |
---|
146 | ! daily turnover rates (gC/m**2/day) |
---|
147 | REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(out) :: turnover_daily |
---|
148 | ! "monthly" moisture availability |
---|
149 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: moiavail_month |
---|
150 | ! "weekly" moisture availability |
---|
151 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: moiavail_week |
---|
152 | ! "long term" 2 meter temperatures (K) |
---|
153 | REAL(r_std),DIMENSION(npts),INTENT(out) :: t2m_longterm |
---|
154 | ! "tau_longterm" |
---|
155 | REAL(r_std), INTENT(out) :: tau_longterm |
---|
156 | ! "monthly" 2 meter temperatures (K) |
---|
157 | REAL(r_std),DIMENSION(npts),INTENT(out) :: t2m_month |
---|
158 | ! "seasonal" 2 meter temperatures (K) |
---|
159 | REAL(r_std),DIMENSION(npts),INTENT(out) :: Tseason |
---|
160 | ! temporary variable to calculate Tseason |
---|
161 | REAL(r_std),DIMENSION(npts),INTENT(out) :: Tseason_length |
---|
162 | ! temporary variable to calculate Tseason |
---|
163 | REAL(r_std),DIMENSION(npts),INTENT(out) :: Tseason_tmp |
---|
164 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: Tmin_spring_time |
---|
165 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: onset_date |
---|
166 | LOGICAL,DIMENSION(npts,nvm),INTENT(out) :: begin_leaves |
---|
167 | |
---|
168 | ! "weekly" 2 meter temperatures (K) |
---|
169 | REAL(r_std),DIMENSION(npts),INTENT(out) :: t2m_week |
---|
170 | ! "monthly" soil temperatures (K) |
---|
171 | REAL(r_std),DIMENSION(npts,nslm),INTENT(out) :: tsoil_month |
---|
172 | ! "monthly" soil humidity |
---|
173 | REAL(r_std),DIMENSION(npts,nslm),INTENT(out) :: soilhum_month |
---|
174 | ! Probability of fire |
---|
175 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: fireindex |
---|
176 | ! Longer term total litter above the ground, gC/m**2 of ground |
---|
177 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: firelitter |
---|
178 | ! last year's maximum moisture availability |
---|
179 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxmoiavail_lastyear |
---|
180 | ! this year's maximum moisture availability |
---|
181 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxmoiavail_thisyear |
---|
182 | ! last year's minimum moisture availability |
---|
183 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: minmoiavail_lastyear |
---|
184 | ! this year's minimum moisture availability |
---|
185 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: minmoiavail_thisyear |
---|
186 | ! last year's maximum weekly GPP |
---|
187 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxgppweek_lastyear |
---|
188 | ! this year's maximum weekly GPP |
---|
189 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxgppweek_thisyear |
---|
190 | ! last year's annual GDD0 |
---|
191 | REAL(r_std),DIMENSION(npts),INTENT(out) :: gdd0_lastyear |
---|
192 | ! this year's annual GDD0 |
---|
193 | REAL(r_std),DIMENSION(npts),INTENT(out) :: gdd0_thisyear |
---|
194 | ! last year's annual precipitation (mm/year) |
---|
195 | REAL(r_std),DIMENSION(npts),INTENT(out) :: precip_lastyear |
---|
196 | ! this year's annual precipitation (mm/year) |
---|
197 | REAL(r_std),DIMENSION(npts),INTENT(out) :: precip_thisyear |
---|
198 | ! growing degree days, threshold -5 deg C (for phenology) |
---|
199 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: gdd_m5_dormance |
---|
200 | ! growing degree days, from begin of season |
---|
201 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: gdd_from_growthinit |
---|
202 | ! growing degree days since midwinter (for phenology) |
---|
203 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: gdd_midwinter |
---|
204 | ! number of chilling days since leaves were lost (for phenology) |
---|
205 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: ncd_dormance |
---|
206 | ! number of growing days, threshold -5 deg C (for phenology) |
---|
207 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: ngd_minus5 |
---|
208 | ! PFT exists (equivalent to fpc_max > 0 for natural PFTs) |
---|
209 | LOGICAL,DIMENSION(npts,nvm),INTENT(out) :: PFTpresent |
---|
210 | ! "long term" net primary productivity (gC/m**2/year) |
---|
211 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: npp_longterm |
---|
212 | ! last year's maximum leaf mass, for each PFT (gC/m**2) |
---|
213 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: lm_lastyearmax |
---|
214 | ! this year's maximum leaf mass, for each PFT (gC/m**2) |
---|
215 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: lm_thisyearmax |
---|
216 | ! last year's maximum fpc for each natural PFT, on ground |
---|
217 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxfpc_lastyear |
---|
218 | ! this year's maximum fpc for each PFT, |
---|
219 | ! on *total* ground (see stomate_season) |
---|
220 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: maxfpc_thisyear |
---|
221 | ! "long term" turnover rate (gC/m**2/year) |
---|
222 | REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(out) :: turnover_longterm |
---|
223 | ! "weekly" GPP (gC/day/(m**2 covered) |
---|
224 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: gpp_week |
---|
225 | ! biomass (gC/m**2) |
---|
226 | REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(out) :: biomass |
---|
227 | ! maintenance resp (gC/m**2) |
---|
228 | REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(out) :: resp_maint_part |
---|
229 | ! leaf age (days) |
---|
230 | REAL(r_std),DIMENSION(npts,nvm,nleafages),INTENT(out) :: leaf_age |
---|
231 | ! fraction of leaves in leaf age class |
---|
232 | REAL(r_std),DIMENSION(npts,nvm,nleafages),INTENT(out) :: leaf_frac |
---|
233 | ! is the plant senescent ? |
---|
234 | !(only for deciduous trees - carbohydrate reserve) |
---|
235 | LOGICAL,DIMENSION(npts,nvm),INTENT(out) :: senescence |
---|
236 | ! how many days ago was the beginning of the growing season |
---|
237 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: when_growthinit |
---|
238 | ! mean age (years) |
---|
239 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: age |
---|
240 | ! heterotrophic respiration (gC/day/m**2) |
---|
241 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: resp_hetero |
---|
242 | ! maintenance respiration (gC/day/m**2) |
---|
243 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: resp_maint |
---|
244 | ! growth respiration (gC/day/m**2) |
---|
245 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: resp_growth |
---|
246 | ! carbon emitted into the atmosphere by fire (living and dead biomass) |
---|
247 | ! (in gC/m**2/time step) |
---|
248 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: co2_fire |
---|
249 | ! biomass uptaken (gC/(m**2 of total ground)/day) |
---|
250 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: co2_to_bm_dgvm |
---|
251 | ! biomass uptaken (gC/(m**2 of total ground)/dt_sechiba) |
---|
252 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: co2_to_bm_radia |
---|
253 | ! vegetation fractions (on ground) after last light competition |
---|
254 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: veget_lastlight |
---|
255 | ! is the PFT everywhere in the grid box or very localized |
---|
256 | ! (after its introduction) |
---|
257 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: everywhere |
---|
258 | ! in order for this PFT to be introduced, |
---|
259 | ! does it have to be present in an adjacent grid box? |
---|
260 | LOGICAL,DIMENSION(npts,nvm),INTENT(out) :: need_adjacent |
---|
261 | ! How much time ago was the PFT eliminated for the last time (y) |
---|
262 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: RIP_time |
---|
263 | ! time elapsed since strongest moisture availability (d) |
---|
264 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: time_hum_min |
---|
265 | ! minimum moisture during dormance |
---|
266 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: hum_min_dormance |
---|
267 | ! fraction of litter above the ground belonging to different PFTs |
---|
268 | ! separated for natural and agricultural PFTs. |
---|
269 | REAL(r_std),DIMENSION(npts,nvm,nlitt),INTENT(out) :: litterpart |
---|
270 | ! metabolic and structural litter, natural and agricultural, |
---|
271 | ! above and below ground (gC/m**2) |
---|
272 | REAL(r_std),DIMENSION(npts,nlitt,nvm,nlevs,nelements),INTENT(out):: litter |
---|
273 | ! dead leaves on ground, per PFT, metabolic and structural, |
---|
274 | ! in gC/(m**2 of ground) |
---|
275 | REAL(r_std),DIMENSION(npts,nvm,nlitt),INTENT(out) :: dead_leaves |
---|
276 | ! carbon pool: active, slow, or passive, (gC/m**2) |
---|
277 | REAL(r_std),DIMENSION(npts,ncarb,nvm),INTENT(out) :: carbon |
---|
278 | ! ratio Lignine/Carbon in structural litter, above and below ground,(gC/m**2) |
---|
279 | REAL(r_std),DIMENSION(npts,nvm,nlevs),INTENT(out) :: lignin_struc |
---|
280 | REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: turnover_time |
---|
281 | |
---|
282 | ! For Spinup matrix resolution |
---|
283 | INTEGER(i_std), INTENT(out) :: global_years |
---|
284 | LOGICAL, DIMENSION(npts), INTENT(out) :: ok_equilibrium |
---|
285 | REAL(r_std), DIMENSION(npts), INTENT(out) :: nbp_accu !! Accumulated Net Biospheric Production over the year |
---|
286 | REAL(r_std), DIMENSION(npts), INTENT(out) :: nbp_flux !! Net Biospheric Production over the year |
---|
287 | !- |
---|
288 | REAL(r_std), DIMENSION(npts,nvm,nbpools,nbpools), INTENT(out) :: MatrixV |
---|
289 | REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(out) :: VectorU |
---|
290 | REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(out) :: previous_stock |
---|
291 | REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(out) :: current_stock |
---|
292 | REAL(r_std), DIMENSION(npts,nvm,npco2), INTENT(out) :: assim_param |
---|
293 | |
---|
294 | ! 0.4 local |
---|
295 | !- |
---|
296 | ! date, real |
---|
297 | REAL(r_std) :: date_real |
---|
298 | ! PFT exists (equivalent to fpc_max > 0 for natural PFTs), real |
---|
299 | REAL(r_std),DIMENSION(npts,nvm) :: PFTpresent_real |
---|
300 | ! is the plant senescent ? |
---|
301 | ! (only for deciduous trees - carbohydrate reserve), real |
---|
302 | REAL(r_std),DIMENSION(npts,nvm) :: senescence_real |
---|
303 | REAL(r_std),DIMENSION(npts,nvm) :: begin_leaves_real |
---|
304 | ! in order for this PFT to be introduced, |
---|
305 | ! does it have to be present in an adjacent grid box? - real |
---|
306 | REAL(r_std),DIMENSION(npts,nvm) :: need_adjacent_real |
---|
307 | REAL(r_std), DIMENSION(1) :: vartmp !! temporary variable because restget/restput needs an array and not a scalar |
---|
308 | ! To store variables names for I/O |
---|
309 | CHARACTER(LEN=80) :: var_name |
---|
310 | ! string suffix indicating an index |
---|
311 | CHARACTER(LEN=10) :: part_str |
---|
312 | ! string suffix indicating litter type |
---|
313 | CHARACTER(LEN=3),DIMENSION(nlitt) :: litter_str |
---|
314 | ! string suffix indicating level |
---|
315 | CHARACTER(LEN=2),DIMENSION(nlevs) :: level_str |
---|
316 | ! temporary storage |
---|
317 | REAL(r_std),DIMENSION(1) :: xtmp |
---|
318 | ! index |
---|
319 | INTEGER(i_std) :: j,k,l,m |
---|
320 | ! reference temperature (K) |
---|
321 | |
---|
322 | CHARACTER(LEN=1),DIMENSION(nelements) :: element_str !! string suffix indicating element |
---|
323 | REAL(r_std), DIMENSION(1) :: temp_global_years |
---|
324 | CHARACTER(LEN=6), DIMENSION(nbpools) :: pools_str |
---|
325 | REAL(r_std), DIMENSION(npts) :: ok_equilibrium_real |
---|
326 | ! land cover change variables |
---|
327 | ! products remaining in the 10/100 year-turnover pool after the annual release for each compartment |
---|
328 | ! (10 or 100 + 1 : input from year of land cover change) |
---|
329 | REAL(r_std),DIMENSION(npts, nvm),INTENT(out) :: co2_flux |
---|
330 | REAL(r_std),DIMENSION(npts),INTENT(out) :: fco2_lu |
---|
331 | REAL(r_std),DIMENSION(npts),INTENT(out) :: fco2_wh |
---|
332 | REAL(r_std),DIMENSION(npts),INTENT(out) :: fco2_ha |
---|
333 | REAL(r_std),DIMENSION(npts,0:10),INTENT(out) :: prod10 |
---|
334 | REAL(r_std),DIMENSION(npts,0:100),INTENT(out) :: prod100 |
---|
335 | ! annual release from the 10/100 year-turnover pool compartments |
---|
336 | REAL(r_std),DIMENSION(npts,10),INTENT(out) :: flux10 |
---|
337 | REAL(r_std),DIMENSION(npts,100),INTENT(out) :: flux100 |
---|
338 | REAL(r_std), DIMENSION(npts), INTENT(out) :: convflux |
---|
339 | REAL(r_std), DIMENSION(npts), INTENT(out) :: cflux_prod10 |
---|
340 | REAL(r_std), DIMENSION(npts), INTENT(out) :: cflux_prod100 |
---|
341 | ! wood harvest variables |
---|
342 | ! products remaining in the 10/100 year-turnover pool after the annual release for each compartment |
---|
343 | ! (10 or 100 + 1 : input from year of land cover change) |
---|
344 | REAL(r_std),DIMENSION(npts,0:10),INTENT(out) :: prod10_harvest |
---|
345 | REAL(r_std),DIMENSION(npts,0:100),INTENT(out) :: prod100_harvest |
---|
346 | ! annual release from the 10/100 year-turnover pool compartments |
---|
347 | REAL(r_std),DIMENSION(npts,10),INTENT(out) :: flux10_harvest |
---|
348 | REAL(r_std),DIMENSION(npts,100),INTENT(out) :: flux100_harvest |
---|
349 | REAL(r_std), DIMENSION(npts), INTENT(out) :: convflux_harvest |
---|
350 | REAL(r_std), DIMENSION(npts), INTENT(out) :: cflux_prod10_harvest |
---|
351 | REAL(r_std), DIMENSION(npts), INTENT(out) :: cflux_prod100_harvest |
---|
352 | REAL(r_std), DIMENSION(npts,nvm), INTENT(out) :: convfluxpft |
---|
353 | REAL(r_std), DIMENSION(npts,nvm), INTENT(out) :: fDeforestToProduct |
---|
354 | REAL(r_std), DIMENSION(npts,nvm), INTENT(out) :: fLulccResidue |
---|
355 | REAL(r_std), DIMENSION(npts,nvm), INTENT(out) :: fHarvestToProduct |
---|
356 | REAL(r_std), DIMENSION(npts,nvm), INTENT(out) :: woodharvestpft |
---|
357 | REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(out) :: bm_to_litter |
---|
358 | REAL(r_std),DIMENSION(npts),INTENT(out) :: carb_mass_total |
---|
359 | REAL(r_std),DIMENSION(npts,nvm) :: vcmax_tmp |
---|
360 | !--------------------------------------------------------------------- |
---|
361 | IF (printlev >= 3) WRITE(numout,*) 'Entering readstart' |
---|
362 | !- |
---|
363 | ! 1 string definitions |
---|
364 | !- |
---|
365 | DO l=1,nlitt |
---|
366 | IF (l == imetabolic) THEN |
---|
367 | litter_str(l) = 'met' |
---|
368 | ELSEIF (l == istructural) THEN |
---|
369 | litter_str(l) = 'str' |
---|
370 | ELSE |
---|
371 | CALL ipslerr_p(3,'stomate_io readstart', 'Define litter_str','','') |
---|
372 | ENDIF |
---|
373 | ENDDO |
---|
374 | !- |
---|
375 | DO l=1,nlevs |
---|
376 | IF (l == iabove) THEN |
---|
377 | level_str(l) = 'ab' |
---|
378 | ELSEIF (l == ibelow) THEN |
---|
379 | level_str(l) = 'be' |
---|
380 | ELSE |
---|
381 | CALL ipslerr_p(3,'stomate_io readstart','Define level_str','','') |
---|
382 | ENDIF |
---|
383 | ENDDO |
---|
384 | |
---|
385 | pools_str(1:nbpools) =(/'str_ab','str_be','met_ab','met_be','actif ','slow ','passif'/) |
---|
386 | |
---|
387 | !- |
---|
388 | DO l=1,nelements |
---|
389 | IF (l == icarbon) THEN |
---|
390 | element_str(l) = '' |
---|
391 | !!$ ELSEIF (l == initrogen) THEN |
---|
392 | !!$ element_str(l) = '_n' |
---|
393 | ELSE |
---|
394 | CALL ipslerr_p(3,'stomate_io readstart','Define element_str','','') |
---|
395 | ENDIF |
---|
396 | ENDDO |
---|
397 | !- |
---|
398 | ! 2 run control |
---|
399 | !- |
---|
400 | ! 2.2 time step of STOMATE in days |
---|
401 | !- |
---|
402 | IF (is_root_prc) THEN |
---|
403 | var_name = 'dt_days' |
---|
404 | CALL restget (rest_id_stomate, var_name, 1 , 1 , 1, itime, & |
---|
405 | & .TRUE., xtmp) |
---|
406 | dt_days = xtmp(1) |
---|
407 | IF (dt_days == val_exp) dt_days = un |
---|
408 | ENDIF |
---|
409 | CALL bcast(dt_days) |
---|
410 | !- |
---|
411 | ! 2.3 date |
---|
412 | !- |
---|
413 | IF (is_root_prc) THEN |
---|
414 | var_name = 'date' |
---|
415 | CALL restget (rest_id_stomate, var_name, 1 , 1 , 1, itime, & |
---|
416 | & .TRUE., xtmp) |
---|
417 | date_real = xtmp(1) |
---|
418 | IF (date_real == val_exp) date_real = zero |
---|
419 | date_loc = NINT(date_real) |
---|
420 | ENDIF |
---|
421 | CALL bcast(date_loc) |
---|
422 | !- |
---|
423 | ! 3 daily meteorological variables |
---|
424 | !- |
---|
425 | moiavail_daily(:,:) = val_exp |
---|
426 | var_name = 'moiavail_daily' |
---|
427 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
428 | & .TRUE., moiavail_daily, 'gather', nbp_glo, index_g) |
---|
429 | IF (ALL(moiavail_daily(:,:) == val_exp)) moiavail_daily(:,:) = zero |
---|
430 | !- |
---|
431 | gdd_init_date(:,:) = val_exp |
---|
432 | var_name = 'gdd_init_date' |
---|
433 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 2 , 1, itime, & |
---|
434 | & .TRUE., gdd_init_date, 'gather', nbp_glo, index_g) |
---|
435 | ! Keep val_exp as initial value for gdd_init_date(:,2) |
---|
436 | IF (ALL(gdd_init_date(:,1) == val_exp)) gdd_init_date(:,1) = 365. |
---|
437 | |
---|
438 | !- |
---|
439 | litterhum_daily(:) = val_exp |
---|
440 | var_name = 'litterhum_daily' |
---|
441 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
442 | & .TRUE., litterhum_daily, 'gather', nbp_glo, index_g) |
---|
443 | IF (ALL(litterhum_daily(:) == val_exp)) litterhum_daily(:) = zero |
---|
444 | !- |
---|
445 | t2m_daily(:) = val_exp |
---|
446 | var_name = 't2m_daily' |
---|
447 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
448 | & .TRUE., t2m_daily, 'gather', nbp_glo, index_g) |
---|
449 | IF (ALL(t2m_daily(:) == val_exp)) t2m_daily(:) = zero |
---|
450 | !- |
---|
451 | t2m_min_daily(:) = val_exp |
---|
452 | var_name = 't2m_min_daily' |
---|
453 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
454 | & .TRUE., t2m_min_daily, 'gather', nbp_glo, index_g) |
---|
455 | IF (ALL(t2m_min_daily(:) == val_exp)) t2m_min_daily(:) = large_value |
---|
456 | !- |
---|
457 | tsurf_daily(:) = val_exp |
---|
458 | var_name = 'tsurf_daily' |
---|
459 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
460 | & .TRUE., tsurf_daily, 'gather', nbp_glo, index_g) |
---|
461 | ! The initial value is set to the current temperature at 2m |
---|
462 | IF (ALL(tsurf_daily(:) == val_exp)) tsurf_daily(:) = temp_air(:) |
---|
463 | !- |
---|
464 | tsoil_daily(:,:) = val_exp |
---|
465 | var_name = 'tsoil_daily' |
---|
466 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, & |
---|
467 | & .TRUE., tsoil_daily, 'gather', nbp_glo, index_g) |
---|
468 | IF (ALL(tsoil_daily(:,:) == val_exp)) tsoil_daily(:,:) = zero |
---|
469 | !- |
---|
470 | soilhum_daily(:,:) = val_exp |
---|
471 | var_name = 'soilhum_daily' |
---|
472 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, & |
---|
473 | & .TRUE., soilhum_daily, 'gather', nbp_glo, index_g) |
---|
474 | IF (ALL(soilhum_daily(:,:) == val_exp)) soilhum_daily(:,:) = zero |
---|
475 | !- |
---|
476 | precip_daily(:) = val_exp |
---|
477 | var_name = 'precip_daily' |
---|
478 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
479 | & .TRUE., precip_daily, 'gather', nbp_glo, index_g) |
---|
480 | IF (ALL(precip_daily(:) == val_exp)) precip_daily(:) = zero |
---|
481 | !- |
---|
482 | ! 4 productivities |
---|
483 | !- |
---|
484 | gpp_daily(:,:) = val_exp |
---|
485 | var_name = 'gpp_daily' |
---|
486 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
487 | & .TRUE., gpp_daily, 'gather', nbp_glo, index_g) |
---|
488 | IF (ALL(gpp_daily(:,:) == val_exp)) gpp_daily(:,:) = zero |
---|
489 | !- |
---|
490 | npp_daily(:,:) = val_exp |
---|
491 | var_name = 'npp_daily' |
---|
492 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
493 | & .TRUE., npp_daily, 'gather', nbp_glo, index_g) |
---|
494 | IF (ALL(npp_daily(:,:) == val_exp)) npp_daily(:,:) = zero |
---|
495 | !- |
---|
496 | turnover_daily(:,:,:,:) = val_exp |
---|
497 | DO l = 1,nelements |
---|
498 | DO k = 1,nparts |
---|
499 | WRITE(part_str,'(I2)') k |
---|
500 | IF (k < 10) part_str(1:1) = '0' |
---|
501 | var_name = 'turnover_daily_'//part_str(1:LEN_TRIM(part_str))//element_str(l) |
---|
502 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
503 | & .TRUE., turnover_daily(:,:,k,l), 'gather', nbp_glo, index_g) |
---|
504 | IF (ALL(turnover_daily(:,:,k,l) == val_exp)) & |
---|
505 | & turnover_daily(:,:,k,l) = zero |
---|
506 | ENDDO |
---|
507 | END DO |
---|
508 | !- |
---|
509 | ! 5 monthly meteorological variables |
---|
510 | !- |
---|
511 | moiavail_month(:,:) = val_exp |
---|
512 | var_name = 'moiavail_month' |
---|
513 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
514 | & .TRUE., moiavail_month, 'gather', nbp_glo, index_g) |
---|
515 | IF (ALL(moiavail_month(:,:) == val_exp)) moiavail_month(:,:) = zero |
---|
516 | !- |
---|
517 | moiavail_week(:,:) = val_exp |
---|
518 | var_name = 'moiavail_week' |
---|
519 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
520 | & .TRUE., moiavail_week, 'gather', nbp_glo, index_g) |
---|
521 | IF (ALL(moiavail_week(:,:) == val_exp)) moiavail_week(:,:) = zero |
---|
522 | |
---|
523 | |
---|
524 | ! |
---|
525 | ! Longterm temperature at 2m |
---|
526 | ! |
---|
527 | var_name = 't2m_longterm' |
---|
528 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
529 | & .TRUE., t2m_longterm, 'gather', nbp_glo, index_g) |
---|
530 | |
---|
531 | IF (ALL(t2m_longterm(:) == val_exp)) THEN |
---|
532 | ! t2m_longterm is not in restart file |
---|
533 | ! The initial value for the reference temperature is set to the current temperature |
---|
534 | t2m_longterm(:)=temp_air(:) |
---|
535 | ! Set the counter to 2 time steps |
---|
536 | tau_longterm=2 |
---|
537 | ELSE |
---|
538 | ! t2m_longterm was in the restart file |
---|
539 | ! Now read tau_longterm |
---|
540 | ! tau_longterm is a scalar, therefor only master process read this value |
---|
541 | IF (is_root_prc) THEN |
---|
542 | CALL restget (rest_id_stomate, 'tau_longterm', 1 ,1 , 1, itime, & |
---|
543 | .TRUE., vartmp) |
---|
544 | IF (vartmp(1) == val_exp) THEN |
---|
545 | ! tau_longterm is not found in restart file. |
---|
546 | ! This is not normal as t2m_longterm was in restart file. Write a warning and initialize it to tau_longterm_max |
---|
547 | CALL ipslerr(2, 'stomate_io readstart','tau_longterm was not in restart file',& |
---|
548 | 'But t2m_longterm was in restart file','') |
---|
549 | tau_longterm = tau_longterm_max |
---|
550 | ELSE |
---|
551 | tau_longterm = vartmp(1) |
---|
552 | END IF |
---|
553 | ENDIF |
---|
554 | CALL bcast(tau_longterm) |
---|
555 | |
---|
556 | END IF |
---|
557 | !- |
---|
558 | t2m_month(:) = val_exp |
---|
559 | var_name = 't2m_month' |
---|
560 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
561 | & .TRUE., t2m_month, 'gather', nbp_glo, index_g) |
---|
562 | IF (ALL(t2m_month(:) == val_exp)) t2m_month(:) = temp_air(:) |
---|
563 | |
---|
564 | CALL restget_p (rest_id_stomate, 'Tseason', nbp_glo, 1 , 1, itime, & |
---|
565 | .TRUE., Tseason, 'gather', nbp_glo, index_g) |
---|
566 | IF (ALL(Tseason(:) == val_exp)) Tseason(:) = temp_air(:) |
---|
567 | |
---|
568 | CALL restget_p (rest_id_stomate,'Tseason_length', nbp_glo, 1 , 1, itime, & |
---|
569 | .TRUE., Tseason_length, 'gather', nbp_glo, index_g) |
---|
570 | IF (ALL(Tseason_length(:) == val_exp)) Tseason_length(:) = zero |
---|
571 | |
---|
572 | CALL restget_p (rest_id_stomate, 'Tseason_tmp', nbp_glo, 1 , 1, itime, & |
---|
573 | .TRUE., Tseason_tmp, 'gather', nbp_glo, index_g) |
---|
574 | IF (ALL(Tseason_tmp(:) == val_exp)) Tseason_tmp(:) = zero |
---|
575 | |
---|
576 | CALL restget_p (rest_id_stomate, 'Tmin_spring_time', nbp_glo, nvm, 1, itime, & |
---|
577 | .TRUE., Tmin_spring_time, 'gather', nbp_glo, index_g) |
---|
578 | IF (ALL(Tmin_spring_time(:,:) == val_exp)) Tmin_spring_time(:,:) = zero |
---|
579 | |
---|
580 | CALL restget_p (rest_id_stomate, 'onset_date', nbp_glo, nvm , 1, itime, & |
---|
581 | .TRUE., onset_date(:,:), 'gather', nbp_glo, index_g) |
---|
582 | IF (ALL(onset_date(:,:) == val_exp)) onset_date(:,:) = zero |
---|
583 | |
---|
584 | t2m_week(:) = val_exp |
---|
585 | var_name = 't2m_week' |
---|
586 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
587 | & .TRUE., t2m_week, 'gather', nbp_glo, index_g) |
---|
588 | ! The initial value is set to the current temperature |
---|
589 | IF (ALL(t2m_week(:) == val_exp)) t2m_week(:) = temp_air(:) |
---|
590 | |
---|
591 | tsoil_month(:,:) = val_exp |
---|
592 | var_name = 'tsoil_month' |
---|
593 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, & |
---|
594 | & .TRUE., tsoil_month, 'gather', nbp_glo, index_g) |
---|
595 | |
---|
596 | ! The initial value is set to the current temperature |
---|
597 | IF (ALL(tsoil_month(:,:) == val_exp)) THEN |
---|
598 | DO l=1,nslm |
---|
599 | tsoil_month(:,l) = temp_air(:) |
---|
600 | ENDDO |
---|
601 | ENDIF |
---|
602 | !- |
---|
603 | soilhum_month(:,:) = val_exp |
---|
604 | var_name = 'soilhum_month' |
---|
605 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, & |
---|
606 | & .TRUE., soilhum_month, 'gather', nbp_glo, index_g) |
---|
607 | IF (ALL(soilhum_month(:,:) == val_exp)) soilhum_month(:,:) = zero |
---|
608 | !- |
---|
609 | ! 6 fire probability |
---|
610 | !- |
---|
611 | fireindex(:,:) = val_exp |
---|
612 | var_name = 'fireindex' |
---|
613 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
614 | & .TRUE., fireindex, 'gather', nbp_glo, index_g) |
---|
615 | IF (ALL(fireindex(:,:) == val_exp)) fireindex(:,:) = zero |
---|
616 | !- |
---|
617 | firelitter(:,:) = val_exp |
---|
618 | var_name = 'firelitter' |
---|
619 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
620 | & .TRUE., firelitter, 'gather', nbp_glo, index_g) |
---|
621 | IF (ALL(firelitter(:,:) == val_exp)) firelitter(:,:) = zero |
---|
622 | !- |
---|
623 | ! 7 maximum and minimum moisture availabilities for tropic phenology |
---|
624 | !- |
---|
625 | maxmoiavail_lastyear(:,:) = val_exp |
---|
626 | var_name = 'maxmoistr_last' |
---|
627 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
628 | & .TRUE., maxmoiavail_lastyear, 'gather', nbp_glo, index_g) |
---|
629 | IF (ALL(maxmoiavail_lastyear(:,:) == val_exp)) & |
---|
630 | & maxmoiavail_lastyear(:,:) = zero |
---|
631 | !- |
---|
632 | maxmoiavail_thisyear(:,:) = val_exp |
---|
633 | var_name = 'maxmoistr_this' |
---|
634 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
635 | & .TRUE., maxmoiavail_thisyear, 'gather', nbp_glo, index_g) |
---|
636 | IF (ALL(maxmoiavail_thisyear(:,:) == val_exp)) & |
---|
637 | & maxmoiavail_thisyear(:,:) = zero |
---|
638 | !- |
---|
639 | minmoiavail_lastyear(:,:) = val_exp |
---|
640 | var_name = 'minmoistr_last' |
---|
641 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
642 | & .TRUE., minmoiavail_lastyear, 'gather', nbp_glo, index_g) |
---|
643 | IF (ALL(minmoiavail_lastyear(:,:) == val_exp)) & |
---|
644 | & minmoiavail_lastyear(:,:) = un |
---|
645 | !- |
---|
646 | minmoiavail_thisyear(:,:) = val_exp |
---|
647 | var_name = 'minmoistr_this' |
---|
648 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
649 | & .TRUE., minmoiavail_thisyear, 'gather', nbp_glo, index_g) |
---|
650 | IF (ALL( minmoiavail_thisyear(:,:) == val_exp)) & |
---|
651 | & minmoiavail_thisyear(:,:) = un |
---|
652 | !- |
---|
653 | ! 8 maximum "weekly" GPP |
---|
654 | !- |
---|
655 | maxgppweek_lastyear(:,:) = val_exp |
---|
656 | var_name = 'maxgppweek_lastyear' |
---|
657 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
658 | & .TRUE., maxgppweek_lastyear, 'gather', nbp_glo, index_g) |
---|
659 | IF (ALL(maxgppweek_lastyear(:,:) == val_exp)) & |
---|
660 | & maxgppweek_lastyear(:,:) = zero |
---|
661 | !- |
---|
662 | maxgppweek_thisyear(:,:) = val_exp |
---|
663 | var_name = 'maxgppweek_thisyear' |
---|
664 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
665 | & .TRUE., maxgppweek_thisyear, 'gather', nbp_glo, index_g) |
---|
666 | IF (ALL(maxgppweek_thisyear(:,:) == val_exp)) & |
---|
667 | & maxgppweek_thisyear(:,:) = zero |
---|
668 | !- |
---|
669 | ! 9 annual GDD0 |
---|
670 | !- |
---|
671 | gdd0_thisyear(:) = val_exp |
---|
672 | var_name = 'gdd0_thisyear' |
---|
673 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
674 | & .TRUE., gdd0_thisyear, 'gather', nbp_glo, index_g) |
---|
675 | IF (ALL(gdd0_thisyear(:) == val_exp)) gdd0_thisyear(:) = zero |
---|
676 | !- |
---|
677 | gdd0_lastyear(:) = val_exp |
---|
678 | var_name = 'gdd0_lastyear' |
---|
679 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
680 | & .TRUE., gdd0_lastyear, 'gather', nbp_glo, index_g) |
---|
681 | IF (ALL(gdd0_lastyear(:) == val_exp)) gdd0_lastyear(:) = gdd_crit_estab |
---|
682 | !- |
---|
683 | ! 10 annual precipitation |
---|
684 | !- |
---|
685 | precip_thisyear(:) = val_exp |
---|
686 | var_name = 'precip_thisyear' |
---|
687 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
688 | & .TRUE., precip_thisyear, 'gather', nbp_glo, index_g) |
---|
689 | IF (ALL(precip_thisyear(:) == val_exp)) precip_thisyear(:) = zero |
---|
690 | !- |
---|
691 | precip_lastyear(:) = val_exp |
---|
692 | var_name = 'precip_lastyear' |
---|
693 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
694 | & .TRUE., precip_lastyear, 'gather', nbp_glo, index_g) |
---|
695 | IF (ALL(precip_lastyear(:) == val_exp)) & |
---|
696 | & precip_lastyear(:) = precip_crit |
---|
697 | !- |
---|
698 | ! 11 derived "biometeorological" variables |
---|
699 | !- |
---|
700 | gdd_m5_dormance(:,:) = val_exp |
---|
701 | var_name = 'gdd_m5_dormance' |
---|
702 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
703 | & .TRUE., gdd_m5_dormance, 'gather', nbp_glo, index_g) |
---|
704 | IF (ALL(gdd_m5_dormance(:,:) == val_exp)) & |
---|
705 | & gdd_m5_dormance(:,:) = undef |
---|
706 | !- |
---|
707 | gdd_from_growthinit(:,:) = val_exp |
---|
708 | var_name = 'gdd_from_growthinit' |
---|
709 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
710 | & .TRUE., gdd_from_growthinit, 'gather', nbp_glo, index_g) |
---|
711 | IF (ALL(gdd_from_growthinit(:,:) == val_exp)) & |
---|
712 | & gdd_from_growthinit(:,:) = zero |
---|
713 | !- |
---|
714 | gdd_midwinter(:,:) = val_exp |
---|
715 | var_name = 'gdd_midwinter' |
---|
716 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
717 | & .TRUE., gdd_midwinter, 'gather', nbp_glo, index_g) |
---|
718 | IF (ALL(gdd_midwinter(:,:) == val_exp)) gdd_midwinter(:,:) = undef |
---|
719 | !- |
---|
720 | ncd_dormance(:,:) = val_exp |
---|
721 | var_name = 'ncd_dormance' |
---|
722 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
723 | & .TRUE., ncd_dormance, 'gather', nbp_glo, index_g) |
---|
724 | IF (ALL(ncd_dormance(:,:) == val_exp)) ncd_dormance(:,:) = undef |
---|
725 | !- |
---|
726 | ngd_minus5(:,:) = val_exp |
---|
727 | var_name = 'ngd_minus5' |
---|
728 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
729 | & .TRUE., ngd_minus5, 'gather', nbp_glo, index_g) |
---|
730 | IF (ALL(ngd_minus5(:,:) == val_exp)) ngd_minus5(:,:) = zero |
---|
731 | !- |
---|
732 | time_hum_min(:,:) = val_exp |
---|
733 | var_name = 'time_hum_min' |
---|
734 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
735 | & .TRUE., time_hum_min, 'gather', nbp_glo, index_g) |
---|
736 | IF (ALL(time_hum_min(:,:) == val_exp)) time_hum_min(:,:) = undef |
---|
737 | !- |
---|
738 | hum_min_dormance(:,:) = val_exp |
---|
739 | var_name = 'hum_min_dormance' |
---|
740 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
741 | & .TRUE., hum_min_dormance, 'gather', nbp_glo, index_g) |
---|
742 | IF (ALL(hum_min_dormance(:,:) == val_exp)) & |
---|
743 | & hum_min_dormance(:,:) = undef |
---|
744 | !- |
---|
745 | ! 12 Plant status |
---|
746 | !- |
---|
747 | PFTpresent_real(:,:) = val_exp |
---|
748 | var_name = 'PFTpresent' |
---|
749 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
750 | & .TRUE., PFTpresent_real, 'gather', nbp_glo, index_g) |
---|
751 | IF (ALL(PFTpresent_real(:,:) == val_exp)) PFTpresent_real(:,:) = zero |
---|
752 | WHERE (PFTpresent_real(:,:) >= .5) |
---|
753 | PFTpresent = .TRUE. |
---|
754 | ELSEWHERE |
---|
755 | PFTpresent = .FALSE. |
---|
756 | ENDWHERE |
---|
757 | !- |
---|
758 | ind(:,:) = val_exp |
---|
759 | var_name = 'ind' |
---|
760 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
761 | & .TRUE., ind, 'gather', nbp_glo, index_g) |
---|
762 | IF (ALL(ind(:,:) == val_exp)) ind(:,:) = zero |
---|
763 | !- |
---|
764 | adapted(:,:) = val_exp |
---|
765 | var_name = 'adapted' |
---|
766 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
767 | & .TRUE., adapted, 'gather', nbp_glo, index_g) |
---|
768 | IF (ALL(adapted(:,:) == val_exp)) adapted(:,:) = zero |
---|
769 | !- |
---|
770 | regenerate(:,:) = val_exp |
---|
771 | var_name = 'regenerate' |
---|
772 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
773 | & .TRUE., regenerate, 'gather', nbp_glo, index_g) |
---|
774 | IF (ALL(regenerate(:,:) == val_exp)) regenerate(:,:) = zero |
---|
775 | !- |
---|
776 | npp_longterm(:,:) = val_exp |
---|
777 | var_name = 'npp_longterm' |
---|
778 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
779 | & .TRUE., npp_longterm, 'gather', nbp_glo, index_g) |
---|
780 | IF (ALL(npp_longterm(:,:) == val_exp)) npp_longterm(:,:) = zero |
---|
781 | !- |
---|
782 | lm_lastyearmax(:,:) = val_exp |
---|
783 | var_name = 'lm_lastyearmax' |
---|
784 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
785 | & .TRUE., lm_lastyearmax, 'gather', nbp_glo, index_g) |
---|
786 | IF (ALL(lm_lastyearmax(:,:) == val_exp)) lm_lastyearmax(:,:) = zero |
---|
787 | !- |
---|
788 | lm_thisyearmax(:,:) = val_exp |
---|
789 | var_name = 'lm_thisyearmax' |
---|
790 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
791 | & .TRUE., lm_thisyearmax, 'gather', nbp_glo, index_g) |
---|
792 | IF (ALL(lm_thisyearmax(:,:) == val_exp)) lm_thisyearmax(:,:) = zero |
---|
793 | !- |
---|
794 | maxfpc_lastyear(:,:) = val_exp |
---|
795 | var_name = 'maxfpc_lastyear' |
---|
796 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
797 | & .TRUE., maxfpc_lastyear, 'gather', nbp_glo, index_g) |
---|
798 | IF (ALL(maxfpc_lastyear(:,:) == val_exp)) maxfpc_lastyear(:,:) = zero |
---|
799 | !- |
---|
800 | maxfpc_thisyear(:,:) = val_exp |
---|
801 | var_name = 'maxfpc_thisyear' |
---|
802 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
803 | & .TRUE., maxfpc_thisyear, 'gather', nbp_glo, index_g) |
---|
804 | IF (ALL(maxfpc_thisyear(:,:) == val_exp)) maxfpc_thisyear(:,:) = zero |
---|
805 | !- |
---|
806 | turnover_time(:,:) = val_exp |
---|
807 | var_name = 'turnover_time' |
---|
808 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
809 | & .TRUE., turnover_time, 'gather', nbp_glo, index_g) |
---|
810 | IF ( ALL( turnover_time(:,:) == val_exp)) turnover_time(:,:) = 100. |
---|
811 | !- |
---|
812 | turnover_longterm(:,:,:,:) = val_exp |
---|
813 | DO l = 1,nelements |
---|
814 | DO k = 1,nparts |
---|
815 | WRITE(part_str,'(I2)') k |
---|
816 | IF ( k < 10 ) part_str(1:1) = '0' |
---|
817 | var_name = 'turnover_longterm_'//part_str(1:LEN_TRIM(part_str))//element_str(l) |
---|
818 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
819 | & .TRUE., turnover_longterm(:,:,k,l), 'gather', nbp_glo, index_g) |
---|
820 | IF (ALL(turnover_longterm(:,:,k,l) == val_exp)) & |
---|
821 | & turnover_longterm(:,:,k,l) = zero |
---|
822 | ENDDO |
---|
823 | END DO |
---|
824 | !- |
---|
825 | gpp_week(:,:) = val_exp |
---|
826 | var_name = 'gpp_week' |
---|
827 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
828 | & .TRUE., gpp_week, 'gather', nbp_glo, index_g) |
---|
829 | IF (ALL(gpp_week(:,:) == val_exp)) gpp_week(:,:) = zero |
---|
830 | !- |
---|
831 | biomass(:,:,:,:) = val_exp |
---|
832 | DO l = 1,nelements |
---|
833 | DO k = 1,nparts |
---|
834 | WRITE(part_str,'(I2)') k |
---|
835 | IF ( k < 10 ) part_str(1:1) = '0' |
---|
836 | var_name = 'biomass_'//part_str(1:LEN_TRIM(part_str))//element_str(l) |
---|
837 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
838 | & .TRUE., biomass(:,:,k,l), 'gather', nbp_glo, index_g) |
---|
839 | IF (ALL(biomass(:,:,k,l) == val_exp)) biomass(:,:,k,l) = zero |
---|
840 | ENDDO |
---|
841 | END DO |
---|
842 | !- |
---|
843 | resp_maint_part(:,:,:) = val_exp |
---|
844 | DO k=1,nparts |
---|
845 | WRITE(part_str,'(I2)') k |
---|
846 | IF ( k < 10 ) part_str(1:1) = '0' |
---|
847 | var_name = 'maint_resp_'//part_str(1:LEN_TRIM(part_str)) |
---|
848 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
849 | & .TRUE., resp_maint_part(:,:,k), 'gather', nbp_glo, index_g) |
---|
850 | IF (ALL(resp_maint_part(:,:,k) == val_exp)) resp_maint_part(:,:,k) = zero |
---|
851 | ENDDO |
---|
852 | !- |
---|
853 | leaf_age(:,:,:) = val_exp |
---|
854 | DO m=1,nleafages |
---|
855 | WRITE (part_str,'(I2)') m |
---|
856 | IF ( m < 10 ) part_str(1:1) = '0' |
---|
857 | var_name = 'leaf_age_'//part_str(1:LEN_TRIM(part_str)) |
---|
858 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
859 | & .TRUE., leaf_age(:,:,m), 'gather', nbp_glo, index_g) |
---|
860 | IF (ALL(leaf_age(:,:,m) == val_exp)) leaf_age(:,:,m) = zero |
---|
861 | ENDDO |
---|
862 | !- |
---|
863 | leaf_frac(:,:,:) = val_exp |
---|
864 | DO m=1,nleafages |
---|
865 | WRITE(part_str,'(I2)') m |
---|
866 | IF ( m < 10 ) part_str(1:1) = '0' |
---|
867 | var_name = 'leaf_frac_'//part_str(1:LEN_TRIM(part_str)) |
---|
868 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
869 | & .TRUE., leaf_frac(:,:,m), 'gather', nbp_glo, index_g) |
---|
870 | IF (ALL(leaf_frac(:,:,m) == val_exp)) leaf_frac(:,:,m) = zero |
---|
871 | ENDDO |
---|
872 | !- |
---|
873 | senescence_real(:,:) = val_exp |
---|
874 | var_name = 'senescence' |
---|
875 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
876 | & .TRUE., senescence_real, 'gather', nbp_glo, index_g) |
---|
877 | IF (ALL(senescence_real(:,:) == val_exp)) senescence_real(:,:) = zero |
---|
878 | WHERE ( senescence_real(:,:) >= .5 ) |
---|
879 | senescence = .TRUE. |
---|
880 | ELSEWHERE |
---|
881 | senescence = .FALSE. |
---|
882 | ENDWHERE |
---|
883 | |
---|
884 | |
---|
885 | ! Read real value for begin_leaves |
---|
886 | CALL restget_p (rest_id_stomate, 'begin_leaves', nbp_glo, nvm , 1, itime, & |
---|
887 | .TRUE., begin_leaves_real, 'gather', nbp_glo, index_g) |
---|
888 | IF (ALL(begin_leaves_real(:,:) == val_exp)) begin_leaves_real(:,:) = zero |
---|
889 | |
---|
890 | ! Transform into logical needed by the modele |
---|
891 | WHERE ( begin_leaves_real(:,:) >= 0.5 ) |
---|
892 | begin_leaves = .TRUE. |
---|
893 | ELSEWHERE |
---|
894 | begin_leaves = .FALSE. |
---|
895 | ENDWHERE |
---|
896 | |
---|
897 | |
---|
898 | when_growthinit(:,:) = val_exp |
---|
899 | var_name = 'when_growthinit' |
---|
900 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
901 | & .TRUE., when_growthinit, 'gather', nbp_glo, index_g) |
---|
902 | IF (ALL(when_growthinit(:,:) == val_exp)) & |
---|
903 | & when_growthinit(:,:) = zero |
---|
904 | !- |
---|
905 | age(:,:) = val_exp |
---|
906 | var_name = 'age' |
---|
907 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
908 | & .TRUE., age, 'gather', nbp_glo, index_g) |
---|
909 | IF (ALL(age(:,:) == val_exp)) age(:,:) = zero |
---|
910 | !- |
---|
911 | ! 13 CO2 |
---|
912 | !- |
---|
913 | resp_hetero(:,:) = val_exp |
---|
914 | var_name = 'resp_hetero' |
---|
915 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
916 | & .TRUE., resp_hetero, 'gather', nbp_glo, index_g) |
---|
917 | IF (ALL(resp_hetero(:,:) == val_exp)) resp_hetero(:,:) = zero |
---|
918 | !- |
---|
919 | resp_maint(:,:) = val_exp |
---|
920 | var_name = 'resp_maint' |
---|
921 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
922 | & .TRUE., resp_maint, 'gather', nbp_glo, index_g) |
---|
923 | IF (ALL(resp_maint(:,:) == val_exp)) resp_maint(:,:) = zero |
---|
924 | !- |
---|
925 | resp_growth(:,:) = val_exp |
---|
926 | var_name = 'resp_growth' |
---|
927 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
928 | & .TRUE., resp_growth, 'gather', nbp_glo, index_g) |
---|
929 | IF (ALL(resp_growth(:,:) == val_exp)) resp_growth(:,:) = zero |
---|
930 | !- |
---|
931 | co2_fire(:,:) = val_exp |
---|
932 | var_name = 'co2_fire' |
---|
933 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
934 | & .TRUE., co2_fire, 'gather', nbp_glo, index_g) |
---|
935 | IF (ALL(co2_fire(:,:) == val_exp)) co2_fire(:,:) = zero |
---|
936 | !- |
---|
937 | co2_to_bm_dgvm(:,:) = val_exp |
---|
938 | var_name = 'co2_to_bm_dgvm' |
---|
939 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
940 | & .TRUE., co2_to_bm_dgvm, 'gather', nbp_glo, index_g) |
---|
941 | IF (ALL(co2_to_bm_dgvm(:,:) == val_exp)) co2_to_bm_dgvm(:,:) = zero |
---|
942 | |
---|
943 | co2_to_bm_radia(:,:) = val_exp |
---|
944 | var_name = 'co2_to_bm_radia' |
---|
945 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
946 | & .TRUE., co2_to_bm_radia, 'gather', nbp_glo, index_g) |
---|
947 | IF (ALL(co2_to_bm_radia(:,:) == val_exp)) co2_to_bm_radia(:,:) = zero |
---|
948 | !- |
---|
949 | ! 14 vegetation distribution after last light competition |
---|
950 | !- |
---|
951 | veget_lastlight(:,:) = val_exp |
---|
952 | var_name = 'veget_lastlight' |
---|
953 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
954 | & .TRUE., veget_lastlight, 'gather', nbp_glo, index_g) |
---|
955 | IF (ALL(veget_lastlight(:,:) == val_exp)) veget_lastlight(:,:) = zero |
---|
956 | !- |
---|
957 | ! 15 establishment criteria |
---|
958 | !- |
---|
959 | everywhere(:,:) = val_exp |
---|
960 | var_name = 'everywhere' |
---|
961 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
962 | & .TRUE., everywhere, 'gather', nbp_glo, index_g) |
---|
963 | IF (ALL(everywhere(:,:) == val_exp)) everywhere(:,:) = zero |
---|
964 | !- |
---|
965 | need_adjacent_real(:,:) = val_exp |
---|
966 | var_name = 'need_adjacent' |
---|
967 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
968 | & .TRUE., need_adjacent_real, 'gather', nbp_glo, index_g) |
---|
969 | IF (ALL(need_adjacent_real(:,:) == val_exp)) & |
---|
970 | & need_adjacent_real(:,:) = zero |
---|
971 | WHERE ( need_adjacent_real(:,:) >= .5 ) |
---|
972 | need_adjacent = .TRUE. |
---|
973 | ELSEWHERE |
---|
974 | need_adjacent = .FALSE. |
---|
975 | ENDWHERE |
---|
976 | !- |
---|
977 | RIP_time(:,:) = val_exp |
---|
978 | var_name = 'RIP_time' |
---|
979 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
980 | & .TRUE., RIP_time, 'gather', nbp_glo, index_g) |
---|
981 | IF (ALL(RIP_time(:,:) == val_exp)) RIP_time(:,:) = large_value |
---|
982 | !- |
---|
983 | ! 17 litter |
---|
984 | !- |
---|
985 | litterpart(:,:,:) = val_exp |
---|
986 | DO l=1,nlitt |
---|
987 | var_name = 'litterpart_'//litter_str(l) |
---|
988 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
989 | & .TRUE., litterpart(:,:,l), 'gather', nbp_glo, index_g) |
---|
990 | IF (ALL(litterpart(:,:,l) == val_exp)) litterpart(:,:,l) = zero |
---|
991 | ENDDO |
---|
992 | !- |
---|
993 | litter(:,:,:,:,:) = val_exp |
---|
994 | DO k = 1,nelements |
---|
995 | DO l = 1,nlevs |
---|
996 | DO m = 1,nvm |
---|
997 | WRITE (part_str, '(I2)') m |
---|
998 | IF (m<10) part_str(1:1)='0' |
---|
999 | var_name = 'litter_'//part_str(1:LEN_TRIM(part_str))//'_'//level_str(l)//element_str(k) |
---|
1000 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nlitt , 1, itime, & |
---|
1001 | & .TRUE., litter(:,:,m,l,k), 'gather', nbp_glo, index_g) |
---|
1002 | IF (ALL(litter(:,:,m,l,k) == val_exp)) litter(:,:,m,l,k) = zero |
---|
1003 | ENDDO |
---|
1004 | ENDDO |
---|
1005 | END DO |
---|
1006 | !- |
---|
1007 | dead_leaves(:,:,:) = val_exp |
---|
1008 | DO l=1,nlitt |
---|
1009 | var_name = 'dead_leaves_'//litter_str(l) |
---|
1010 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
1011 | & .TRUE., dead_leaves(:,:,l), 'gather', nbp_glo, index_g) |
---|
1012 | IF (ALL(dead_leaves(:,:,l) == val_exp)) dead_leaves(:,:,l) = zero |
---|
1013 | ENDDO |
---|
1014 | !- |
---|
1015 | carbon(:,:,:) = val_exp |
---|
1016 | DO m=1,nvm |
---|
1017 | WRITE (part_str, '(I2)') m |
---|
1018 | IF (m<10) part_str(1:1)='0' |
---|
1019 | var_name = 'carbon_'//part_str(1:LEN_TRIM(part_str)) |
---|
1020 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, ncarb , 1, itime, & |
---|
1021 | & .TRUE., carbon(:,:,m), 'gather', nbp_glo, index_g) |
---|
1022 | IF (ALL(carbon(:,:,m) == val_exp)) carbon(:,:,m) = zero |
---|
1023 | ENDDO |
---|
1024 | !- |
---|
1025 | lignin_struc(:,:,:) = val_exp |
---|
1026 | DO l=1,nlevs |
---|
1027 | var_name = 'lignin_struc_'//level_str(l) |
---|
1028 | CALL restget_p & |
---|
1029 | & (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1030 | & .TRUE., lignin_struc(:,:,l), 'gather', nbp_glo, index_g) |
---|
1031 | IF (ALL(lignin_struc(:,:,l) == val_exp)) lignin_struc(:,:,l) = zero |
---|
1032 | ENDDO |
---|
1033 | |
---|
1034 | |
---|
1035 | !- |
---|
1036 | ! 18 land cover change |
---|
1037 | !- |
---|
1038 | ! Read from restart file or set to zero if the variables or restart file were not found |
---|
1039 | |
---|
1040 | var_name = 'co2_flux' |
---|
1041 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1042 | .TRUE., co2_flux, 'gather', nbp_glo, index_g) |
---|
1043 | IF (ALL(co2_flux(:,:) == val_exp)) co2_flux(:,:) = zero |
---|
1044 | |
---|
1045 | var_name = 'fco2_lu' |
---|
1046 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1047 | .TRUE., fco2_lu, 'gather', nbp_glo, index_g) |
---|
1048 | IF (ALL(fco2_lu(:) == val_exp)) fco2_lu(:) = zero |
---|
1049 | |
---|
1050 | var_name = 'fco2_wh' |
---|
1051 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1052 | .TRUE., fco2_wh, 'gather', nbp_glo, index_g) |
---|
1053 | IF (ALL(fco2_wh(:) == val_exp)) fco2_wh(:) = zero |
---|
1054 | |
---|
1055 | var_name = 'fco2_ha' |
---|
1056 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1057 | .TRUE., fco2_ha, 'gather', nbp_glo, index_g) |
---|
1058 | IF (ALL(fco2_ha(:) == val_exp)) fco2_ha(:) = zero |
---|
1059 | |
---|
1060 | |
---|
1061 | IF (vegetmap_reset) THEN |
---|
1062 | ! Reset vegetation map related variables instead of reading from restart file |
---|
1063 | prod10(:,:) = zero |
---|
1064 | prod100(:,:) = zero |
---|
1065 | flux10(:,:) = zero |
---|
1066 | flux100(:,:) = zero |
---|
1067 | convflux(:) = zero |
---|
1068 | cflux_prod10(:) = zero |
---|
1069 | cflux_prod100(:) = zero |
---|
1070 | convfluxpft(:,:) = zero |
---|
1071 | |
---|
1072 | ELSE |
---|
1073 | ! Read from restart file or set to zero if the variables or restart file were not found |
---|
1074 | prod10(:,:) = val_exp |
---|
1075 | var_name = 'prod10' |
---|
1076 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 11 , 1, itime, & |
---|
1077 | .TRUE., prod10, 'gather', nbp_glo, index_g) |
---|
1078 | IF (ALL(prod10(:,:) == val_exp)) prod10(:,:) = zero |
---|
1079 | |
---|
1080 | prod100(:,:) = val_exp |
---|
1081 | var_name = 'prod100' |
---|
1082 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 101 , 1, itime, & |
---|
1083 | .TRUE., prod100, 'gather', nbp_glo, index_g) |
---|
1084 | IF (ALL(prod100(:,:) == val_exp)) prod100(:,:) = zero |
---|
1085 | |
---|
1086 | flux10(:,:) = val_exp |
---|
1087 | var_name = 'flux10' |
---|
1088 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 10 , 1, itime, & |
---|
1089 | .TRUE., flux10, 'gather', nbp_glo, index_g) |
---|
1090 | IF (ALL(flux10(:,:) == val_exp)) flux10(:,:) = zero |
---|
1091 | |
---|
1092 | flux100(:,:) = val_exp |
---|
1093 | var_name = 'flux100' |
---|
1094 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 100 , 1, itime, & |
---|
1095 | .TRUE., flux100, 'gather', nbp_glo, index_g) |
---|
1096 | IF (ALL(flux100(:,:) == val_exp)) flux100(:,:) = zero |
---|
1097 | |
---|
1098 | convflux(:) = val_exp |
---|
1099 | var_name = 'convflux' |
---|
1100 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
1101 | .TRUE., convflux, 'gather', nbp_glo, index_g) |
---|
1102 | IF (ALL(convflux(:) == val_exp)) convflux(:) = zero |
---|
1103 | |
---|
1104 | cflux_prod10(:) = val_exp |
---|
1105 | var_name = 'cflux_prod10' |
---|
1106 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
1107 | .TRUE., cflux_prod10, 'gather', nbp_glo, index_g) |
---|
1108 | IF (ALL(cflux_prod10(:) == val_exp)) cflux_prod10(:) = zero |
---|
1109 | |
---|
1110 | cflux_prod100(:) = val_exp |
---|
1111 | var_name = 'cflux_prod100' |
---|
1112 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
1113 | .TRUE., cflux_prod100, 'gather', nbp_glo, index_g) |
---|
1114 | IF (ALL(cflux_prod100(:) == val_exp)) cflux_prod100(:) = zero |
---|
1115 | |
---|
1116 | convfluxpft(:,:) = val_exp |
---|
1117 | var_name = 'convfluxpft' |
---|
1118 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
1119 | .TRUE., convfluxpft, 'gather', nbp_glo, index_g) |
---|
1120 | IF (ALL(convfluxpft(:,:) == val_exp)) convfluxpft(:,:) = zero |
---|
1121 | END IF |
---|
1122 | |
---|
1123 | fDeforestToProduct(:,:) = val_exp |
---|
1124 | var_name = 'fDeforestToProduct' |
---|
1125 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
1126 | & .TRUE., fDeforestToProduct, 'gather', nbp_glo, index_g) |
---|
1127 | IF (ALL(fDeforestToProduct(:,:) ==val_exp)) fDeforestToProduct(:,:) = zero |
---|
1128 | |
---|
1129 | fLulccResidue(:,:) = val_exp |
---|
1130 | var_name = 'fLulccResidue' |
---|
1131 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
1132 | & .TRUE., fLulccResidue, 'gather', nbp_glo, index_g) |
---|
1133 | IF (ALL(fLulccResidue(:,:) ==val_exp)) fLulccResidue(:,:) = zero |
---|
1134 | |
---|
1135 | fHarvestToProduct(:,:) = val_exp |
---|
1136 | var_name = 'fHarvestToProduct' |
---|
1137 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
1138 | & .TRUE., fHarvestToProduct, 'gather', nbp_glo, index_g) |
---|
1139 | IF (ALL(fHarvestToProduct(:,:) ==val_exp)) fHarvestToProduct(:,:) = zero |
---|
1140 | |
---|
1141 | !- |
---|
1142 | ! 18-bis wood harvest |
---|
1143 | !- |
---|
1144 | IF (do_wood_harvest) THEN |
---|
1145 | prod10_harvest(:,:) = val_exp |
---|
1146 | var_name = 'prod10_harvest' |
---|
1147 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 11 , 1, itime, & |
---|
1148 | .TRUE., prod10_harvest, 'gather', nbp_glo, index_g) |
---|
1149 | IF (ALL(prod10_harvest(:,:) == val_exp)) prod10_harvest(:,:) = zero |
---|
1150 | |
---|
1151 | prod100_harvest(:,:) = val_exp |
---|
1152 | var_name = 'prod100_harvest' |
---|
1153 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 101 , 1, itime, & |
---|
1154 | .TRUE., prod100_harvest, 'gather', nbp_glo, index_g) |
---|
1155 | IF (ALL(prod100_harvest(:,:) == val_exp)) prod100_harvest(:,:) = zero |
---|
1156 | |
---|
1157 | flux10_harvest(:,:) = val_exp |
---|
1158 | var_name = 'flux10_harvest' |
---|
1159 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 10 , 1, itime, & |
---|
1160 | .TRUE., flux10_harvest, 'gather', nbp_glo, index_g) |
---|
1161 | IF (ALL(flux10_harvest(:,:) == val_exp)) flux10_harvest(:,:) = zero |
---|
1162 | |
---|
1163 | flux100_harvest(:,:) = val_exp |
---|
1164 | var_name = 'flux100_harvest' |
---|
1165 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 100 , 1, itime, & |
---|
1166 | .TRUE., flux100_harvest, 'gather', nbp_glo, index_g) |
---|
1167 | IF (ALL(flux100_harvest(:,:) == val_exp)) flux100_harvest(:,:) = zero |
---|
1168 | |
---|
1169 | convflux_harvest(:) = val_exp |
---|
1170 | var_name = 'convflux_harvest' |
---|
1171 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
1172 | .TRUE., convflux_harvest, 'gather', nbp_glo, index_g) |
---|
1173 | IF (ALL(convflux_harvest(:) == val_exp)) convflux_harvest(:) = zero |
---|
1174 | |
---|
1175 | cflux_prod10_harvest(:) = val_exp |
---|
1176 | var_name = 'cflux_prod10_harvest' |
---|
1177 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
1178 | .TRUE., cflux_prod10_harvest, 'gather', nbp_glo, index_g) |
---|
1179 | IF (ALL(cflux_prod10_harvest(:) == val_exp)) cflux_prod10_harvest(:) = zero |
---|
1180 | |
---|
1181 | cflux_prod100_harvest(:) = val_exp |
---|
1182 | var_name = 'cfluxprod100_harvest' |
---|
1183 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
1184 | .TRUE., cflux_prod100_harvest, 'gather', nbp_glo, index_g) |
---|
1185 | IF (ALL(cflux_prod100_harvest(:) == val_exp)) cflux_prod100_harvest(:) = zero |
---|
1186 | |
---|
1187 | woodharvestpft(:,:) = val_exp |
---|
1188 | var_name = 'woodharvestpft' |
---|
1189 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
1190 | .TRUE., woodharvestpft, 'gather', nbp_glo, index_g) |
---|
1191 | IF (ALL(woodharvestpft(:,:) == val_exp)) woodharvestpft(:,:) = zero |
---|
1192 | END IF |
---|
1193 | |
---|
1194 | |
---|
1195 | bm_to_litter(:,:,:,:) = val_exp |
---|
1196 | DO l = 1,nelements |
---|
1197 | DO k = 1,nparts |
---|
1198 | WRITE(part_str,'(I2)') k |
---|
1199 | IF ( k < 10 ) part_str(1:1) = '0' |
---|
1200 | var_name = 'bm_to_litter_'//part_str(1:LEN_TRIM(part_str))//element_str(l) |
---|
1201 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
1202 | & .TRUE., bm_to_litter(:,:,k,l), 'gather', nbp_glo, index_g) |
---|
1203 | IF (ALL(bm_to_litter(:,:,k,l) == val_exp)) bm_to_litter(:,:,k,l) = zero |
---|
1204 | ENDDO |
---|
1205 | END DO |
---|
1206 | |
---|
1207 | carb_mass_total(:) = val_exp |
---|
1208 | var_name = 'carb_mass_total' |
---|
1209 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
1210 | & .TRUE., carb_mass_total, 'gather', nbp_glo, index_g) |
---|
1211 | IF (ALL(carb_mass_total(:) == val_exp)) carb_mass_total(:) = zero |
---|
1212 | !- |
---|
1213 | ! 19. Spinup |
---|
1214 | !- |
---|
1215 | IF (spinup_analytic) THEN |
---|
1216 | |
---|
1217 | IF (is_root_prc) THEN |
---|
1218 | temp_global_years(1) = val_exp |
---|
1219 | var_name = 'Global_years' |
---|
1220 | CALL restget (rest_id_stomate, var_name, 1 ,1 , 1, itime, & |
---|
1221 | & .TRUE., temp_global_years) |
---|
1222 | IF(temp_global_years(1) == val_exp) temp_global_years(1) = zero |
---|
1223 | global_years = INT(temp_global_years(1)) |
---|
1224 | ENDIF |
---|
1225 | CALL bcast(global_years) |
---|
1226 | |
---|
1227 | nbp_accu(:) = val_exp |
---|
1228 | var_name = 'nbp_sum' |
---|
1229 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
1230 | & .TRUE., nbp_accu, 'gather', nbp_glo, index_g) |
---|
1231 | IF (ALL(nbp_accu(:) == val_exp)) nbp_accu(:) = zero |
---|
1232 | |
---|
1233 | nbp_flux(:) = val_exp |
---|
1234 | var_name = 'nbp_flux' |
---|
1235 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1 , 1, itime, & |
---|
1236 | & .TRUE., nbp_flux, 'gather', nbp_glo, index_g) |
---|
1237 | IF (ALL(nbp_flux(:) == val_exp)) nbp_flux(:) = zero |
---|
1238 | |
---|
1239 | !- |
---|
1240 | ok_equilibrium_real(:) = val_exp |
---|
1241 | var_name = 'ok_equilibrium' |
---|
1242 | CALL restget_p (rest_id_stomate, var_name, nbp_glo , 1 , 1, itime, & |
---|
1243 | & .TRUE., ok_equilibrium_real,'gather', nbp_glo, index_g) |
---|
1244 | IF (ALL(ok_equilibrium_real(:) == val_exp)) ok_equilibrium_real(:) = zero |
---|
1245 | WHERE(ok_equilibrium_real(:) >= 0.5) |
---|
1246 | ok_equilibrium = .TRUE. |
---|
1247 | ELSEWHERE |
---|
1248 | ok_equilibrium = .FALSE. |
---|
1249 | ENDWHERE |
---|
1250 | |
---|
1251 | MatrixV(:,:,:,:) = val_exp |
---|
1252 | DO k = 1,nbpools |
---|
1253 | DO j = 1,nbpools |
---|
1254 | WRITE(part_str,'(I2)') k |
---|
1255 | IF (k < 10) part_str(1:1) = '0' |
---|
1256 | var_name = 'MatrixV_'//part_str(1:LEN_TRIM(part_str))//'_'//TRIM(pools_str(j)) |
---|
1257 | CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
1258 | & .TRUE., MatrixV(:,:,k,j), 'gather', nbp_glo, index_g) |
---|
1259 | ENDDO |
---|
1260 | ENDDO |
---|
1261 | ! If nothing is found in the restart file, we initialize each submatrix by identity |
---|
1262 | IF (ALL(MatrixV(:,:,:,:) == val_exp)) THEN |
---|
1263 | MatrixV(:,:,:,:) = zero |
---|
1264 | DO l = 1,nbpools |
---|
1265 | MatrixV(:,:,l,l) = un |
---|
1266 | END DO |
---|
1267 | END IF |
---|
1268 | |
---|
1269 | VectorU(:,:,:) = val_exp |
---|
1270 | DO k= 1,nbpools |
---|
1271 | WRITE(part_str,'(I2)') k |
---|
1272 | IF (k < 10) part_str(1:1) = '0' |
---|
1273 | var_name = 'Vector_U_'//part_str(1:LEN_TRIM(part_str)) |
---|
1274 | CALL restget_p & |
---|
1275 | & (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1276 | & .TRUE., VectorU(:,:,k), 'gather', nbp_glo, index_g) |
---|
1277 | IF (ALL(VectorU(:,:,k) == val_exp)) VectorU(:,:,k) = zero |
---|
1278 | ENDDO |
---|
1279 | |
---|
1280 | previous_stock(:,:,:) = val_exp |
---|
1281 | DO k= 1,nbpools |
---|
1282 | WRITE(part_str,'(I2)') k |
---|
1283 | IF (k < 10) part_str(1:1) = '0' |
---|
1284 | var_name = 'previous_stock_'//part_str(1:LEN_TRIM(part_str)) |
---|
1285 | CALL restget_p & |
---|
1286 | & (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1287 | & .TRUE., previous_stock(:,:,k), 'gather', nbp_glo, index_g) |
---|
1288 | IF (ALL(previous_stock(:,:,k) == val_exp)) previous_stock(:,:,k) = undef_sechiba |
---|
1289 | ENDDO |
---|
1290 | |
---|
1291 | current_stock(:,:,:) = val_exp |
---|
1292 | DO k= 1,nbpools |
---|
1293 | WRITE(part_str,'(I2)') k |
---|
1294 | IF (k < 10) part_str(1:1) = '0' |
---|
1295 | var_name = 'current_stock_'//part_str(1:LEN_TRIM(part_str)) |
---|
1296 | CALL restget_p & |
---|
1297 | & (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1298 | & .TRUE., current_stock(:,:,k), 'gather', nbp_glo, index_g) |
---|
1299 | IF (ALL(current_stock(:,:,k) == val_exp)) current_stock(:,:,k) = zero |
---|
1300 | ENDDO |
---|
1301 | |
---|
1302 | |
---|
1303 | ENDIF ! spinup_matrix_method |
---|
1304 | |
---|
1305 | |
---|
1306 | ! Read assim_param from restart file. The initialization of assim_param will |
---|
1307 | ! be done in stomate_var_init if the variable is not in the restart file. |
---|
1308 | assim_param(:,:,:) = val_exp |
---|
1309 | DO k= 1,npco2 |
---|
1310 | WRITE(part_str,'(I2)') k |
---|
1311 | IF (k < 10) part_str(1:1) = '0' |
---|
1312 | var_name = 'assim_param_'//part_str(1:LEN_TRIM(part_str)) |
---|
1313 | CALL restget_p & |
---|
1314 | & (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1315 | & .TRUE., assim_param(:,:,k), 'gather', nbp_glo, index_g) |
---|
1316 | END DO |
---|
1317 | |
---|
1318 | IF (printlev >= 4) WRITE(numout,*) 'Leaving readstart' |
---|
1319 | !----------------------- |
---|
1320 | END SUBROUTINE readstart |
---|
1321 | |
---|
1322 | !! ================================================================================================================================ |
---|
1323 | !! SUBROUTINE : writerestart |
---|
1324 | !! |
---|
1325 | !>\BRIEF Write all variables for stomate from restart file. |
---|
1326 | !! |
---|
1327 | !! DESCRIPTION : Write all variables for stomate from restart file. |
---|
1328 | !! |
---|
1329 | !! \n |
---|
1330 | !_ ================================================================================================================================ |
---|
1331 | |
---|
1332 | SUBROUTINE writerestart & |
---|
1333 | & (npts, index, dt_days, date_loc, & |
---|
1334 | & ind, adapted, regenerate, moiavail_daily, gdd_init_date, litterhum_daily, & |
---|
1335 | & t2m_daily, t2m_min_daily, tsurf_daily, tsoil_daily, & |
---|
1336 | & soilhum_daily, precip_daily, gpp_daily, npp_daily, & |
---|
1337 | & turnover_daily, moiavail_month, moiavail_week, & |
---|
1338 | & t2m_longterm, tau_longterm, t2m_month, t2m_week, & |
---|
1339 | & tsoil_month, soilhum_month, fireindex, firelitter, & |
---|
1340 | & maxmoiavail_lastyear, maxmoiavail_thisyear, & |
---|
1341 | & minmoiavail_lastyear, minmoiavail_thisyear, & |
---|
1342 | & maxgppweek_lastyear, maxgppweek_thisyear, & |
---|
1343 | & gdd0_lastyear, gdd0_thisyear, precip_lastyear, precip_thisyear, & |
---|
1344 | & gdd_m5_dormance, gdd_from_growthinit, gdd_midwinter, ncd_dormance, ngd_minus5, & |
---|
1345 | & PFTpresent, npp_longterm, lm_lastyearmax, lm_thisyearmax, & |
---|
1346 | & maxfpc_lastyear, maxfpc_thisyear, & |
---|
1347 | & turnover_longterm, gpp_week, biomass, resp_maint_part, & |
---|
1348 | & leaf_age, leaf_frac, senescence, when_growthinit, age, & |
---|
1349 | & resp_hetero, resp_maint, resp_growth, co2_fire, co2_to_bm_dgvm, co2_to_bm_radia, & |
---|
1350 | & veget_lastlight, everywhere, need_adjacent, RIP_time, & |
---|
1351 | & time_hum_min, hum_min_dormance, & |
---|
1352 | & litterpart, litter, dead_leaves, & |
---|
1353 | & carbon, lignin_struc, turnover_time, & |
---|
1354 | & co2_flux, fco2_lu, fco2_wh, fco2_ha, & |
---|
1355 | & prod10,prod100 ,flux10, flux100, & |
---|
1356 | & convflux, cflux_prod10, cflux_prod100, & |
---|
1357 | & prod10_harvest,prod100_harvest ,flux10_harvest, flux100_harvest, & |
---|
1358 | & convflux_harvest, cflux_prod10_harvest, cflux_prod100_harvest, & |
---|
1359 | & convfluxpft, fDeforestToProduct, fLulccResidue, fHarvestToProduct, & |
---|
1360 | & woodharvestpft, bm_to_litter, carb_mass_total, & |
---|
1361 | & Tseason, Tseason_length, Tseason_tmp, & |
---|
1362 | & Tmin_spring_time, begin_leaves, onset_date, & |
---|
1363 | & global_years, ok_equilibrium, nbp_accu, nbp_flux, & |
---|
1364 | & MatrixV, VectorU, previous_stock, current_stock, assim_param) |
---|
1365 | |
---|
1366 | !--------------------------------------------------------------------- |
---|
1367 | !- write restart file |
---|
1368 | !--------------------------------------------------------------------- |
---|
1369 | !- |
---|
1370 | ! 0 declarations |
---|
1371 | !- |
---|
1372 | ! 0.1 input |
---|
1373 | !- |
---|
1374 | ! Domain size |
---|
1375 | INTEGER(i_std),INTENT(in) :: npts |
---|
1376 | ! Indices of the points on the map |
---|
1377 | INTEGER(i_std),DIMENSION(npts),INTENT(in) :: index |
---|
1378 | ! time step of STOMATE in days |
---|
1379 | REAL(r_std),INTENT(in) :: dt_days |
---|
1380 | ! date_loc (d) |
---|
1381 | INTEGER(i_std),INTENT(in) :: date_loc |
---|
1382 | ! density of individuals (1/m**2) |
---|
1383 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: ind |
---|
1384 | ! Winter too cold? between 0 and 1 |
---|
1385 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: adapted |
---|
1386 | ! Winter sufficiently cold? between 0 and 1 |
---|
1387 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: regenerate |
---|
1388 | ! daily moisture availability |
---|
1389 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: moiavail_daily |
---|
1390 | ! gdd init date |
---|
1391 | REAL(r_std),DIMENSION(npts,2),INTENT(in) :: gdd_init_date |
---|
1392 | ! daily litter humidity |
---|
1393 | REAL(r_std),DIMENSION(npts),INTENT(in) :: litterhum_daily |
---|
1394 | ! daily 2 meter temperatures (K) |
---|
1395 | REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_daily |
---|
1396 | ! daily minimum 2 meter temperatures (K) |
---|
1397 | REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_min_daily |
---|
1398 | ! daily surface temperatures (K) |
---|
1399 | REAL(r_std),DIMENSION(npts),INTENT(in) :: tsurf_daily |
---|
1400 | ! daily soil temperatures (K) |
---|
1401 | REAL(r_std),DIMENSION(npts,nslm),INTENT(in) :: tsoil_daily |
---|
1402 | ! daily soil humidity |
---|
1403 | REAL(r_std),DIMENSION(npts,nslm),INTENT(in) :: soilhum_daily |
---|
1404 | ! daily precipitations (mm/day) (for phenology) |
---|
1405 | REAL(r_std),DIMENSION(npts),INTENT(in) :: precip_daily |
---|
1406 | ! daily gross primary productivity (gC/m**2/day) |
---|
1407 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: gpp_daily |
---|
1408 | ! daily net primary productivity (gC/m**2/day) |
---|
1409 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: npp_daily |
---|
1410 | ! daily turnover rates (gC/m**2/day) |
---|
1411 | REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(in) :: turnover_daily |
---|
1412 | ! "monthly" moisture availability |
---|
1413 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: moiavail_month |
---|
1414 | ! "weekly" moisture availability |
---|
1415 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: moiavail_week |
---|
1416 | ! "long term" 2 meter temperatures (K) |
---|
1417 | REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_longterm |
---|
1418 | ! "tau_longterm" |
---|
1419 | REAL(r_std), INTENT(IN) :: tau_longterm |
---|
1420 | ! "monthly" 2 meter temperatures (K) |
---|
1421 | REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_month |
---|
1422 | ! "seasonal" 2 meter temperatures (K) |
---|
1423 | REAL(r_std),DIMENSION(npts),INTENT(in) :: Tseason |
---|
1424 | ! temporary variable to calculate Tseason |
---|
1425 | REAL(r_std),DIMENSION(npts),INTENT(in) :: Tseason_length |
---|
1426 | ! temporary variable to calculate Tseason |
---|
1427 | REAL(r_std),DIMENSION(npts),INTENT(in) :: Tseason_tmp |
---|
1428 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: Tmin_spring_time |
---|
1429 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: onset_date |
---|
1430 | LOGICAL,DIMENSION(npts,nvm),INTENT(in) :: begin_leaves |
---|
1431 | |
---|
1432 | ! "weekly" 2 meter temperatures (K) |
---|
1433 | REAL(r_std),DIMENSION(npts),INTENT(in) :: t2m_week |
---|
1434 | ! "monthly" soil temperatures (K) |
---|
1435 | REAL(r_std),DIMENSION(npts,nslm),INTENT(in) :: tsoil_month |
---|
1436 | ! "monthly" soil humidity |
---|
1437 | REAL(r_std),DIMENSION(npts,nslm),INTENT(in) :: soilhum_month |
---|
1438 | ! Probability of fire |
---|
1439 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: fireindex |
---|
1440 | ! Longer term total litter above the ground, gC/m**2 of ground |
---|
1441 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: firelitter |
---|
1442 | ! last year's maximum moisture availability |
---|
1443 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxmoiavail_lastyear |
---|
1444 | ! this year's maximum moisture availability |
---|
1445 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxmoiavail_thisyear |
---|
1446 | ! last year's minimum moisture availability |
---|
1447 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: minmoiavail_lastyear |
---|
1448 | ! this year's minimum moisture availability |
---|
1449 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: minmoiavail_thisyear |
---|
1450 | ! last year's maximum weekly GPP |
---|
1451 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxgppweek_lastyear |
---|
1452 | ! this year's maximum weekly GPP |
---|
1453 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxgppweek_thisyear |
---|
1454 | ! last year's annual GDD0 |
---|
1455 | REAL(r_std),DIMENSION(npts),INTENT(in) :: gdd0_lastyear |
---|
1456 | ! this year's annual GDD0 |
---|
1457 | REAL(r_std),DIMENSION(npts),INTENT(in) :: gdd0_thisyear |
---|
1458 | ! last year's annual precipitation (mm/year) |
---|
1459 | REAL(r_std),DIMENSION(npts),INTENT(in) :: precip_lastyear |
---|
1460 | ! this year's annual precipitation (mm/year) |
---|
1461 | REAL(r_std),DIMENSION(npts),INTENT(in) :: precip_thisyear |
---|
1462 | ! growing degree days, threshold -5 deg C (for phenology) |
---|
1463 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: gdd_m5_dormance |
---|
1464 | ! growing degree days, from begin of season (crops) |
---|
1465 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: gdd_from_growthinit |
---|
1466 | ! growing degree days since midwinter (for phenology) |
---|
1467 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: gdd_midwinter |
---|
1468 | ! number of chilling days since leaves were lost (for phenology) |
---|
1469 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: ncd_dormance |
---|
1470 | ! number of growing days, threshold -5 deg C (for phenology) |
---|
1471 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: ngd_minus5 |
---|
1472 | ! PFT exists (equivalent to fpc_max > 0 for natural PFTs) |
---|
1473 | LOGICAL,DIMENSION(npts,nvm),INTENT(in) :: PFTpresent |
---|
1474 | ! "long term" net primary productivity (gC/m**2/year) |
---|
1475 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: npp_longterm |
---|
1476 | ! last year's maximum leaf mass, for each PFT (gC/m**2) |
---|
1477 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: lm_lastyearmax |
---|
1478 | ! this year's maximum leaf mass, for each PFT (gC/m**2) |
---|
1479 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: lm_thisyearmax |
---|
1480 | ! last year's maximum fpc for each natural PFT, on ground |
---|
1481 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxfpc_lastyear |
---|
1482 | ! this year's maximum fpc for each PFT, |
---|
1483 | ! on *total* ground (see stomate_season) |
---|
1484 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: maxfpc_thisyear |
---|
1485 | ! "long term" turnover rate (gC/m**2/year) |
---|
1486 | REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(in) :: turnover_longterm |
---|
1487 | ! "weekly" GPP (gC/day/(m**2 covered) |
---|
1488 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: gpp_week |
---|
1489 | ! biomass (gC/m**2) |
---|
1490 | REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(in) :: biomass |
---|
1491 | ! maintenance respiration (gC/m**2) |
---|
1492 | REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(in) :: resp_maint_part |
---|
1493 | ! leaf age (days) |
---|
1494 | REAL(r_std),DIMENSION(npts,nvm,nleafages),INTENT(in) :: leaf_age |
---|
1495 | ! fraction of leaves in leaf age class |
---|
1496 | REAL(r_std),DIMENSION(npts,nvm,nleafages),INTENT(in) :: leaf_frac |
---|
1497 | ! is the plant senescent ? |
---|
1498 | ! (only for deciduous trees - carbohydrate reserve) |
---|
1499 | LOGICAL,DIMENSION(npts,nvm),INTENT(in) :: senescence |
---|
1500 | ! how many days ago was the beginning of the growing season |
---|
1501 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: when_growthinit |
---|
1502 | ! mean age (years) |
---|
1503 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: age |
---|
1504 | ! heterotrophic respiration (gC/day/m**2) |
---|
1505 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: resp_hetero |
---|
1506 | ! maintenance respiration (gC/day/m**2) |
---|
1507 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: resp_maint |
---|
1508 | ! growth respiration (gC/day/m**2) |
---|
1509 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: resp_growth |
---|
1510 | ! carbon emitted into the atmosphere by fire (living and dead biomass) |
---|
1511 | ! (in gC/m**2/time step) |
---|
1512 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: co2_fire |
---|
1513 | ! biomass uptaken (gC/(m**2 of total ground)/day) |
---|
1514 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: co2_to_bm_dgvm |
---|
1515 | ! biomass uptaken (gC/(m**2 of total ground)/dt_sechiba) |
---|
1516 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: co2_to_bm_radia |
---|
1517 | ! vegetation fractions (on ground) after last light competition |
---|
1518 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: veget_lastlight |
---|
1519 | ! is the PFT everywhere in the grid box or very localized |
---|
1520 | ! (after its introduction) |
---|
1521 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: everywhere |
---|
1522 | ! in order for this PFT to be introduced, |
---|
1523 | ! does it have to be present in an adjacent grid box? |
---|
1524 | LOGICAL,DIMENSION(npts,nvm),INTENT(in) :: need_adjacent |
---|
1525 | ! How much time ago was the PFT eliminated for the last time (y) |
---|
1526 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: RIP_time |
---|
1527 | ! time elapsed since strongest moisture availability (d) |
---|
1528 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: time_hum_min |
---|
1529 | ! minimum moisture during dormance |
---|
1530 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: hum_min_dormance |
---|
1531 | ! fraction of litter above the ground belonging to different PFTs |
---|
1532 | REAL(r_std),DIMENSION(npts,nvm,nlitt),INTENT(in) :: litterpart |
---|
1533 | ! metabolic and structural litter, above and below ground (gC/m**2) |
---|
1534 | REAL(r_std),DIMENSION(npts,nlitt,nvm,nlevs,nelements),INTENT(in) :: litter |
---|
1535 | ! dead leaves on ground, per PFT, metabolic and structural, |
---|
1536 | ! in gC/(m**2 of ground) |
---|
1537 | REAL(r_std),DIMENSION(npts,nvm,nlitt),INTENT(in) :: dead_leaves |
---|
1538 | ! carbon pool: active, slow, or passive, (gC/m**2) |
---|
1539 | REAL(r_std),DIMENSION(npts,ncarb,nvm),INTENT(in) :: carbon |
---|
1540 | ! ratio Lignine/Carbon in structural litter, above and below ground, (gC/m**2) |
---|
1541 | REAL(r_std),DIMENSION(npts,nvm,nlevs),INTENT(in) :: lignin_struc |
---|
1542 | ! turnover_time of leaves |
---|
1543 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: turnover_time |
---|
1544 | |
---|
1545 | ! For Spinup matrix resolution |
---|
1546 | INTEGER(i_std), INTENT(in) :: global_years |
---|
1547 | LOGICAL, DIMENSION(npts), INTENT(in) :: ok_equilibrium |
---|
1548 | REAL(r_std), DIMENSION(npts), INTENT(in) :: nbp_accu !! Accumulated Net Biospheric Production over the year |
---|
1549 | REAL(r_std), DIMENSION(npts), INTENT(in) :: nbp_flux !! Net Biospheric Production over the year |
---|
1550 | !- |
---|
1551 | REAL(r_std), DIMENSION(npts,nvm,nbpools,nbpools), INTENT(in) :: MatrixV |
---|
1552 | REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(in) :: VectorU |
---|
1553 | REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(in) :: previous_stock |
---|
1554 | REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(in) :: current_stock |
---|
1555 | REAL(r_std), DIMENSION(npts,nvm,npco2), INTENT(in) :: assim_param |
---|
1556 | !- |
---|
1557 | ! 0.2 local |
---|
1558 | !- |
---|
1559 | ! date, real |
---|
1560 | REAL(r_std) :: date_real |
---|
1561 | ! PFT exists (equivalent to fpc_max > 0 for natural PFTs), real |
---|
1562 | REAL(r_std),DIMENSION(npts,nvm) :: PFTpresent_real |
---|
1563 | ! is the plant senescent ? |
---|
1564 | ! (only for deciduous trees - carbohydrate reserve), real |
---|
1565 | REAL(r_std),DIMENSION(npts,nvm) :: senescence_real |
---|
1566 | REAL(r_std),DIMENSION(npts,nvm) :: begin_leaves_real |
---|
1567 | |
---|
1568 | ! in order for this PFT to be introduced, |
---|
1569 | ! does it have to be present in an adjacent grid box? - real |
---|
1570 | REAL(r_std),DIMENSION(npts,nvm) :: need_adjacent_real |
---|
1571 | ! To store variables names for I/O |
---|
1572 | CHARACTER(LEN=80) :: var_name |
---|
1573 | ! string suffix indicating an index |
---|
1574 | CHARACTER(LEN=10) :: part_str |
---|
1575 | ! string suffix indicating litter type |
---|
1576 | CHARACTER(LEN=3),DIMENSION(nlitt) :: litter_str |
---|
1577 | ! string suffix indicating level |
---|
1578 | CHARACTER(LEN=2),DIMENSION(nlevs) :: level_str |
---|
1579 | ! temporary storage |
---|
1580 | REAL(r_std),DIMENSION(1) :: xtmp |
---|
1581 | REAL(r_std), DIMENSION(1) :: vartmp !! temporary variable because restget/restput needs a variable with DIMESION(:) |
---|
1582 | ! index |
---|
1583 | INTEGER(i_std) :: j,k,l,m |
---|
1584 | CHARACTER(LEN=1),DIMENSION(nelements) :: element_str !! string suffix indicating element |
---|
1585 | REAL(r_std), DIMENSION(1) :: temp_global_years |
---|
1586 | CHARACTER(LEN=6),DIMENSION(nbpools) :: pools_str |
---|
1587 | REAL(r_std), DIMENSION(npts) :: ok_equilibrium_real |
---|
1588 | |
---|
1589 | ! land cover change variables |
---|
1590 | ! products remaining in the 10/100 year-turnover pool after the annual release for each compartment |
---|
1591 | ! (10 or 100 + 1 : input from year of land cover change) |
---|
1592 | REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: co2_flux |
---|
1593 | REAL(r_std),DIMENSION(npts),INTENT(in) :: fco2_lu |
---|
1594 | REAL(r_std),DIMENSION(npts),INTENT(in) :: fco2_wh |
---|
1595 | REAL(r_std),DIMENSION(npts),INTENT(in) :: fco2_ha |
---|
1596 | REAL(r_std),DIMENSION(npts,0:10),INTENT(in) :: prod10 |
---|
1597 | REAL(r_std),DIMENSION(npts,0:100),INTENT(in) :: prod100 |
---|
1598 | ! annual release from the 10/100 year-turnover pool compartments |
---|
1599 | REAL(r_std),DIMENSION(npts,10),INTENT(in) :: flux10 |
---|
1600 | REAL(r_std),DIMENSION(npts,100),INTENT(in) :: flux100 |
---|
1601 | REAL(r_std), DIMENSION(npts), INTENT(in) :: convflux |
---|
1602 | REAL(r_std), DIMENSION(npts), INTENT(in) :: cflux_prod10 |
---|
1603 | REAL(r_std), DIMENSION(npts), INTENT(in) :: cflux_prod100 |
---|
1604 | |
---|
1605 | ! wood harvest variables |
---|
1606 | ! products remaining in the 10/100 year-turnover pool after the annual release for each compartment |
---|
1607 | ! (10 or 100 + 1 : input from year of land cover change) |
---|
1608 | REAL(r_std),DIMENSION(npts,0:10),INTENT(in) :: prod10_harvest |
---|
1609 | REAL(r_std),DIMENSION(npts,0:100),INTENT(in) :: prod100_harvest |
---|
1610 | ! annual release from the 10/100 year-turnover pool compartments |
---|
1611 | REAL(r_std),DIMENSION(npts,10),INTENT(in) :: flux10_harvest |
---|
1612 | REAL(r_std),DIMENSION(npts,100),INTENT(in) :: flux100_harvest |
---|
1613 | REAL(r_std), DIMENSION(npts), INTENT(in) :: convflux_harvest |
---|
1614 | REAL(r_std), DIMENSION(npts), INTENT(in) :: cflux_prod10_harvest |
---|
1615 | REAL(r_std), DIMENSION(npts), INTENT(in) :: cflux_prod100_harvest |
---|
1616 | REAL(r_std), DIMENSION(npts,nvm), INTENT(in) :: convfluxpft |
---|
1617 | REAL(r_std), DIMENSION(npts,nvm), INTENT(in) :: fDeforestToProduct |
---|
1618 | REAL(r_std), DIMENSION(npts,nvm), INTENT(in) :: fLulccResidue |
---|
1619 | REAL(r_std), DIMENSION(npts,nvm), INTENT(in) :: fHarvestToProduct |
---|
1620 | REAL(r_std), DIMENSION(npts,nvm), INTENT(in) :: woodharvestpft |
---|
1621 | REAL(r_std),DIMENSION(npts,nvm,nparts,nelements),INTENT(in) :: bm_to_litter |
---|
1622 | REAL(r_std),DIMENSION(npts),INTENT(in) :: carb_mass_total |
---|
1623 | !--------------------------------------------------------------------- |
---|
1624 | IF (printlev >= 3) WRITE(numout,*) 'Entering writerestart' |
---|
1625 | !- |
---|
1626 | ! 1 string definitions |
---|
1627 | !- |
---|
1628 | DO l=1,nlitt |
---|
1629 | IF (l == imetabolic) THEN |
---|
1630 | litter_str(l) = 'met' |
---|
1631 | ELSEIF (l == istructural) THEN |
---|
1632 | litter_str(l) = 'str' |
---|
1633 | ELSE |
---|
1634 | CALL ipslerr_p(3,'stomate_io writerestart','Define litter_str','','') |
---|
1635 | ENDIF |
---|
1636 | ENDDO |
---|
1637 | !- |
---|
1638 | DO l=1,nlevs |
---|
1639 | IF (l == iabove) THEN |
---|
1640 | level_str(l) = 'ab' |
---|
1641 | ELSEIF (l == ibelow) THEN |
---|
1642 | level_str(l) = 'be' |
---|
1643 | ELSE |
---|
1644 | CALL ipslerr_p(3,'stomate_io writerestart','Define level_str','','') |
---|
1645 | ENDIF |
---|
1646 | ENDDO |
---|
1647 | !- |
---|
1648 | DO l=1,nelements |
---|
1649 | IF (l == icarbon) THEN |
---|
1650 | element_str(l) = '' |
---|
1651 | !!$ ELSEIF (l == initrogen) THEN |
---|
1652 | !!$ element_str(l) = '_n' |
---|
1653 | ELSE |
---|
1654 | CALL ipslerr_p(3,'stomate_io writerestart','Define element_str','','') |
---|
1655 | ENDIF |
---|
1656 | ENDDO |
---|
1657 | !- |
---|
1658 | pools_str(1:nbpools) =(/'str_ab','str_be','met_ab','met_be','actif ','slow ','passif'/) |
---|
1659 | !- |
---|
1660 | IF (is_root_prc) THEN |
---|
1661 | CALL ioconf_setatt_p ('UNITS','-') |
---|
1662 | CALL ioconf_setatt_p ('LONG_NAME',' ') |
---|
1663 | ENDIF |
---|
1664 | !- |
---|
1665 | ! 2 run control |
---|
1666 | !- |
---|
1667 | ! 2.2 time step of STOMATE in days |
---|
1668 | !- |
---|
1669 | IF (is_root_prc) THEN |
---|
1670 | var_name = 'dt_days' |
---|
1671 | xtmp(1) = dt_days |
---|
1672 | CALL restput (rest_id_stomate, var_name, 1, 1, 1, itime, xtmp) |
---|
1673 | ENDIF |
---|
1674 | !- |
---|
1675 | ! 2.3 date |
---|
1676 | !- |
---|
1677 | IF (is_root_prc) THEN |
---|
1678 | var_name = 'date' |
---|
1679 | date_real = REAL(date_loc,r_std) |
---|
1680 | xtmp(1) = date_real |
---|
1681 | CALL restput (rest_id_stomate, var_name, 1, 1, 1, itime, xtmp) |
---|
1682 | ENDIF |
---|
1683 | !- |
---|
1684 | ! 3 daily meteorological variables |
---|
1685 | !- |
---|
1686 | var_name = 'moiavail_daily' |
---|
1687 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1688 | & moiavail_daily, 'scatter', nbp_glo, index_g) |
---|
1689 | !- |
---|
1690 | var_name = 'gdd_init_date' |
---|
1691 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 2, 1, itime, & |
---|
1692 | & gdd_init_date, 'scatter', nbp_glo, index_g) |
---|
1693 | !- |
---|
1694 | var_name = 'litterhum_daily' |
---|
1695 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1696 | & litterhum_daily, 'scatter', nbp_glo, index_g) |
---|
1697 | !- |
---|
1698 | var_name = 't2m_daily' |
---|
1699 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1700 | & t2m_daily, 'scatter', nbp_glo, index_g) |
---|
1701 | !- |
---|
1702 | var_name = 't2m_min_daily' |
---|
1703 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1704 | & t2m_min_daily, 'scatter', nbp_glo, index_g) |
---|
1705 | !- |
---|
1706 | var_name = 'tsurf_daily' |
---|
1707 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1708 | & tsurf_daily, 'scatter', nbp_glo, index_g) |
---|
1709 | !- |
---|
1710 | var_name = 'tsoil_daily' |
---|
1711 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, & |
---|
1712 | & tsoil_daily, 'scatter', nbp_glo, index_g) |
---|
1713 | !- |
---|
1714 | var_name = 'soilhum_daily' |
---|
1715 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, & |
---|
1716 | & soilhum_daily, 'scatter', nbp_glo, index_g) |
---|
1717 | !- |
---|
1718 | var_name = 'precip_daily' |
---|
1719 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1720 | & precip_daily, 'scatter', nbp_glo, index_g) |
---|
1721 | !- |
---|
1722 | ! 4 productivities |
---|
1723 | !- |
---|
1724 | var_name = 'gpp_daily' |
---|
1725 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1726 | & gpp_daily, 'scatter', nbp_glo, index_g) |
---|
1727 | !- |
---|
1728 | var_name = 'npp_daily' |
---|
1729 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1730 | & npp_daily, 'scatter', nbp_glo, index_g) |
---|
1731 | !- |
---|
1732 | DO l = 1,nelements |
---|
1733 | DO k = 1,nparts |
---|
1734 | WRITE(part_str,'(I2)') k |
---|
1735 | IF (k < 10) part_str(1:1) = '0' |
---|
1736 | var_name = 'turnover_daily_'//part_str(1:LEN_TRIM(part_str))//element_str(l) |
---|
1737 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1738 | & turnover_daily(:,:,k,l), 'scatter', nbp_glo, index_g) |
---|
1739 | ENDDO |
---|
1740 | END DO |
---|
1741 | !- |
---|
1742 | ! 5 monthly meteorological variables |
---|
1743 | !- |
---|
1744 | var_name = 'moiavail_month' |
---|
1745 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1746 | & moiavail_month, 'scatter', nbp_glo, index_g) |
---|
1747 | !- |
---|
1748 | var_name = 'moiavail_week' |
---|
1749 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1750 | & moiavail_week, 'scatter', nbp_glo, index_g) |
---|
1751 | !- |
---|
1752 | var_name = 't2m_longterm' |
---|
1753 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1754 | & t2m_longterm, 'scatter', nbp_glo, index_g) |
---|
1755 | |
---|
1756 | IF (is_root_prc) THEN |
---|
1757 | var_name='tau_longterm' |
---|
1758 | vartmp(1)=tau_longterm |
---|
1759 | CALL restput (rest_id_stomate, var_name, 1, 1, 1, itime, vartmp) |
---|
1760 | ENDIF |
---|
1761 | |
---|
1762 | |
---|
1763 | var_name = 't2m_month' |
---|
1764 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1765 | t2m_month, 'scatter', nbp_glo, index_g) |
---|
1766 | |
---|
1767 | |
---|
1768 | CALL restput_p (rest_id_stomate, 'Tseason', nbp_glo, 1, 1, itime, & |
---|
1769 | Tseason, 'scatter', nbp_glo, index_g) |
---|
1770 | |
---|
1771 | CALL restput_p (rest_id_stomate, 'Tseason_length', nbp_glo, 1, 1, itime, & |
---|
1772 | Tseason_length, 'scatter', nbp_glo, index_g) |
---|
1773 | |
---|
1774 | CALL restput_p (rest_id_stomate, 'Tseason_tmp', nbp_glo, 1, 1, itime, & |
---|
1775 | Tseason_tmp, 'scatter', nbp_glo, index_g) |
---|
1776 | |
---|
1777 | CALL restput_p (rest_id_stomate, 'Tmin_spring_time', nbp_glo, nvm, 1, itime, & |
---|
1778 | Tmin_spring_time, 'scatter', nbp_glo, index_g) |
---|
1779 | |
---|
1780 | CALL restput_p (rest_id_stomate, 'onset_date', nbp_glo, nvm, 1, itime, & |
---|
1781 | onset_date(:,:), 'scatter', nbp_glo, index_g) |
---|
1782 | |
---|
1783 | var_name = 't2m_week' |
---|
1784 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1785 | & t2m_week, 'scatter', nbp_glo, index_g) |
---|
1786 | !- |
---|
1787 | var_name = 'tsoil_month' |
---|
1788 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, & |
---|
1789 | & tsoil_month, 'scatter', nbp_glo, index_g) |
---|
1790 | !- |
---|
1791 | var_name = 'soilhum_month' |
---|
1792 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, & |
---|
1793 | & soilhum_month, 'scatter', nbp_glo, index_g) |
---|
1794 | !- |
---|
1795 | ! 6 fire probability |
---|
1796 | !- |
---|
1797 | var_name = 'fireindex' |
---|
1798 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1799 | & fireindex, 'scatter', nbp_glo, index_g) |
---|
1800 | !- |
---|
1801 | var_name = 'firelitter' |
---|
1802 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1803 | & firelitter, 'scatter', nbp_glo, index_g) |
---|
1804 | !- |
---|
1805 | ! 7 maximum and minimum moisture availabilities for tropic phenology |
---|
1806 | !- |
---|
1807 | var_name = 'maxmoistr_last' |
---|
1808 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1809 | & maxmoiavail_lastyear, 'scatter', nbp_glo, index_g) |
---|
1810 | !- |
---|
1811 | var_name = 'maxmoistr_this' |
---|
1812 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1813 | & maxmoiavail_thisyear, 'scatter', nbp_glo, index_g) |
---|
1814 | !- |
---|
1815 | var_name = 'minmoistr_last' |
---|
1816 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1817 | & minmoiavail_lastyear, 'scatter', nbp_glo, index_g) |
---|
1818 | !- |
---|
1819 | var_name = 'minmoistr_this' |
---|
1820 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1821 | & minmoiavail_thisyear, 'scatter', nbp_glo, index_g) |
---|
1822 | !- |
---|
1823 | ! 8 maximum "weekly" GPP |
---|
1824 | !- |
---|
1825 | var_name = 'maxgppweek_lastyear' |
---|
1826 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1827 | & maxgppweek_lastyear, 'scatter', nbp_glo, index_g) |
---|
1828 | !- |
---|
1829 | var_name = 'maxgppweek_thisyear' |
---|
1830 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1831 | & maxgppweek_thisyear, 'scatter', nbp_glo, index_g) |
---|
1832 | !- |
---|
1833 | ! 9 annual GDD0 |
---|
1834 | !- |
---|
1835 | var_name = 'gdd0_thisyear' |
---|
1836 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1837 | & gdd0_thisyear, 'scatter', nbp_glo, index_g) |
---|
1838 | !- |
---|
1839 | var_name = 'gdd0_lastyear' |
---|
1840 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1841 | & gdd0_lastyear, 'scatter', nbp_glo, index_g) |
---|
1842 | !- |
---|
1843 | ! 10 annual precipitation |
---|
1844 | !- |
---|
1845 | var_name = 'precip_thisyear' |
---|
1846 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1847 | & precip_thisyear, 'scatter', nbp_glo, index_g) |
---|
1848 | !- |
---|
1849 | var_name = 'precip_lastyear' |
---|
1850 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
1851 | & precip_lastyear, 'scatter', nbp_glo, index_g) |
---|
1852 | !- |
---|
1853 | ! 11 derived "biometeorological" variables |
---|
1854 | !- |
---|
1855 | var_name = 'gdd_m5_dormance' |
---|
1856 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1857 | & gdd_m5_dormance, 'scatter', nbp_glo, index_g) |
---|
1858 | !- |
---|
1859 | var_name = 'gdd_from_growthinit' |
---|
1860 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1861 | & gdd_from_growthinit, 'scatter', nbp_glo, index_g) |
---|
1862 | !- |
---|
1863 | var_name = 'gdd_midwinter' |
---|
1864 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1865 | & gdd_midwinter, 'scatter', nbp_glo, index_g) |
---|
1866 | !- |
---|
1867 | var_name = 'ncd_dormance' |
---|
1868 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1869 | & ncd_dormance, 'scatter', nbp_glo, index_g) |
---|
1870 | !- |
---|
1871 | var_name = 'ngd_minus5' |
---|
1872 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1873 | & ngd_minus5, 'scatter', nbp_glo, index_g) |
---|
1874 | !- |
---|
1875 | var_name = 'time_hum_min' |
---|
1876 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1877 | & time_hum_min, 'scatter', nbp_glo, index_g) |
---|
1878 | !- |
---|
1879 | var_name = 'hum_min_dormance' |
---|
1880 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1881 | & hum_min_dormance, 'scatter', nbp_glo, index_g) |
---|
1882 | !- |
---|
1883 | ! 12 Plant status |
---|
1884 | !- |
---|
1885 | var_name = 'PFTpresent' |
---|
1886 | WHERE ( PFTpresent(:,:) ) |
---|
1887 | PFTpresent_real = un |
---|
1888 | ELSEWHERE |
---|
1889 | PFTpresent_real = zero |
---|
1890 | ENDWHERE |
---|
1891 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1892 | & PFTpresent_real, 'scatter', nbp_glo, index_g) |
---|
1893 | !- |
---|
1894 | var_name = 'ind' |
---|
1895 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1896 | & ind, 'scatter', nbp_glo, index_g) |
---|
1897 | !- |
---|
1898 | var_name = 'turnover_time' |
---|
1899 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1900 | & turnover_time, 'scatter', nbp_glo, index_g) |
---|
1901 | !- |
---|
1902 | var_name = 'adapted' |
---|
1903 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1904 | & adapted, 'scatter', nbp_glo, index_g) |
---|
1905 | !- |
---|
1906 | var_name = 'regenerate' |
---|
1907 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1908 | & regenerate, 'scatter', nbp_glo, index_g) |
---|
1909 | !- |
---|
1910 | var_name = 'npp_longterm' |
---|
1911 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1912 | & npp_longterm, 'scatter', nbp_glo, index_g) |
---|
1913 | !- |
---|
1914 | var_name = 'lm_lastyearmax' |
---|
1915 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1916 | & lm_lastyearmax, 'scatter', nbp_glo, index_g) |
---|
1917 | !- |
---|
1918 | var_name = 'lm_thisyearmax' |
---|
1919 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1920 | & lm_thisyearmax, 'scatter', nbp_glo, index_g) |
---|
1921 | !- |
---|
1922 | var_name = 'maxfpc_lastyear' |
---|
1923 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1924 | & maxfpc_lastyear, 'scatter', nbp_glo, index_g) |
---|
1925 | !- |
---|
1926 | var_name = 'maxfpc_thisyear' |
---|
1927 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1928 | & maxfpc_thisyear, 'scatter', nbp_glo, index_g) |
---|
1929 | !- |
---|
1930 | DO l = 1,nelements |
---|
1931 | DO k = 1,nparts |
---|
1932 | WRITE(part_str,'(I2)') k |
---|
1933 | IF (k < 10) part_str(1:1) = '0' |
---|
1934 | var_name = 'turnover_longterm_'//part_str(1:LEN_TRIM(part_str))//element_str(l) |
---|
1935 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1936 | & turnover_longterm(:,:,k,l), 'scatter', nbp_glo, index_g) |
---|
1937 | ENDDO |
---|
1938 | END DO |
---|
1939 | !- |
---|
1940 | var_name = 'gpp_week' |
---|
1941 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1942 | & gpp_week, 'scatter', nbp_glo, index_g) |
---|
1943 | !- |
---|
1944 | DO l = 1,nelements |
---|
1945 | DO k = 1,nparts |
---|
1946 | WRITE(part_str,'(I2)') k |
---|
1947 | IF (k < 10) part_str(1:1) = '0' |
---|
1948 | var_name = 'biomass_'//part_str(1:LEN_TRIM(part_str))//element_str(l) |
---|
1949 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1950 | & biomass(:,:,k,l), 'scatter', nbp_glo, index_g) |
---|
1951 | ENDDO |
---|
1952 | END DO |
---|
1953 | !- |
---|
1954 | DO k=1,nparts |
---|
1955 | WRITE(part_str,'(I2)') k |
---|
1956 | IF (k < 10) part_str(1:1) = '0' |
---|
1957 | var_name = 'maint_resp_'//part_str(1:LEN_TRIM(part_str)) |
---|
1958 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1959 | & resp_maint_part(:,:,k), 'scatter', nbp_glo, index_g) |
---|
1960 | ENDDO |
---|
1961 | !- |
---|
1962 | DO m=1,nleafages |
---|
1963 | WRITE(part_str,'(I2)') m |
---|
1964 | IF (m < 10) part_str(1:1) = '0' |
---|
1965 | var_name = 'leaf_age_'//part_str(1:LEN_TRIM(part_str)) |
---|
1966 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1967 | & leaf_age(:,:,m), 'scatter', nbp_glo, index_g) |
---|
1968 | ENDDO |
---|
1969 | !- |
---|
1970 | DO m=1,nleafages |
---|
1971 | WRITE(part_str,'(I2)') m |
---|
1972 | IF (m < 10) part_str(1:1) = '0' |
---|
1973 | var_name = 'leaf_frac_'//part_str(1:LEN_TRIM(part_str)) |
---|
1974 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1975 | & leaf_frac(:,:,m), 'scatter', nbp_glo, index_g) |
---|
1976 | ENDDO |
---|
1977 | !- |
---|
1978 | var_name = 'senescence' |
---|
1979 | WHERE ( senescence(:,:) ) |
---|
1980 | senescence_real = un |
---|
1981 | ELSEWHERE |
---|
1982 | senescence_real = zero |
---|
1983 | ENDWHERE |
---|
1984 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1985 | & senescence_real, 'scatter', nbp_glo, index_g) |
---|
1986 | |
---|
1987 | ! Transform the logical variable begin_leaves to real before writing to restart file |
---|
1988 | WHERE ( begin_leaves(:,:) ) |
---|
1989 | begin_leaves_real = un |
---|
1990 | ELSEWHERE |
---|
1991 | begin_leaves_real = zero |
---|
1992 | ENDWHERE |
---|
1993 | CALL restput_p (rest_id_stomate, 'begin_leaves', nbp_glo, nvm, 1, itime, & |
---|
1994 | begin_leaves_real, 'scatter', nbp_glo, index_g) |
---|
1995 | |
---|
1996 | |
---|
1997 | var_name = 'when_growthinit' |
---|
1998 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
1999 | & when_growthinit, 'scatter', nbp_glo, index_g) |
---|
2000 | !- |
---|
2001 | var_name = 'age' |
---|
2002 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
2003 | & age, 'scatter', nbp_glo, index_g) |
---|
2004 | !- |
---|
2005 | ! 13 CO2 |
---|
2006 | !- |
---|
2007 | var_name = 'resp_hetero' |
---|
2008 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2009 | & resp_hetero, 'scatter', nbp_glo, index_g) |
---|
2010 | !- |
---|
2011 | var_name = 'resp_maint' |
---|
2012 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2013 | & resp_maint, 'scatter', nbp_glo, index_g) |
---|
2014 | !- |
---|
2015 | var_name = 'resp_growth' |
---|
2016 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2017 | & resp_growth, 'scatter', nbp_glo, index_g) |
---|
2018 | !- |
---|
2019 | var_name = 'co2_fire' |
---|
2020 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2021 | & co2_fire, 'scatter', nbp_glo, index_g) |
---|
2022 | !- |
---|
2023 | var_name = 'co2_to_bm_dgvm' |
---|
2024 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2025 | & co2_to_bm_dgvm, 'scatter', nbp_glo, index_g) |
---|
2026 | !- |
---|
2027 | var_name = 'co2_to_bm_radia' |
---|
2028 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2029 | & co2_to_bm_radia, 'scatter', nbp_glo, index_g) |
---|
2030 | !- |
---|
2031 | ! 14 vegetation distribution after last light competition |
---|
2032 | !- |
---|
2033 | var_name = 'veget_lastlight' |
---|
2034 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2035 | & veget_lastlight, 'scatter', nbp_glo, index_g) |
---|
2036 | !- |
---|
2037 | ! 15 establishment criteria |
---|
2038 | !- |
---|
2039 | var_name = 'everywhere' |
---|
2040 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2041 | & everywhere, 'scatter', nbp_glo, index_g) |
---|
2042 | !- |
---|
2043 | var_name = 'need_adjacent' |
---|
2044 | WHERE (need_adjacent(:,:)) |
---|
2045 | need_adjacent_real = un |
---|
2046 | ELSEWHERE |
---|
2047 | need_adjacent_real = zero |
---|
2048 | ENDWHERE |
---|
2049 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2050 | & need_adjacent_real, 'scatter', nbp_glo, index_g) |
---|
2051 | !- |
---|
2052 | var_name = 'RIP_time' |
---|
2053 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2054 | & RIP_time, 'scatter', nbp_glo, index_g) |
---|
2055 | !- |
---|
2056 | ! 17 litter |
---|
2057 | !- |
---|
2058 | DO l=1,nlitt |
---|
2059 | var_name = 'litterpart_'//litter_str(l) |
---|
2060 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2061 | & litterpart(:,:,l), 'scatter', nbp_glo, index_g) |
---|
2062 | ENDDO |
---|
2063 | !- |
---|
2064 | DO k = 1,nelements |
---|
2065 | DO l = 1,nlevs |
---|
2066 | DO m = 1,nvm |
---|
2067 | WRITE (part_str, '(I2)') m |
---|
2068 | IF (m<10) part_str(1:1)='0' |
---|
2069 | var_name = 'litter_'//part_str(1:LEN_TRIM(part_str))//'_'//level_str(l)//element_str(k) |
---|
2070 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nlitt, 1, itime, & |
---|
2071 | & litter(:,:,m,l,k), 'scatter', nbp_glo, index_g) |
---|
2072 | ENDDO |
---|
2073 | ENDDO |
---|
2074 | END DO |
---|
2075 | !- |
---|
2076 | DO l=1,nlitt |
---|
2077 | var_name = 'dead_leaves_'//litter_str(l) |
---|
2078 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2079 | & dead_leaves(:,:,l), 'scatter', nbp_glo, index_g) |
---|
2080 | ENDDO |
---|
2081 | !- |
---|
2082 | DO m=1,nvm |
---|
2083 | WRITE (part_str, '(I2)') m |
---|
2084 | IF (m<10) part_str(1:1)='0' |
---|
2085 | var_name = 'carbon_'//part_str(1:LEN_TRIM(part_str)) |
---|
2086 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, ncarb, 1, itime, & |
---|
2087 | & carbon(:,:,m), 'scatter', nbp_glo, index_g) |
---|
2088 | ENDDO |
---|
2089 | !- |
---|
2090 | DO l=1,nlevs |
---|
2091 | var_name = 'lignin_struc_'//level_str(l) |
---|
2092 | CALL restput_p & |
---|
2093 | & (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2094 | & lignin_struc(:,:,l), 'scatter', nbp_glo, index_g) |
---|
2095 | ENDDO |
---|
2096 | !- |
---|
2097 | ! 18 land cover change |
---|
2098 | !- |
---|
2099 | var_name = 'co2_flux' |
---|
2100 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2101 | & co2_flux, 'scatter', nbp_glo, index_g) |
---|
2102 | var_name = 'fco2_lu' |
---|
2103 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
2104 | & fco2_lu, 'scatter', nbp_glo, index_g) |
---|
2105 | var_name = 'fco2_wh' |
---|
2106 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
2107 | & fco2_wh, 'scatter', nbp_glo, index_g) |
---|
2108 | var_name = 'fco2_ha' |
---|
2109 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
2110 | & fco2_ha, 'scatter', nbp_glo, index_g) |
---|
2111 | |
---|
2112 | var_name = 'prod10' |
---|
2113 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 11, 1, itime, & |
---|
2114 | & prod10, 'scatter', nbp_glo, index_g) |
---|
2115 | var_name = 'prod100' |
---|
2116 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 101, 1, itime, & |
---|
2117 | & prod100, 'scatter', nbp_glo, index_g) |
---|
2118 | var_name = 'flux10' |
---|
2119 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 10, 1, itime, & |
---|
2120 | & flux10, 'scatter', nbp_glo, index_g) |
---|
2121 | var_name = 'flux100' |
---|
2122 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 100, 1, itime, & |
---|
2123 | & flux100, 'scatter', nbp_glo, index_g) |
---|
2124 | |
---|
2125 | var_name = 'convflux' |
---|
2126 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
2127 | & convflux, 'scatter', nbp_glo, index_g) |
---|
2128 | var_name = 'cflux_prod10' |
---|
2129 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
2130 | & cflux_prod10, 'scatter', nbp_glo, index_g) |
---|
2131 | var_name = 'cflux_prod100' |
---|
2132 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
2133 | & cflux_prod100, 'scatter', nbp_glo, index_g) |
---|
2134 | |
---|
2135 | var_name = 'convfluxpft' |
---|
2136 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
2137 | & convfluxpft, 'scatter', nbp_glo, index_g) |
---|
2138 | |
---|
2139 | var_name = 'fDeforestToProduct' |
---|
2140 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
2141 | & fDeforestToProduct, 'scatter', nbp_glo, index_g) |
---|
2142 | |
---|
2143 | var_name = 'fLulccResidue' |
---|
2144 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
2145 | & fLulccResidue, 'scatter', nbp_glo, index_g) |
---|
2146 | |
---|
2147 | var_name = 'fHarvestToProduct' |
---|
2148 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm , 1, itime, & |
---|
2149 | & fHarvestToProduct, 'scatter', nbp_glo, index_g) |
---|
2150 | |
---|
2151 | !- |
---|
2152 | ! 18-bis wood harvest |
---|
2153 | !- |
---|
2154 | IF (do_wood_harvest) THEN |
---|
2155 | var_name = 'prod10_harvest' |
---|
2156 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 11, 1, itime, & |
---|
2157 | prod10_harvest, 'scatter', nbp_glo, index_g) |
---|
2158 | var_name = 'prod100_harvest' |
---|
2159 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 101, 1, itime, & |
---|
2160 | prod100_harvest, 'scatter', nbp_glo, index_g) |
---|
2161 | var_name = 'flux10_harvest' |
---|
2162 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 10, 1, itime, & |
---|
2163 | flux10_harvest, 'scatter', nbp_glo, index_g) |
---|
2164 | var_name = 'flux100_harvest' |
---|
2165 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 100, 1, itime, & |
---|
2166 | flux100_harvest, 'scatter', nbp_glo, index_g) |
---|
2167 | var_name = 'convflux_harvest' |
---|
2168 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
2169 | convflux_harvest, 'scatter', nbp_glo, index_g) |
---|
2170 | var_name = 'cflux_prod10_harvest' |
---|
2171 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
2172 | cflux_prod10_harvest, 'scatter', nbp_glo, index_g) |
---|
2173 | var_name = 'cfluxprod100_harvest' |
---|
2174 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
2175 | cflux_prod100_harvest, 'scatter', nbp_glo, index_g) |
---|
2176 | var_name = 'woodharvestpft' |
---|
2177 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2178 | woodharvestpft, 'scatter', nbp_glo, index_g) |
---|
2179 | END IF |
---|
2180 | |
---|
2181 | DO l = 1,nelements |
---|
2182 | DO k = 1,nparts |
---|
2183 | WRITE(part_str,'(I2)') k |
---|
2184 | IF (k < 10) part_str(1:1) = '0' |
---|
2185 | var_name = 'bm_to_litter_'//part_str(1:LEN_TRIM(part_str))//element_str(l) |
---|
2186 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2187 | & bm_to_litter(:,:,k,l), 'scatter', nbp_glo, index_g) |
---|
2188 | ENDDO |
---|
2189 | END DO |
---|
2190 | |
---|
2191 | var_name = 'carb_mass_total' |
---|
2192 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
2193 | & carb_mass_total, 'scatter', nbp_glo, index_g) |
---|
2194 | !- |
---|
2195 | ! 19. Spinup |
---|
2196 | !- |
---|
2197 | IF (spinup_analytic) THEN |
---|
2198 | |
---|
2199 | IF (is_root_prc) THEN |
---|
2200 | temp_global_years(1) = REAL(global_years) |
---|
2201 | var_name='Global_years' |
---|
2202 | CALL restput (rest_id_stomate, var_name, 1, 1, 1, itime, temp_global_years) |
---|
2203 | ENDIF |
---|
2204 | |
---|
2205 | var_name = 'nbp_sum' |
---|
2206 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
2207 | & nbp_accu, 'scatter', nbp_glo, index_g) |
---|
2208 | |
---|
2209 | var_name = 'nbp_flux' |
---|
2210 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
2211 | & nbp_flux, 'scatter', nbp_glo, index_g) |
---|
2212 | |
---|
2213 | var_name = 'ok_equilibrium' |
---|
2214 | WHERE(ok_equilibrium(:)) |
---|
2215 | ok_equilibrium_real = un |
---|
2216 | ELSEWHERE |
---|
2217 | ok_equilibrium_real = zero |
---|
2218 | ENDWHERE |
---|
2219 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & |
---|
2220 | & ok_equilibrium_real, 'scatter', nbp_glo, index_g) |
---|
2221 | |
---|
2222 | DO k = 1,nbpools |
---|
2223 | DO j = 1,nbpools |
---|
2224 | WRITE(part_str,'(I2)') k |
---|
2225 | IF (k < 10) part_str(1:1) = '0' |
---|
2226 | var_name = 'MatrixV_'//part_str(1:LEN_TRIM(part_str))//'_'//TRIM(pools_str(j)) |
---|
2227 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2228 | & MatrixV(:,:,k,j), 'scatter', nbp_glo, index_g) |
---|
2229 | ENDDO |
---|
2230 | ENDDO |
---|
2231 | |
---|
2232 | DO k = 1,nbpools |
---|
2233 | WRITE(part_str,'(I2)') k |
---|
2234 | IF (k < 10) part_str(1:1) = '0' |
---|
2235 | var_name = 'Vector_U_'//part_str(1:LEN_TRIM(part_str)) |
---|
2236 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2237 | & VectorU(:,:,k), 'scatter', nbp_glo, index_g) |
---|
2238 | ENDDO |
---|
2239 | |
---|
2240 | DO k = 1,nbpools |
---|
2241 | WRITE(part_str,'(I2)') k |
---|
2242 | IF (k < 10) part_str(1:1) = '0' |
---|
2243 | var_name = 'previous_stock_'//part_str(1:LEN_TRIM(part_str)) |
---|
2244 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2245 | & previous_stock(:,:,k), 'scatter', nbp_glo, index_g) |
---|
2246 | ENDDO |
---|
2247 | |
---|
2248 | DO k = 1,nbpools |
---|
2249 | WRITE(part_str,'(I2)') k |
---|
2250 | IF (k < 10) part_str(1:1) = '0' |
---|
2251 | var_name = 'current_stock_'//part_str(1:LEN_TRIM(part_str)) |
---|
2252 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2253 | & current_stock(:,:,k), 'scatter', nbp_glo, index_g) |
---|
2254 | ENDDO |
---|
2255 | |
---|
2256 | ENDIF !(spinup_analytic) |
---|
2257 | |
---|
2258 | |
---|
2259 | DO k = 1,npco2 |
---|
2260 | WRITE(part_str,'(I2)') k |
---|
2261 | IF (k < 10) part_str(1:1) = '0' |
---|
2262 | var_name = 'assim_param_'//part_str(1:LEN_TRIM(part_str)) |
---|
2263 | CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & |
---|
2264 | & assim_param(:,:,k), 'scatter', nbp_glo, index_g) |
---|
2265 | ENDDO |
---|
2266 | |
---|
2267 | |
---|
2268 | IF (printlev >= 4) WRITE(numout,*) 'Leaving writerestart' |
---|
2269 | !-------------------------- |
---|
2270 | END SUBROUTINE writerestart |
---|
2271 | !- |
---|
2272 | !=== |
---|
2273 | !- |
---|
2274 | END MODULE stomate_io |
---|