source: lmdz_wrf/trunk/tools/module_ForInterpolate.F90 @ 734

Last change on this file since 734 was 733, checked in by lfita, 9 years ago

Adding new modules on 'module_ForInterpolate':

  • Interpolate: finds the closest grid point within a projection
  • lonlatFind: Function to search a given value from a coarser version of the data
File size: 18.7 KB
Line 
1! Module to interpolate values from a giving projection
2! To be included in a python
3! f2py -m module_ForInterpolate --f90exec=/usr/bin/gfortran-4.7 -c module_ForInterpolate.F90 module_generic.F90 >& run_f2py.log
4MODULE module_ForInterpolate
5
6  CONTAINS
7
8SUBROUTINE CoarselonlatFind(dx, dy, ilon, ilat, nxlon, nxlat, fraclon, fraclat, lonv, latv, per,      &
9  Nperx, Npery, ilonlat, mindiffLl)
10! Function to search a given value from a coarser version of the data
11
12  USE module_generic
13
14  IMPLICIT NONE
15
16  INTEGER, PARAMETER                                     :: r_k = KIND(1.d0)
17  INTEGER, INTENT(in)                                    :: dx, dy
18  REAL(r_k), DIMENSION(dx,dy), INTENT(in)                :: ilon, ilat
19  REAL(r_k), DIMENSION(Nperx,Npery), INTENT(in)          :: fraclon, fraclat
20  REAL(r_k), INTENT(in)                                  :: lonv, latv, per
21  REAL(r_k), DIMENSION(2), INTENT(in)                    :: nxlon, nxlat
22  INTEGER, INTENT(in)                                    :: Nperx, Npery
23  INTEGER, DIMENSION(2), INTENT(out)                     :: ilonlat
24  REAL(r_k), INTENT(out)                                 :: mindiffLl
25! Local
26  REAL(r_k), DIMENSION(Nperx,Npery)                      :: difffraclonlat
27  REAL(r_k)                                              :: mindifffracLl
28  INTEGER, DIMENSION(2)                                  :: ilonlatfrac
29  INTEGER                                                :: ixbeg, ixend, iybeg, iyend
30  INTEGER                                                :: fracx, fracy
31  REAL(r_k)                                              :: fraclonv, fraclatv
32  REAL(r_k), ALLOCATABLE, DIMENSION(:,:)                 :: difflonlat, lon, lat
33  CHARACTER(LEN=50)                                      :: fname
34 
35! Variables
36! ilon, ilat: original 2D matrices with the longitudes and the latitudes
37! lonv, latv: longitude and latitude to find
38! nxlon, nxlat: minimum and maximum longitude and latitude of the target lon,lat
39! per: fraction of the whole domain (as percentage)
40! Nper[x/y]: period (as fraction over 1) of the fractions of the original grid to use to explore
41! fraclon, fraclat: longitude and latitude fractional matricies to perform the first guess
42
43  fname = 'CoarselonlatFind'
44
45  IF (lonv < nxlon(1) .OR. lonv > nxlon(2)) THEN
46    PRINT *, TRIM(ErrWarnMsg('err'))
47    PRINT *,'  ' // TRIM(fname) // ': longitude outside data range!!'
48    PRINT *,'    given value:', lonv,' outside (',nxlon(1),' ,',nxlon(2),' )'
49    STOP
50  END IF
51  IF (latv < nxlat(1) .OR. latv > nxlat(2)) THEN
52    PRINT *, TRIM(ErrWarnMsg('err'))
53    PRINT *,'  ' // TRIM(fname) // ': latitude outside data range!!'
54    PRINT *,'    given value:', latv,' outside (',nxlat(1),' ,',nxlat(2),' )'
55    STOP
56  END IF
57
58! Initializing variables
59  ixbeg = 0
60  ixend = 0
61  iybeg = 0
62  iyend = 0
63
64  fracx = int(dx*per)
65  fracy = int(dy*per)
66
67!  PRINT *,'fraclon _______'
68!  PRINT *,fraclon
69
70!  PRINT *,'fraclat _______'
71!  PRINT *,fraclat
72
73! Fraction point
74  difffraclonlat = SQRT((fraclon-lonv)**2. + (fraclat-latv)**2.)
75  mindifffracLl = MINVAL(difffraclonlat)
76  ilonlatfrac = index2DArrayR(difffraclonlat, Nperx, Npery, mindifffracLl)
77
78!  PRINT *, 'mindifffracLl:', mindifffracLl, ' ilonlatfrac:', ilonlatfrac
79!  PRINT *, 'frac lon, lat:', fraclon(ilonlatfrac(1),ilonlatfrac(2)), ' ,',                            &
80!    fraclat(ilonlatfrac(1),ilonlatfrac(2))
81!  PRINT *, 'values lon, lat:', lonv, latv
82     
83! Providing fraction range
84  fraclonv = fraclon(ilonlatfrac(1),ilonlatfrac(2))
85  fraclatv = fraclat(ilonlatfrac(1),ilonlatfrac(2))
86
87  IF (fraclonv >= lonv .AND. fraclatv >= latv) THEN
88    IF (ilonlatfrac(1) > 0) THEN
89      ixbeg = (ilonlatfrac(1)-1)*fracx
90      ixend = ilonlatfrac(1)*fracx+1
91    ELSE
92      ixbeg = 0
93      ixend = fracx+1
94    END IF
95    IF (ilonlatfrac(2) > 0) THEN
96      iybeg = (ilonlatfrac(2)-1)*fracy
97      iyend = ilonlatfrac(2)*fracy+1
98    ELSE
99      iybeg = 0
100      iyend = fracy+1
101    END IF
102  ELSE IF (fraclonv < lonv .AND. fraclatv >= latv) THEN
103    IF (ilonlatfrac(1) < Nperx) THEN
104      IF (ilonlatfrac(1) /= 0) THEN
105        ixbeg = (ilonlatfrac(1)-1)*fracx
106        ixend = ilonlatfrac(1)*fracx+1
107      ELSE
108        ixbeg = 0
109        ixend = fracx+1
110      END IF
111    ELSE
112      ixbeg = Nperx*fracx
113      ixend = dx+1
114    END IF
115    IF (ilonlatfrac(2) > 0) THEN
116      iybeg = (ilonlatfrac(2)-1)*fracy
117      iyend = ilonlatfrac(2)*fracy+1
118    ELSE
119      iybeg = 0
120      iyend = fracy+1
121    END IF   
122  ELSE IF (fraclonv < lonv .AND. fraclatv < latv) THEN
123    IF (ilonlatfrac(1) < Nperx) THEN
124      IF (ilonlatfrac(1) /= 0) THEN
125        ixbeg = (ilonlatfrac(1)-1)*fracx
126        ixend = ilonlatfrac(1)*fracx+1
127      ELSE
128        ixbeg = 0
129        ixend = fracx+1
130      END IF
131    ELSE
132      ixbeg = Nperx*fracx
133      ixend = dx+1
134    ENDIF
135    IF (ilonlatfrac(2) < Npery) THEN
136      IF (ilonlatfrac(2) /= 0) THEN
137        iybeg = (ilonlatfrac(2)-1)*fracy
138        iyend = ilonlatfrac(2)*fracy+1
139      ELSE
140        iybeg = 0
141        iyend = fracy+1
142      END IF
143    ELSE
144      iybeg = Npery*fracy
145      iyend = dy+1
146    END IF
147  ELSE IF (fraclonv >= lonv .AND. fraclatv < latv) THEN
148    IF (ilonlatfrac(1) > 0) THEN
149      ixbeg = (ilonlatfrac(1)-1)*fracx
150      ixend = ilonlatfrac(1)*fracx+1
151    ELSE
152      ixbeg = 0
153      ixend = fracx+1
154    END IF
155    IF (ilonlatfrac(2) < Npery) THEN
156      IF (ilonlatfrac(2) /= 0) THEN
157        iybeg = (ilonlatfrac(2)-1)*fracy
158        iyend = ilonlatfrac(2)*fracy+1
159      ELSE
160        iybeg = 0
161        iyend = fracy+1
162      END IF
163    ELSE
164      iybeg = Npery*fracy
165      iyend = dy+1
166    END IF
167  END IF
168
169  IF (ALLOCATED(lon)) DEALLOCATE(lon)
170  ALLOCATE(lon(ixend-ixbeg+1, iyend-iybeg+1))
171  IF (ALLOCATED(lat)) DEALLOCATE(lat)
172  ALLOCATE(lat(ixend-ixbeg+1, iyend-iybeg+1))
173  IF (ALLOCATED(difflonlat)) DEALLOCATE(difflonlat)
174  ALLOCATE(difflonlat(ixend-ixbeg+1, iyend-iybeg+1))
175
176  lon = ilon(ixbeg:ixend,iybeg:iyend)
177  lat = ilat(ixbeg:ixend,iybeg:iyend)
178
179!  print *,'lon _______'
180!  print *,lon
181!  print *,'lat _______'
182!  print *,lat
183
184! Find point
185  difflonlat = SQRT((lon-lonv)**2. + (lat-latv)**2.)
186  mindiffLl = MINVAL(difflonlat)
187  ilonlat = index2DArrayR(difflonlat, ixend-ixbeg+1, iyend-iybeg+1, mindiffLl)
188
189  ilonlat(1) = ilonlat(1) + ixbeg
190  ilonlat(2) = ilonlat(2) + iybeg
191
192!  PRINT *,'mindiffLl:', mindiffLl, ' ilatlon:', ilatlon
193!  PRINT *,'lon, lat:', lon(ilonlat(1),ilonlat(2)), ' ,', lat(ilonlat(1),ilonlat(2))
194
195  RETURN
196
197END SUBROUTINE CoarselonlatFind
198
199SUBROUTINE lonlatFind(dx, dy, ilon, ilat, nxlon, nxlat, lonv, latv, ilonlat, mindiffLl)
200! Function to search a given value from a coarser version of the data
201
202  USE module_generic
203
204  IMPLICIT NONE
205
206  INTEGER, PARAMETER                                     :: r_k = KIND(1.d0)
207  INTEGER, INTENT(in)                                    :: dx, dy
208  REAL(r_k), DIMENSION(dx,dy), INTENT(in)                :: ilon, ilat
209  REAL(r_k), INTENT(in)                                  :: lonv, latv
210  REAL(r_k), DIMENSION(2), INTENT(in)                    :: nxlon, nxlat
211  INTEGER, DIMENSION(2), INTENT(out)                     :: ilonlat
212  REAL(r_k), INTENT(out)                                 :: mindiffLl
213! Local
214  REAL(r_k), DIMENSION(dx,dy)                            :: difflonlat
215  CHARACTER(LEN=50)                                      :: fname
216 
217! Variables
218! ilon, ilat: original 2D matrices with the longitudes and the latitudes
219! lonv, latv: longitude and latitude to find
220! nxlon, nxlat: minimum and maximum longitude and latitude of the target lon,lat
221
222  fname = 'lonlatFind'
223
224  IF (lonv < nxlon(1) .OR. lonv > nxlon(2)) THEN
225    PRINT *, TRIM(ErrWarnMsg('err'))
226    PRINT *,'  ' // TRIM(fname) // ': longitude outside data range!!'
227    PRINT *,'    given value:', lonv,' outside (',nxlon(1),' ,',nxlon(2),' )'
228    STOP
229  END IF
230  IF (latv < nxlat(1) .OR. latv > nxlat(2)) THEN
231    PRINT *, TRIM(ErrWarnMsg('err'))
232    PRINT *,'  ' // TRIM(fname) // ': latitude outside data range!!'
233    PRINT *,'    given value:', latv,' outside (',nxlat(1),' ,',nxlat(2),' )'
234    STOP
235  END IF
236
237! Find point
238  difflonlat = SQRT((ilon-lonv)**2. + (ilat-latv)**2.)
239  mindiffLl = MINVAL(difflonlat)
240  ilonlat = index2DArrayR(difflonlat, dx, dy, mindiffLl)
241
242!  PRINT *,'mindiffLl:', mindiffLl, ' ilatlon:', ilatlon
243!  PRINT *,'lon, lat:', lon(ilonlat(1),ilonlat(2)), ' ,', lat(ilonlat(1),ilonlat(2))
244
245  RETURN
246
247END SUBROUTINE lonlatFind
248
249SUBROUTINE CoarseInterpolate(projlon, projlat, lonvs, latvs, percen, mindiff, ivar, newvar, newvarin, &
250  newvarinpt, newvarindiff, dimx, dimy, Ninpts)
251! Subroutine which finds the closest grid point within a projection throughout a first guest
252!   approche from percentages of the whole domain
253
254  USE module_generic
255
256  IMPLICIT NONE
257
258  INTEGER, PARAMETER                                     :: r_k = KIND(1.d0)
259  INTEGER, INTENT(in)                                    :: dimx, dimy
260  REAL(r_k), DIMENSION(dimx,dimy), INTENT(in)            :: projlon, projlat
261  INTEGER, INTENT(in)                                    :: Ninpts
262  REAL(r_k), DIMENSION(Ninpts), INTENT(in)               :: ivar, lonvs, latvs
263  REAL(r_k), INTENT(in)                                  :: mindiff, percen
264  REAL(r_k), DIMENSION(dimx,dimy), INTENT(out)           :: newvar
265  INTEGER, DIMENSION(dimx,dimy), INTENT(out)             :: newvarin
266  INTEGER, DIMENSION(Ninpts), INTENT(out)                :: newvarinpt
267  REAL(r_k), DIMENSION(Ninpts), INTENT(out)              :: newvarindiff
268
269! Local
270  INTEGER                                                :: iv,i,j
271  INTEGER                                                :: ierr
272  INTEGER, DIMENSION(2)                                  :: ilonlat
273  REAL(r_k)                                              :: mindiffLl
274  INTEGER                                                :: Ninpts1
275  REAL(r_k), DIMENSION(2)                                :: extremelon, extremelat
276  REAL(r_k), ALLOCATABLE, DIMENSION(:,:)                 :: fractionlon, fractionlat
277  INTEGER                                                :: dfracdx, dfracdy, fracdx, fracdy
278  CHARACTER(LEN=50)                                      :: fname
279
280!!!!!!! Variables
281! dimx, dimy: dimension length of the target interpolation
282! proj[lon/lat]: longitudes and latitudes of the target interpolation
283! Ninpts: number of points to interpolate
284! [lon/lat]vs: longitudes and latitudes of the points to interpolate
285! mindiff: minimal accepted distance to the target point
286! percen: size (as percentage of the total domain) of the first guess portions to provide the first gues
287! ivar: values to localize in the target projection
288! newvar: localisation of the [lon/lat]vs point in the target projection
289! newvarin: number of point from the input data
290! newvarinpt: integer value indicating if the value has been already located (0: no, 1: yes)
291! newvarindiff: distance of point from the input data to the closest target point
292! ncid: netCDF output file id
293
294  fname = 'CoarseInterpolate'
295  Ninpts1 = Ninpts/100
296
297  extremelon = (/ MINVAL(projlon), MAXVAL(projlon) /)
298  extremelat = (/ MINVAL(projlat), MAXVAL(projlat) /)
299
300  PRINT *,'  ' // TRIM(fname) //' total space:', dimx, ', ', dimy, ' %', percen
301
302  dfracdx = INT(1./percen+1)
303  dfracdy = INT(1./percen+1)
304  fracdx = INT(dimx*percen)
305  fracdy = INT(dimy*percen)
306  PRINT *,'  ' // TRIM(fname) //' fraction:', dfracdx, ', ', dfracdy, ' freq:', fracdx,', ',fracdy
307
308  IF (ALLOCATED(fractionlon)) DEALLOCATE(fractionlon)
309  ALLOCATE(fractionlon(dfracdx, dfracdy), STAT=ierr)
310  IF (ierr /= 0) THEN
311    PRINT *,TRIM(ErrWarnMsg('err'))
312    PRINT *,'  ' // TRIM(fname) //": problem allocating 'fractionlon' !!"
313    STOP
314  END IF
315  IF (ALLOCATED(fractionlat)) DEALLOCATE(fractionlat)
316  ALLOCATE(fractionlat(dfracdx, dfracdy), STAT=ierr)
317  IF (ierr /= 0) THEN
318    PRINT *,TRIM(ErrWarnMsg('err'))
319    PRINT *,'  ' // TRIM(fname) //": problem allocating 'fractionlat' !!"
320    STOP
321  END IF
322
323  DO i=1,dfracdx
324    DO j=1,dfracdy
325      fractionlon(i,j) = projlon(fracdx*(i-1)+1,fracdy*(j-1)+1)
326      fractionlat(i,j) = projlat(fracdx*(i-1)+1,fracdy*(j-1)+1)
327!      PRINT *,'i,j:',i,', ',j,' frac ij:',fracdx*(i-1),', ',fracdy*(j-1),' lonlat:', fractionlon(i,j),&
328!        ', ',fractionlat(i,j)
329    END DO
330  END DO
331
332!  PRINT *,'  ' // TRIM(fname) // ' fractions of:'
333!  PRINT *,' lon _______ (',dfracdx,', ',dfracdy,')'
334!  DO i=1,dfracdx
335!    PRINT *,fractionlon(i,:)
336!  END DO
337!  PRINT *,' lat_______'
338!  DO i=1,dfracdx
339!    PRINT *,fractionlat(i,:)
340!  END DO
341
342  DO iv=1,Ninpts
343    IF (newvarinpt(iv) == 0) THEN
344      CALL CoarselonlatFind(dimx, dimy, projlon, projlat, extremelon, extremelat, fractionlon,        &
345        fractionlat, lonvs(iv), latvs(iv), percen, dfracdx, dfracdy, ilonlat, mindiffLl)
346
347      PRINT *,'  Lluis: iv',iv,', ', mindiffLl,'<= ',mindiff,' ilonlat:',ilonlat
348      IF (mindiffLl <= mindiff) THEN
349!        percendone(iv,Ninpts,0.5,'done:')
350
351        IF (ilonlat(1) >= 0 .AND. ilonlat(1) >= 0) THEN
352          newvar(ilonlat(1),ilonlat(2)) = ivar(iv)
353          newvarin(ilonlat(1),ilonlat(2)) = iv
354          newvarinpt(iv) = 1
355          newvarindiff(iv) = mindiffLl
356!          PRINT *,'Lluis iv:', newvarin(ilonlat(1),ilonlat(2)), ' localized:', newvarinpt(iv),        &
357!            ' values:', newvar(ilonlat(1),ilonlat(2)), ' invalues:', ivar(iv), ' mindist:',           &
358!            newvarindiff(iv), ' point:',ilonlat   
359        ELSE
360          PRINT *,TRIM(ErrWarnMsg('err'))
361          PRINT *,'  ' // TRIM(fname) // ': point iv:', iv, ' at', lonvs(iv), ' ,', latvs(iv),        &
362            ' not relocated !!'
363          PRINT *,'    mindiffl:', mindiffLl, ' ilon:', ilonlat(1), ' ilat:', ilonlat(2)
364          STOP
365        END IF
366
367!        IF (MOD(iv,Ninpts1) == 0) newnc.sync()
368!      ELSE
369! Because doing boxes and Goode is not conitnuos, we should jump this error message
370!        PRINT *,TRIM(ErrWarnMsg('err'))
371!        PRINT *,'  ' // TRIM(fname) // ': for point #', iv,' lon,lat in incomplet map:', lonvs(iv),   &
372!          ' ,', latvs(iv), ' there is not a set of lon,lat in the completed map closer than: ',       &
373!          mindiff, ' !!'
374!        PRINT *,'    found minimum difference:', mindiffLl
375!        STOP
376      END IF
377    END IF
378  END DO
379
380END SUBROUTINE CoarseInterpolate
381
382SUBROUTINE Interpolate(projlon, projlat, lonvs, latvs, mindiff, ivar, newvar, newvarin, newvarinpt,   &
383  newvarindiff, dimx, dimy, Ninpts)
384! Subroutine which finds the closest grid point within a projection
385
386  USE module_generic
387
388  IMPLICIT NONE
389
390  INTEGER, PARAMETER                                     :: r_k = KIND(1.d0)
391  INTEGER, INTENT(in)                                    :: dimx, dimy
392  REAL(r_k), DIMENSION(dimx,dimy), INTENT(in)            :: projlon, projlat
393  INTEGER, INTENT(in)                                    :: Ninpts
394  REAL(r_k), DIMENSION(Ninpts), INTENT(in)               :: ivar, lonvs, latvs
395  REAL(r_k), INTENT(in)                                  :: mindiff
396  REAL(r_k), DIMENSION(dimx,dimy), INTENT(out)           :: newvar
397  INTEGER, DIMENSION(dimx,dimy), INTENT(out)             :: newvarin
398  INTEGER, DIMENSION(Ninpts), INTENT(out)                :: newvarinpt
399  REAL(r_k), DIMENSION(Ninpts), INTENT(out)              :: newvarindiff
400
401! Local
402  INTEGER                                                :: iv,i,j
403  INTEGER                                                :: ierr
404  INTEGER, DIMENSION(2)                                  :: ilonlat
405  REAL(r_k), DIMENSION(dimx,dimy)                        :: difflonlat
406  REAL(r_k)                                              :: mindiffLl
407  INTEGER                                                :: Ninpts1
408  REAL(r_k), DIMENSION(2)                                :: extremelon, extremelat
409  CHARACTER(LEN=50)                                      :: fname
410
411!!!!!!! Variables
412! dimx, dimy: dimension length of the target interpolation
413! proj[lon/lat]: longitudes and latitudes of the target interpolation
414! Ninpts: number of points to interpolate
415! [lon/lat]vs: longitudes and latitudes of the points to interpolate
416! mindiff: minimal accepted distance to the target point
417! ivar: values to localize in the target projection
418! newvar: localisation of the [lon/lat]vs point in the target projection
419! newvarin: number of point from the input data
420! newvarinpt: integer value indicating if the value has been already located (0: no, 1: yes)
421! newvarindiff: distance of point from the input data to the closest target point
422! ncid: netCDF output file id
423
424  fname = 'Interpolate'
425  Ninpts1 = Ninpts/100
426
427  extremelon = (/ MINVAL(projlon), MAXVAL(projlon) /)
428  extremelat = (/ MINVAL(projlat), MAXVAL(projlat) /)
429
430  DO iv=1,Ninpts
431    IF (newvarinpt(iv) == 0) THEN
432! Not using the subroutine, not efficient!
433!      CALL lonlatFind(dimx, dimy, projlon, projlat, extremelon, extremelat, lonvs(iv), latvs(iv),     &
434!        ilonlat, mindiffLl)
435
436      IF (lonvs(iv) < extremelon(1) .OR. lonvs(iv) > extremelon(2)) THEN
437        PRINT *, TRIM(ErrWarnMsg('err'))
438        PRINT *,'  ' // TRIM(fname) // ': longitude outside data range!!'
439        PRINT *,'    given value:', lonvs(iv),' outside (',extremelon(1),' ,',extremelon(2),' )'
440        STOP
441      END IF
442      IF (latvs(iv) < extremelat(1) .OR. latvs(iv) > extremelat(2)) THEN
443        PRINT *, TRIM(ErrWarnMsg('err'))
444        PRINT *,'  ' // TRIM(fname) // ': latitude outside data range!!'
445        PRINT *,'    given value:', latvs(iv),' outside (',extremelat(1),' ,',extremelat(2),' )'
446        STOP
447      END IF
448
449! Find point
450      difflonlat = SQRT((projlon-lonvs(iv))**2. + (projlat-latvs(iv))**2.)
451      mindiffLl = MINVAL(difflonlat)
452      ilonlat = index2DArrayR(difflonlat, dimx, dimy, mindiffLl)
453
454      IF (mindiffLl <= mindiff) THEN
455!        percendone(iv,Ninpts,0.5,'done:')
456
457        IF (ilonlat(1) >= 0 .AND. ilonlat(1) >= 0) THEN
458          newvar(ilonlat(1),ilonlat(2)) = ivar(iv)
459          newvarin(ilonlat(1),ilonlat(2)) = iv
460          newvarinpt(iv) = 1
461          newvarindiff(iv) = mindiffLl
462!          PRINT *,'Lluis iv:', newvarin(ilonlat(1),ilonlat(2)), ' localized:', newvarinpt(iv),        &
463!            ' values:', newvar(ilonlat(1),ilonlat(2)), ' invalues:', ivar(iv), ' mindist:',           &
464!            newvarindiff(iv), ' point:',ilonlat   
465        ELSE
466          PRINT *,TRIM(ErrWarnMsg('err'))
467          PRINT *,'  ' // TRIM(fname) // ': point iv:', iv, ' at', lonvs(iv), ' ,', latvs(iv),        &
468            ' not relocated !!'
469          PRINT *,'    mindiffl:', mindiffLl, ' ilon:', ilonlat(1), ' ilat:', ilonlat(2)
470          STOP
471        END IF
472
473!        IF (MOD(iv,Ninpts1) == 0) newnc.sync()
474!      ELSE
475! Because doing boxes and Goode is not conitnuos, we should jump this error message
476!        PRINT *,TRIM(ErrWarnMsg('err'))
477!        PRINT *,'  ' // TRIM(fname) // ': for point #', iv,' lon,lat in incomplet map:', lonvs(iv),   &
478!          ' ,', latvs(iv), ' there is not a set of lon,lat in the completed map closer than: ',       &
479!          mindiff, ' !!'
480!        PRINT *,'    found minimum difference:', mindiffLl
481!        STOP
482      END IF
483    END IF
484  END DO
485
486END SUBROUTINE Interpolate
487
488END MODULE module_ForInterpolate
Note: See TracBrowser for help on using the repository browser.