SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
ecoclimap2_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 ! #########################
6  SUBROUTINE ecoclimap2_lai (DTCO)
7 ! #########################
8 !
9 !!**** *ECOCLIMAP2_LAI* initializes cover-field correspondance arrays
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! METHOD
15 !! ------
16 !!
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !! AUTHOR
28 !! ------
29 !!
30 !! V. Masson Meteo-France
31 !!
32 !! MODIFICATION
33 !! ------------
34 !!
35 !! Original 09/2008
36 !----------------------------------------------------------------------------
37 !
38 !* 0. DECLARATION
39 ! -----------
40 !
41 !
43 !
44 USE modd_surf_par, ONLY : xundef
45 !
46 USE modd_data_cover, ONLY : xdata_lai, xdata_lai_all_years, lclim_lai, &
47  neco2_start_year, neco2_end_year
48 USE modd_data_cover_par, ONLY : nvegtype, jpcover
49 
50 !
51 !
52 USE yomhook ,ONLY : lhook, dr_hook
53 USE parkind1 ,ONLY : jprb
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1 Declaration of arguments
58 ! ------------------------
59 !
60 !* 0.2 Declaration of local variables
61 ! ------------------------------
62 !
63 !
64 TYPE(data_cover_t), INTENT(INOUT) :: dtco
65 !
66 REAL, DIMENSION(36) :: zlai
67 !
68 INTEGER :: iyear ! year index
69 INTEGER :: jcover,jvegtype ! loop counters on covers and decades
70 INTEGER :: jyear ! loop counter on years
71 REAL(KIND=JPRB) :: zhook_handle
72 !
73 !-------------------------------------------------------------------------------
74 !
75 !* 1. definition of LAI data
76 ! ----------------------
77 !
78 IF (lhook) CALL dr_hook('ECOCLIMAP2_LAI',0,zhook_handle)
79 xdata_lai(301:,:,:) = xundef
80 !
81 !* 2. if averaged LAI
82 ! ---------------
83 !
84 IF (lclim_lai .OR. dtco%NYEAR<neco2_start_year .OR. dtco%NYEAR>neco2_end_year) THEN
85 !
86  DO jcover=301,jpcover
87  DO jvegtype=1,nvegtype
88  IF (dtco%XDATA_VEGTYPE(jcover,jvegtype).ne.0.) THEN
89  zlai(:) = 0.
90  DO jyear=1,5
91  zlai(:) = zlai(:) + xdata_lai_all_years(jcover,(jyear-1)*36+1:jyear*36,jvegtype)/5.
92  END DO
93  xdata_lai(jcover,:,jvegtype) = zlai(:)
94  ENDIF
95  END DO
96  END DO
97 
98 !
99 !* 3. if LAI of a specific year
100 ! -------------------------
101 ELSE
102 !
103  iyear = dtco%NYEAR - neco2_start_year
104  DO jcover=301,jpcover
105  DO jvegtype=1,nvegtype
106  IF (dtco%XDATA_VEGTYPE(jcover,jvegtype).ne.0.) THEN
107  xdata_lai(jcover,:,jvegtype)=xdata_lai_all_years(jcover,iyear*36+1:(iyear+1)*36,jvegtype)
108  ENDIF
109  ENDDO
110  ENDDO
111 !
112 END IF
113 IF (lhook) CALL dr_hook('ECOCLIMAP2_LAI',1,zhook_handle)
114 !
115 !
116 !-------------------------------------------------------------------------------
117 !
118 END SUBROUTINE ecoclimap2_lai
subroutine ecoclimap2_lai(DTCO)