source: branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/stomate_data.f90 @ 107

Last change on this file since 107 was 107, checked in by didier.solyga, 13 years ago

Put the 2D parameters of stomate in order to have their components updated after the calling to getin

File size: 19.5 KB
Line 
1! defines PFT parameters
2! the geographical coordinates might be used for defining some additional parameters
3! (e.g. frequency of anthropogenic fires, irrigation of agricultural surfaces, etc.)
4!
5! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_stomate/stomate_data.f90,v 1.12 2009/06/24 10:53:17 ssipsl Exp $
6! IPSL (2006)
7!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9MODULE stomate_data
10
11  ! modules used:
12
13  USE constantes
14  USE pft_parameters
15  USE defprec
16 
17
18  IMPLICIT NONE
19
20  ! bare soil in Sechiba
21  INTEGER(i_std),PARAMETER :: ibare_sechiba = 1
22  !-
23  ! 0 = no, 4 = full online diagnostics
24  INTEGER(i_std),SAVE :: bavard=1
25
26
27  ! Move to
28  ! Horizontal indices
29  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:) :: hori_index
30  ! Horizonatal + PFT indices
31  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:) :: horipft_index
32  !-
33  ! Land cover change
34  ! Horizontal + P10 indices
35  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip10_index
36  ! Horizontal + P100 indices
37  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip100_index 
38  ! Horizontal + P11 indices
39  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip11_index
40  ! Horizontal + P101 indices
41  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip101_index 
42  !-
43  ! time step
44  INTEGER(i_std),SAVE :: itime
45  ! STOMATE history file ID
46  INTEGER(i_std),SAVE :: hist_id_stomate
47  ! STOMATE history file ID for IPCC output
48  INTEGER(i_std),SAVE :: hist_id_stomate_IPCC
49  ! STOMATE restart file ID
50  INTEGER(i_std),SAVE :: rest_id_stomate
51
52  ! critical value for being adapted (1-1/e)
53  REAL(r_std),PARAMETER :: adapted_crit = 1. - ( 1. / euler )
54  ! critical value for being regenerative (1/e)
55  REAL(r_std),PARAMETER :: regenerate_crit = 1. / euler
56
57
58  ! private & public routines
59
60  PUBLIC data
61
62CONTAINS
63
64  SUBROUTINE data (npts, lalo)
65
66    !
67    ! 0 declarations
68    !
69
70    ! 0.1 input
71
72    ! Domain size
73    INTEGER(i_std), INTENT(in)                               :: npts
74    ! Geographical coordinates (latitude,longitude)
75    REAL(r_std),DIMENSION (npts,2), INTENT (in)        :: lalo
76
77    ! 0.2 local variables
78
79    ! Index
80    INTEGER(i_std)                                    :: j
81    ! alpha's : ?
82    REAL(r_std)                                        :: alpha
83    ! stem diameter
84    REAL(r_std)                                        :: dia
85    ! Sapling CSA
86    REAL(r_std)                                        :: csa_sap
87
88    ! =========================================================================
89
90!!$    DS :Correction 11/02/2011 : update 2D parameters after the call to getin
91!!$      before the components were updated but not the  parameter itself!
92      !- pheno_gdd_crit
93      pheno_gdd_crit(:,1) = pheno_gdd_crit_c(:)
94      pheno_gdd_crit(:,2) = pheno_gdd_crit_b(:)         
95      pheno_gdd_crit(:,3) = pheno_gdd_crit_a(:) 
96      !
97      !- senescence_temp
98      senescence_temp(:,1) = senescence_temp_c(:)
99      senescence_temp(:,2) = senescence_temp_b(:)
100      senescence_temp(:,3) = senescence_temp_a(:)
101      !
102      !- maint_resp_slope
103      maint_resp_slope(:,1)= maint_resp_slope_c(:)             
104      maint_resp_slope(:,2) = maint_resp_slope_b(:)
105      maint_resp_slope(:,3) = maint_resp_slope_a(:)
106      !
107      !-coeff_maint_zero
108      coeff_maint_zero(:,ileaf) = cm_zero_leaf(:)
109      coeff_maint_zero(:,isapabove) = cm_zero_sapabove(:)
110      coeff_maint_zero(:,isapbelow) = cm_zero_sapbelow(:)
111      coeff_maint_zero(:,iheartabove) = cm_zero_heartabove(:)
112      coeff_maint_zero(:,iheartbelow) = cm_zero_heartbelow(:)
113      coeff_maint_zero(:,iroot) = cm_zero_root(:)
114      coeff_maint_zero(:,ifruit) = cm_zero_fruit(:)
115      coeff_maint_zero(:,icarbres) = cm_zero_carbres(:)
116
117
118    IF ( bavard .GE. 1 ) WRITE(numout,*) 'data: PFT characteristics'
119
120    DO j = 2,nvm
121
122       IF ( bavard .GE. 1 ) WRITE(numout,'(a,i3,a,a)') '    > PFT#',j,': ', PFT_name(j)
123
124       !
125       ! 1 tree?
126       !
127
128       IF ( leaf_tab(j) .LE. 2 ) THEN
129          tree(j) = .TRUE.
130       ELSE
131          tree(j) = .FALSE.
132       ENDIF
133
134       IF ( bavard .GE. 1 ) WRITE(numout,*) '       tree: ', tree(j)
135
136       !
137       ! 2 flamability
138       !
139
140       IF ( bavard .GE. 1 ) WRITE(numout,*) '       litter flamability:', flam(j)
141
142       !
143       ! 3 fire resistance
144       !
145
146       IF ( bavard .GE. 1 ) WRITE(numout,*) '       fire resistance:', resist(j)
147
148       !
149       ! 4 specific leaf area per mass carbon = 2 * sla / dry mass
150       !
151
152       ! SZ: Reich et al, 1992 find no statistically significant differences between broadleaved and coniferous
153       ! forests, specifically, the assumption that grasses grow needles is not justified. Replacing the function
154       ! with the one based on Reich et al. 1997. Given that sla=100cm2/gDW at 9 months, sla is:
155       ! sla=exp(5.615-0.46*ln(leaflon in months))
156       ! Oct 2010 : replaced by values given by N.Viovy
157
158       IF ( bavard .GE. 1 ) WRITE(numout,*) '       specific leaf area (m**2/gC):', sla(j) !, 12./leaflife(j)
159
160       !
161       ! 5 sapling characteristics
162       !
163
164       IF ( tree(j) ) THEN
165
166          ! 5.1 trees
167
168          alpha = alpha_tree
169
170          bm_sapl(j,ileaf) = &
171               ( (bm_sapl_leaf(1)*pipe_tune1 * ( mass_ratio_heart_sap *bm_sapl_leaf(2)*sla(j)/(pi*pipe_k1))**bm_sapl_leaf(3) ) / sla(j) ) ** bm_sapl_leaf(4)
172
173          IF ( pheno_type(j) .NE. 1 ) THEN
174             ! not evergreen
175             bm_sapl(j,icarbres) = bm_sapl_carbres * bm_sapl(j,ileaf)
176          ELSE
177             bm_sapl(j,icarbres) = 0.0
178          ENDIF
179
180          csa_sap = bm_sapl(j,ileaf) / ( pipe_k1 / sla(j) )
181
182          dia = (mass_ratio_heart_sap * csa_sap * dia_coeff(1) / pi ) ** dia_coeff(2)
183
184          bm_sapl(j,isapabove) = &
185               bm_sapl_sapabove * pipe_density * csa_sap * pipe_tune2 * dia ** pipe_tune3
186          bm_sapl(j,isapbelow) = bm_sapl(j,isapabove)
187
188          bm_sapl(j,iheartabove) = bm_sapl_heartabove * bm_sapl(j,isapabove)
189          bm_sapl(j,iheartbelow) = bm_sapl_heartbelow * bm_sapl(j,isapbelow)
190
191       ELSE
192
193          ! 5.2 grasses
194
195          alpha = alpha_grass
196
197          IF ( natural(j) ) THEN
198             bm_sapl(j,ileaf) = init_sapl_mass_leaf_nat / sla(j)
199          ELSE
200             bm_sapl(j,ileaf) = init_sapl_mass_leaf_agri / sla(j)
201          ENDIF
202
203          bm_sapl(j,icarbres) = init_sapl_mass_carbres *bm_sapl(j,ileaf)
204
205          bm_sapl(j,isapabove) = 0.
206          bm_sapl(j,isapbelow) = 0.
207
208          bm_sapl(j,iheartabove) = 0.
209          bm_sapl(j,iheartbelow) = 0.
210
211       ENDIF
212
213       bm_sapl(j,iroot) = init_sapl_mass_carbres * (1./alpha) * bm_sapl(j,ileaf)
214
215       bm_sapl(j,ifruit) = init_sapl_mass_fruit  * bm_sapl(j,ileaf)
216
217       IF ( bavard .GE. 1 ) THEN
218          WRITE(numout,*) '       sapling biomass (gC):'
219          WRITE(numout,*) '         leaves:',bm_sapl(j,ileaf)
220          WRITE(numout,*) '         sap above ground:',bm_sapl(j,isapabove)
221          WRITE(numout,*) '         sap below ground:',bm_sapl(j,isapbelow)
222          WRITE(numout,*) '         heartwood above ground:',bm_sapl(j,iheartabove)
223          WRITE(numout,*) '         heartwood below ground:',bm_sapl(j,iheartbelow)
224          WRITE(numout,*) '         roots:',bm_sapl(j,iroot)
225          WRITE(numout,*) '         fruits:',bm_sapl(j,ifruit)
226          WRITE(numout,*) '         carbohydrate reserve:',bm_sapl(j,icarbres)
227       ENDIF
228
229       !
230       ! 6 migration speed (m/year)
231       !
232
233       IF ( tree(j) ) THEN
234
235          migrate(j) = migrate_tree
236
237       ELSE
238
239          ! can be any value as grasses are, per definitionem, everywhere (big leaf).
240          migrate(j) = migrate_grass
241
242       ENDIF
243
244       IF ( bavard .GE. 1 ) WRITE(numout,*) '       migration speed (m/year):', migrate(j)
245
246       !
247       ! 7 critical stem diameter: beyond this diameter, the crown area no longer
248       !     increases
249       !
250
251       IF ( tree(j) ) THEN
252
253          maxdia(j) = ( ( pipe_tune4 / ((pipe_tune2*pipe_tune3)/(maxdia_coeff(1)**pipe_tune3)) ) &
254               ** ( 1. / ( pipe_tune3 - 1. ) ) ) * maxdia_coeff(2)
255          cn_sapl(j) = cn_sapl_init !crown of individual tree, first year
256
257       ELSE
258
259          maxdia(j) = undef
260          cn_sapl(j)=1
261
262       ENDIF
263
264       IF ( bavard .GE. 1 ) WRITE(numout,*) '       critical stem diameter (m):', maxdia(j)
265
266       !
267       ! 8 Coldest tolerable temperature
268       !
269
270       IF ( ABS( tmin_crit(j) - undef ) .GT. min_stomate ) THEN
271          tmin_crit(j) = tmin_crit(j) + ZeroCelsius
272       ELSE
273          tmin_crit(j) = undef
274       ENDIF
275
276       IF ( bavard .GE. 1 ) &
277            WRITE(numout,*) '       coldest tolerable temperature (K):', tmin_crit(j)
278
279       !
280       ! 9 Maximum temperature of the coldest month: need to be below this temperature
281       !      for a certain time to regrow leaves next spring
282       !
283
284       IF ( ABS ( tcm_crit(j) - undef ) .GT. min_stomate ) THEN
285          tcm_crit(j) = tcm_crit(j) + ZeroCelsius
286       ELSE
287          tcm_crit(j) = undef
288       ENDIF
289
290       IF ( bavard .GE. 1 ) &
291            WRITE(numout,*) '       vernalization temperature (K):', tcm_crit(j)
292
293       !
294       ! 10 critical values for phenology
295       !
296
297       ! 10.1 model used
298
299       IF ( bavard .GE. 1 ) &
300            WRITE(numout,*) '       phenology model used: ',pheno_model(j)
301
302       ! 10.2 growing degree days. What kind of gdd is meant (i.e. threshold 0 or -5 deg C
303       !        or whatever), depends on how this is used in stomate_phenology.
304
305
306       IF ( ( bavard .GE. 1 ) .AND. ( ALL(pheno_gdd_crit(j,:) .NE. undef) ) ) THEN
307          WRITE(numout,*) '         critical GDD is a function of long term T (C):'
308          WRITE(numout,*) '          ',pheno_gdd_crit(j,1), &
309               ' + T *',pheno_gdd_crit(j,2), &
310               ' + T^2 *',pheno_gdd_crit(j,3)
311       ENDIF
312
313       ! consistency check
314
315       IF ( ( ( pheno_model(j) .EQ. 'moigdd' ) .OR. &
316            ( pheno_model(j) .EQ. 'humgdd' )       ) .AND. &
317            ( ANY(pheno_gdd_crit(j,:) .EQ. undef) )                      ) THEN
318         STOP 'problem with phenology parameters, critical GDD.'
319       ENDIF
320
321       ! 10.3 number of growing days
322
323       IF ( ( bavard .GE. 1 ) .AND. ( ngd_crit(j) .NE. undef ) ) &
324            WRITE(numout,*) '         critical NGD:', ngd_crit(j)
325
326       ! 10.4 critical temperature for ncd vs. gdd function in phenology
327
328       IF ( ( bavard .GE. 1 ) .AND. ( ncdgdd_temp(j) .NE. undef ) ) &
329            WRITE(numout,*) '         critical temperature for NCD vs. GDD (C):', &
330            ncdgdd_temp(j)
331
332       ! 10.5 humidity fractions
333
334       IF ( ( bavard .GE. 1 ) .AND. ( hum_frac(j) .NE. undef ) ) &
335            WRITE(numout,*) '         critical humidity fraction:', hum_frac(j)
336
337       ! 10.6 minimum time during which there was no photosynthesis
338
339       IF ( ( bavard .GE. 1 ) .AND. ( lowgpp_time(j) .NE. undef ) ) &
340            WRITE(numout,*) '         minimum dormance duration (d):',lowgpp_time(j)
341
342       ! 10.7 minimum time elapsed since moisture minimum (d)
343
344       IF ( ( bavard .GE. 1 ) .AND. ( hum_min_time(j) .NE. undef ) ) &
345            WRITE(numout,*) '         time to wait after moisture min (d):', hum_min_time(j)
346
347       !
348       ! 11 critical values for senescence
349       !
350
351       ! 11.1 type of senescence
352
353
354       IF ( bavard .GE. 1 ) &
355            WRITE(numout,*) '       type of senescence: ',senescence_type(j)
356
357       ! 11.2 critical temperature for senescence
358
359       IF ( ( bavard .GE. 1 ) .AND. ( ALL(senescence_temp(j,:) .NE. undef) ) ) THEN
360          WRITE(numout,*) '         critical temperature for senescence (C) is'
361          WRITE(numout,*) '          a function of long term T (C):'
362          WRITE(numout,*) '          ',senescence_temp(j,1), &
363               ' + T *',senescence_temp(j,2), &
364               ' + T^2 *',senescence_temp(j,3)
365       ENDIF
366
367       ! consistency check
368
369       IF ( ( ( senescence_type(j) .EQ. 'cold' ) .OR. &
370            ( senescence_type(j) .EQ. 'mixed' )      ) .AND. &
371            ( ANY(senescence_temp(j,:) .EQ. undef ) )           ) THEN
372          STOP 'problem with senescence parameters, temperature.'
373       ENDIF
374
375       ! 11.3 critical relative moisture availability for senescence
376
377       IF ( ( bavard .GE. 1 ) .AND. ( senescence_hum(j) .NE. undef ) ) &
378            WRITE(numout,*) '         max. critical relative moisture availability for senescence:', &
379            senescence_hum(j)
380
381       ! consistency check
382
383       IF ( ( ( senescence_type(j) .EQ. 'dry' ) .OR. &
384            ( senescence_type(j) .EQ. 'mixed' )     ) .AND. &
385            ( senescence_hum(j) .EQ. undef )                   ) THEN
386          STOP 'problem with senescence parameters, humidity.'
387       ENDIF
388
389       ! 14.3 relative moisture availability above which there is no moisture-related
390       !      senescence
391
392       IF ( ( bavard .GE. 1 ) .AND. ( nosenescence_hum(j) .NE. undef ) ) &
393            WRITE(numout,*) '         relative moisture availability above which there is'
394       WRITE(numout,*) '             no moisture-related senescence:', &
395            nosenescence_hum(j)
396
397       ! consistency check
398
399       IF ( ( ( senescence_type(j) .EQ. 'dry' ) .OR. &
400            ( senescence_type(j) .EQ. 'mixed' )     ) .AND. &
401            ( nosenescence_hum(j) .EQ. undef )                   ) THEN
402          STOP 'problem with senescence parameters, humidity.'
403       ENDIF
404
405       !
406       ! 12 sapwood -> heartwood conversion time
407       !
408
409       IF ( bavard .GE. 1 ) &
410            WRITE(numout,*) '       sapwood -> heartwood conversion time (d):', tau_sap(j)
411
412       !
413       ! 13 fruit lifetime
414       !
415
416       IF ( bavard .GE. 1 ) WRITE(numout,*) '       fruit lifetime (d):', tau_fruit(j)
417
418       !
419       ! 14 length of leaf death
420       !      For evergreen trees, this variable determines the lifetime of the leaves.
421       !      Note that it is different from the value given in leaflife_tab.
422       !
423
424       IF ( bavard .GE. 1 ) &
425            WRITE(numout,*) '       length of leaf death (d):', leaffall(j)
426
427       !
428       ! 15 maximum lifetime of leaves
429       !
430
431       IF ( ( bavard .GE. 1 ) .AND. ( leafagecrit(j) .NE. undef ) ) &
432            WRITE(numout,*) '       critical leaf age (d):', leafagecrit(j)
433
434       !
435       ! 16 time constant for leaf age discretisation (d)
436       !
437
438       leaf_timecst(j) = leafagecrit(j) / REAL( nleafages,r_std )
439
440       IF ( bavard .GE. 1 ) &
441            WRITE(numout,*) '       time constant for leaf age discretisation (d):', &
442            leaf_timecst(j)
443
444       !
445       ! 17 minimum lai, initial
446       !
447
448       IF ( tree(j) ) THEN
449          lai_initmin(j) = 0.3
450       ELSE
451          lai_initmin(j) = 0.1
452       ENDIF
453
454       IF ( bavard .GE. 1 ) &
455            WRITE(numout,*) '       initial LAI:', lai_initmin(j)
456
457       !
458       ! 19 maximum LAI
459       !
460
461       IF ( bavard .GE. 1 ) &
462            WRITE(numout,*) '       critical LAI above which no leaf allocation:', lai_max(j)
463
464       !
465       ! 20 fraction of primary leaf and root allocation put into reserve
466       !
467
468       IF ( bavard .GE. 1 ) &
469            WRITE(numout,*) '       reserve allocation factor:', ecureuil(j)
470
471       !
472       ! 21 maintenance respiration coefficient (g/g/day) at 0 deg C
473       !
474
475       IF ( bavard .GE. 1 ) THEN
476
477          WRITE(numout,*) '       maintenance respiration coefficient (g/g/day) at 0 deg C:'
478          WRITE(numout,*) '         . leaves: ',coeff_maint_zero(j,ileaf)
479          WRITE(numout,*) '         . sapwood above ground: ',coeff_maint_zero(j,isapabove)
480          WRITE(numout,*) '         . sapwood below ground: ',coeff_maint_zero(j,isapbelow)
481          WRITE(numout,*) '         . heartwood above ground: ',coeff_maint_zero(j,iheartabove)
482          WRITE(numout,*) '         . heartwood below ground: ',coeff_maint_zero(j,iheartbelow)
483          WRITE(numout,*) '         . roots: ',coeff_maint_zero(j,iroot)
484          WRITE(numout,*) '         . fruits: ',coeff_maint_zero(j,ifruit)
485          WRITE(numout,*) '         . carbohydrate reserve: ',coeff_maint_zero(j,icarbres)
486
487       ENDIF
488
489       !
490       ! 22 parameter for temperature sensitivity of maintenance respiration
491       !
492
493       IF ( bavard .GE. 1 ) &
494            WRITE(numout,*) '       temperature sensitivity of maintenance respiration (1/K) is'
495       WRITE(numout,*) '          a function of long term T (C):'
496       WRITE(numout,*) '          ',maint_resp_slope(j,1),' + T *',maint_resp_slope(j,2), &
497            ' + T^2 *',maint_resp_slope(j,3)
498
499       !
500       ! 23 natural ?
501       !
502
503       IF ( bavard .GE. 1 ) &
504            WRITE(numout,*) '       Natural:', natural(j)
505
506       !
507       ! 24 Vcmax et Vjmax
508       !
509
510       IF ( bavard .GE. 1 ) &
511            WRITE(numout,*) '       Maximum rate of carboxylation:', vcmax_opt(j)
512
513       IF ( bavard .GE. 1 ) &
514            WRITE(numout,*) '       Maximum rate of RUbp regeneration:', vjmax_opt(j)
515
516       !
517       ! 25 constants for photosynthesis temperatures
518       !
519
520
521       IF ( bavard .GE. 1 ) THEN
522          WRITE(numout,*) '       min. temperature for photosynthesis as a function of long term T (C):'
523          WRITE(numout,*) '          ',tphoto_min_c(j), &
524               ' + T*',tphoto_min_b(j), &
525               ' + T^2*',tphoto_min_a(j)
526          WRITE(numout,*) '       opt. temperature for photosynthesis as a function of long term T (C):'
527          WRITE(numout,*) '          ',tphoto_opt_c(j), &
528               ' + T*',tphoto_opt_b(j), &
529               ' + T^2*',tphoto_opt_a(j)
530          WRITE(numout,*) '       max. temperature for photosynthesis as a function of long term T (C):'
531          WRITE(numout,*) '          ',tphoto_max_c(j), &
532               ' + T*',tphoto_max_b(j), &
533               ' + T^2*',tphoto_max_a(j)
534
535
536          !
537          ! 26 Properties
538          !
539
540          WRITE(numout,*) '       Slope of the gs/A relation:', gsslope(j)
541          WRITE(numout,*) '       Intercept of the gs/A relation:', gsoffset(j)
542          WRITE(numout,*) '       C4 photosynthesis:', is_c4(j)
543          WRITE(numout,*) '       Depth constant for root profile (m):', 1./humcste(j)
544
545       ENDIF
546
547       !
548       ! 27 extinction coefficient of the Monsi&Seaki (53) relationship
549       !
550
551
552       IF ( bavard .GE. 1 ) THEN
553          WRITE(numout,*) '       extinction coefficient:', ext_coeff(j)
554       ENDIF
555
556       !
557       ! 28 check coherence between tree definitions
558       !      this is not absolutely necessary (just security)
559       !
560
561       IF ( tree(j) .NEQV. is_tree(j) ) THEN
562          STOP 'Definition of tree/not tree not coherent'
563       ENDIF
564
565    ENDDO
566
567    !
568    ! 29 time scales for phenology and other processes (in days)
569    !
570
571    tau_longterm = coeff_tau_longterm * one_year
572
573    IF ( bavard .GE. 1 ) THEN
574
575       WRITE(numout,*) '   > time scale for ''monthly'' moisture availability (d):', &
576            tau_hum_month
577       WRITE(numout,*) '   > time scale for ''weekly'' moisture availability (d):', &
578           tau_hum_week
579       WRITE(numout,*) '   > time scale for ''monthly'' 2 meter temperature (d):', &
580            tau_t2m_month
581       WRITE(numout,*) '   > time scale for ''weekly'' 2 meter temperature (d):', &
582            tau_t2m_week
583       WRITE(numout,*) '   > time scale for ''weekly'' GPP (d):', &
584            tau_gpp_week
585       WRITE(numout,*) '   > time scale for ''monthly'' soil temperature (d):', &
586            tau_tsoil_month
587       WRITE(numout,*) '   > time scale for ''monthly'' soil humidity (d):', &
588            tau_soilhum_month
589       WRITE(numout,*) '   > time scale for vigour calculations (y):', &
590            tau_longterm / one_year
591
592    ENDIF
593
594    !
595    ! 30 fraction of allocatable biomass which is lost as growth respiration
596    !
597
598    IF ( bavard .GE. 1 ) &
599         WRITE(numout,*) '   > growth respiration fraction:', frac_growthresp
600
601    IF (bavard.GE.4) WRITE(numout,*) 'Leaving data'
602
603  END SUBROUTINE data
604
605END MODULE stomate_data
Note: See TracBrowser for help on using the repository browser.