SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
dry_wet_soil_albedos.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 ! #########################
7 ! #########################
8 !
10 !
11 !
12  SUBROUTINE dry_wet_soil_albedos_1d(PSAND,PCLAY, &
13  pvegtype, &
14  palbnir_dry,palbvis_dry,palbuv_dry, &
15  palbnir_wet,palbvis_wet,palbuv_wet )
16 !
17 !
18 !* 0.1 declarations of arguments
19 ! -------------------------
20 !
21 !
22 REAL, DIMENSION(:), INTENT(IN) :: psand ! sand fraction
23 REAL, DIMENSION(:), INTENT(IN) :: pclay ! clay fraction
24 REAL, DIMENSION(:,:), INTENT(IN):: pvegtype ! vegetation type
25 !
26 REAL, DIMENSION(:), INTENT(OUT) :: palbvis_dry ! visible, near infra-red and UV
27 REAL, DIMENSION(:), INTENT(OUT) :: palbnir_dry ! dry bare soil albedo
28 REAL, DIMENSION(:), INTENT(OUT) :: palbuv_dry !
29 REAL, DIMENSION(:), INTENT(OUT) :: palbvis_wet ! visible, near infra-red and UV
30 REAL, DIMENSION(:), INTENT(OUT) :: palbnir_wet ! wet bare soil albedo
31 REAL, DIMENSION(:), INTENT(OUT) :: palbuv_wet !
32 !
33 END SUBROUTINE dry_wet_soil_albedos_1d
34 !
35 !
36  SUBROUTINE dry_wet_soil_albedos_2d(PSAND,PCLAY, &
37  pvegtype, &
38  palbnir_dry,palbvis_dry,palbuv_dry, &
39  palbnir_wet,palbvis_wet,palbuv_wet )
40 !
41 !
42 !* 0.1 declarations of arguments
43 ! -------------------------
44 !
45 !
46 REAL, DIMENSION(:,:), INTENT(IN) :: psand ! sand fraction
47 REAL, DIMENSION(:,:), INTENT(IN) :: pclay ! clay fraction
48 REAL, DIMENSION(:,:,:), INTENT(IN):: pvegtype ! vegetation type
49 !
50 REAL, DIMENSION(:,:), INTENT(OUT) :: palbvis_dry ! visible, near infra-red and UV
51 REAL, DIMENSION(:,:), INTENT(OUT) :: palbnir_dry ! dry bare soil albedo
52 REAL, DIMENSION(:,:), INTENT(OUT) :: palbuv_dry !
53 REAL, DIMENSION(:,:), INTENT(OUT) :: palbvis_wet ! visible, near infra-red and UV
54 REAL, DIMENSION(:,:), INTENT(OUT) :: palbnir_wet ! wet bare soil albedo
55 REAL, DIMENSION(:,:), INTENT(OUT) :: palbuv_wet !
56 !
57 END SUBROUTINE dry_wet_soil_albedos_2d
58 !
59 END INTERFACE
60 !
62 !
63 ! ##################################################################
64  SUBROUTINE dry_wet_soil_albedos_1d(PSAND,PCLAY, &
65  pvegtype, &
66  palbnir_dry,palbvis_dry,palbuv_dry, &
67  palbnir_wet,palbvis_wet,palbuv_wet )
68 ! ##################################################################
69 !
70 !!**** *DRY_WET_SOIL_ALBEDOS*
71 !!
72 !! PURPOSE
73 !! -------
74 ! computes the albedo of bare soil, for dry or wet conditions
75 !
76 !
77 !!** METHOD
78 !! ------
79 !
80 !! EXTERNAL
81 !! --------
82 !!
83 !! IMPLICIT ARGUMENTS
84 !! ------------------
85 !!
86 !!
87 !! REFERENCE
88 !! ---------
89 !!
90 !!
91 !! AUTHOR
92 !! ------
93 !! V. Masson * Meteo-France *
94 !!
95 !! MODIFICATIONS
96 !! -------------
97 !! Original 17/12/99
98 !
99 ! (V. Masson) 16/02/01 Better fit with ISLSCP2;
100 ! Ba et al 2001;
101 ! Pinty et al 2000
102 ! (V. Masson) 01/2004 Add UV albedo
103 ! (R. Alkama) 05/2012 Add 7 new vegtype (19 rather than 12)
104 !-------------------------------------------------------------------------------
105 !
106 !* 0. DECLARATIONS
107 ! ------------
108 !
109 USE modd_data_cover_par, ONLY : nvt_park, nvt_tebd, nvt_bone, nvt_trbe, nvt_trbd, &
110  nvt_tebe, nvt_tene, nvt_bobd, nvt_bond, nvt_shrb, &
111  nvt_c3, nvt_c4, nvt_irr, nvt_gras, nvt_bogr, &
112  nvt_trog
113 !
114 !
115 !
116 USE yomhook ,ONLY : lhook, dr_hook
117 USE parkind1 ,ONLY : jprb
118 !
119 IMPLICIT NONE
120 !
121 !* 0.1 declarations of arguments
122 ! -------------------------
123 !
124 REAL, DIMENSION(:), INTENT(IN) :: psand ! sand fraction
125 REAL, DIMENSION(:), INTENT(IN) :: pclay ! clay fraction
126 REAL, DIMENSION(:,:), INTENT(IN):: pvegtype ! vegetation type
127 !
128 REAL, DIMENSION(:), INTENT(OUT) :: palbvis_dry ! visible, near infra-red and UV
129 REAL, DIMENSION(:), INTENT(OUT) :: palbnir_dry ! dry bare soil albedo
130 REAL, DIMENSION(:), INTENT(OUT) :: palbuv_dry !
131 REAL, DIMENSION(:), INTENT(OUT) :: palbvis_wet ! visible, near infra-red and UV
132 REAL, DIMENSION(:), INTENT(OUT) :: palbnir_wet ! wet bare soil albedo
133 REAL, DIMENSION(:), INTENT(OUT) :: palbuv_wet !
134 REAL(KIND=JPRB) :: zhook_handle
135 !
136 !-------------------------------------------------------------------------------
137 !
138 IF (lhook) CALL dr_hook('MODI_DRY_WET_SOIL_ALBEDOS:DRY_WET_SOIL_ALBEDOS_1D',0,zhook_handle)
139 palbvis_dry(:) = 0.05 + ( 0.05 + max(0.30 * psand(:), 0.10) ) &
140  * ( 1. - 0.9 * ( pvegtype(:,nvt_c3) &
141  + pvegtype(:,nvt_c4) &
142  + pvegtype(:,nvt_irr) &
143  + pvegtype(:,nvt_gras) &
144  + pvegtype(:,nvt_trog) &
145  + pvegtype(:,nvt_park) &
146  + pvegtype(:,nvt_trbe) &
147  + pvegtype(:,nvt_bone) &
148  + pvegtype(:,nvt_tebd) &
149  + pvegtype(:,nvt_trbd) &
150  + pvegtype(:,nvt_tebe) &
151  + pvegtype(:,nvt_tene) &
152  + pvegtype(:,nvt_bobd) &
153  + pvegtype(:,nvt_bond) &
154  + pvegtype(:,nvt_bogr) &
155  + pvegtype(:,nvt_shrb))**2 )
156 !
157 palbnir_dry(:) = palbvis_dry(:) + 0.10
158 !
159 palbuv_dry(:) = 0.06 + 0.14 * psand(:)
160 !
161 palbvis_wet(:) = palbvis_dry(:) / 2.
162 palbnir_wet(:) = palbnir_dry(:) / 2.
163 palbuv_wet(:) = palbuv_dry(:) / 2.
164 IF (lhook) CALL dr_hook('MODI_DRY_WET_SOIL_ALBEDOS:DRY_WET_SOIL_ALBEDOS_1D',1,zhook_handle)
165 !
166 !-------------------------------------------------------------------------------
167 !
168 END SUBROUTINE dry_wet_soil_albedos_1d
169 !
170 ! ##################################################################
171  SUBROUTINE dry_wet_soil_albedos_2d(PSAND,PCLAY, &
172  pvegtype, &
173  palbnir_dry,palbvis_dry,palbuv_dry, &
174  palbnir_wet,palbvis_wet,palbuv_wet )
175 ! ##################################################################
176 !
177 !!**** *DRY_WET_SOIL_ALBEDOS*
178 !!
179 !! PURPOSE
180 !! -------
181 ! computes the albedo of bare soil, for dry or wet conditions
182 !
183 !
184 !!** METHOD
185 !! ------
186 !
187 !! EXTERNAL
188 !! --------
189 !!
190 !! IMPLICIT ARGUMENTS
191 !! ------------------
192 !!
193 !!
194 !! REFERENCE
195 !! ---------
196 !!
197 !!
198 !! AUTHOR
199 !! ------
200 !! V. Masson * Meteo-France *
201 !!
202 !! MODIFICATIONS
203 !! -------------
204 !! Original 17/12/99
205 ! (V. Masson) 16/02/01 Better fit with ISLSCP2;
206 ! Ba et al 2001;
207 ! Pinty et al 2000
208 ! (V. Masson) Add UV albedo
209 !-------------------------------------------------------------------------------
210 !
211 !* 0. DECLARATIONS
212 ! ------------
213 !
214 USE modd_surf_par, ONLY : xundef
215 USE modd_data_cover_par, ONLY : nvt_park, nvt_tebd, nvt_bone, nvt_trbe, nvt_trbd, &
216  nvt_tebe, nvt_tene, nvt_bobd, nvt_bond, nvt_shrb, &
217  nvt_c3, nvt_c4, nvt_irr, nvt_gras, nvt_bogr, &
218  nvt_trog
219 !
220 !
221 USE yomhook ,ONLY : lhook, dr_hook
222 USE parkind1 ,ONLY : jprb
223 !
224 IMPLICIT NONE
225 !
226 !* 0.1 declarations of arguments
227 ! -------------------------
228 !
229 REAL, DIMENSION(:,:), INTENT(IN) :: psand ! sand fraction
230 REAL, DIMENSION(:,:), INTENT(IN) :: pclay ! clay fraction
231 REAL, DIMENSION(:,:,:), INTENT(IN):: pvegtype ! vegetation type
232 !
233 REAL, DIMENSION(:,:), INTENT(OUT) :: palbvis_dry ! visible, near infra-red and UV
234 REAL, DIMENSION(:,:), INTENT(OUT) :: palbnir_dry ! dry bare soil albedo
235 REAL, DIMENSION(:,:), INTENT(OUT) :: palbuv_dry !
236 REAL, DIMENSION(:,:), INTENT(OUT) :: palbvis_wet ! visible, near infra-red and UV
237 REAL, DIMENSION(:,:), INTENT(OUT) :: palbnir_wet ! wet bare soil albedo
238 REAL, DIMENSION(:,:), INTENT(OUT) :: palbuv_wet !
239 REAL(KIND=JPRB) :: zhook_handle
240 !-------------------------------------------------------------------------------
241 !
242 IF (lhook) CALL dr_hook('MODI_DRY_WET_SOIL_ALBEDOS:DRY_WET_SOIL_ALBEDOS_2D',0,zhook_handle)
243 palbvis_dry(:,:) = xundef
244 palbnir_dry(:,:) = xundef
245 palbuv_dry(:,:) = xundef
246 palbvis_wet(:,:) = xundef
247 palbnir_wet(:,:) = xundef
248 palbuv_wet(:,:) = xundef
249 !
250 WHERE (psand(:,:)/=xundef)
251  palbvis_dry(:,:) = 0.05 + ( 0.05 + max( 0.30 * psand(:,:), 0.10) ) &
252  * ( 1. - 0.9 * ( pvegtype(:,:,nvt_c3) &
253  + pvegtype(:,:,nvt_c4) &
254  + pvegtype(:,:,nvt_irr) &
255  + pvegtype(:,:,nvt_gras) &
256  + pvegtype(:,:,nvt_trog) &
257  + pvegtype(:,:,nvt_park) &
258  + pvegtype(:,:,nvt_trbe) &
259  + pvegtype(:,:,nvt_bone) &
260  + pvegtype(:,:,nvt_tebd) &
261  + pvegtype(:,:,nvt_trbd) &
262  + pvegtype(:,:,nvt_tebe) &
263  + pvegtype(:,:,nvt_tene) &
264  + pvegtype(:,:,nvt_bobd) &
265  + pvegtype(:,:,nvt_bond) &
266  + pvegtype(:,:,nvt_bogr) &
267  + pvegtype(:,:,nvt_shrb))**2 )
268  !
269  palbnir_dry(:,:) = palbvis_dry(:,:) + 0.10
270  !
271  palbuv_dry(:,:) = 0.06 + 0.14 * psand(:,:)
272  !
273  palbvis_wet(:,:) = palbvis_dry(:,:) / 2.
274  palbnir_wet(:,:) = palbnir_dry(:,:) / 2.
275  palbuv_wet(:,:) = palbuv_dry(:,:) / 2.
276 END WHERE
277 IF (lhook) CALL dr_hook('MODI_DRY_WET_SOIL_ALBEDOS:DRY_WET_SOIL_ALBEDOS_2D',1,zhook_handle)
278 !
279 !-------------------------------------------------------------------------------
280 !
281 END SUBROUTINE dry_wet_soil_albedos_2d
282 
subroutine dry_wet_soil_albedos_1d(PSAND, PCLAY, PVEGTYPE, PALBNIR_DRY, PALBVIS_DRY, PALBUV_DRY, PALBNIR_WET, PALBVIS_WET, PALBUV_WET)
subroutine dry_wet_soil_albedos_2d(PSAND, PCLAY, PVEGTYPE, PALBNIR_DRY, PALBVIS_DRY, PALBUV_DRY, PALBNIR_WET, PALBVIS_WET, PALBUV_WET)