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

Legend:
Removed from v.1.10  
changed lines
  Added in v.1.31

  ViewVC Help
Powered by ViewVC 1.1.22