SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
average1_cover.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 average1_cover(KLUOUT,KNBLINES,PLAT,PLON,PVALUE,PNODATA)
7 ! #######################################################
8 !
9 !!**** *AVERAGE1_COVER* computes the sum of values of a cover fractions
10 !! and the nature of terrain on the grid
11 !! from a data in land-cover file
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !! METHOD
17 !! ------
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !! AUTHOR
30 !! ------
31 !!
32 !! V. Masson Meteo-France
33 !!
34 !! MODIFICATION
35 !! ------------
36 !!
37 !! Original 12/09/95
38 !!
39 !----------------------------------------------------------------------------
40 !
41 !* 0. DECLARATION
42 ! -----------
43 !
44 USE modd_pgdwork, ONLY : xsumcover, nsize
45 !
46 USE modi_get_mesh_index
48 !
49 !
50 USE yomhook ,ONLY : lhook, dr_hook
51 USE parkind1 ,ONLY : jprb
52 !
53 IMPLICIT NONE
54 !
55 !* 0.1 Declaration of arguments
56 ! ------------------------
57 !
58 INTEGER, INTENT(IN) :: kluout
59 INTEGER, INTENT(IN) :: knblines
60 REAL, DIMENSION(:), INTENT(IN) :: plat ! latitude of the point to add
61 REAL, DIMENSION(:), INTENT(IN) :: plon ! longitude of the point to add
62 REAL, DIMENSION(:), INTENT(IN) :: pvalue ! value of the point to add
63 REAL, OPTIONAL, INTENT(IN) :: pnodata
64 !
65 !* 0.2 Declaration of other local variables
66 ! ------------------------------------
67 !
68 INTEGER, DIMENSION(NOVMX,SIZE(PLAT)) :: iindex ! mesh index of all input points
69  ! 0 indicates the point is out of the domain
70 !
71 REAL, DIMENSION(SIZE(PLAT)) :: zvalue
72 REAL :: znodata
73 INTEGER :: jloop, jover ! loop index on input arrays
74 INTEGER :: icoverclass ! class of cover type
75 REAL(KIND=JPRB) :: zhook_handle
76 !----------------------------------------------------------------------------
77 !
78 !
79 !* 1. Get position
80 ! ------------
81 !
82 IF (lhook) CALL dr_hook('AVERAGE1_COVER',0,zhook_handle)
83 !
84 IF (present(pnodata)) THEN
85  zvalue(:) = pvalue(:)
86  znodata = pnodata
87  CALL get_mesh_index(kluout,knblines,plat,plon,iindex,zvalue,znodata)
88 ELSE
89  zvalue(:) = 1.
90  znodata = 0.
91  CALL get_mesh_index(kluout,knblines,plat,plon,iindex)
92 ENDIF
93 !
94 !* 2. Loop on all input data points
95 ! -----------------------------
96 !
97 bloop: &
98 DO jloop = 1 , SIZE(plat)
99 !
100 !* 3. Tests on position
101 ! -----------------
102 !
103  DO jover = 1, novmx
104 
105  IF (iindex(jover,jloop)==0) cycle bloop
106 !
107 !* 4. Test on value meaning
108 ! ---------------------
109 !
110  icoverclass = nint(pvalue(jloop))
111 !
112  IF (icoverclass<1 .OR. icoverclass > SIZE(xsumcover,2) ) cycle
113 !
114 !* 5. Summation
115 ! ---------
116 !
117  nsize(iindex(jover,jloop))=nsize(iindex(jover,jloop))+1
118 !
119 !* 6. Fraction of cover type
120 ! ----------------------
121 !
122  xsumcover(iindex(jover,jloop),icoverclass)=xsumcover(iindex(jover,jloop),icoverclass)+1.
123 !
124  ENDDO
125 !
126 END DO bloop
127 !
128 IF (lhook) CALL dr_hook('AVERAGE1_COVER',1,zhook_handle)
129 !
130 !-------------------------------------------------------------------------------
131 !
132 END SUBROUTINE average1_cover
subroutine get_mesh_index(KLUOUT, KNBLINES, PLAT, PLON, KINDEX, PVALUE, PNODATA, KSSO, KISSOX, KISSOY)
subroutine average1_cover(KLUOUT, KNBLINES, PLAT, PLON, PVALUE, PNODATA)