SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
average1_ldb.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_ldb(KLUOUT,KNBLINES,PLAT,PLON,PVALUE,HTYPE,PNODATA)
7 ! #######################################################
8 !
9 !!**** *AVERAGE1_LDB*
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! METHOD
15 !! ------
16 !!
17 !! EXTERNAL
18 !! --------
19 !!
20 !! IMPLICIT ARGUMENTS
21 !! ------------------
22 !!
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !! AUTHOR
28 !! ------
29 !!
30 !! S. Faroux Meteo-France
31 !!
32 !! MODIFICATION
33 !! ------------
34 !!
35 !! Original 17/02/11
36 !!
37 !----------------------------------------------------------------------------
38 !
39 !* 0. DECLARATION
40 ! -----------
41 !
42 USE modd_pgdwork, ONLY : xtng, nsize
43 USE modd_data_lake, ONLY : xboundgraddepth_ldb, xboundgradstatus_ldb
44 !
46 !
47 USE modi_get_mesh_index
48 USE modi_abor1_sfx
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  CHARACTER(LEN=1), INTENT(IN) :: htype
64 REAL, OPTIONAL, INTENT(IN) :: pnodata
65 !
66 !* 0.2 Declaration of other local variables
67 ! ------------------------------------
68 !
69 REAL, DIMENSION(:), ALLOCATABLE :: zbound
70 !
71 INTEGER, DIMENSION(NOVMX,SIZE(PLAT)) :: iindex ! mesh index of all input points
72  ! 0 indicates the point is out of the domain
73 !
74 REAL, DIMENSION(SIZE(PLAT)) :: zvalue
75 REAL :: znodata
76 !
77 REAL :: zcut
78 INTEGER :: jloop, jgrad, jover ! loop index on input arrays
79 REAL(KIND=JPRB) :: zhook_handle
80 !----------------------------------------------------------------------------
81 !
82 !* 1. Get position
83 ! ------------
84 !
85 IF (lhook) CALL dr_hook('AVERAGE1_LDB',0,zhook_handle)
86 !
87 SELECT CASE (htype)
88 !
89  CASE('D')
90  ALLOCATE(zbound(SIZE(xboundgraddepth_ldb)))
91  zbound(:) = xboundgraddepth_ldb(:)
92 !
93  CASE('S')
94  ALLOCATE(zbound(SIZE(xboundgradstatus_ldb)))
95  zbound(:) = xboundgradstatus_ldb(:)
96 !
97  CASE default
98  CALL abor1_sfx("AVERAGE1_LDB: HTYPE NOT SUPPORTED")
99 !
100 END SELECT
101 !
102 !
103 IF (present(pnodata)) THEN
104  zvalue(:) = pvalue(:)
105  znodata = pnodata
106  CALL get_mesh_index(kluout,knblines,plat,plon,iindex,zvalue,znodata)
107 ELSE
108  zvalue(:) = 1.
109  znodata = 0.
110  CALL get_mesh_index(kluout,knblines,plat,plon,iindex)
111 ENDIF
112 !
113 !* 2. Loop on all input data points
114 ! -----------------------------
115 !
116 bloop: &
117 DO jloop = 1 , SIZE(plat)
118 !
119  DO jover = 1, novmx
120 !
121 !* 3. Tests on position
122 ! -----------------
123 !
124  IF (iindex(jover,jloop)==0) cycle bloop
125 !
126 !* 4. Test on value meaning
127 ! ---------------------
128 !
129  zcut = pvalue(jloop)
130 !
131  DO jgrad = 1, SIZE(zbound)-1
132  IF (zcut.GT.zbound(jgrad) .AND. zcut.LE.zbound(jgrad+1)) THEN
133  xtng(iindex(1,jloop),jgrad) = xtng(iindex(1,jloop),jgrad) + 1
134  EXIT
135  ENDIF
136  ENDDO
137 !
138 !* 5. Summation
139 ! ---------
140 !
141  nsize(iindex(1,jloop))=nsize(iindex(1,jloop))+1
142 !
143  END DO
144 !
145 ENDDO bloop
146 !
147 DEALLOCATE(zbound)
148 !
149 IF (lhook) CALL dr_hook('AVERAGE1_LDB',1,zhook_handle)
150 !
151 !-------------------------------------------------------------------------------
152 !
153 END SUBROUTINE average1_ldb
subroutine get_mesh_index(KLUOUT, KNBLINES, PLAT, PLON, KINDEX, PVALUE, PNODATA, KSSO, KISSOX, KISSOY)
subroutine average1_ldb(KLUOUT, KNBLINES, PLAT, PLON, PVALUE, HTYPE, PNODATA)
Definition: average1_ldb.F90:6
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6