SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
get_mesh_index_lonlatval.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 get_mesh_index_lonlatval(KGRID_PAR,KSSO,PGRID_PAR,PLAT,PLON,KINDEX,KISSOX,KISSOY)
7 ! ###############################################################
8 !
9 !!**** *GET_MESH_INDEX_LONLATVAL* get the grid mesh where point (lat,lon) is located
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! AUTHOR
15 !! ------
16 !!
17 !! E. Martin Meteo-France
18 !!
19 !! MODIFICATION
20 !! ------------
21 !!
22 !! Original 10/2007
23 !!
24 !----------------------------------------------------------------------------
25 !
26 !* 0. DECLARATION
27 ! -----------
28 !
29 USE modd_get_mesh_index_lonlatval, ONLY : xxlim, xylim, xx_min, xx_max, xy_min, &
30  xy_max, xdx, xdy, xxlims, nxids, xdx_max,&
31  nfracd
33 !
35 !
36 !
37 USE yomhook ,ONLY : lhook, dr_hook
38 USE parkind1 ,ONLY : jprb
39 !
40 IMPLICIT NONE
41 !
42 !* 0.1 Declaration of arguments
43 ! ------------------------
44 !
45 INTEGER, INTENT(IN) :: kgrid_par ! size of PGRID_PAR
46 INTEGER, INTENT(IN) :: ksso ! number of subgrid mesh in each direction
47 REAL, DIMENSION(:), INTENT(IN) :: pgrid_par ! grid parameters
48 REAL, DIMENSION(:), INTENT(IN) :: plat ! latitude of the point
49 REAL, DIMENSION(:), INTENT(IN) :: plon ! longitude of the point
50 INTEGER, DIMENSION(:,:), INTENT(OUT) :: kindex ! index of the grid mesh where the point is
51 INTEGER, DIMENSION(:,:), INTENT(OUT) :: kissox ! X index of the subgrid mesh
52 INTEGER, DIMENSION(:,:), INTENT(OUT) :: kissoy ! Y index of the subgrid mesh
53 !
54 !* 0.2 Declaration of other local variables
55 ! ------------------------------------
56 !
57 REAL :: xlon0
58 REAL :: zvalx
59 !
60 REAL, DIMENSION(SIZE(PLON)) :: zlon
61 !
62 REAL, DIMENSION(:), ALLOCATABLE :: zx ! X Lambert coordinate
63 REAL, DIMENSION(:), ALLOCATABLE :: zy ! Y Lambert coordinate
64 REAL, DIMENSION(:), ALLOCATABLE :: zxlim ! X Lambert coordinate
65 !
66 INTEGER :: isize, ifact
67 INTEGER :: il, icpt ! Grid dimension
68 INTEGER :: jl ! loop counter in lambert grid
69 INTEGER :: ji, jj ! loop counter on input points
70 INTEGER, DIMENSION(SIZE(PLAT),2) :: ici
71 INTEGER, DIMENSION(1) :: idx0
72 !
73 LOGICAL, DIMENSION(SIZE(PLAT)) :: gmask
74 !
75 REAL(KIND=JPRB) :: zhook_handle
76 !----------------------------------------------------------------------------
77 !
78 !
79 IF (lhook) CALL dr_hook('GET_MESH_INDEX_LONLATVAL',0,zhook_handle)
80 IF (.NOT. ALLOCATED(xxlim)) THEN
81 !
82 !* 1. Uncode parameters of the grid
83 ! -----------------------------
84 !
85  CALL get_gridtype_lonlatval(pgrid_par,kl=il)
86 !
87  ifact = floor(sqrt(float(il)))
88  isize = floor(float(il) / ifact)
89  ALLOCATE(nfracd(ifact+1))
90  nfracd(1) = 1
91  nfracd(ifact+1) = il
92  DO jj=2,ifact
93  nfracd(jj) = 1 + (jj-1)*isize
94  ENDDO
95 !
96  ALLOCATE(zx(il))
97  ALLOCATE(zy(il))
98  ALLOCATE(xdx(il))
99  ALLOCATE(xdy(il))
100  ALLOCATE(xxlim(il))
101  ALLOCATE(xylim(il))
102 
103  ALLOCATE(xxlims(0:il))
104  ALLOCATE(nxids(il))
105 
106  ALLOCATE(zxlim(il))
107 !
108  CALL get_gridtype_lonlatval(pgrid_par,px=zx,py=zy,pdx=xdx,pdy=xdy)
109 !
110 !* 2. Limits of grid meshes in x and y
111 ! --------------------------------
112 !
113  xxlim(:)=zx(:)-xdx(:)/2.
114  xylim(:)=zy(:)-xdy(:)/2.
115 
116  xx_min = minval(xxlim)
117  xx_max = maxval(xxlim+xdx)
118  xy_min = minval(xylim)
119  xy_max = maxval(xylim+xdy)
120 
121  xdx_max = minval(xdx)
122 
123  zxlim(:) = xxlim(:)
124 
125  zvalx = maxval(zxlim) + 1.
126  DO ji=1,il
127  idx0 = minloc(zxlim)
128  xxlims(ji) = zxlim(idx0(1))
129  nxids(ji) = idx0(1)
130  zxlim(idx0(1)) = zvalx
131  ENDDO
132  xxlims(0) = xxlims(1) - xdx_max -1.
133 
134  DEALLOCATE(zxlim)
135  DEALLOCATE(zx )
136  DEALLOCATE(zy )
137 
138 END IF
139 !
140 xlon0 = 0.5*(xx_min+xx_max)
141 !
142 !* 3. Projection
143 ! ----------
144 !
145  CALL get_gridtype_lonlatval(pgrid_par)
146 !
147  zlon(:) = plon(:)+nint((xlon0-plon(:))/360.)*360.
148 !
149 gmask(:) = .false.
150 DO jl=1,SIZE(plat)
151  IF ( zlon(jl)<xx_min .OR. zlon(jl)>xx_max &
152  .OR. plat(jl)<xy_min .OR. plat(jl)>xy_max ) gmask(jl) = .true.
153 ENDDO
154 
155 !* 5. Localisation of the data points on (x,y) grid
156 ! ---------------------------------------------
157 !
158 ifact = SIZE(nfracd) - 1
159 !
160 kindex(:,:)=0
161 !
162 kissox(:,:) = 0
163 kissoy(:,:) = 0
164 !
165 ici(:,:) = 0
166 !$OMP PARALLEL DO PRIVATE(JL,JI,JJ)
167 DO jl=1,SIZE(plat)
168  !
169  IF (gmask(jl)) cycle
170  !
171  frac: &
172  DO jj=ifact,1,-1
173  !
174  IF (zlon(jl)>xxlims(nfracd(jj))) THEN
175  !
176  DO ji = nfracd(jj+1),nfracd(jj),-1
177  IF (zlon(jl)>xxlims(ji)) THEN
178  ici(jl,2) = ji
179  EXIT
180  ENDIF
181  ENDDO
182  !
183  DO ji = ici(jl,2),0,-1
184  IF (zlon(jl)>=xxlims(ji)+xdx_max) THEN
185  ici(jl,1) = ji+1
186  EXIT
187  ENDIF
188  ENDDO
189  !
190  EXIT frac
191  !
192  ENDIF
193  !
194  ENDDO frac
195  !
196 ENDDO
197 !$OMP END PARALLEL DO
198 !
199 DO jl=1,SIZE(plat)
200  !
201  IF (gmask(jl)) cycle
202  !
203  icpt = 0
204  DO ji=ici(jl,1),ici(jl,2)
205  !
206  IF (plat(jl)>xylim(nxids(ji)) .AND. plat(jl)<xylim(nxids(ji))+xdy(nxids(ji)) &
207  .AND. zlon(jl)<xxlims(ji)+xdx(nxids(ji))) THEN
208  !
209  icpt = icpt + 1
210  !
211  kindex(icpt,jl) = nxids(ji)
212  !
213  IF (ksso/=0) THEN
214  kissox(icpt,jl) = 1 + int( float(ksso) * (zlon(jl)-xxlim(nxids(ji)))/xdx(nxids(ji)) )
215  kissoy(icpt,jl) = 1 + int( float(ksso) * (plat(jl)-xylim(nxids(ji)))/xdy(nxids(ji)) )
216  ENDIF
217  !
218  IF (icpt==novmx) EXIT
219  !
220  ENDIF
221  !
222  ENDDO
223  !
224 ENDDO
225 !
226 IF (lhook) CALL dr_hook('GET_MESH_INDEX_LONLATVAL',1,zhook_handle)
227 !-------------------------------------------------------------------------------
228 !
229 END SUBROUTINE get_mesh_index_lonlatval
subroutine get_mesh_index_lonlatval(KGRID_PAR, KSSO, PGRID_PAR, PLAT, PLON, KINDEX, KISSOX, KISSOY)
subroutine get_gridtype_lonlatval(PGRID_PAR, KL, PX, PY, PDX, PDY)