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

Legend:
Removed from v.1.14  
changed lines
  Added in v.1.29

  ViewVC Help
Powered by ViewVC 1.1.22