source: branches/publications/ORCHIDEE-PEAT_r5488/src_sticslai/F_humirac.f90 @ 5491

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

New: CROP module. Done by Xuhui.

File size: 2.1 KB
Line 
1! *----------------------------------------------------------------* c
2! *   introduction d'une fonction continue entre pf4.2 et CC pour  * c
3! *   contraindre la germination et la levée                       * c
4! *----------------------------------------------------------------* c
5!> Introduction of a continuous function between pf4.2 and CC to Constrain germination and emergence
6!> calculate the effects of soil moisture in the seedbed on germination and this effect can be estimated by using the parameter of F_humirac as shown below--Xiuchen Wu
7
8module Divers_water
9
10  USE Stics
11
12  IMPLICIT NONE
13  PRIVATE
14  PUBLIC F_humirac
15 
16  contains
17 
18  real function F_humirac(h)
19 
20    IMPLICIT NONE
21 
22    real, intent(IN) :: h 
23    !real, intent(IN) :: hmin 
24    !real, intent(IN) :: hmax      !> // OUTPUT // Maximum height of water table between drains // cm
25    !real, intent(IN) :: P_sensrsec  !> // PARAMETER // root sensitivity to drought (1=insensitive) // SD // PARPLT // 1
26   
27    !real :: x 
28 
29       
30        if (h > 0) then
31           F_humirac = P_sensrsec + (1. - P_sensrsec) * h
32        else
33           F_humirac = 0
34        endif
35 
36 
37 
38        if (F_humirac > 1.)  F_humirac = 1.
39        if (F_humirac < 0.)  F_humirac = 0.
40 
41       ! if (hmax /= hmin) then 
42       !   !: 10/06/03 - modif de fonction humirac avant pfp pour
43       !   !-            aboutir à une absorption nulle pour h = 0
44       !   if (h > hmin) then
45       !     x = (h - hmin) / (hmax - hmin)
46       !     F_humirac = P_sensrsec + (1. - P_sensrsec) * x
47       !   else
48       !     F_humirac = P_sensrsec / hmin * h
49       !   endif
50       ! else
51       !   !: NB - 10/06/03
52       !   ! --if (h < hmin) humirac = P_sensrsec
53       !   if (h >= hmin) then
54       !     F_humirac = 1.0
55       !   else
56       !     F_humirac = P_sensrsec / hmin * h
57       !   endif
58       ! endif
59 
60       ! if (F_humirac > 1.)  F_humirac = 1.
61       ! if (F_humirac < 0.)  F_humirac = 0.
62 
63  return
64  end function F_humirac
65end module Divers_water
Note: See TracBrowser for help on using the repository browser.