source: branches/publications/ORCHIDEE_CAN_r2290/src_stomate/lpj_constraints.f90 @ 7540

Last change on this file since 7540 was 1831, checked in by matthew.mcgrath, 11 years ago

DEV: Trunk merges up to and including r1789

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 10.1 KB
Line 
1! =================================================================================================================================
2! MODULE       : lpj_constraints
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.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  LOGICAL, SAVE                           :: firstcall = .TRUE.      !! first call
48!$OMP THREADPRIVATE(firstcall)
49CONTAINS
50
51!! ================================================================================================================================
52!! SUBROUTINE   : constraints_clear
53!!
54!>\BRIEF        Set the flag ::firstcall to .TRUE. and as such activate section
55!!              1.1 of the subroutine constraints (see subroutine constraints).
56!!
57!_ ================================================================================================================================
58
59  SUBROUTINE constraints_clear
60    firstcall = .TRUE. 
61  END SUBROUTINE constraints_clear
62
63
64!! ================================================================================================================================
65!! SUBROUTINE   : constraints
66!!
67!>\BRIEF        Determine whether each PFT can adapt to and regenerate under the prevailing climate
68!! conditions. Climate conditions are characterised by different threshold values for air temperature.
69!!
70!! DESCRIPTION : PFTs are adapted to the climate conditions if the daily air temperature does not drop below
71!! the treshold values ::tcm_crit. Some PFT's do not have a ::tcm_crit treshold. Seasonal trees die if leafage
72!! does not show a clear seasonality. (i.e. if the start of the growing season is never detected)
73!!
74!! If the monthly temperature is below ::tcm_crit i.e. the critical temperature of the coldest month, the
75!! PFT will be able to regenerate. If minimum temperatures do not drop below ::tcm_crit, its regenerative
76!! capacity decreases with time. Hence, plants that need vernalization die after a few years if they don't
77!! vernalize (even if they would not loose their leaves).
78!!
79!! The treshold values ::t_min_crit, the critical temperature of the coldest month is defined in
80!! stomate_constants.f90'. However, ::regenerate_min, the critical temperature to support regeneration is
81!! calculated in this routine from parameters of which none depenent on the PFT. The value for
82!! ::large_value is defined as 1.E33 in stomata_constraints
83!!
84!! RECENT CHANGE(S) : None
85!!
86!! MAIN OUTPUT VARIABLE(S) : ::adapted (0-1, unitless) and ::regenerate (0-1, unitless)
87!!
88!! REFERENCE(S) : None
89!!
90!! FLOWCHART :
91!! \latexonly
92!!     \includegraphics[scale=0.3]{lpj_constraints_flowchart.png}
93!! \endlatexonly
94!! \n
95!_ ================================================================================================================================
96 
97    SUBROUTINE constraints (npts, dt, &
98       t2m_month, t2m_min_daily, when_growthinit, &
99       adapted, regenerate)
100   
101    !! 0. Variable and parameter declaration
102   
103    !! 0.1 Input variable
104
105    INTEGER(i_std), INTENT(in)                      :: npts            !! Domain size (unitless)
106    REAL(r_std), INTENT(in)                         :: dt              !! Time step   (days)
107    REAL(r_std), DIMENSION(npts), INTENT(in)        :: t2m_month       !! "Monthly" 2-meter temperature by defualt
108                                                                       !! monthly spans 20 days a (K)
109    REAL(r_std), DIMENSION(npts), INTENT(in)        :: t2m_min_daily   !! Daily minimum 2-meter temperature (K)
110    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)    :: when_growthinit !! Days since beginning of growing season (days)
111
112    !! 0.2 Output variables
113
114    !! 0.3 Modified variables
115 
116    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout) :: adapted         !! Winter too cold? (0 to 1, unitless)
117    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout) :: regenerate      !! Winter sufficiently cold? (0 to 1, unitless)
118
119    !! 0.4 Local variables
120
121    REAL(r_std)                                     :: tau_adapt       !! Memory length for adaption (days)
122    REAL(r_std)                                     :: tau_regenerate  !! Memory length for regeneration (days)
123    REAL(r_std)                                     :: regenerate_min  !! Critical value of "regenerate" below which plant
124                                                                       !! dies (unitless)
125    INTEGER(i_std)                                  :: j               !! Index
126!_ ================================================================================================================================
127
128    IF (bavard.GE.3) WRITE(numout,*) 'Entering constraints' ! diagnostic level in implimentation
129
130  !! 1. Initializations
131
132    tau_adapt = one_year
133    tau_regenerate = one_year
134
135    !! 1.1 Print parameter settings
136    IF ( firstcall ) THEN
137
138       WRITE(numout,*) 'constraints:'
139       
140       WRITE(numout,*) '   > Memory length for adaption (d): ',tau_adapt
141       WRITE(numout,*) '   > Memory length for regeneration (d): ',tau_regenerate
142       WRITE(numout,*) '   > Longest sustainable time without vernalization (y):', too_long
143       WRITE(numout,*) '   > For trees, longest sustainable time without growth init (y):', too_long
144       
145       firstcall = .FALSE.
146       
147    ENDIF
148
149    !! 1.2 Calculate critical value for "regenerate"
150    !      Critical value for "regenerate", below this value, the last vernalization
151    !      happened too far in the past, The PFT is can not regenerate under the
152    !      prevailing climate conditions.
153    regenerate_min = exp ( - too_long * one_year / tau_regenerate )
154
155  !! 2. Calculate ::adapted and ::regenerate
156
157    DO j = 2,nvm ! Loop over # PFTs
158
159       !! 2.1 PFT mask for natural or agriculture vegetations
160       IF ( natural(j) .OR. agriculture ) THEN
161
162          !! 2.1.1 Climate criteria
163 
164          !! 2.1.1.1 There is no critical temperature for the PFT
165          !          Frost restistant PFT do not have a critical temperature for growth
166          IF ( tmin_crit(j) .EQ. undef ) THEN
167             
168             adapted(:,j) = un 
169
170          !! 2.1.1.2 Frost occured in frost sensitive PFTs
171          !          For example, tropical plants will die if frost, below the treshold, occured
172          ELSE
173
174             WHERE ( t2m_min_daily(:) .LT. tmin_crit(j) )
175                adapted(:,j) = zero
176             ENDWHERE
177
178             ! The PFT does not disappear after a single cold shock. The PFT has a memory
179             ! and if the cold shock do not happen too often, it will get forgotten.
180             ! No reference found for this approach
181             adapted(:,j) = un - ( un - adapted(:,j) ) * (tau_adapt- dt)/tau_adapt 
182             
183          ENDIF
184
185          !! 2.1.2 Seasonal trees die if leafage does not show a clear seasonality.
186          !        Seasonal trees die if leafage does not show a clear seasonality
187          !        (i.e. if the start of the growing season is never detected).
188          IF ( is_tree(j) .AND. ( pheno_model(j) .NE. 'none' ) ) THEN
189
190             WHERE ( when_growthinit(:,j) .GT. too_long*one_year .AND. when_growthinit(:,j).LT. large_value)
191                adapted(:,j) = zero
192             ENDWHERE
193
194          ENDIF
195
196          !! 2.1.3 Test if PFT is regenerative
197
198          !! 2.1.3.1 Check PFT vernalization.
199          !          If sufficiently cold, PFT will be able to regenerate for some time.
200          !          Several PFTs (ex: evergreen) don't need vernalization
201          IF ( tcm_crit(j) .EQ. undef ) THEN
202
203             regenerate(:,j) = un
204
205          !! 2.1.3.2 PFT needs vernalization
206          ELSE
207
208             WHERE ( t2m_month(:) .LE. tcm_crit(j) )
209                regenerate(:,j) = un
210             ENDWHERE
211
212             ! Limited memory: after some time, the winter is forgotten and the PFT can no longer
213             ! produce seeds, hence, with time ::regenerate approaches 0
214             regenerate(:,j) = regenerate(:,j) * (tau_regenerate-dt)/tau_regenerate
215
216          ENDIF
217
218          !! 2.1.4 Plants that need vernalization die
219          !        Plants that need vernalization die after a few years if they don't
220          !        vernalize (even if they would not loose their leaves).
221          WHERE ( regenerate(:,j) .LE. regenerate_min )
222             adapted(:,j) = zero
223          ENDWHERE
224
225       !! 2.1 PFT except natual and agriculture vegetation
226       !      Should be developed if needed
227       ELSE
228
229          adapted(:,j) = zero
230
231          regenerate(:,j) = zero
232
233       ENDIF ! PFT of natural or agriculture
234
235    ENDDO ! Loop over # PFTs
236
237  !! 3. Write history files
238    CALL xios_orchidee_send_field("ADAPTATION",adapted)
239    CALL xios_orchidee_send_field("REGENERATION",regenerate)
240
241    CALL histwrite_p (hist_id_stomate, 'ADAPTATION', itime, &
242         adapted, npts*nvm, horipft_index)
243    CALL histwrite_p (hist_id_stomate, 'REGENERATION', itime, &
244         regenerate, npts*nvm, horipft_index)
245
246    IF (bavard.GE.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.