SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
thrmcondz.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 thrmcondz(PSANDZ,PWSATZ,PCONDDRY,PCONDSLD)
7 ! ###############################################################
8 !!**** *THRMCONDZ*
9 !!
10 !! PURPOSE
11 !! -------
12 !
13 ! Calculates soil thermal conductivity components
14 ! using sand fraction and model constants in
15 ! order to calculate the thermal conductivity
16 ! following the method of Johansen (1975) as recommended
17 ! by Farouki (1986) parameterized for SVAT schemes
18 ! following Peters-Lidard et al. 1998 (JAS). This is
19 ! used in explicit calculation of CG (soil thermal
20 ! inertia): it is an option. DEFAULT is method of
21 ! Noilhan and Planton (1989) (see SOIL.F90).
22 !
23 !!** METHOD
24 !! ------
25 !!
26 !! EXTERNAL
27 !! --------
28 !! none
29 !!
30 !! IMPLICIT ARGUMENTS
31 !! ------------------
32 !!
33 !! none
34 !!
35 !! REFERENCE
36 !! ---------
37 !!
38 !! Peters-Lidard et al. 1998 (JAS)
39 !!
40 !! AUTHOR
41 !! ------
42 !!
43 !! A. Boone * Meteo-France *
44 !!
45 !! MODIFICATIONS
46 !! -------------
47 !! Original 25/03/99
48 !! 18/02/00 2D for veritcal profiles
49 !!
50 !-------------------------------------------------------------------------------
51 !
52 !* 0. DECLARATIONS
53 ! ------------
54 !
55 USE modd_surf_par, ONLY : xundef
56 USE modd_isba_par, ONLY : xdrywght, xsphsoil, xcondqrtz, xcondoth1, xcondoth2
57 !
58 !
59 USE yomhook ,ONLY : lhook, dr_hook
60 USE parkind1 ,ONLY : jprb
61 !
62 IMPLICIT NONE
63 !
64 !* 0.1 declarations of arguments
65 !
66 REAL, DIMENSION(:,:), INTENT(IN) :: psandz ! soil sand fraction (-)
67 REAL, DIMENSION(:,:), INTENT(IN) :: pwsatz ! soil porosity (m3 m-3)
68 !
69 REAL, DIMENSION(:,:), INTENT(OUT):: pconddry ! soil dry thermal conductivity
70 ! (W m-1 K-1)
71 REAL, DIMENSION(:,:), INTENT(OUT):: pcondsld ! soil solids thermal
72 ! conductivity (W m-1 K-1)
73 !
74 !* 0.2 declarations of local variables
75 !
76 REAL, DIMENSION(SIZE(PSANDZ,1),SIZE(PSANDZ,2)) :: zquartz, zgammad
77 REAL(KIND=JPRB) :: zhook_handle
78 !
79 !-----------------------------------------------------------------
80 !
81 IF (lhook) CALL dr_hook('THRMCONDZ',0,zhook_handle)
82 zquartz(:,:) = xundef
83 zgammad(:,:) = xundef
84 pcondsld(:,:) = xundef
85 pconddry(:,:) = xundef
86 !
87 !
88 ! Quartz content estimated from sand fraction:
89 !
90 WHERE(psandz(:,:)/=xundef)
91 !
92  zquartz(:,:) = 0.038 + 0.95*psandz(:,:)
93 !
94 ! Note, ZGAMMAD (soil dry density) can be supplied from obs, but
95 ! for mesoscale modeling, we use the following approximation
96 ! from Peters-Lidard et al. 1998:
97 !
98  zgammad(:,:) = (1.0-pwsatz(:,:))*xdrywght
99 !
100 END WHERE
101 !
102 ! Soil solids conductivity:
103 !
104 WHERE(zquartz > 0.20 .AND. psandz(:,:)/=xundef)
105  pcondsld(:,:) = (xcondqrtz**zquartz(:,:))* &
106  (xcondoth1**(1.0-zquartz(:,:)))
107 END WHERE
108 WHERE(zquartz <= 0.20 .AND. psandz(:,:)/=xundef)
109  pcondsld(:,:) = (xcondqrtz**zquartz(:,:))* &
110  (xcondoth2**(1.0-zquartz(:,:)))
111 ENDWHERE
112 !
113 ! Soil dry conductivity:
114 !
115 WHERE(psandz(:,:)/=xundef)
116  pconddry(:,:) = (0.135*zgammad(:,:) + 64.7)/ &
117  (xdrywght - 0.947*zgammad(:,:))
118 END WHERE
119 IF (lhook) CALL dr_hook('THRMCONDZ',1,zhook_handle)
120 !
121 !
122 !
123 END SUBROUTINE thrmcondz
subroutine thrmcondz(PSANDZ, PWSATZ, PCONDDRY, PCONDSLD)
Definition: thrmcondz.F90:6