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

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

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

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

Legend:
Removed from v.1.3  
changed lines
  Added in v.1.27

  ViewVC Help
Powered by ViewVC 1.1.22