source: branches/publications/ORCHIDEE_GLUC_r6545/src_stomate/lpj_constraints.f90 @ 6737

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

Merge: from revisions [4491:4695/trunk/ORCHIDEE]

Merge done in [4671:4718/perso/albert.jornet/MICT_MERGE]

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 10.8 KB
Line 
1! =================================================================================================================================
2! MODULE       : lpj_constraints
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7!              This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF       Groups the subroutines that: (1) initialize all variables in
10!! lpj_constraints and (2) check the temperature threshold to decide for each PFT
11!! if it can adapt to and regenerate under prevailing climate conditions**1
12!!
13!!\n RECENT CHANGE(S) : None
14!!
15!! REFERENCE(S) :
16!! - Sitch, S., B. Smith, et al. (2003), Evaluation of ecosystem dynamics,
17!!   plant geography and terrestrial carbon cycling in the LPJ dynamic
18!!   global vegetation model, Global Change Biology, 9, 161-185.\n
19!! - Smith, B., I. C. Prentice, et al. (2001), Representation of vegetation
20!!   dynamics in the modelling of terrestrial ecosystems: comparing two
21!!   contrasting approaches within European climate space,
22!!   Global Ecology and Biogeography, 10, 621-637.\n
23!!
24!! SVN          :
25!! $HeadURL$
26!! $Date$
27!! $Revision$
28!! \n
29!_ ================================================================================================================================
30
31MODULE lpj_constraints
32
33  ! modules used:
34  USE xios_orchidee
35  USE ioipsl_para
36  USE stomate_data
37  USE constantes
38  USE pft_parameters
39
40  IMPLICIT NONE
41
42  ! private & public routines
43
44  PRIVATE
45  PUBLIC constraints,constraints_clear
46
47  REAL(r_std), PARAMETER          :: grow_limit = 7+ZeroCelsius          !! Growing-season temperature limit to tree extension (K)
48  LOGICAL, SAVE                   :: firstcall_constraints = .TRUE.      !! first call
49!$OMP THREADPRIVATE(firstcall_constraints)
50
51CONTAINS
52
53!! ================================================================================================================================
54!! SUBROUTINE   : constraints_clear
55!!
56!>\BRIEF        Set the flag ::firstcall_constraints to .TRUE. and as such activate section
57!!              1.1 of the subroutine constraints (see subroutine constraints).
58!!
59!_ ================================================================================================================================
60
61  SUBROUTINE constraints_clear
62    firstcall_constraints = .TRUE. 
63  END SUBROUTINE constraints_clear
64
65
66!! ================================================================================================================================
67!! SUBROUTINE   : constraints
68!!
69!>\BRIEF        Determine whether each PFT can adapt to and regenerate under the prevailing climate
70!! conditions. Climate conditions are characterised by different threshold values for air temperature.
71!!
72!! DESCRIPTION : PFTs are adapted to the climate conditions if the daily air temperature does not drop below
73!! the treshold values ::tcm_crit. Some PFT's do not have a ::tcm_crit treshold. Seasonal trees die if leafage
74!! does not show a clear seasonality. (i.e. if the start of the growing season is never detected)
75!!
76!! If the monthly temperature is below ::tcm_crit i.e. the critical temperature of the coldest month, the
77!! PFT will be able to regenerate. If minimum temperatures do not drop below ::tcm_crit, its regenerative
78!! capacity decreases with time. Hence, plants that need vernalization die after a few years if they don't
79!! vernalize (even if they would not loose their leaves).
80!!
81!! The treshold values ::t_min_crit, the critical temperature of the coldest month is defined in
82!! stomate_constants.f90'. However, ::regenerate_min, the critical temperature to support regeneration is
83!! calculated in this routine from parameters of which none depenent on the PFT. The value for
84!! ::large_value is defined as 1.E33 in stomata_constraints
85!!
86!! RECENT CHANGE(S) : None
87!!
88!! MAIN OUTPUT VARIABLE(S) : ::adapted (0-1, unitless) and ::regenerate (0-1, unitless)
89!!
90!! REFERENCE(S) : None
91!!
92!! FLOWCHART :
93!! \latexonly
94!!     \includegraphics[scale=0.3]{lpj_constraints_flowchart.png}
95!! \endlatexonly
96!! \n
97!_ ================================================================================================================================
98 
99    SUBROUTINE constraints (npts, dt, &
100       t2m_month, t2m_min_daily, when_growthinit, &
101       adapted, regenerate, Tseason)
102   
103    !! 0. Variable and parameter declaration
104   
105    !! 0.1 Input variable
106
107    INTEGER(i_std), INTENT(in)                      :: npts            !! Domain size (unitless)
108    REAL(r_std), INTENT(in)                         :: dt              !! Time step   (days)
109    REAL(r_std), DIMENSION(npts), INTENT(in)        :: t2m_month       !! "Monthly" 2-meter temperature by defualt
110                                                                       !! monthly spans 20 days a (K)
111    REAL(r_std), DIMENSION(npts), INTENT(in)        :: Tseason         !! "seasonal" 2-meter temperature (K)
112    REAL(r_std), DIMENSION(npts), INTENT(in)        :: t2m_min_daily   !! Daily minimum 2-meter temperature (K)
113    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)    :: when_growthinit !! Days since beginning of growing season (days)
114
115    !! 0.2 Output variables
116
117    !! 0.3 Modified variables
118 
119    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout) :: adapted         !! plant adaptation to climate: progressively decrease if temperature is too low
120    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout) :: regenerate      !! plant regeneration: if vernalization criteria is not reached (i.e not allow
121                                                                       !! plant to correctly seed and reproduce) then regeneration progressively decrease
122
123    !! 0.4 Local variables
124
125    REAL(r_std)                                     :: tau_adapt       !! Memory length for adaption (days)
126    REAL(r_std)                                     :: tau_regenerate  !! Memory length for regeneration (days)
127    REAL(r_std)                                     :: regenerate_min  !! Critical value of "regenerate" below which plant
128                                                                       !! dies (unitless)
129    INTEGER(i_std)                                  :: j               !! Index
130!_ ================================================================================================================================
131
132    IF (printlev>=3) WRITE(numout,*) 'Entering constraints' ! diagnostic level in implimentation
133
134  !! 1. Initializations
135
136    tau_adapt = one_year
137    tau_regenerate = one_year
138
139    !! 1.1 Print parameter settings
140    IF ( firstcall_constraints ) THEN
141       IF (printlev >= 2) THEN
142          WRITE(numout,*) 'constraints:'
143       
144          WRITE(numout,*) '   > Memory length for adaption (d): ',tau_adapt
145          WRITE(numout,*) '   > Memory length for regeneration (d): ',tau_regenerate
146          WRITE(numout,*) '   > Longest sustainable time without vernalization (y):', too_long
147          WRITE(numout,*) '   > For trees, longest sustainable time without growth init (y):', too_long
148       END IF
149       firstcall_constraints = .FALSE.
150       
151    ENDIF
152
153    !! 1.2 Calculate critical value for "regenerate"
154    !      Critical value for "regenerate", below this value, the last vernalization
155    !      happened too far in the past, The PFT is can not regenerate under the
156    !      prevailing climate conditions.
157    regenerate_min = exp ( - too_long * one_year / tau_regenerate )
158
159  !! 2. Calculate ::adapted and ::regenerate
160
161    DO j = 2,nvm ! Loop over # PFTs
162
163       !! 2.1 PFT mask for natural or agriculture vegetations
164       IF ( natural(j) .OR. agriculture ) THEN
165
166          !! 2.1.1 Climate criteria
167          !! There is no critical temperature for the PFT
168          !  Frost restistant PFT do not have a critical temperature for growth
169          IF ( tmin_crit(j) .EQ. undef ) THEN
170             adapted(:,j) = un 
171          ENDIF
172
173          !! 2.1.2 Seasonal trees die if leafage does not show a clear seasonality.
174          !        Seasonal trees die if leafage does not show a clear seasonality
175          !        (i.e. if the start of the growing season is never detected).
176          IF ( is_tree(j) .AND. ( pheno_model(j) .NE. 'none' ) ) THEN
177
178             WHERE ( when_growthinit(:,j) .GT. too_long*one_year .AND. when_growthinit(:,j).LT. large_value)
179                adapted(:,j) = zero
180             ENDWHERE
181
182          ENDIF
183
184          ! "seasonal" temperature Tseason must exceed gro_limit degree (grow_limit) for trees to be declared adapted.
185          IF ( is_tree(j) ) THEN
186             WHERE ( Tseason(:) .LT. grow_limit )
187                adapted(:,j)=zero
188             ENDWHERE
189          ENDIF
190          ! if Tseason was less than grow_limit from previous year then the adataption decrease
191          adapted(:,j) = un - ( un - adapted(:,j) ) * (tau_adapt- dt)/tau_adapt 
192
193          !! 2.1.3 Test if PFT is regenerative
194
195          !! 2.1.3.1 Check PFT vernalization.
196          !          If sufficiently cold, PFT will be able to regenerate for some time.
197          !          Several PFTs (ex: evergreen) don't need vernalization
198          IF ( tcm_crit(j) .EQ. undef ) THEN
199
200             regenerate(:,j) = un
201
202          !! 2.1.3.2 PFT needs vernalization
203          ELSE
204             ! if the vernalization is reach, the plant flowering will be correct and then the production of seed
205             ! will be correct, making the plant able to reproduce and regenerate (i.e fitness)
206             WHERE ( t2m_month(:) .LE. tcm_crit(j) )
207                regenerate(:,j) = un
208             ENDWHERE
209
210             ! each time vernalization is not reached, the fitness decrease
211             !  hence, with time ::regenerate approaches 0
212             regenerate(:,j) = regenerate(:,j) * (tau_regenerate-dt)/tau_regenerate
213
214          ENDIF
215
216          !! 2.1.4
217          !        Plants that need vernalization die after a few years if they don't
218          !        vernalize (even if they would not loose their leaves).
219          WHERE ( regenerate(:,j) .LE. regenerate_min )
220             adapted(:,j) = zero
221          ENDWHERE
222
223       !! 2.1 PFT except natural and agriculture vegetation
224       !      Should be developed if needed
225       ELSE
226
227          adapted(:,j) = zero
228
229          regenerate(:,j) = zero
230
231       ENDIF ! PFT of natural or agriculture
232
233    ENDDO ! Loop over # PFTs
234
235  !! 3. Write history files
236    CALL xios_orchidee_send_field("ADAPTATION",adapted)
237    CALL xios_orchidee_send_field("REGENERATION",regenerate)
238
239    CALL histwrite_p (hist_id_stomate, 'ADAPTATION', itime, &
240         adapted, npts*nvm, horipft_index)
241    CALL histwrite_p (hist_id_stomate, 'REGENERATION', itime, &
242         regenerate, npts*nvm, horipft_index)
243    CALL histwrite_p (hist_id_stomate, 'T2M_MIN_DAILY', itime, &
244         t2m_min_daily, npts, horipft_index)
245
246    IF (printlev>=4) WRITE(numout,*) 'Leaving constraints'
247
248  END SUBROUTINE constraints
249
250END MODULE lpj_constraints
Note: See TracBrowser for help on using the repository browser.