SURFEX v8.1
General documentation of Surfex
ini_data_rootfrac.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE ini_data_rootfrac( PDG, PROOTDEPTH, PROOT_EXT, PROOT_LIN, &
7  PROOTFRAC, OGV )
8 
9 ! ##########################################################################
10 !
11 !!**** *INI_DATA_ROOTFRAC*
12 !!
13 !! PURPOSE
14 !! -------
15 !
16 ! Calculates the soil grid configuration using a reference grid
17 ! Also compute the root fraction
18 !
19 !
20 !!** METHOD
21 !! ------
22 !
23 ! Direct calculation
24 !
25 !! EXTERNAL
26 !! --------
27 !
28 ! None
29 !!
30 !! IMPLICIT ARGUMENTS
31 !! ------------------
32 !!
33 !! REFERENCE
34 !! ---------
35 !!
36 !! Noilhan and Planton (1989)
37 !! Belair (1995)
38 !! Boone (2000)
39 !! Boone et al. (2000)
40 !! Habets et al. (2003)
41 !! Decharme et al. (2011)
42 !!
43 !! AUTHOR
44 !! ------
45 !! A. Boone * Meteo-France *
46 !! new version :
47 !! B. Decharme * Meteo-France *
48 !!
49 !! MODIFICATIONS
50 !! -------------
51 !! Original 12/04/03
52 !! new version :10/08/2011
53 !! P. Samuelsson 02/2012 MEB
54 !-------------------------------------------------------------------------------
55 !
56 !* 0. DECLARATIONS
57 ! ------------
58 !
59 USE modd_surf_par, ONLY : xundef, nundef
60 USE modd_isba_par, ONLY : noptimlayer, xoptimgrid
61 !
62 USE yomhook ,ONLY : lhook, dr_hook
63 USE parkind1 ,ONLY : jprb
64 !
65 IMPLICIT NONE
66 !
67 !* 0.1 declarations of arguments
68 !
69 REAL, DIMENSION(:,:), INTENT(IN) :: PDG ! depth of base of soil layers (m)
70 REAL, DIMENSION(:), INTENT(IN) :: PROOTDEPTH ! effective root depth (m)
71 REAL, DIMENSION(:), INTENT(IN) :: PROOT_EXT
72 REAL, DIMENSION(:), INTENT(IN) :: PROOT_LIN
73 LOGICAL, OPTIONAL, INTENT(IN) :: OGV
74 !
75 REAL, DIMENSION(:,:), INTENT(OUT) :: PROOTFRAC
76 !
77 !* 0.2 declarations of local variables
78 !
79 REAL :: ZLOG1, ZLOG2
80 REAL :: ZJACKSON ! Jackson (1996) formulation for cumulative root fraction
81 REAL :: ZUNIF ! linear formulation for cumulative root fraction
82 REAL :: ZROOTFRGV ! Fraction of patch root depth given to
83 ! ! grass root depth for understory ground vegetation.
84 ! ! =1 for non-understory vegetation
85 
86 !
87 INTEGER :: INI,INL
88 INTEGER :: JJ,JL
89 !
90 REAL(KIND=JPRB) :: ZHOOK_HANDLE
91 !-------------------------------------------------------------------------------
92 ! 0. Initialization
93 ! --------------
94 !
95 IF (lhook) CALL dr_hook('INI_DATA_ROOTFRAC',0,zhook_handle)
96 !
97 ini = SIZE(pdg,1)
98 inl = SIZE(pdg,2)
99 !
100 zrootfrgv = 1.0
101 IF (PRESENT(ogv)) THEN
102  IF(ogv) zrootfrgv = 0.5
103 ENDIF
104 !
105 prootfrac(:,:) = xundef
106 !
107  DO jj=1,ini
108  !
109  IF ( prootdepth(jj)/=xundef .AND. prootdepth(jj)/=0.0 ) THEN
110  !
111  DO jl=1,inl
112  zlog1 = 100. * log(proot_ext(jj)) * pdg(jj,jl)
113  zlog2 = 100. * log(proot_ext(jj)) * zrootfrgv * prootdepth(jj)
114  zjackson = min(1.0,(1.0-exp(zlog1))/(1.0-exp(zlog2)))
115  zunif = min(1.0,(pdg(jj,jl)/zrootfrgv/prootdepth(jj)))
116  prootfrac(jj,jl) = proot_lin(jj) * zunif &
117  + (1.0-proot_lin(jj)) * zjackson
118  ENDDO
119 ! No vegetation case
120  ELSE
121  prootfrac(jj,:) = 0.0
122  ENDIF
123  !
124  ENDDO
125 
126 !
127 IF (lhook) CALL dr_hook('INI_DATA_ROOTFRAC',1,zhook_handle)
128 !-------------------------------------------------------------------------------
129 END SUBROUTINE ini_data_rootfrac
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
integer, parameter nundef
subroutine ini_data_rootfrac(PDG, PROOTDEPTH, PROOT_EXT, PROOT_LI
logical lhook
Definition: yomhook.F90:15