SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
exp_decay_soil_fr.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 exp_decay_soil_fr (HISBA, PF, PC1SAT, PC2REF, PD_G, PD_ICE, &
7  pc4ref, pc3, pcondsat, pksat_ice )
8 ! ##########################################################################
9 !
10 !!**** *EXP_DECAY_SOIL_FR*
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 ! We caculate the hydraulic coductivity decay factor for each FR-coefficients.
16 ! Also, we redefine the surface hydraulic coductivity at saturation for
17 ! convective precipitation parametrisation.
18 !
19 !!** METHOD
20 !! ------
21 !
22 ! Direct calculation
23 !
24 !! EXTERNAL
25 !! --------
26 !
27 ! None
28 !!
29 !! IMPLICIT ARGUMENTS
30 !! ------------------
31 !!
32 !!
33 !! REFERENCE
34 !! ---------
35 !!
36 !! AUTHOR
37 !! ------
38 !! B. Decharme
39 !!
40 !! MODIFICATIONS
41 !! -------------
42 !! Original 17/11/03
43 !-------------------------------------------------------------------------------
44 !
45 !* 0. DECLARATIONS
46 ! ------------
47 !
48 USE modd_surf_par,ONLY : xundef
49 USE modd_sgh_par, ONLY : x2
50 USE modd_csts, ONLY : xday
51 #ifdef TOPD
52 USE modd_dummy_exp_profile,ONLY : xc_depth_ratio
53 #endif
54 !
55 USE yomhook ,ONLY : lhook, dr_hook
56 USE parkind1 ,ONLY : jprb
57 !
58 IMPLICIT NONE
59 !
60 !* 0.1 declarations of arguments
61 !
62  CHARACTER(LEN=*) :: hisba ! hydrology/soil:
63 ! ! '2-L' = single column
64 ! ! '3-L' = root zone/baseflow layer
65 ! ! 'DIF' = N-layer diffusion: Richard's Eq.
66 !
67 REAL, DIMENSION(:), INTENT(IN) :: pf
68 ! PF = exponential decay factor (1/m)
69 !
70 REAL, DIMENSION(:), INTENT(INOUT) :: pc2ref,pc1sat
71 ! PC1SAT = C1 at saturation
72 ! PC2REF = reference value of C2
73 !
74 REAL, DIMENSION(:,:),INTENT(INOUT):: pcondsat
75 ! PCONDSAT = hydraulic conductivity at saturation (m s-1)
76 !
77 REAL, DIMENSION(:,:), INTENT(IN) :: pd_g
78 ! PD_G = Depth of bottom of Soil layers (m)
79 !
80 REAL, DIMENSION(:), INTENT(IN) :: pd_ice
81 ! PD_ICE = depth of the soil column for
82 ! fraction of frozen soil calculation (m)
83 
84 REAL, DIMENSION(:,:),INTENT(INOUT):: pc3
85 ! PC3 = C3 coef with exponential decay of hydraulic soil profil
86 !
87 REAL, DIMENSION(:), INTENT(INOUT) :: pc4ref
88 ! PC4REF = fiiting soil paramater for vertical diffusion (C4)
89 ! with exponential decay of hydraulic soil profil
90 !
91 REAL, DIMENSION(:), INTENT(OUT) :: pksat_ice
92 ! PKSAT_ICE = hydraulic conductivity at saturation (m s-1)
93 ! on frozen soil depth (Horton calculation)
94 !
95 !* 0.2 declarations of local variables
96 !
97 REAL, DIMENSION(SIZE(PF)) :: zd_g_tot, zc_depth, zksat_noexp, zc_depth_ratio
98 ! ZD_G_TOT = depth of the soil column (m)
99 ! ZC_DEPTH = assumed as the depth where the vertical
100 ! satured hydraulic conductivities reach
101 ! the compacted value given in Clapp and
102 ! Hornberger. (m)
103 ! For ISBA-FR, we take the root depth.
104 !
105 REAL(KIND=JPRB) :: zhook_handle
106 !
107 !-------------------------------------------------------------------------------
108 !
109 IF (lhook) CALL dr_hook('EXP_DECAY_SOIL_FR',0,zhook_handle)
110 !
111 zd_g_tot(:) = pd_g(:,2)
112 IF(hisba=='3-L')zd_g_tot(:) = pd_g(:,3)
113 !
114 zksat_noexp(:) = pcondsat(:,2)
115 !
116 zc_depth_ratio(:) = 1.
117 !
118 #ifdef TOPD
119 IF (ALLOCATED(xc_depth_ratio)) zc_depth_ratio(:) = xc_depth_ratio(:)
120 #endif
121 !
122 WHERE(zd_g_tot(:)/=xundef)
123 !
124 !compacted depth
125 !
126 zc_depth(:) = pd_g(:,2)*zc_depth_ratio(:)
127 !ZC_DEPTH(:) = PD_G(:,2)
128 !
129 !surface hydraulic conductivity at saturation
130 !
131 pcondsat(:,1) = pcondsat(:,1)*exp(pf(:)*zc_depth(:))
132 !
133 !mean hydraulic conductivity at saturation over the root zone
134 !
135 pcondsat(:,2) = zksat_noexp(:)*( exp(pf(:)*zc_depth)-exp(pf(:)*(zc_depth(:)-pd_g(:,2))) ) &
136  /(pf(:)*pd_g(:,2))
137 !
138 !mean hydraulic conductivity at saturation over the first soil centimeters
139 !
140 pksat_ice(:) = zksat_noexp(:)*( exp(pf(:)*zc_depth)-exp(pf(:)*(zc_depth(:)-pd_ice(:))) ) &
141  /(pf(:)*pd_ice(:))
142 !
143 !decay factor for C1 coef
144 !
145 pc1sat(:) = pc1sat(:)*sqrt( exp(-pf(:)*zc_depth(:)) )
146 !
147 !decay factor for C2 coef
148 !
149 pc2ref(:)=pc2ref(:)+( pcondsat(:,2)-zksat_noexp(:) ) * xday/pd_g(:,2)
150 !
151 !C3 coef with exponential decay in root soil layer
152 !
153 pc3(:,1)=pc3(:,1)*( exp(pf(:)*zc_depth(:))-exp(pf(:)*(zc_depth(:)-pd_g(:,2))) ) / (pf(:)*pd_g(:,2))
154 !
155 ENDWHERE
156 !
157 IF(hisba=='3-L')THEN
158 !
159  WHERE(pd_g(:,2)< zd_g_tot(:).AND.pd_g(:,2)/=xundef)
160 !
161 ! C3 coef with exponential decay in deep soil layer
162 !
163  pc3(:,2)=pc3(:,2)*( exp(pf(:)*(zc_depth(:)-pd_g(:,2)))-exp(pf(:)*(zc_depth(:)-zd_g_tot(:))) ) &
164  / (pf(:)*(zd_g_tot(:)-pd_g(:,2)))
165 !
166 ! decay factor for C4 coef
167 !
168  pc4ref(:)=pc4ref(:)*( exp(pf(:)*(zc_depth(:)-pd_g(:,2)/x2))-exp(pf(:)*(zc_depth(:)&
169  -((pd_g(:,2)+zd_g_tot(:))/2.))) ) * x2/(pf(:)*zd_g_tot(:))
170 !
171  ENDWHERE
172 !
173 ENDIF
174 !
175 IF (lhook) CALL dr_hook('EXP_DECAY_SOIL_FR',1,zhook_handle)
176 !
177 END SUBROUTINE exp_decay_soil_fr
subroutine exp_decay_soil_fr(HISBA, PF, PC1SAT, PC2REF, PD_G, PD_ICE, PC4REF, PC3, PCONDSAT, PKSAT_ICE)