source: branches/publications/ORCHIDEE_GLUC_r6545/src_sticslai/stress.f90 @ 6737

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

New: CROP module. Done by Xuhui.

File size: 5.4 KB
Line 
1! ml_com !
2! *-----------------------------------------------------------------------------------------------------------------------------------------------------------* c!
3!! This module calculates the water stress indices, swfac and turfac.
4!> - Stics book paragraphe 7.3.1, 7.3.2, page 138-140
5!>
6!! Relative transpiration, i.e. the relationship between actual transpiration and maximal transpiration (ep/eop), is a bilinear function of the available
7!! water content in the root zone, teta (i.e. the water content above the wilting point in cm3 of water/cm3 of dry soil).
8!!
9!! The water content threshold separating the maximal transpiration stage and the reduced transpiration stage (tetstomate) depends on root density,
10!! the stomatal functioning of the plant, and the evaporative demand (Brisson, 1998c). It was shown that this threshold does not depend on the soil type,
11!! for example via the maximal available water content, as is commonly assumed.
12!!
13!! In the calculations below, cumlracz is the summation over the whole rooting depth, zrac, of effective root length density lracz,
14!! psisto is the critical potential of stomatal closure (positive in bars) and rayon is the mean root radius which is assumed to be equal to 0.02 cm.
15!!
16!! The ep/eop ratio is equal to the stomatal stress index, swfac.  The stress turgor index turfac which affects leaf growth comes into play earlier.
17!! The method for calculating it is copied from the method used for swfac using the critical potential of cell expansion psiturg.
18!! Since psiturg is lower than psisto, we obtain a higher teturg threshold.  In other words, leaf growth can be inhibited even when transpiration is still at
19!! its maximum level.
20
21
22
23!!
24!! However, in our model, we just use the relative of available soil moisture to fielding capacity to represent the slowing effects on LAI.
25!! The humrel is harmonized.
26! *-----------------------------------------------------------------------------------------------------------------------------------------------------------* c!
27subroutine stress(n,                  &   ! IN
28                  nrec,               & 
29                  lai,                & 
30                  eop,                &
31                  shumdiag_cm_day,    &   ! IN
32                  vswc,               &   ! IN
33                  humrel,             &
34                  shumrel,            &
35                  swfac,              &   ! INOUT
36                  turfac,             &
37                  senfac)                 
38  USE Stics
39  USE constantes 
40
41
42 
43  IMPLICIT NONE
44
45!: Arguments
46!: IN
47
48  integer, intent(IN)                  :: n 
49  integer, intent(IN)                  :: nrec 
50  real,    intent(IN)                  :: lai           ! leaf area index
51  real,    intent(IN)                  :: eop      !> // OUTPUT // Maximum transpiration flux  // mm
52  real,    intent(IN), dimension(3)    :: shumdiag_cm_day 
53  real,    intent(IN)                  :: vswc      !> daily humrel data
54  real,    intent(IN)                  :: humrel
55 
56!: INOUT
57  real,    intent(INOUT) :: swfac      !> // OUTPUT // Index of stomatic water stress  // 0-1
58  real,    intent(INOUT) :: turfac      !> // OUTPUT // Index of turgescence water stress  // 0-1
59  real,    intent(INOUT) :: senfac      !> // OUTPUT // Water stress index on senescence // 0-1
60! OUT
61  real,    intent(OUT)    :: shumrel     ! average relative soil moisture to holding capacity at sowing depth
62
63! temporal variables
64
65  real  ::    teta   ! volumetric soil water content m3/m3
66
67!      print *, 'in stress, the vegstress and humrel is', vswc, humrel
68     
69
70      ! ** si pas de plante
71      shumrel = sum(shumdiag_cm_day)/3.0 ! relative to soil holding capacity
72!      print *, 'humrel in stress is', humrel
73!      print *, 'eop and lai in stress is', eop, lai
74      if ((P_codelaitr == 1 .and. lai <= 0.)          &
75          .or. (nrec /= 0 .and. nrec > 0 .and. P_codcueille <= 1)     &
76          .or. (eop <= 0.)                                 &
77         ) then
78
79        swfac  = 1.
80        turfac = 1.
81        senfac = 1.
82      else
83         ! we calculate the water stress based on the volumic soil water contents.
84         
85         teta = vswc  ! this is the volumetric soil water contents
86         !teta = vswc       
87
88         !: Calcul de swfac
89              if (teta <= tetstomate) then
90                swfac = teta / tetstomate
91              else
92                swfac = 1.
93              endif
94              !write(70,*) n,'swfac=',swfac,teta,tetstomate,P_swfacmin
95              swfac = max(swfac, P_swfacmin)
96   
97   
98              !: Calcul de turfac
99              if (teta <= teturg) then
100                turfac = teta / teturg
101              else
102                turfac = 1.
103              endif
104              turfac = max(turfac, P_swfacmin)
105       
106              !: Calcul de senfac
107              if (teta <= tetsen) then
108                senfac = teta / tetsen
109              else
110                senfac = 1.0
111              endif
112              senfac = max(senfac, P_swfacmin) 
113 
114!          print *, 'do we go into here? in stress'
115!          print *, 'in stress, the swfac, senfac, and turfac is :', swfac, senfac, turfac
116      endif
117      !!! a temporary setting to remove water stress for rice
118!      if (P_codeplante == 'ric') then
119!          swfac = 1
120!          senfac = 1
121!          turfac = 1
122!      endif
123
124return
125end subroutine stress
126 
127 
Note: See TracBrowser for help on using the repository browser.