SURFEX v8.1
General documentation of Surfex
trip_nearest.F90
Go to the documentation of this file.
1 ! #########
2  SUBROUTINE trip_nearest(KNI,KCODE,PLON,PLAT,PFIELD)
3 ! #########################################################
4 !
5 !!**** *TRIP_NEAREST*
6 !!
7 !! PURPOSE
8 !! -------
9 !!
10 !! Approximation : Pythagora theorem is used on an
11 !! equirectangular projection for
12 !! computing performance.
13 !!
14 !! The points are all on only one grid (defined with the coordinates
15 !! of all the points). The code to apply for each point is:
16 !!
17 !! KCODE>0 : data point (with field valid for interpolation)
18 !! KCODE=-1: point to ignore
19 !! KCODE=0 : point to interpolate
20 !!
21 !!
22 !!
23 !! METHOD
24 !! ------
25 !!
26 !! EXTERNAL
27 !! --------
28 !!
29 !! IMPLICIT ARGUMENTS
30 !! ------------------
31 !!
32 !!
33 !!
34 !! REFERENCE
35 !! ---------
36 !!
37 !! AUTHOR
38 !! ------
39 !!
40 !! B. Decharme Meteo-France
41 !!
42 !! MODIFICATION
43 !! ------------
44 !!
45 !! Original 10/2016
46 !! Modification
47 !----------------------------------------------------------------------------
48 !
49 !* 0. DECLARATION
50 ! -----------
51 !
52 USE modd_trip_par, ONLY : xundef, xrad, xpi
53 !
54 USE yomhook ,ONLY : lhook, dr_hook
55 USE parkind1 ,ONLY : jprb
56 !
57 IMPLICIT NONE
58 !
59 !* 0.1 Declaration of arguments
60 ! ------------------------
61 !
62 INTEGER, INTENT(IN) :: KNI !
63 INTEGER,DIMENSION(KNI), INTENT(INOUT) :: KCODE ! code for each point
64  ! >0 point used for interpolation
65  ! 0 point to interpolate
66  ! -1 point not used
67 REAL, DIMENSION(KNI), INTENT(IN) :: PLON ! x of each grid mesh.
68 REAL, DIMENSION(KNI), INTENT(IN) :: PLAT ! y of each grid mesh.
69 REAL, DIMENSION(KNI), INTENT(INOUT) :: PFIELD ! pgd field on grid mesh.
70 !
71 !* 0.2 Declaration of local variables
72 ! ------------------------------
73 !
74 INTEGER :: JD ! data point index
75 INTEGER :: JS ! loop counter on data points
76 INTEGER :: JL ! loop counter on points to initialize
77 !
78 REAL, DIMENSION(KNI) :: ZDIST ! square distance between two interpolating and interpolated points
79 REAL, DIMENSION(KNI) :: ZNDIST ! nearest square distances
80 REAL, DIMENSION(KNI) :: ZNVAL ! corresponding field values
81 REAL, DIMENSION(KNI) :: ZLON
82 REAL, DIMENSION(KNI) :: ZLAT
83 REAL, DIMENSION(KNI) :: ZDLON
84 REAL :: ZRAD
85 !
86 INTEGER :: ISCAN ! number of points to scan
87 INTEGER, DIMENSION(KNI) :: IINDEX ! list of index to scan
88 !
89 REAL(KIND=JPRB) :: ZHOOK_HANDLE
90 !
91 !-------------------------------------------------------------------------------
92 !
93 IF (lhook) CALL dr_hook('TRIP_NEAREST',0,zhook_handle)
94 !
95 zrad = xpi/180.
96 !
97 zlon(:) = plon(:)*zrad
98 zlat(:) = plat(:)*zrad
99 !
100 iindex(:) = 0
101 !
102 iscan = count(kcode(:)>0)
103 !
104 js = 0
105 DO jd=1,kni
106  IF (kcode(jd)>0) THEN
107  js = js+1
108  iindex(js) = jd
109  END IF
110 END DO
111 !
112 DO jl=1,kni
113  !
114  IF (kcode(jl)/=0) cycle
115  !
116  zndist(jl) = xundef
117  znval(jl) = 0.0
118  !
119  DO js=1,iscan
120  !
121  jd = iindex(js)
122  !
123  zdlon(jl)= zlon(jd)-zlon(jl)
124  IF(zdlon(jl)>=xpi)zdlon(jl) = abs(2.0*xpi-zdlon(jl))
125 
126  zdist(jl)= (zdlon(jl)*cos(0.5*(zlat(jd)+zlat(jl))))**2 + (zlat(jd)-zlat(jl))**2
127  !
128  IF ( zdist(jl)>zndist(jl) ) cycle
129  !
130  zndist(jl) = zdist(jl)
131  znval(jl) = pfield(jd)
132  !
133  ENDDO
134  !
135  pfield(jl) = znval(jl)
136  !
137 END DO
138 !
139 IF (lhook) CALL dr_hook('TRIP_NEAREST',1,zhook_handle)
140 !
141 !-------------------------------------------------------------------------------
142 !
143 END SUBROUTINE trip_nearest
subroutine trip_nearest(KNI, KCODE, PLON, PLAT, PFIELD)
Definition: trip_nearest.F90:3
integer, parameter jprb
Definition: parkind1.F90:32
real, save xrad
logical lhook
Definition: yomhook.F90:15
real, save xpi
real, save xundef
static int count
Definition: memory_hook.c:21