SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
green_from_lai.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 !
9 INTERFACE green_from_lai
10 !
11  FUNCTION green_from_lai_0d(PLAI,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PGREEN)
12 !
13 REAL, INTENT(IN) :: plai ! Leaf area Index
14 REAL, DIMENSION(:), INTENT(IN) :: pvegtype ! type of vegetation
15 LOGICAL, INTENT(IN) :: oagri_to_grass
16 !
17 REAL :: pgreen ! greeness fraction
18 !
19 END FUNCTION green_from_lai_0d
20 !
21 !
22  FUNCTION green_from_lai_1d(PLAI,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PGREEN)
23 !
24 REAL, DIMENSION(:), INTENT(IN) :: plai ! Leaf area Index
25 REAL, DIMENSION(:,:), INTENT(IN) :: pvegtype ! type of vegetation
26 LOGICAL, INTENT(IN) :: oagri_to_grass
27 !
28 REAL, DIMENSION(SIZE(PLAI)) :: pgreen ! greeness fraction
29 !
30 END FUNCTION green_from_lai_1d
31 !
32 !
33  FUNCTION green_from_lai_2d(PLAI,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PGREEN)
34 !
35 REAL, DIMENSION(:,:), INTENT(IN) :: plai ! Leaf area Index
36 REAL, DIMENSION(:,:,:), INTENT(IN) :: pvegtype ! type of vegetation
37 LOGICAL, INTENT(IN) :: oagri_to_grass
38 !
39 REAL, DIMENSION(SIZE(PLAI,1),SIZE(PLAI,2))::pgreen ! greeness fraction
40 !
41 END FUNCTION green_from_lai_2d
42 !
43 
44  FUNCTION green_from_lai_patch_1d(PLAI,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PGREEN)
45 !
46 REAL, DIMENSION(:), INTENT(IN) :: plai ! Leaf area Index for each vegtype
47 REAL, DIMENSION(:), INTENT(IN) :: pvegtype !
48 LOGICAL, INTENT(IN) :: oagri_to_grass
49 !
50 REAL, DIMENSION(SIZE(PLAI)) :: pgreen ! greeness fraction
51 !
52 END FUNCTION green_from_lai_patch_1d
53 !
54 END INTERFACE
55 !
56 END MODULE modi_green_from_lai
57 !
58 ! ####################################################
59  FUNCTION green_from_lai_0d(PLAI,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PGREEN)
60 ! ####################################################
61 !!
62 !! PURPOSE
63 !! -------
64 !
65 ! Calculates coverage of soil by vegetation from leaf
66 ! area index and type of vegetation
67 ! (most of types; forest and vineyards; grassland)
68 !
69 !!** METHOD
70 !! ------
71 !!
72 !! EXTERNAL
73 !! --------
74 !! none
75 !!
76 !! IMPLICIT ARGUMENTS
77 !! ------------------
78 !!
79 !! none
80 !!
81 !! REFERENCE
82 !! ---------
83 !!
84 !!
85 !! AUTHOR
86 !! ------
87 !!
88 !! V. Masson and A. Boone * Meteo-France *
89 !!
90 !! MODIFICATIONS
91 !! -------------
92 !! Original 25/03/99
93 !!
94 !! R. Alkama 05/2012 : Add 7 new vegtype (19 rather than 12)
95 !! B. Decharme 05/2013 new param for equatorial forest
96 !-------------------------------------------------------------------------------
97 !
98 !* 0. DECLARATIONS
99 ! ------------
100 !
101 USE modd_data_cover_par, ONLY : nvt_no, nvt_rock, nvt_snow, nvt_park, &
102  nvt_tebd, nvt_bone, nvt_trbe, nvt_trbd, &
103  nvt_tebe, nvt_tene, nvt_bobd, nvt_bond, &
104  nvt_shrb, nvt_c3, nvt_c4, nvt_irr, &
105  nvt_gras, nvt_bogr, nvt_trog
106 !
107 USE modd_reprod_oper, ONLY : xeverg_veg
108 !
109 USE yomhook ,ONLY : lhook, dr_hook
110 USE parkind1 ,ONLY : jprb
111 !
112 IMPLICIT NONE
113 !
114 !* 0.1 declarations of arguments
115 !
116 REAL, INTENT(IN) :: plai ! Leaf area Index
117 REAL, DIMENSION(:), INTENT(IN) :: pvegtype ! type of vegetation
118 LOGICAL, INTENT(IN) :: oagri_to_grass
119 !
120 REAL :: pgreen ! greeness fraction
121 !
122 !* 0.2 declarations of local variables
123 !
124 REAL :: zlai, zagri
125 REAL(KIND=JPRB) :: zhook_handle
126 !-----------------------------------------------------------------
127 IF (lhook) CALL dr_hook('MODI_GREEN_FROM_LAI:GREEN_FROM_LAI_0D',0,zhook_handle)
128 !
129 zlai = plai
130 IF ( pvegtype(nvt_no ) + pvegtype(nvt_rock)< 1.) THEN
131  zlai = plai / (1.-pvegtype(nvt_no)-pvegtype(nvt_rock))
132 END IF
133 !
134 zagri=(1. - exp( -0.6 * zlai ))
135 IF(oagri_to_grass)zagri=min(zagri,0.95)
136 !
137 pgreen= zagri *(pvegtype(nvt_c4 ) + &! C4 crops
138  pvegtype(nvt_irr ) + &! irrigated crops
139  pvegtype(nvt_c3 ) ) &! C3 crops
140  + min(1. - exp( -0.5 * zlai ),0.95) &
141  *(pvegtype(nvt_trbd) + &! tropical broadleaf deciduous
142  pvegtype(nvt_tebe) + &! temperate broadleaf evergreen
143  pvegtype(nvt_tebd) + &! temperate broadleaf cold-deciduous (summergreen)
144  pvegtype(nvt_tene) + &! temperate needleleaf evergreen
145  pvegtype(nvt_bobd) + &! boreal broadleaf cold-deciduous (summergreen)
146  pvegtype(nvt_bone) + &! boreal needleleaf evergreen
147  pvegtype(nvt_bone) + &! boreal needleleaf cold-deciduous (summergreen)
148  pvegtype(nvt_shrb) ) &! shrub
149  + xeverg_veg * pvegtype(nvt_trbe) &! tropical broadleaf evergreen
150  + min(1. - exp( -0.6 * zlai ),0.95) &
151  *(pvegtype(nvt_gras) + &! grassland
152  pvegtype(nvt_bogr) + &! Boreal grassland
153  pvegtype(nvt_trog) + &! tropical grassland
154  pvegtype(nvt_park) ) &! irr. parks
155  + 0. * pvegtype(nvt_no ) &! no vegetation (smooth)
156  + 0. * pvegtype(nvt_snow) &! no vegetation (snow)
157  + 0. * pvegtype(nvt_rock) ! no vegetation (rocks)
158 !
159 IF (lhook) CALL dr_hook('MODI_GREEN_FROM_LAI:GREEN_FROM_LAI_0D',1,zhook_handle)
160 !-----------------------------------------------------------------
161 !
162 END FUNCTION green_from_lai_0d
163 !
164 ! ####################################################
165  FUNCTION green_from_lai_1d(PLAI,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PGREEN)
166 ! ####################################################
167 !!
168 !! PURPOSE
169 !! -------
170 !
171 ! Calculates coverage of soil by vegetation from leaf
172 ! area index and type of vegetation
173 ! (most of types; forest and vineyards; grassland)
174 !
175 !!** METHOD
176 !! ------
177 !!
178 !! EXTERNAL
179 !! --------
180 !! none
181 !!
182 !! IMPLICIT ARGUMENTS
183 !! ------------------
184 !!
185 !! none
186 !!
187 !! REFERENCE
188 !! ---------
189 !!
190 !!
191 !! AUTHOR
192 !! ------
193 !!
194 !! V. Masson and A. Boone * Meteo-France *
195 !!
196 !! MODIFICATIONS
197 !! -------------
198 !! Original 25/03/99
199 !! B. Decharme 05/2013 new param for equatorial forest
200 !!
201 !-------------------------------------------------------------------------------
202 !
203 !* 0. DECLARATIONS
204 ! ------------
205 !
206 USE modd_data_cover_par, ONLY : nvt_no, nvt_rock, nvt_snow, nvt_park, &
207  nvt_tebd, nvt_bone, nvt_trbe, nvt_trbd, &
208  nvt_tebe, nvt_tene, nvt_bobd, nvt_bond, &
209  nvt_shrb, nvt_c3, nvt_c4, nvt_irr, &
210  nvt_gras, nvt_bogr, nvt_trog
211 !
212 USE modd_reprod_oper, ONLY : xeverg_veg
213 !
214 USE yomhook ,ONLY : lhook, dr_hook
215 USE parkind1 ,ONLY : jprb
216 !
217 IMPLICIT NONE
218 !
219 !* 0.1 declarations of arguments
220 !
221 REAL, DIMENSION(:), INTENT(IN) :: plai ! Leaf area Index
222 REAL, DIMENSION(:,:), INTENT(IN) :: pvegtype ! type of vegetation
223 LOGICAL, INTENT(IN) :: oagri_to_grass
224 !
225 REAL, DIMENSION(SIZE(PLAI)) :: pgreen ! greeness fraction
226 !
227 !* 0.2 declarations of local variables
228 !
229 REAL, DIMENSION(SIZE(PLAI)) :: zlai, zagri
230 REAL(KIND=JPRB) :: zhook_handle
231 !-----------------------------------------------------------------
232 IF (lhook) CALL dr_hook('MODI_GREEN_FROM_LAI:GREEN_FROM_LAI_1D',0,zhook_handle)
233 !
234 zlai(:) = plai(:)
235 WHERE ( pvegtype(:,nvt_no ) + pvegtype(:,nvt_rock) + pvegtype(:,nvt_snow) < 1.)
236  zlai(:) = plai(:) / (1.-pvegtype(:,nvt_no)-pvegtype(:,nvt_rock)-pvegtype(:,nvt_snow))
237 END WHERE
238 !
239 zagri(:)=(1. - exp( -0.6 * zlai(:) ))
240 IF(oagri_to_grass)zagri(:)=min(zagri(:),0.95)
241 !
242 pgreen(:)= zagri(:) *(pvegtype(:,nvt_c4 ) + &! C4 crops
243  pvegtype(:,nvt_irr ) + &! irrigated crops
244  pvegtype(:,nvt_c3 ) ) &! C3 crops
245  + min(1. - exp( -0.5 * zlai(:) ),0.95) &
246  *(pvegtype(:,nvt_trbd) + &! tropical broadleaf deciduous
247  pvegtype(:,nvt_tebe) + &! temperate broadleaf evergreen
248  pvegtype(:,nvt_tebd) + &! temperate broadleaf cold-deciduous (summergreen)
249  pvegtype(:,nvt_tene) + &! temperate needleleaf evergreen
250  pvegtype(:,nvt_bobd) + &! boreal broadleaf cold-deciduous (summergreen)
251  pvegtype(:,nvt_bone) + &! boreal needleleaf evergreen
252  pvegtype(:,nvt_bone) + &! boreal needleleaf cold-deciduous (summergreen)
253  pvegtype(:,nvt_shrb) ) &! shrub
254  + xeverg_veg * pvegtype(:,nvt_trbe) &! tropical broadleaf evergreen
255  + min(1. - exp( -0.6 * zlai(:) ),0.95) &
256  *(pvegtype(:,nvt_gras) + &! grassland
257  pvegtype(:,nvt_bogr) + &! Boreal grassland
258  pvegtype(:,nvt_trog) + &! torp. grass
259  pvegtype(:,nvt_park) ) &! irr. parks
260  + 0. * pvegtype(:,nvt_no ) &! no vegetation (smooth)
261  + 0. * pvegtype(:,nvt_snow) &! no vegetation (snow)
262  + 0. * pvegtype(:,nvt_rock) ! no vegetation (rocks)
263 !
264 IF (lhook) CALL dr_hook('MODI_GREEN_FROM_LAI:GREEN_FROM_LAI_1D',1,zhook_handle)
265 !-----------------------------------------------------------------
266 !
267 END FUNCTION green_from_lai_1d
268 !
269 ! ####################################################
270  FUNCTION green_from_lai_2d(PLAI,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PGREEN)
271 ! ####################################################
272 !!
273 !! PURPOSE
274 !! -------
275 !
276 ! Calculates coverage of soil by vegetation from leaf
277 ! area index and type of vegetation
278 ! (most of types; forest and vineyards; grassland)
279 !
280 !!** METHOD
281 !! ------
282 !!
283 !! EXTERNAL
284 !! --------
285 !! none
286 !!
287 !! IMPLICIT ARGUMENTS
288 !! ------------------
289 !!
290 !! none
291 !!
292 !! REFERENCE
293 !! ---------
294 !!
295 !!
296 !! AUTHOR
297 !! ------
298 !!
299 !! V. Masson and A. Boone * Meteo-France *
300 !!
301 !! MODIFICATIONS
302 !! -------------
303 !! Original 25/03/99
304 !!
305 !-------------------------------------------------------------------------------
306 !
307 !* 0. DECLARATIONS
308 ! ------------
309 !
310 USE modd_data_cover_par, ONLY : nvt_no, nvt_rock, nvt_snow, nvt_park, &
311  nvt_tebd, nvt_bone, nvt_trbe, nvt_trbd, &
312  nvt_tebe, nvt_tene, nvt_bobd, nvt_bond, &
313  nvt_shrb, nvt_c3, nvt_c4, nvt_irr, &
314  nvt_gras, nvt_bogr, nvt_trog
315 USE modd_surf_par, ONLY : xundef
316 !
317 USE modd_reprod_oper, ONLY : xeverg_veg
318 !
319 USE yomhook ,ONLY : lhook, dr_hook
320 USE parkind1 ,ONLY : jprb
321 !
322 IMPLICIT NONE
323 !
324 !* 0.1 declarations of arguments
325 !
326 REAL, DIMENSION(:,:), INTENT(IN) :: plai ! Leaf area Index
327 REAL, DIMENSION(:,:,:), INTENT(IN) :: pvegtype ! type of vegetation
328 LOGICAL, INTENT(IN) :: oagri_to_grass
329 !
330 REAL, DIMENSION(SIZE(PLAI,1),SIZE(PLAI,2))::pgreen ! greeness fraction
331 !
332 !* 0.2 declarations of local variables
333 !
334 REAL, DIMENSION(SIZE(PLAI,1),SIZE(PLAI,2)) :: zlai, zagri
335 REAL(KIND=JPRB) :: zhook_handle
336 !-----------------------------------------------------------------
337 IF (lhook) CALL dr_hook('MODI_GREEN_FROM_LAI:GREEN_FROM_LAI_2D',0,zhook_handle)
338 zlai(:,:) = plai(:,:)
339 WHERE ( pvegtype(:,:,nvt_no ) + pvegtype(:,:,nvt_rock) + pvegtype(:,:,nvt_snow) < 1.)
340  zlai(:,:) = plai(:,:) / (1.-pvegtype(:,:,nvt_no)-pvegtype(:,:,nvt_rock)-pvegtype(:,:,nvt_snow))
341 END WHERE
342 !
343 pgreen(:,:) = xundef
344 zagri(:,:) = xundef
345 !
346 WHERE (plai(:,:) /= xundef)
347  zagri(:,:)=(1. - exp( -0.6 * zlai(:,:) ))
348 ENDWHERE
349 IF(oagri_to_grass)zagri(:,:)=min(zagri(:,:),0.95)
350 !
351 WHERE (plai(:,:) /= xundef)
352 pgreen(:,:)= zagri(:,:) *(pvegtype(:,:,nvt_c4 ) + &! C4 crops
353  pvegtype(:,:,nvt_irr ) + &! irrigated crops
354  pvegtype(:,:,nvt_c3 ) ) &! C3 crops
355  + min((1. - exp( -0.5 * zlai(:,:) )),0.95) &
356  *(pvegtype(:,:,nvt_trbd) + &! tropical broadleaf deciduous
357  pvegtype(:,:,nvt_tebe) + &! temperate broadleaf evergreen
358  pvegtype(:,:,nvt_tebd) + &! temperate broadleaf cold-deciduous (summergreen)
359  pvegtype(:,:,nvt_tene) + &! temperate needleleaf evergreen
360  pvegtype(:,:,nvt_bobd) + &! boreal broadleaf cold-deciduous (summergreen)
361  pvegtype(:,:,nvt_bone) + &! boreal needleleaf evergreen
362  pvegtype(:,:,nvt_bone) + &! boreal needleleaf cold-deciduous (summergreen)
363  pvegtype(:,:,nvt_shrb) ) &! shrub
364  + xeverg_veg * pvegtype(:,:,nvt_trbe) &! tropical broadleaf evergreen
365  + min((1. - exp( -0.6 * zlai(:,:) )),0.95) &
366  *(pvegtype(:,:,nvt_gras) + &! grassland
367  pvegtype(:,:,nvt_bogr) + &! Boreal grassland
368  pvegtype(:,:,nvt_trog) + &! trop grassland
369  pvegtype(:,:,nvt_park) )&! irr. parks
370  + 0. * pvegtype(:,:,nvt_no ) &! no vegetation (smooth)
371  + 0. * pvegtype(:,:,nvt_snow) &! no vegetation (snow)
372  + 0. * pvegtype(:,:,nvt_rock) ! no vegetation (rocks)
373 END WHERE
374 IF (lhook) CALL dr_hook('MODI_GREEN_FROM_LAI:GREEN_FROM_LAI_2D',1,zhook_handle)
375 !
376 !-----------------------------------------------------------------
377 !
378 END FUNCTION green_from_lai_2d
379 !
380 !
381 !
382 ! ####################################################
383  FUNCTION green_from_lai_patch_1d(PLAI,PVEGTYPE,OAGRI_TO_GRASS) RESULT(PGREEN)
384 ! ####################################################
385 !!
386 !! PURPOSE
387 !! -------
388 !
389 ! Calculates coverage of soil by vegetation from leaf
390 ! area index and type of vegetation for each vegetation patch
391 ! (most of types; forest and vineyards; grassland)
392 !
393 !!** METHOD
394 !! ------
395 !!
396 !! EXTERNAL
397 !! --------
398 !! none
399 !!
400 !! IMPLICIT ARGUMENTS
401 !! ------------------
402 !!
403 !! none
404 !!
405 !! REFERENCE
406 !! ---------
407 !!
408 !!
409 !! AUTHOR
410 !! ------
411 !!
412 !! F.Solmon/V.Masson
413 !!
414 !! MODIFICATIONS
415 !! -------------
416 !! Original 25/03/99
417 !!
418 !-------------------------------------------------------------------------------
419 !
420 !* 0. DECLARATIONS
421 ! ------------
422 !
423 USE modd_data_cover_par, ONLY : nvt_no, nvt_rock, nvt_snow, nvt_park, &
424  nvt_tebd, nvt_bone, nvt_trbe, nvt_trbd, &
425  nvt_tebe, nvt_tene, nvt_bobd, nvt_bond, &
426  nvt_shrb, nvt_c3, nvt_c4, nvt_irr, &
427  nvt_gras, nvt_bogr, nvt_trog
428 !
429 USE modd_surf_par, ONLY : xundef
430 !
431 USE modd_reprod_oper, ONLY : xeverg_veg
432 !
433 USE yomhook ,ONLY : lhook, dr_hook
434 USE parkind1 ,ONLY : jprb
435 !
436 IMPLICIT NONE
437 !
438 !* 0.1 declarations of arguments
439 !
440 REAL, DIMENSION(:), INTENT(IN) :: plai ! Leaf area Index
441 REAL, DIMENSION(:), INTENT(IN) :: pvegtype ! type of vegetation
442 LOGICAL, INTENT(IN) :: oagri_to_grass
443 !
444 REAL, DIMENSION(SIZE(PLAI)) :: pgreen ! greeness fraction
445 !
446 !* 0.2 declarations of local variables
447 !
448 REAL, DIMENSION(SIZE(PLAI)) :: zlai
449 REAL(KIND=JPRB) :: zhook_handle
450 !-----------------------------------------------------------------
451 IF (lhook) CALL dr_hook('MODI_GREEN_FROM_LAI:GREEN_FROM_LAI_PATCH_1D',0,zhook_handle)
452 zlai(:) = plai(:)
453 pgreen(:) = xundef
454 !
455 IF(oagri_to_grass)THEN
456  IF (pvegtype(nvt_c4 )>0.) pgreen(nvt_c4 )= min(1. - exp( -0.6 * zlai(nvt_c4 ) ),0.95)
457  IF (pvegtype(nvt_irr )>0.) pgreen(nvt_irr )= min(1. - exp( -0.6 * zlai(nvt_irr ) ),0.95)
458  IF (pvegtype(nvt_c3 )>0.) pgreen(nvt_c3 )= min(1. - exp( -0.6 * zlai(nvt_c3 ) ),0.95)
459 ELSE
460  IF (pvegtype(nvt_c4 )>0.) pgreen(nvt_c4 )= 1. - exp( -0.6 * zlai(nvt_c4 ) )
461  IF (pvegtype(nvt_irr )>0.) pgreen(nvt_irr )= 1. - exp( -0.6 * zlai(nvt_irr ) )
462  IF (pvegtype(nvt_c3 )>0.) pgreen(nvt_c3 )= 1. - exp( -0.6 * zlai(nvt_c3 ) )
463 ENDIF
464 !
465 IF (pvegtype(nvt_tebd)>0.) pgreen(nvt_tebd)= min(1. - exp( -0.5 * zlai(nvt_tebd) ),0.95)
466 IF (pvegtype(nvt_bone)>0.) pgreen(nvt_bone)= min(1. - exp( -0.5 * zlai(nvt_bone) ),0.95)
467 IF (pvegtype(nvt_trbd)>0.) pgreen(nvt_trbd)= min(1. - exp( -0.5 * zlai(nvt_trbd) ),0.95)
468 IF (pvegtype(nvt_tebe)>0.) pgreen(nvt_tebe)= min(1. - exp( -0.5 * zlai(nvt_tebe) ),0.95)
469 IF (pvegtype(nvt_tene)>0.) pgreen(nvt_tene)= min(1. - exp( -0.5 * zlai(nvt_tene) ),0.95)
470 IF (pvegtype(nvt_bobd)>0.) pgreen(nvt_bobd)= min(1. - exp( -0.5 * zlai(nvt_bobd) ),0.95)
471 IF (pvegtype(nvt_bond)>0.) pgreen(nvt_bond)= min(1. - exp( -0.5 * zlai(nvt_bond) ),0.95)
472 IF (pvegtype(nvt_shrb)>0.) pgreen(nvt_shrb)= min(1. - exp( -0.5 * zlai(nvt_shrb) ),0.95)
473 
474 IF (pvegtype(nvt_trbe)>0.) pgreen(nvt_trbe)= xeverg_veg
475 !
476 IF (pvegtype(nvt_gras)>0.) pgreen(nvt_gras)= min(1. - exp( -0.6 * zlai(nvt_gras) ),0.95)
477 IF (pvegtype(nvt_bogr)>0.) pgreen(nvt_bogr)= min(1. - exp( -0.6 * zlai(nvt_bogr) ),0.95)
478 IF (pvegtype(nvt_trog)>0.) pgreen(nvt_trog)= min(1. - exp( -0.6 * zlai(nvt_trog) ),0.95)
479 IF (pvegtype(nvt_park)>0.) pgreen(nvt_park)= min(1. - exp( -0.6 * zlai(nvt_park) ),0.95)
480 !
481 IF (pvegtype(nvt_no )>0.) pgreen(nvt_no )= 0.
482 IF (pvegtype(nvt_snow)>0.) pgreen(nvt_snow)= 0.
483 IF (pvegtype(nvt_rock)>0.) pgreen(nvt_rock)= 0.
484 IF (lhook) CALL dr_hook('MODI_GREEN_FROM_LAI:GREEN_FROM_LAI_PATCH_1D',1,zhook_handle)
485 
486 !
487 END FUNCTION green_from_lai_patch_1d
488 !
489 !--------------------------------------------
490 !
real function, dimension(size(plai, 1), size(plai, 2)) green_from_lai_2d(PLAI, PVEGTYPE, OAGRI_TO_GRASS)
real function, dimension(size(plai)) green_from_lai_1d(PLAI, PVEGTYPE, OAGRI_TO_GRASS)
real function green_from_lai_0d(PLAI, PVEGTYPE, OAGRI_TO_GRASS)
real function, dimension(size(plai)) green_from_lai_patch_1d(PLAI, PVEGTYPE, OAGRI_TO_GRASS)