1 | |
---|
2 | |
---|
3 | module Divers_develop |
---|
4 | |
---|
5 | USE Stics |
---|
6 | |
---|
7 | |
---|
8 | IMPLICIT NONE |
---|
9 | PRIVATE |
---|
10 | PUBLIC calcul_UDev, cRFPI |
---|
11 | |
---|
12 | |
---|
13 | contains |
---|
14 | !======================================================================================! |
---|
15 | !======================================================================================! |
---|
16 | !======================================================================================! |
---|
17 | |
---|
18 | !> calculate the effects of temperature on UDev_cult (in unit of degree days), UDev_cult is something like the temperature of crop, but different with Tcult |
---|
19 | !> for more detailed information please see eq. 2.11 in page 29 in the STICS documentation -- XCWU |
---|
20 | |
---|
21 | real function calcul_UDev(temp) |
---|
22 | |
---|
23 | real, intent(IN) :: temp !> I don't know what is the temp? From the documentation , the temp should be the Tcult, but not the air temperature. |
---|
24 | !real, intent(IN) :: P_tdmax !> // PARAMETER // Maximum threshold temperature for development // degree C // PARPLT // 1 |
---|
25 | !real, intent(IN) :: P_tdmin !> // PARAMETER // Minimum threshold temperature for development // degree C // PARPLT // 1 |
---|
26 | !real, intent(IN) :: P_tcxstop !> // PARAMETER // threshold temperature beyond which the foliar growth stops (phasic growth stop) // degree C // PARPLT // 1 |
---|
27 | |
---|
28 | real :: udev ! pour alléger l'écriture, utilisation variable temporaire udev |
---|
29 | |
---|
30 | udev = max(0.,temp - P_tdmin) |
---|
31 | if (P_tcxstop >= 100.0) then !> the threshold temperature seems strange here but could be defined in the running definition file |
---|
32 | if (temp > P_tdmax) udev = P_tdmax - P_tdmin |
---|
33 | else ! (P_tcxstop < 100) |
---|
34 | if (temp > P_tdmax) then |
---|
35 | udev = (P_tdmax - P_tdmin) / (-P_tcxstop + P_tdmax) * (temp - P_tcxstop) |
---|
36 | udev = max(0.,udev) |
---|
37 | endif |
---|
38 | endif |
---|
39 | |
---|
40 | calcul_UDev = udev ! on affecte la valeur de retour |
---|
41 | |
---|
42 | return |
---|
43 | end function calcul_UDev |
---|
44 | |
---|
45 | !======================================================================================! |
---|
46 | !======================================================================================! |
---|
47 | !======================================================================================! |
---|
48 | !> calculating the hourly temperatures |
---|
49 | !function calcul_TemperaturesHoraires(tmin, tmin_demain, tmax) |
---|
50 | ! |
---|
51 | ! real, intent(IN) :: tmin !> arg. Température minimum // OUTPUT // Minimum active temperature of air // degree C |
---|
52 | ! real, intent(IN) :: tmin_demain !> arg. Température minimum du lendemain // Minimum temperature of the following day---Xiuchen Wu |
---|
53 | ! real, intent(IN) :: tmax !> arg. Température maximum // OUTPUT // Maximum active temperature of air // degree C |
---|
54 | ! |
---|
55 | ! real, dimension(24) :: calcul_TemperaturesHoraires ! variable de retour |
---|
56 | ! |
---|
57 | ! integer :: ih ! locale |
---|
58 | ! |
---|
59 | ! do ih = 1,12 |
---|
60 | ! calcul_TemperaturesHoraires(ih) = tmin + (ih * (tmax - tmin)/12.0) |
---|
61 | ! end do |
---|
62 | ! |
---|
63 | ! do ih = 13,24 |
---|
64 | ! calcul_TemperaturesHoraires(ih) = tmax - ((ih-12) * (tmax - tmin_demain)/12.0) |
---|
65 | ! end do |
---|
66 | ! |
---|
67 | !return |
---|
68 | !end |
---|
69 | |
---|
70 | !======================================================================================! |
---|
71 | !======================================================================================! |
---|
72 | !======================================================================================! |
---|
73 | !> calculating the GDH, it seems a variable representing the accumulated active temperature for developement--XCW |
---|
74 | !real function calcul_GDH(thor,P_tdmin,P_tdmax) |
---|
75 | ! |
---|
76 | ! real, intent(IN), dimension(24) :: thor ! arg. Temperatures Horaires sur 24 heures |
---|
77 | ! real, intent(IN) :: P_tdmin ! arg. Température de développement minimum // PARAMETER // Minimum threshold temperature for development // degree C // PARPLT // 1 |
---|
78 | ! real, intent(IN) :: P_tdmax ! arg. Température de développement maximum // PARAMETER // Maximum threshold temperature for development // degree C // PARPLT // 1 |
---|
79 | ! |
---|
80 | ! integer :: ih ! locale |
---|
81 | ! real :: udh ! locale |
---|
82 | ! |
---|
83 | ! calcul_GDH = 0. |
---|
84 | ! do ih = 1,24 |
---|
85 | ! udh = thor(ih) - P_tdmin |
---|
86 | ! if (thor(ih) < P_tdmin) udh = 0.0 |
---|
87 | ! if (thor(ih) > P_tdmax) udh = P_tdmax - P_tdmin |
---|
88 | ! calcul_GDH = calcul_GDH + udh |
---|
89 | ! end do |
---|
90 | ! |
---|
91 | !return |
---|
92 | !end |
---|
93 | |
---|
94 | |
---|
95 | !======================================================================================! |
---|
96 | !> slowly effect of the photoperiod on plant development |
---|
97 | real function cRFPI(phoi) |
---|
98 | |
---|
99 | !real, intent(IN) :: P_sensiphot !> // PARAMETER // photoperiod sensitivity (1=insensitive) // SD // PARPLT // 1 |
---|
100 | !real, intent(IN) :: P_phosat !> // PARAMETER // saturating photoperiod // hours // PARPLT // 1 |
---|
101 | !real, intent(IN) :: P_phobase !> // PARAMETER // Base photoperiod // hours // PARPLT // 1 |
---|
102 | real, intent(IN) :: phoi !> // OUTPUT // Photoperiod // hours |
---|
103 | |
---|
104 | cRFPI = (1.0 - P_sensiphot) / (P_phosat - P_phobase) * (phoi - P_phosat) + 1.0 |
---|
105 | cRFPI = min(cRFPI,1.0) |
---|
106 | cRFPI = max(cRFPI,P_sensiphot) |
---|
107 | |
---|
108 | ! ! there may be problematic |
---|
109 | ! cRFPI = max(cRFPI, 0.5) |
---|
110 | ! cRFPI = min(cRFPI, 1.0) |
---|
111 | return |
---|
112 | end function cRFPI |
---|
113 | |
---|
114 | !======================================================================================! |
---|
115 | ! fonction de calcul de l'humidité correspondant à un potentiel du sol |
---|
116 | ! utile pour la germination |
---|
117 | ! NB 15/02 2007 |
---|
118 | |
---|
119 | ! calculate the moisture corresponding to a ground potential useful for germination |
---|
120 | |
---|
121 | !real function humpotsol(P_psihucc,P_psihumin,humin,hucc,dacouche,psiref,P_codefente) |
---|
122 | ! |
---|
123 | !!: ARGUMENTS |
---|
124 | ! real, intent(IN) :: P_psihucc !> // PARAMETER // soil potential corresponding to field capacity // Mpa // PARAM // 1 |
---|
125 | ! real, intent(IN) :: P_psihumin !> // PARAMETER // soil potential corresponding to wilting point // Mpa // PARAM // 1 |
---|
126 | ! real, intent(IN) :: hucc |
---|
127 | ! real, intent(IN) :: humin |
---|
128 | ! real, intent(IN) :: dacouche |
---|
129 | ! real, intent(IN) :: psiref |
---|
130 | ! integer, intent(IN) :: P_codefente !> // PARAMETER // option allowing an additional water compartment for the swelling soils: yes (1), no (0) // code 0/1 // PARSOL // 0 |
---|
131 | ! |
---|
132 | !!: Variables locales |
---|
133 | ! real :: bpsisol |
---|
134 | ! real :: psisols |
---|
135 | ! real :: wsat |
---|
136 | ! |
---|
137 | ! ! Calcul des paramètres de la courbe de rétention |
---|
138 | ! if (P_codefente == 1) then |
---|
139 | ! wsat = ((1.5 * hucc) - (0.5 * humin)) / 10. |
---|
140 | ! else |
---|
141 | ! wsat = 1. - (dacouche / 2.66) |
---|
142 | ! endif |
---|
143 | ! |
---|
144 | ! bpsisol = log(P_psihucc / P_psihumin) / log(humin / hucc) |
---|
145 | ! psisols = P_psihumin * ((humin / (wsat *10 ))**bpsisol) |
---|
146 | ! |
---|
147 | ! ! Calcul de l'humidité |
---|
148 | ! humpotsol = wsat * 10. * ((psiref / psisols)**(-1/bpsisol)) |
---|
149 | ! |
---|
150 | !return |
---|
151 | !end function humpotsol |
---|
152 | |
---|
153 | end module Divers_develop |
---|