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

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

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


Revision 1.28 - (show annotations) (download)
Sun Jan 1 15:25:23 2012 UTC (12 years, 5 months ago) by jmc
Branch: MAIN
Changes since 1.27: +4 -2 lines
for TAF, remove function DFLOAT.

1 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_interp.F,v 1.27 2012/01/01 01:24:54 jmc Exp $
2 C $Name: $
3
4 #include "EXF_OPTIONS.h"
5 #undef OLD_EXF_INTERP_LAT_INDEX
6
7 C==========================================*
8 C Flux Coupler using |
9 C Bilinear interpolation of forcing fields |
10 C |
11 C B. Cheng (12/2002) |
12 C |
13 C added Bicubic (bnc 1/2003) |
14 C |
15 C==========================================*
16
17 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
18
19 _RL FUNCTION LAGRAN(i,x,a,sp)
20
21 IMPLICIT NONE
22
23 INTEGER i
24 _RS x
25 _RL a(4)
26 INTEGER sp
27
28 C- local variables:
29 INTEGER k
30 _RL numer,denom
31
32 numer = 1. _d 0
33 denom = 1. _d 0
34
35 #ifdef TARGET_NEC_SX
36 !CDIR UNROLL=8
37 #endif /* TARGET_NEC_SX */
38 DO k=1,sp
39 IF ( k .NE. i) THEN
40 denom = denom*(a(i) - a(k))
41 numer = numer*(x - a(k))
42 ENDIF
43 ENDDO
44
45 LAGRAN = numer/denom
46
47 RETURN
48 END
49
50 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
51
52 CBOP
53 C !ROUTINE: EXF_INTERP
54 C !INTERFACE:
55 SUBROUTINE EXF_INTERP(
56 I inFile,
57 I filePrec,
58 O arrayout,
59 I irecord, xG_in, yG,
60 I lon_0, lon_inc,
61 I lat_0, lat_inc,
62 I nxIn, nyIn, method, myThid )
63
64 C !DESCRIPTION: \bv
65 C *==========================================================*
66 C | SUBROUTINE EXF_INTERP
67 C | o Load from file a regular lat-lon input field
68 C | and interpolate on to the model grid location
69 C *==========================================================*
70 C \ev
71
72 C !USES:
73 IMPLICIT NONE
74 C === Global variables ===
75 #include "SIZE.h"
76 #include "EEPARAMS.h"
77 #include "PARAMS.h"
78
79
80 C !INPUT/OUTPUT PARAMETERS:
81 C inFile (string) :: name of the binary input file (direct access)
82 C filePrec (integer) :: number of bits per word in file (32 or 64)
83 C arrayout ( _RL ) :: output array
84 C irecord (integer) :: record number to read
85 C xG_in,yG :: coordinates for output grid to interpolate to
86 C lon_0, lat_0 :: lon and lat of sw corner of global input grid
87 C lon_inc :: scalar x-grid increment
88 C lat_inc :: vector y-grid increments
89 C nxIn,nyIn (integer) :: size in x & y direction of input file to read
90 C method :: 1,11,21 for bilinear; 2,12,22 for bicubic
91 C :: 1,2 for tracer; 11,12 for U; 21,22 for V
92 C myThid (integer) :: My Thread Id number
93
94 CHARACTER*(*) infile
95 INTEGER filePrec, irecord, nxIn, nyIn
96 _RL arrayout(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
97 _RS xG_in (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
98 _RS yG (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
99 _RL lon_0, lon_inc
100 c _RL lat_0, lat_inc(nyIn-1)
101 _RL lat_0, lat_inc(*)
102 INTEGER method, myThid
103
104 C !FUNCTIONS:
105 EXTERNAL LAGRAN
106 _RL LAGRAN
107 INTEGER ILNBLNK
108 EXTERNAL ILNBLNK
109
110 C !LOCAL VARIABLES:
111 C msgBuf :: Informational/error message buffer
112 C bi, bj :: tile indices
113 CHARACTER*(MAX_LEN_MBUF) msgBuf
114 INTEGER bi, bj
115 INTEGER w_ind(sNx,sNy), s_ind(sNx,sNy)
116 _RL px_ind(4), py_ind(4), ew_val(4)
117 _RL arrayin( -1:nxIn+2, -1:nyIn+2 )
118 _RL x_in(-1:nxIn+2), y_in(-1:nyIn+2)
119 _RL NorthValue
120 INTEGER i, j, k, l, sp
121 #ifdef OLD_EXF_INTERP_LAT_INDEX
122 INTEGER js
123 #else
124 INTEGER nLoop
125 _RL tmpVar
126 #endif
127 #ifdef TARGET_NEC_SX
128 INTEGER ic, ii, icnt
129 INTEGER inx(sNx*sNy,2)
130 _RL ew_val1, ew_val2, ew_val3, ew_val4
131 #endif
132 _RS xG(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
133 _RL ninety
134 PARAMETER ( ninety = 90. )
135 _RS threeSixtyRS
136 PARAMETER ( threeSixtyRS = 360. )
137 LOGICAL xIsPeriodic
138 CEOP
139
140 C-- put xG in interval [ lon_0 , lon_0+360 [
141 DO bj=myByLo(myThid),myByHi(myThid)
142 DO bi=myBxLo(myThid),myBxHi(myThid)
143 DO j=1-OLy,sNy+OLy
144 DO i=1-OLx,sNx+OLx
145 xG(i,j,bi,bj) = xG_in(i,j,bi,bj)-lon_0
146 & + threeSixtyRS*2.
147 xG(i,j,bi,bj) = lon_0+MOD(xG(i,j,bi,bj),threeSixtyRS)
148 ENDDO
149 ENDDO
150 ENDDO
151 ENDDO
152
153 C-- Load inut field
154 CALL EXF_INTERP_READ(
155 I inFile, filePrec,
156 O arrayin,
157 I irecord, nxIn, nyIn, myThid )
158
159 C-- setup input longitude grid
160 DO i=-1,nxIn+2
161 x_in(i) = lon_0 + (i-1)*lon_inc
162 ENDDO
163 xIsPeriodic = nxIn.EQ.NINT( threeSixtyRS / lon_inc )
164
165 C-- setup input latitude grid
166 y_in(1) = lat_0
167 DO j=1,nyIn+1
168 i = MIN(j,nyIn-1)
169 y_in(j+1) = y_in(j) + lat_inc(i)
170 ENDDO
171 C- Add 2 row @ southern end; if one is beyond S.pole, put one @ S.pole
172 y_in(0) = y_in(1) - lat_inc(1)
173 y_in(-1)= y_in(0) - lat_inc(1)
174 c IF ( y_in(1).GT.-ninety .AND. y_in(0).LT.-ninety ) THEN
175 c y_in(0) = -ninety
176 c y_in(-1) = -2.*ninety - y_in(1)
177 c ENDIF
178 c IF ( y_in(0).GT.-ninety .AND. y_in(-1).LT.-ninety ) THEN
179 c y_in(-1) = -ninety
180 c ENDIF
181 C- Add 2 row @ northern end; if one is beyond N.pole, put one @ N.pole
182 j = nyIn+1
183 IF ( y_in(j-1).LT.ninety .AND. y_in(j).GT.ninety ) THEN
184 y_in(j) = ninety
185 y_in(j+1) = 2.*ninety - y_in(j-1)
186 ENDIF
187 j = nyIn+2
188 IF ( y_in(j-1).LT.ninety .AND. y_in(j).GT.ninety ) THEN
189 y_in(j) = ninety
190 ENDIF
191
192 C-- enlarge boundary
193 IF ( xIsPeriodic ) THEN
194 DO j=1,nyIn
195 arrayin( 0,j) = arrayin(nxIn ,j)
196 arrayin(-1,j) = arrayin(nxIn-1,j)
197 arrayin(nxIn+1,j) = arrayin(1,j)
198 arrayin(nxIn+2,j) = arrayin(2,j)
199 ENDDO
200 ELSE
201 DO j=1,nyIn
202 arrayin( 0,j) = arrayin(1,j)
203 arrayin(-1,j) = arrayin(1,j)
204 arrayin(nxIn+1,j) = arrayin(nxIn,j)
205 arrayin(nxIn+2,j) = arrayin(nxIn,j)
206 ENDDO
207 ENDIF
208 DO i=-1,nxIn+2
209 arrayin(i, 0) = arrayin(i,1)
210 arrayin(i,-1) = arrayin(i,1)
211 arrayin(i,nyIn+1) = arrayin(i,nyIn)
212 arrayin(i,nyIn+2) = arrayin(i,nyIn)
213 ENDDO
214
215 C- For tracer (method=1,2) set to northernmost zonal-mean value
216 C at 90N to avoid sharp zonal gradients near the Pole.
217 C For U (method=11,12) set to zero at 90N to minimize velocity
218 C gradient at North Pole
219 C For V (method=11,12) set to northernmost zonal value at 90N,
220 C as is already done above in order to allow cross-PoleArctic flow
221 DO j=nyIn,nyIn+2
222 IF (y_in(j).EQ.ninety) THEN
223 IF (method.EQ.1 .OR. method.EQ.2) THEN
224 NorthValue = 0.
225 DO i=1,nxIn
226 NorthValue = NorthValue + arrayin(i,j)
227 ENDDO
228 NorthValue = NorthValue / nxIn
229 DO i=-1,nxIn+2
230 arrayin(i,j) = NorthValue
231 ENDDO
232 ELSEIF (method.EQ.11 .OR. method.EQ.12) THEN
233 DO i=-1,nxIn+2
234 arrayin(i,j) = 0.
235 ENDDO
236 ENDIF
237 ENDIF
238 ENDDO
239
240 DO bj = myByLo(myThid), myByHi(myThid)
241 DO bi = myBxLo(myThid), myBxHi(myThid)
242
243 C-- Check validity of input/output coordinates
244 #ifdef ALLOW_DEBUG
245 IF ( debugLevel.GE.debLevC ) THEN
246 DO j=1,sNy
247 DO i=1,sNx
248 IF ( xG(i,j,bi,bj) .LT. x_in(0) .OR.
249 & xG(i,j,bi,bj) .GE. x_in(nxIn+1) .OR.
250 & yG(i,j,bi,bj) .LT. y_in(0) .OR.
251 & yG(i,j,bi,bj) .GE. y_in(nyIn+1) ) THEN
252 l = ILNBLNK(inFile)
253 WRITE(msgBuf,'(3A,I6)')
254 & 'EXF_INTERP: file="', inFile(1:l), '", rec=', irecord
255 CALL PRINT_ERROR( msgBuf, myThid )
256 WRITE(msgBuf,'(A)')
257 & 'EXF_INTERP: input grid must encompass output grid.'
258 CALL PRINT_ERROR( msgBuf, myThid )
259 WRITE(msgBuf,'(A,2I8,2I6,A,1P2E14.6)') 'i,j,bi,bj=',
260 & i,j,bi,bj, ' , xG,yG=', xG(i,j,bi,bj), yG(i,j,bi,bj)
261 CALL PRINT_ERROR( msgBuf, myThid )
262 WRITE(msgBuf,'(A,I9,A,1P2E14.6)') 'nxIn=', nxIn,
263 & ' , x_in(0,nxIn+1)=', x_in(0) ,x_in(nxIn+1)
264 CALL PRINT_ERROR( msgBuf, myThid )
265 WRITE(msgBuf,'(A,I9,A,1P2E14.6)') 'nyIn=', nyIn,
266 & ' , y_in(0,nyIn+1)=', y_in(0) ,y_in(nyIn+1)
267 CALL PRINT_ERROR( msgBuf, myThid )
268 STOP 'ABNORMAL END: S/R EXF_INTERP'
269 ENDIF
270 ENDDO
271 ENDDO
272 ENDIF
273 #endif /* ALLOW_DEBUG */
274
275 C-- Compute interpolation indices
276 #ifdef OLD_EXF_INTERP_LAT_INDEX
277 DO j=1,sNy
278 DO i=1,sNx
279 IF (xG(i,j,bi,bj)-x_in(1) .GE. 0.) THEN
280 w_ind(i,j) = INT((xG(i,j,bi,bj)-x_in(1))/lon_inc) + 1
281 ELSE
282 w_ind(i,j) = INT((xG(i,j,bi,bj)-x_in(1))/lon_inc)
283 ENDIF
284 ENDDO
285 ENDDO
286 #ifndef TARGET_NEC_SX
287 C- use the original and more readable variant of the algorithm that
288 C has unvectorizable while-loops for each (i,j)
289 DO j=1,sNy
290 DO i=1,sNx
291 js = nyIn*.5
292 DO WHILE (yG(i,j,bi,bj) .LT. y_in(js))
293 js = (js - 1)*.5
294 ENDDO
295 DO WHILE (yG(i,j,bi,bj) .GE. y_in(js+1))
296 js = js + 1
297 ENDDO
298 s_ind(i,j) = js
299 ENDDO
300 ENDDO
301 #else /* TARGET_NEC_SX defined */
302 C- this variant vectorizes more efficiently than the original one because
303 C it moves the while loops out of the i,j loops (loop pushing) but
304 C it is ugly and incomprehensible
305 icnt = 0
306 DO j=1,sNy
307 DO i=1,sNx
308 s_ind(i,j) = nyIn*.5
309 icnt = icnt+1
310 inx(icnt,1) = i
311 inx(icnt,2) = j
312 ENDDO
313 ENDDO
314 DO WHILE (icnt .GT. 0)
315 ii = 0
316 !CDIR NODEP
317 DO ic=1,icnt
318 i = inx(ic,1)
319 j = inx(ic,2)
320 IF (yG(i,j,bi,bj) .LT. y_in(s_ind(i,j))) THEN
321 s_ind(i,j) = (s_ind(i,j) - 1)*.5
322 ii = ii+1
323 inx(ii,1) = i
324 inx(ii,2) = j
325 ENDIF
326 ENDDO
327 icnt = ii
328 ENDDO
329 icnt = 0
330 DO j=1,sNy
331 DO i=1,sNx
332 icnt = icnt+1
333 inx(icnt,1) = i
334 inx(icnt,2) = j
335 ENDDO
336 ENDDO
337 DO WHILE (icnt .GT. 0)
338 ii = 0
339 !CDIR NODEP
340 DO ic=1,icnt
341 i = inx(ic,1)
342 j = inx(ic,2)
343 IF (yG(i,j,bi,bj) .GE. y_in(s_ind(i,j)+1)) THEN
344 s_ind(i,j) = s_ind(i,j) + 1
345 ii = ii+1
346 inx(ii,1) = i
347 inx(ii,2) = j
348 ENDIF
349 ENDDO
350 icnt = ii
351 ENDDO
352 #endif /* TARGET_NEC_SX defined */
353 #else /* OLD_EXF_INTERP_LAT_INDEX */
354 C-- latitude index
355 DO j=1,sNy
356 DO i=1,sNx
357 s_ind(i,j) = 0
358 w_ind(i,j) = nyIn+1
359 ENDDO
360 ENDDO
361 C # of pts = nyIn+2 ; # of interval = nyIn+1 ; evaluate nLoop as
362 C 1 + truncated log2(# interval -1); add epsil=1.e-3 for safey
363 tmpVar = nyIn + 1. _d -3
364 nLoop = 1 + INT( LOG(tmpVar)/LOG(2. _d 0) )
365 DO l=1,nLoop
366 DO j=1,sNy
367 DO i=1,sNx
368 IF ( w_ind(i,j).GT.s_ind(i,j)+1 ) THEN
369 k = NINT( (s_ind(i,j)+w_ind(i,j))*0.5 )
370 IF ( yG(i,j,bi,bj) .LT. y_in(k) ) THEN
371 w_ind(i,j) = k
372 ELSE
373 s_ind(i,j) = k
374 ENDIF
375 ENDIF
376 ENDDO
377 ENDDO
378 ENDDO
379 #ifdef ALLOW_DEBUG
380 IF ( debugLevel.GE.debLevC ) THEN
381 C- Check that we found the right lat. index
382 DO j=1,sNy
383 DO i=1,sNx
384 IF ( w_ind(i,j).NE.s_ind(i,j)+1 ) THEN
385 l = ILNBLNK(inFile)
386 WRITE(msgBuf,'(3A,I4,A,I4)')
387 & 'EXF_INTERP: file="', inFile(1:l), '", rec=', irecord,
388 & ', nLoop=', nLoop
389 CALL PRINT_ERROR( msgBuf, myThid )
390 WRITE(msgBuf,'(A)')
391 & 'EXF_INTERP: did not found Latitude index for grid-pt:'
392 CALL PRINT_ERROR( msgBuf, myThid )
393 WRITE(msgBuf,'(A,2I8,2I6,A,1PE16.8)')
394 & 'EXF_INTERP: i,j,bi,bj=',i,j,bi,bj,' , yG=',yG(i,j,bi,bj)
395 CALL PRINT_ERROR( msgBuf, myThid )
396 WRITE(msgBuf,'(A,I8,A,1PE16.8)')
397 & 'EXF_INTERP: s_ind=',s_ind(i,j),', lat=',y_in(s_ind(i,j))
398 CALL PRINT_ERROR( msgBuf, myThid )
399 WRITE(msgBuf,'(A,I8,A,1PE16.8)')
400 & 'EXF_INTERP: n_ind=',w_ind(i,j),', lat=',y_in(w_ind(i,j))
401 CALL PRINT_ERROR( msgBuf, myThid )
402 STOP 'ABNORMAL END: S/R EXF_INTERP'
403 ENDIF
404 ENDDO
405 ENDDO
406 ENDIF
407 #endif /* ALLOW_DEBUG */
408 C-- longitude index
409 DO j=1,sNy
410 DO i=1,sNx
411 w_ind(i,j) = INT((xG(i,j,bi,bj)-x_in(-1))/lon_inc) - 1
412 ENDDO
413 ENDDO
414 #endif /* ndef OLD_EXF_INTERP_LAT_INDEX */
415
416 IF (method.EQ.1 .OR. method.EQ.11 .OR. method.EQ.21) THEN
417
418 C-- Bilinear interpolation
419 sp = 2
420 DO j=1,sNy
421 DO i=1,sNx
422 arrayout(i,j,bi,bj) = 0.
423 DO l=0,1
424 px_ind(l+1) = x_in(w_ind(i,j)+l)
425 py_ind(l+1) = y_in(s_ind(i,j)+l)
426 ENDDO
427 #ifndef TARGET_NEC_SX
428 DO k=1,2
429 ew_val(k) = arrayin(w_ind(i,j) ,s_ind(i,j)+k-1)
430 & *LAGRAN(1,xG(i,j,bi,bj),px_ind,sp)
431 & + arrayin(w_ind(i,j)+1,s_ind(i,j)+k-1)
432 & *LAGRAN(2,xG(i,j,bi,bj),px_ind,sp)
433 arrayout(i,j,bi,bj) = arrayout(i,j,bi,bj)
434 & + ew_val(k)*LAGRAN(k,yG(i,j,bi,bj),py_ind,sp)
435 ENDDO
436 #else
437 ew_val1 = arrayin(w_ind(i,j) ,s_ind(i,j) )
438 & *LAGRAN(1,xG(i,j,bi,bj),px_ind,sp)
439 & + arrayin(w_ind(i,j)+1,s_ind(i,j) )
440 & *LAGRAN(2,xG(i,j,bi,bj),px_ind,sp)
441 ew_val2 = arrayin(w_ind(i,j) ,s_ind(i,j)+1)
442 & *LAGRAN(1,xG(i,j,bi,bj),px_ind,sp)
443 & + arrayin(w_ind(i,j)+1,s_ind(i,j)+1)
444 & *LAGRAN(2,xG(i,j,bi,bj),px_ind,sp)
445 arrayout(i,j,bi,bj)=
446 & +ew_val1*LAGRAN(1,yG(i,j,bi,bj),py_ind,sp)
447 & +ew_val2*LAGRAN(2,yG(i,j,bi,bj),py_ind,sp)
448 #endif /* TARGET_NEC_SX defined */
449 ENDDO
450 ENDDO
451 ELSEIF (method .EQ. 2 .OR. method.EQ.12 .OR. method.EQ.22) THEN
452
453 C-- Bicubic interpolation
454 sp = 4
455 DO j=1,sNy
456 DO i=1,sNx
457 arrayout(i,j,bi,bj) = 0.
458 DO l=-1,2
459 px_ind(l+2) = x_in(w_ind(i,j)+l)
460 py_ind(l+2) = y_in(s_ind(i,j)+l)
461 ENDDO
462 #ifndef TARGET_NEC_SX
463 DO k=1,4
464 ew_val(k) = arrayin(w_ind(i,j)-1,s_ind(i,j)+k-2)
465 & *LAGRAN(1,xG(i,j,bi,bj),px_ind,sp)
466 & + arrayin(w_ind(i,j) ,s_ind(i,j)+k-2)
467 & *LAGRAN(2,xG(i,j,bi,bj),px_ind,sp)
468 & + arrayin(w_ind(i,j)+1,s_ind(i,j)+k-2)
469 & *LAGRAN(3,xG(i,j,bi,bj),px_ind,sp)
470 & + arrayin(w_ind(i,j)+2,s_ind(i,j)+k-2)
471 & *LAGRAN(4,xG(i,j,bi,bj),px_ind,sp)
472 arrayout(i,j,bi,bj) = arrayout(i,j,bi,bj)
473 & + ew_val(k)*LAGRAN(k,yG(i,j,bi,bj),py_ind,sp)
474 ENDDO
475 #else
476 ew_val1 = arrayin(w_ind(i,j)-1,s_ind(i,j)-1)
477 & *LAGRAN(1,xG(i,j,bi,bj),px_ind,sp)
478 & + arrayin(w_ind(i,j) ,s_ind(i,j)-1)
479 & *LAGRAN(2,xG(i,j,bi,bj),px_ind,sp)
480 & + arrayin(w_ind(i,j)+1,s_ind(i,j)-1)
481 & *LAGRAN(3,xG(i,j,bi,bj),px_ind,sp)
482 & + arrayin(w_ind(i,j)+2,s_ind(i,j)-1)
483 & *LAGRAN(4,xG(i,j,bi,bj),px_ind,sp)
484 ew_val2 = arrayin(w_ind(i,j)-1,s_ind(i,j) )
485 & *LAGRAN(1,xG(i,j,bi,bj),px_ind,sp)
486 & + arrayin(w_ind(i,j) ,s_ind(i,j) )
487 & *LAGRAN(2,xG(i,j,bi,bj),px_ind,sp)
488 & + arrayin(w_ind(i,j)+1,s_ind(i,j) )
489 & *LAGRAN(3,xG(i,j,bi,bj),px_ind,sp)
490 & + arrayin(w_ind(i,j)+2,s_ind(i,j) )
491 & *LAGRAN(4,xG(i,j,bi,bj),px_ind,sp)
492 ew_val3 = arrayin(w_ind(i,j)-1,s_ind(i,j)+1)
493 & *LAGRAN(1,xG(i,j,bi,bj),px_ind,sp)
494 & + arrayin(w_ind(i,j) ,s_ind(i,j)+1)
495 & *LAGRAN(2,xG(i,j,bi,bj),px_ind,sp)
496 & + arrayin(w_ind(i,j)+1,s_ind(i,j)+1)
497 & *LAGRAN(3,xG(i,j,bi,bj),px_ind,sp)
498 & + arrayin(w_ind(i,j)+2,s_ind(i,j)+1)
499 & *LAGRAN(4,xG(i,j,bi,bj),px_ind,sp)
500 ew_val4 = arrayin(w_ind(i,j)-1,s_ind(i,j)+2)
501 & *LAGRAN(1,xG(i,j,bi,bj),px_ind,sp)
502 & + arrayin(w_ind(i,j) ,s_ind(i,j)+2)
503 & *LAGRAN(2,xG(i,j,bi,bj),px_ind,sp)
504 & + arrayin(w_ind(i,j)+1,s_ind(i,j)+2)
505 & *LAGRAN(3,xG(i,j,bi,bj),px_ind,sp)
506 & + arrayin(w_ind(i,j)+2,s_ind(i,j)+2)
507 & *LAGRAN(4,xG(i,j,bi,bj),px_ind,sp)
508 arrayout(i,j,bi,bj) =
509 & ew_val1*LAGRAN(1,yG(i,j,bi,bj),py_ind,sp)
510 & +ew_val2*LAGRAN(2,yG(i,j,bi,bj),py_ind,sp)
511 & +ew_val3*LAGRAN(3,yG(i,j,bi,bj),py_ind,sp)
512 & +ew_val4*LAGRAN(4,yG(i,j,bi,bj),py_ind,sp)
513 #endif /* TARGET_NEC_SX defined */
514 ENDDO
515 ENDDO
516 ELSE
517 l = ILNBLNK(inFile)
518 WRITE(msgBuf,'(3A,I6)')
519 & 'EXF_INTERP: file="', inFile(1:l), '", rec=', irecord
520 CALL PRINT_ERROR( msgBuf, myThid )
521 WRITE(msgBuf,'(A,I8,A)')
522 & 'EXF_INTERP: method=', method,' not supported'
523 CALL PRINT_ERROR( msgBuf, myThid )
524 STOP 'ABNORMAL END: S/R EXF_INTERP: invalid method'
525 ENDIF
526 ENDDO
527 ENDDO
528
529 RETURN
530 END

  ViewVC Help
Powered by ViewVC 1.1.22