/[MITgcm]/MITgcm/pkg/exf/exf_interp.F
ViewVC logotype

Annotation of /MITgcm/pkg/exf/exf_interp.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.38 - (hide annotations) (download)
Thu Jun 15 23:10:30 2017 UTC (6 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, HEAD
Changes since 1.37: +26 -1 lines
- interpolation near the poles, case where second additional row is at the
  pole (or beyond the pole and moved to the pole): change first addition row
  value to a linear interpolation between pole and 1rst (S.pole)/last (N.pole)
  row (instead of just a copy of it).

1 jmc 1.38 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_interp.F,v 1.37 2017/03/10 00:16:11 jmc Exp $
2 jmc 1.19 C $Name: $
3    
4 edhill 1.3 #include "EXF_OPTIONS.h"
5 dimitri 1.1
6 jmc 1.24 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 dimitri 1.1
8 jmc 1.27 CBOP
9     C !ROUTINE: EXF_INTERP
10     C !INTERFACE:
11     SUBROUTINE EXF_INTERP(
12 jmc 1.29 I inFile, filePrec,
13 jmc 1.37 #ifdef EXF_INTERP_USE_DYNALLOC
14 jmc 1.27 O arrayout,
15 jmc 1.37 #else
16     O arrayout, arrayin,
17     #endif
18 jmc 1.27 I irecord, xG_in, yG,
19 jmc 1.29 I lon_0, lon_inc, lat_0, lat_inc,
20     I nxIn, nyIn, method, myIter, myThid )
21 jmc 1.27
22     C !DESCRIPTION: \bv
23     C *==========================================================*
24     C | SUBROUTINE EXF_INTERP
25     C | o Load from file a regular lat-lon input field
26     C | and interpolate on to the model grid location
27     C *==========================================================*
28     C \ev
29    
30     C !USES:
31     IMPLICIT NONE
32     C === Global variables ===
33     #include "SIZE.h"
34     #include "EEPARAMS.h"
35     #include "PARAMS.h"
36 jmc 1.37 #include "EXF_INTERP_SIZE.h"
37 jmc 1.31 #ifdef ALLOW_DEBUG
38     # include "EXF_PARAM.h"
39     #endif
40 dimitri 1.1
41 jmc 1.27 C !INPUT/OUTPUT PARAMETERS:
42     C inFile (string) :: name of the binary input file (direct access)
43 jmc 1.20 C filePrec (integer) :: number of bits per word in file (32 or 64)
44 jmc 1.27 C arrayout ( _RL ) :: output array
45 jmc 1.37 #ifndef EXF_INTERP_USE_DYNALLOC
46     C arrayin ( _RL ) :: input field array (loaded from file)
47     #endif
48 jmc 1.20 C irecord (integer) :: record number to read
49 jmc 1.27 C xG_in,yG :: coordinates for output grid to interpolate to
50 jmc 1.20 C lon_0, lat_0 :: lon and lat of sw corner of global input grid
51     C lon_inc :: scalar x-grid increment
52     C lat_inc :: vector y-grid increments
53 jmc 1.27 C nxIn,nyIn (integer) :: size in x & y direction of input file to read
54 jmc 1.20 C method :: 1,11,21 for bilinear; 2,12,22 for bicubic
55     C :: 1,2 for tracer; 11,12 for U; 21,22 for V
56 jmc 1.29 C myIter (integer) :: current iteration number
57 jmc 1.20 C myThid (integer) :: My Thread Id number
58 jmc 1.29 CHARACTER*(*) inFile
59 jmc 1.27 INTEGER filePrec, irecord, nxIn, nyIn
60 dimitri 1.2 _RL arrayout(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
61 jmc 1.37 #ifndef EXF_INTERP_USE_DYNALLOC
62     _RL arrayin ( -1:nxIn+2, -1:nyIn+2 )
63     #endif
64 jmc 1.20 _RS xG_in (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
65 dimitri 1.2 _RS yG (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
66     _RL lon_0, lon_inc
67 jmc 1.27 c _RL lat_0, lat_inc(nyIn-1)
68 jmc 1.24 _RL lat_0, lat_inc(*)
69 jmc 1.29 INTEGER method, myIter, myThid
70 dimitri 1.1
71 jmc 1.27 C !FUNCTIONS:
72 jmc 1.29 #ifdef ALLOW_DEBUG
73 jmc 1.27 INTEGER ILNBLNK
74     EXTERNAL ILNBLNK
75 jmc 1.29 #endif
76 jmc 1.27
77     C !LOCAL VARIABLES:
78 jmc 1.29 C x_in :: longitude vector defining input field grid
79     C y_in :: latitude vector defining input field grid
80     C w_ind :: input field longitudinal index, on western side of model grid pt
81     C s_ind :: input field latitudinal index, on southern side of model grid pt
82     C bi, bj :: tile indices
83     C i, j, k, l :: loop indices
84 jmc 1.27 C msgBuf :: Informational/error message buffer
85 jmc 1.37 #ifdef EXF_INTERP_USE_DYNALLOC
86     C arrayin :: input field array (loaded from file)
87 jmc 1.27 _RL arrayin( -1:nxIn+2, -1:nyIn+2 )
88     _RL x_in(-1:nxIn+2), y_in(-1:nyIn+2)
89 jmc 1.37 #else /* EXF_INTERP_USE_DYNALLOC */
90     _RL x_in(-1:exf_max_nLon+2), y_in(-1:exf_max_nLat+2)
91     #endif /* EXF_INTERP_USE_DYNALLOC */
92 jmc 1.29 INTEGER w_ind(sNx,sNy), s_ind(sNx,sNy)
93     INTEGER bi, bj
94     INTEGER i, j, k, l
95 jmc 1.27 INTEGER nLoop
96 jmc 1.28 _RL tmpVar
97 heimbach 1.13 _RS xG(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
98 jmc 1.20 _RS threeSixtyRS
99 jmc 1.29 _RL yPole, symSign, poleValue
100 jmc 1.38 _RL edgeFac, poleFac
101 heimbach 1.13 PARAMETER ( threeSixtyRS = 360. )
102 jmc 1.29 PARAMETER ( yPole = 90. )
103     INTEGER nxd2
104 mlosch 1.33 LOGICAL xIsPeriodic, poleSymmetry
105 jmc 1.29 #ifdef ALLOW_DEBUG
106 mlosch 1.33 LOGICAL debugFlag
107 jmc 1.29 CHARACTER*(MAX_LEN_MBUF) msgBuf
108     _RS prtPole(-1:4)
109     #endif
110 jmc 1.27 CEOP
111 heimbach 1.12
112 jmc 1.37 #ifndef EXF_INTERP_USE_DYNALLOC
113     C-- Check size declaration:
114     IF ( nxIn.GT.exf_max_nLon ) THEN
115     STOP 'EXF_INTERP: exf_max_nLon too small'
116     ENDIF
117     IF ( nyIn.GT.exf_max_nLat ) THEN
118     STOP 'EXF_INTERP: exf_max_nLat too small'
119     ENDIF
120     IF ( (nxIn+4)*(nyIn+4).GT.exf_interp_bufferSize ) THEN
121     STOP 'EXF_INTERP: exf_interp_bufferSize too small'
122     ENDIF
123     #endif /* ndef EXF_INTERP_USE_DYNALLOC */
124    
125 jmc 1.29 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
126     C--- Load inut field
127 jmc 1.27
128     CALL EXF_INTERP_READ(
129     I inFile, filePrec,
130     O arrayin,
131     I irecord, nxIn, nyIn, myThid )
132 dimitri 1.2
133 jmc 1.29 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
134     C--- Prepare input grid and input field
135    
136 jmc 1.27 C-- setup input longitude grid
137     DO i=-1,nxIn+2
138 dimitri 1.18 x_in(i) = lon_0 + (i-1)*lon_inc
139 jmc 1.27 ENDDO
140     xIsPeriodic = nxIn.EQ.NINT( threeSixtyRS / lon_inc )
141 jmc 1.29 nxd2 = NINT( nxIn*0.5 )
142     poleSymmetry = xIsPeriodic .AND. ( nxIn.EQ.2*nxd2 )
143     #ifdef EXF_USE_OLD_INTERP_POLE
144     poleSymmetry = .FALSE.
145     #endif
146 heimbach 1.12
147 jmc 1.27 C-- setup input latitude grid
148 dimitri 1.18 y_in(1) = lat_0
149 jmc 1.27 DO j=1,nyIn+1
150     i = MIN(j,nyIn-1)
151     y_in(j+1) = y_in(j) + lat_inc(i)
152     ENDDO
153     y_in(0) = y_in(1) - lat_inc(1)
154     y_in(-1)= y_in(0) - lat_inc(1)
155 jmc 1.29 #ifdef ALLOW_DEBUG
156     DO l=-1,4
157     prtPole(l) = 0.
158     ENDDO
159     #endif
160     C-- For tracer (method=1,2) add 1 row @ the pole (if last row is not)
161     C and will fill it with the polarmost-row zonally averaged value.
162     C For vector component, cannot do much without the other component;
163     C averaging properly done if uvInterp=T in S/R EXF_INTERP_UV
164     #ifdef EXF_USE_OLD_INTERP_POLE
165     IF ( .TRUE. ) THEN
166     #else
167     IF ( method.LT.10 ) THEN
168     C- Add 2 row @ southern end; if one is beyond S.pole, put one @ S.pole
169     j = 0
170     IF ( ABS(y_in(j+1)).LT.yPole .AND. ABS(y_in(j)).GT.yPole ) THEN
171     y_in(j) = -yPole
172 jmc 1.35 y_in(j-1) = -2.*yPole - y_in(j+1)
173 jmc 1.29 #ifdef ALLOW_DEBUG
174     prtPole(j) = 1.
175     prtPole(j-1) = 2.
176     #endif
177     ENDIF
178     j = -1
179 jmc 1.35 IF ( ABS(y_in(j+1)).LT.yPole .AND. ABS(y_in(j)).GT.yPole ) THEN
180 jmc 1.29 y_in(j) = -yPole
181     #ifdef ALLOW_DEBUG
182     prtPole(j) = 1.
183     #endif
184     ENDIF
185     #endif /* EXF_USE_OLD_INTERP_POLE */
186 jmc 1.27 C- Add 2 row @ northern end; if one is beyond N.pole, put one @ N.pole
187 jmc 1.29 j = nyIn+1
188     IF ( ABS(y_in(j-1)).LT.yPole .AND. ABS(y_in(j)).GT.yPole ) THEN
189     y_in(j) = yPole
190     y_in(j+1) = 2.*yPole - y_in(j-1)
191     #ifdef ALLOW_DEBUG
192     prtPole(3) = 1.
193     prtPole(3+1) = 2.
194     #endif
195     ENDIF
196     j = nyIn+2
197     IF ( ABS(y_in(j-1)).LT.yPole .AND. ABS(y_in(j)).GT.yPole ) THEN
198     y_in(j) = yPole
199     #ifdef ALLOW_DEBUG
200     prtPole(4) = 1.
201     #endif
202     ENDIF
203 jmc 1.27 ENDIF
204    
205 jmc 1.29 C-- Enlarge boundary
206 jmc 1.27 IF ( xIsPeriodic ) THEN
207 jmc 1.29 C- fill-in added column assuming periodicity
208 jmc 1.27 DO j=1,nyIn
209     arrayin( 0,j) = arrayin(nxIn ,j)
210     arrayin(-1,j) = arrayin(nxIn-1,j)
211     arrayin(nxIn+1,j) = arrayin(1,j)
212     arrayin(nxIn+2,j) = arrayin(2,j)
213     ENDDO
214     ELSE
215 jmc 1.29 C- fill-in added column from nearest column
216 jmc 1.27 DO j=1,nyIn
217     arrayin( 0,j) = arrayin(1,j)
218     arrayin(-1,j) = arrayin(1,j)
219     arrayin(nxIn+1,j) = arrayin(nxIn,j)
220     arrayin(nxIn+2,j) = arrayin(nxIn,j)
221     ENDDO
222     ENDIF
223 jmc 1.29 symSign = 1. _d 0
224     IF ( method.GE.10 ) symSign = -1. _d 0
225     DO l=-1,2
226     j = l
227     IF ( l.GE.1 ) j = nyIn+l
228     k = MAX(1,MIN(j,nyIn))
229     IF ( poleSymmetry .AND. ABS(y_in(j)).GT.yPole ) THEN
230 jmc 1.38 IF ( nyIn.GE.3 .AND. ABS(y_in(k)).EQ.yPole )
231     & k = MAX(2,MIN(j,nyIn-1))
232 jmc 1.29 C- fill-in added row assuming pole-symmetry
233     DO i=-1,nxd2
234     arrayin(i,j) = symSign*arrayin(i+nxd2,k)
235     ENDDO
236     DO i=1,nxd2+2
237     arrayin(i+nxd2,j) = symSign*arrayin(i,k)
238     ENDDO
239     #ifdef ALLOW_DEBUG
240     i = l + 2*( (l+1)/2 )
241     prtPole(i) = prtPole(i) + 0.2
242     #endif
243     ELSE
244     C- fill-in added row from nearest column values
245     DO i=-1,nxIn+2
246     arrayin(i,j) = arrayin(i,k)
247     ENDDO
248     ENDIF
249 jmc 1.27 ENDDO
250 dimitri 1.4
251 jmc 1.29 C-- For tracer (method=1,2) set to northernmost zonal-mean value
252 dimitri 1.15 C at 90N to avoid sharp zonal gradients near the Pole.
253 jmc 1.29 C For vector component, cannot do much without the other component;
254     C averaging properly done if uvInterp=T in S/R EXF_INTERP_UV
255     #ifdef EXF_USE_OLD_INTERP_POLE
256     IF ( .TRUE. ) THEN
257     DO l= 3,4
258     #else
259     IF ( method.LT.10 ) THEN
260     DO l=-1,4
261     #endif
262     j = l
263     IF ( l.GE.2 ) j = nyIn+l-2
264     IF ( ABS(y_in(j)).EQ.yPole ) THEN
265     IF (method.EQ.1 .OR. method.EQ.2) THEN
266     poleValue = 0.
267     DO i=1,nxIn
268     poleValue = poleValue + arrayin(i,j)
269     ENDDO
270     poleValue = poleValue / nxIn
271     DO i=-1,nxIn+2
272     arrayin(i,j) = poleValue
273     ENDDO
274     #ifdef ALLOW_DEBUG
275     prtPole(l) = prtPole(l) + 0.1
276     #endif
277     #ifdef EXF_USE_OLD_INTERP_POLE
278     ELSEIF (method.EQ.11 .OR. method.EQ.12) THEN
279     DO i=-1,nxIn+2
280     arrayin(i,j) = 0.
281     ENDDO
282     #ifdef ALLOW_DEBUG
283     prtPole(l) = prtPole(l) + 0.9
284     #endif
285     #endif /* EXF_USE_OLD_INTERP_POLE */
286     ENDIF
287 jmc 1.27 ENDIF
288 jmc 1.29 ENDDO
289     ENDIF
290 jmc 1.38 #ifndef EXF_USE_OLD_INTERP_POLE
291     IF (method.EQ.1 .OR. method.EQ.2) THEN
292     C- change first additional row from simple copy to linear interpolation
293     C between nearest column values and pole value
294     DO l=0,1
295     k = l*(nyIn+3) -1
296     IF ( ABS(y_in(k)).EQ.yPole ) THEN
297     j = l*(nyIn+1)
298     i = l*(nyIn-1) +1
299     edgeFac = (y_in(j) - y_in(k)) / (y_in(i) - y_in(k))
300     poleFac = (y_in(i) - y_in(j)) / (y_in(i) - y_in(k))
301     DO i=-1,nxIn+2
302     arrayin(i,j) = arrayin(i,j) * edgeFac
303     & + arrayin(i,k) * poleFac
304     ENDDO
305     #ifdef ALLOW_DEBUG
306     prtPole(3*l) = prtPole(3*l) + 0.3
307     #endif
308     ENDIF
309     ENDDO
310     ENDIF
311     #endif /* EXF_USE_OLD_INTERP_POLE */
312 jmc 1.29
313     #ifdef ALLOW_DEBUG
314 jmc 1.31 debugFlag = ( exf_debugLev.GE.debLevC )
315     & .OR. ( exf_debugLev.GE.debLevB .AND. myIter.LE.nIter0 )
316 jmc 1.29 C prtPole(l)=0 : extended, =1 : changed to pole, =2 : changed to symetric
317     IF ( debugFlag ) THEN
318     l = ILNBLNK(inFile)
319 jmc 1.30 _BEGIN_MASTER(myThid)
320 jmc 1.29 WRITE(msgBuf,'(3A,I6,A,2L5)')
321 jmc 1.36 & ' EXF_INTERP: file="',inFile(1:l),'", rec=', irecord,
322 jmc 1.29 & ' , x-Per,P.Sym=', xIsPeriodic, poleSymmetry
323     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
324     & SQUEEZE_RIGHT, myThid )
325 jmc 1.36 WRITE(msgBuf,'(2A,3F4.1,A,3F12.6)') ' S.edge (j=-1,0,1) :',
326 jmc 1.29 & ' proc=', (prtPole(j),j=-1,1), ', yIn=', (y_in(j),j=-1,1)
327     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
328     & SQUEEZE_RIGHT, myThid )
329 jmc 1.36 WRITE(msgBuf,'(2A,3F4.1,A,3F12.6)') ' N.edge (j=+0,+1,+2)',
330 jmc 1.29 & ' proc=', (prtPole(j),j=2,4), ', yIn=',(y_in(j),j=nyIn,nyIn+2)
331     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
332     & SQUEEZE_RIGHT, myThid )
333 jmc 1.30 _END_MASTER(myThid)
334 jmc 1.29 ENDIF
335     #endif /* ALLOW_DEBUG */
336 dimitri 1.15
337 jmc 1.29 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
338     C--- Prepare output grid and interpolate for each tile
339 dimitri 1.2
340 jmc 1.29 C-- put xG in interval [ lon_0 , lon_0+360 [
341     DO bj=myByLo(myThid),myByHi(myThid)
342     DO bi=myBxLo(myThid),myBxHi(myThid)
343     DO j=1-OLy,sNy+OLy
344     DO i=1-OLx,sNx+OLx
345     xG(i,j,bi,bj) = xG_in(i,j,bi,bj)-lon_0
346     & + threeSixtyRS*2.
347     xG(i,j,bi,bj) = lon_0+MOD(xG(i,j,bi,bj),threeSixtyRS)
348     ENDDO
349     ENDDO
350     #ifdef ALLOW_DEBUG
351 jmc 1.27 C-- Check validity of input/output coordinates
352 jmc 1.29 IF ( debugFlag ) THEN
353 jmc 1.27 DO j=1,sNy
354     DO i=1,sNx
355 mlosch 1.33 IF ( xG(i,j,bi,bj) .LT. x_in(0) .OR.
356     & xG(i,j,bi,bj) .GE. x_in(nxIn+1) .OR.
357     & yG(i,j,bi,bj) .LT. y_in(0) .OR.
358     & yG(i,j,bi,bj) .GE. y_in(nyIn+1) ) THEN
359 jmc 1.27 l = ILNBLNK(inFile)
360     WRITE(msgBuf,'(3A,I6)')
361     & 'EXF_INTERP: file="', inFile(1:l), '", rec=', irecord
362     CALL PRINT_ERROR( msgBuf, myThid )
363     WRITE(msgBuf,'(A)')
364     & 'EXF_INTERP: input grid must encompass output grid.'
365     CALL PRINT_ERROR( msgBuf, myThid )
366     WRITE(msgBuf,'(A,2I8,2I6,A,1P2E14.6)') 'i,j,bi,bj=',
367     & i,j,bi,bj, ' , xG,yG=', xG(i,j,bi,bj), yG(i,j,bi,bj)
368     CALL PRINT_ERROR( msgBuf, myThid )
369     WRITE(msgBuf,'(A,I9,A,1P2E14.6)') 'nxIn=', nxIn,
370     & ' , x_in(0,nxIn+1)=', x_in(0) ,x_in(nxIn+1)
371     CALL PRINT_ERROR( msgBuf, myThid )
372     WRITE(msgBuf,'(A,I9,A,1P2E14.6)') 'nyIn=', nyIn,
373     & ' , y_in(0,nyIn+1)=', y_in(0) ,y_in(nyIn+1)
374     CALL PRINT_ERROR( msgBuf, myThid )
375     STOP 'ABNORMAL END: S/R EXF_INTERP'
376     ENDIF
377     ENDDO
378     ENDDO
379     ENDIF
380 dimitri 1.6 #endif /* ALLOW_DEBUG */
381 jmc 1.29 ENDDO
382     ENDDO
383    
384     DO bj = myByLo(myThid), myByHi(myThid)
385     DO bi = myBxLo(myThid), myBxHi(myThid)
386 dimitri 1.1
387 mlosch 1.33 C-- Compute interpolation lon & lat index mapping
388     C-- latitude index
389     DO j=1,sNy
390     DO i=1,sNx
391     s_ind(i,j) = 0
392     w_ind(i,j) = nyIn+1
393     ENDDO
394     ENDDO
395     C # of pts = nyIn+2 ; # of interval = nyIn+1 ; evaluate nLoop as
396     C 1 + truncated log2(# interval -1); add epsil=1.e-3 for safey
397     tmpVar = nyIn + 1. _d -3
398     nLoop = 1 + INT( LOG(tmpVar)/LOG(2. _d 0) )
399     DO l=1,nLoop
400 mlosch 1.32 DO j=1,sNy
401     DO i=1,sNx
402 mlosch 1.33 IF ( w_ind(i,j).GT.s_ind(i,j)+1 ) THEN
403     k = NINT( (s_ind(i,j)+w_ind(i,j))*0.5 )
404     IF ( yG(i,j,bi,bj) .LT. y_in(k) ) THEN
405 mlosch 1.32 w_ind(i,j) = k
406 mlosch 1.33 ELSE
407 mlosch 1.32 s_ind(i,j) = k
408     ENDIF
409 mlosch 1.33 ENDIF
410 mlosch 1.32 ENDDO
411 jmc 1.27 ENDDO
412 mlosch 1.33 ENDDO
413 jmc 1.27 #ifdef ALLOW_DEBUG
414 jmc 1.29 IF ( debugFlag ) THEN
415 jmc 1.27 C- Check that we found the right lat. index
416     DO j=1,sNy
417     DO i=1,sNx
418 mlosch 1.33 IF ( w_ind(i,j).NE.s_ind(i,j)+1 ) THEN
419 jmc 1.27 l = ILNBLNK(inFile)
420     WRITE(msgBuf,'(3A,I4,A,I4)')
421     & 'EXF_INTERP: file="', inFile(1:l), '", rec=', irecord,
422     & ', nLoop=', nLoop
423     CALL PRINT_ERROR( msgBuf, myThid )
424     WRITE(msgBuf,'(A)')
425 mlosch 1.32 & 'EXF_INTERP: did not find Latitude index for grid-pt:'
426 jmc 1.27 CALL PRINT_ERROR( msgBuf, myThid )
427     WRITE(msgBuf,'(A,2I8,2I6,A,1PE16.8)')
428     & 'EXF_INTERP: i,j,bi,bj=',i,j,bi,bj,' , yG=',yG(i,j,bi,bj)
429     CALL PRINT_ERROR( msgBuf, myThid )
430     WRITE(msgBuf,'(A,I8,A,1PE16.8)')
431     & 'EXF_INTERP: s_ind=',s_ind(i,j),', lat=',y_in(s_ind(i,j))
432     CALL PRINT_ERROR( msgBuf, myThid )
433     WRITE(msgBuf,'(A,I8,A,1PE16.8)')
434     & 'EXF_INTERP: n_ind=',w_ind(i,j),', lat=',y_in(w_ind(i,j))
435     CALL PRINT_ERROR( msgBuf, myThid )
436     STOP 'ABNORMAL END: S/R EXF_INTERP'
437     ENDIF
438     ENDDO
439     ENDDO
440     ENDIF
441     #endif /* ALLOW_DEBUG */
442     C-- longitude index
443     DO j=1,sNy
444     DO i=1,sNx
445     w_ind(i,j) = INT((xG(i,j,bi,bj)-x_in(-1))/lon_inc) - 1
446     ENDDO
447     ENDDO
448 dimitri 1.1
449 jmc 1.29 C-- Do interpolation using lon & lat index mapping
450     CALL EXF_INTERPOLATE(
451     I inFile, irecord, method,
452     I nxIn, nyIn, x_in, y_in,
453 jmc 1.34 I arrayin,
454 jmc 1.29 O arrayout,
455     I xG, yG,
456     I w_ind, s_ind,
457     I bi, bj, myThid )
458 dimitri 1.1
459 jmc 1.27 ENDDO
460     ENDDO
461 dimitri 1.1
462 jmc 1.20 RETURN
463 dimitri 1.1 END

  ViewVC Help
Powered by ViewVC 1.1.22