SURFEX v8.1
General documentation of Surfex
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 (KYEAR)
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 USE modd_surf_par, ONLY : xundef
42 !
45 USE modd_data_cover_par, ONLY : nvegtype, jpcover
46 
47 !
48 !
49 USE yomhook ,ONLY : lhook, dr_hook
50 USE parkind1 ,ONLY : jprb
51 !
52 IMPLICIT NONE
53 !
54 !* 0.1 Declaration of arguments
55 ! ------------------------
56 !
57 !* 0.2 Declaration of local variables
58 ! ------------------------------
59 !
60 INTEGER, INTENT(IN) :: KYEAR
61 !
62 REAL, DIMENSION(36) :: ZLAI
63 !
64 INTEGER :: IYEAR ! year index
65 INTEGER :: JCOVER,JVEGTYPE ! loop counters on covers and decades
66 INTEGER :: JYEAR ! loop counter on years
67 REAL(KIND=JPRB) :: ZHOOK_HANDLE
68 !
69 !-------------------------------------------------------------------------------
70 !
71 !* 1. definition of LAI data
72 ! ----------------------
73 !
74 IF (lhook) CALL dr_hook('ECOCLIMAP2_LAI',0,zhook_handle)
75 xdata_lai(301:,:,:) = xundef
76 !
77 !* 2. if averaged LAI
78 ! ---------------
79 !
80 IF (lclim_lai .OR. kyear<neco2_start_year .OR. kyear>neco2_end_year) THEN
81 !
82  DO jcover=301,jpcover
83  DO jvegtype=1,nvegtype
84  zlai(:) = 0.
85  DO jyear=1,5
86  zlai(:) = zlai(:) + xdata_lai_all_years(jcover,(jyear-1)*36+1:jyear*36,jvegtype)/5.
87  END DO
88  xdata_lai(jcover,:,jvegtype) = zlai(:)
89  END DO
90  END DO
91 
92 !
93 !* 3. if LAI of a specific year
94 ! -------------------------
95 ELSE
96 !
97  iyear = kyear - neco2_start_year
98  DO jcover=301,jpcover
99  DO jvegtype=1,nvegtype
100  xdata_lai(jcover,:,jvegtype)=xdata_lai_all_years(jcover,iyear*36+1:(iyear+1)*36,jvegtype)
101  ENDDO
102  ENDDO
103 !
104 END IF
105 IF (lhook) CALL dr_hook('ECOCLIMAP2_LAI',1,zhook_handle)
106 !
107 !
108 !-------------------------------------------------------------------------------
109 !
110 END SUBROUTINE ecoclimap2_lai
real, dimension(:,:,:), allocatable xdata_lai_all_years
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
subroutine ecoclimap2_lai(KYEAR)
logical lhook
Definition: yomhook.F90:15
real, dimension(:,:,:), allocatable xdata_lai