/[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.25 by jmc, Tue Jun 7 22:17:45 2011 UTC revision 1.34 by jmc, Mon Sep 12 22:31:29 2016 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "EXF_OPTIONS.h"  #include "EXF_OPTIONS.h"
5    
 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  
   
        _RL FUNCTION LAGRAN(i,x,a,sp)  
   
         INTEGER i  
         _RS x  
         _RL a(4)  
         INTEGER sp  
   
 C-      local variables:  
         INTEGER k  
         _RL numer,denom  
   
         numer = 1. _d 0  
         denom = 1. _d 0  
   
 #ifdef TARGET_NEC_SX  
 !CDIR UNROLL=8  
 #endif /* TARGET_NEC_SX */  
         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  
   
6  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7    
8         SUBROUTINE exf_interp(  CBOP
9       I   infile,  C     !ROUTINE: EXF_INTERP
10       I   filePrec,  C     !INTERFACE:
11       O   arrayout,         SUBROUTINE EXF_INTERP(
12       I   irecord, xG_in, yG,       I                inFile, filePrec,
13       I   lon_0, lon_inc,       O                arrayout,
14       I   lat_0, lat_inc,       I                irecord, xG_in, yG,
15       I   nx_in, ny_in, method, mythid)       I                lon_0, lon_inc, lat_0, lat_inc,
16         I                nxIn, nyIn, method, myIter, myThid )
17        implicit none  
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"
30    #include "EEPARAMS.h"
31    #include "PARAMS.h"
32    #ifdef ALLOW_DEBUG
33    # include "EXF_PARAM.h"
34    #endif
35    
36  C  infile      (string)  :: name of the binary input file (direct access)  C !INPUT/OUTPUT PARAMETERS:
37    C  inFile      (string)  :: name of the binary input file (direct access)
38  C  filePrec    (integer) :: number of bits per word in file (32 or 64)  C  filePrec    (integer) :: number of bits per word in file (32 or 64)
39  C  arrout      ( _RL )   :: output array  C  arrayout    ( _RL )   :: output array
40  C  irecord     (integer) :: record number to read  C  irecord     (integer) :: record number to read
41  C     xG,yG              :: coordinates for output grid to interpolate to  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  C     lon_0, lat_0       :: lon and lat of sw corner of global input grid
43  C     lon_inc            :: scalar x-grid increment  C     lon_inc            :: scalar x-grid increment
44  C     lat_inc            :: vector y-grid increments  C     lat_inc            :: vector y-grid increments
45  C  nx_in,ny_in (integer) :: size in x & y direction of input file to read  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  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  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  C  myThid      (integer) :: My Thread Id number
 C  
50    
51  #include "SIZE.h"        CHARACTER*(*) inFile
52  #include "EEPARAMS.h"        INTEGER       filePrec, irecord, nxIn, nyIn
 #include "PARAMS.h"  
   
 C subroutine variables  
       character*(*) infile  
       integer       filePrec, irecord, nx_in, ny_in  
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_in   (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  c     _RL           lat_0, lat_inc(ny_in-1)  c     _RL           lat_0, lat_inc(nyIn-1)
58        _RL           lat_0, lat_inc(*)        _RL           lat_0, lat_inc(*)
59        integer       method, mythid        INTEGER       method, myIter, myThid
60    
61  C functions  C !FUNCTIONS:
62        external lagran  #ifdef ALLOW_DEBUG
63        _RL      lagran        INTEGER  ILNBLNK
64          EXTERNAL ILNBLNK
 C local variables  
       integer  e_ind(snx,sny),w_ind(snx,sny)  
       integer  n_ind(snx,sny),s_ind(snx,sny)  
       _RL      px_ind(4), py_ind(4), ew_val(4)  
       _RL      arrayin(-1:nx_in+2 ,      -1:ny_in+2)  
       _RL      NorthValue  
       _RL      x_in   (-1:nx_in+2), y_in(-1:ny_in+2)  
       integer  i, j, k, l, js, bi, bj, sp, interp_unit  
 #ifdef TARGET_NEC_SX  
       integer  ic, ii, icnt  
       integer  inx(snx*sny,2)  
       _RL      ew_val1, ew_val2, ew_val3, ew_val4  
65  #endif  #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)        _RS      xG(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
       _RL      ninety  
       PARAMETER ( ninety = 90. )  
84        _RS      threeSixtyRS        _RS      threeSixtyRS
85          _RL      yPole, symSign, poleValue
86        PARAMETER ( threeSixtyRS = 360. )        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     put xG in interval [ lon_0 , lon_0+360 [  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
98        do bj=myByLo(myThid),myByHi(myThid)  C---  Load inut field
99         do bi=myBxLo(myThid),myBxHi(myThid)  
100          do j=1-OLy,sNy+OLy        CALL EXF_INTERP_READ(
101           do i=1-OLx,sNx+OLx       I         inFile, filePrec,
102            xG(i,j,bi,bj) = xG_in(i,j,bi,bj)-lon_0       O         arrayin,
103       &                  + threeSixtyRS*2.       I         irecord, nxIn, nyIn, myThid )
104            xG(i,j,bi,bj) = lon_0+mod(xG(i,j,bi,bj),threeSixtyRS)  
105           enddo  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
106          enddo  C---  Prepare input grid and input field
        enddo  
       enddo  
   
        call exf_interp_read(  
      I   infile, filePrec,  
      O   arrayin,  
      I   irecord, nx_in, ny_in, mythid)  
107    
108  C setup input longitude grid  C--   setup input longitude grid
109        do i=-1,nx_in+2        DO i=-1,nxIn+2
110         x_in(i) = lon_0 + (i-1)*lon_inc         x_in(i) = lon_0 + (i-1)*lon_inc
111        enddo        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  C--   setup input latitude grid
       y_in(0) = lat_0 - lat_inc(1)  
       y_in(-1)= lat_0 - 2.*lat_inc(1)  
120        y_in(1) = lat_0        y_in(1) = lat_0
121        do j=2,ny_in        DO j=1,nyIn+1
122         y_in(j) = y_in(j-1) + lat_inc(j-1)         i = MIN(j,nyIn-1)
123        enddo         y_in(j+1) = y_in(j) + lat_inc(i)
124        do j=ny_in+1,ny_in+2        ENDDO
125         if (y_in(j-1).eq.ninety) then        y_in(0) = y_in(1) - lat_inc(1)
126          y_in(j) = 2 * ninety - y_in(j-2)        y_in(-1)= y_in(0) - lat_inc(1)
127         else  #ifdef ALLOW_DEBUG
128          i = max(1,ny_in-1)        DO l=-1,4
129          y_in(j) = min( y_in(j-1)+lat_inc(i), ninety )          prtPole(l) = 0.
130         endif        ENDDO
131        enddo  #endif
132    C--   For tracer (method=1,2) add 1 row @ the pole (if last row is not)
133  C enlarge boundary  C     and will fill it with the polarmost-row zonally averaged value.
134        do j=1,ny_in  C     For vector component, cannot do much without the other component;
135         arrayin(0,j)       = arrayin(nx_in,j)  C     averaging properly done if uvInterp=T in S/R EXF_INTERP_UV
136         arrayin(-1,j)      = arrayin(nx_in-1,j)  #ifdef EXF_USE_OLD_INTERP_POLE
137         arrayin(nx_in+1,j) = arrayin(1,j)        IF ( .TRUE. ) THEN
138         arrayin(nx_in+2,j) = arrayin(2,j)  #else
139        enddo        IF ( method.LT.10 ) THEN
140        do i=-1,nx_in+2  C-    Add 2 row @ southern end; if one is beyond S.pole, put one @ S.pole
141         arrayin(i,0)       = arrayin(i,1)         j = 0
142         arrayin(i,-1)      = arrayin(i,1)         IF ( ABS(y_in(j+1)).LT.yPole .AND. ABS(y_in(j)).GT.yPole ) THEN
143         arrayin(i,ny_in+1) = arrayin(i,ny_in)           y_in(j) = -yPole
144         arrayin(i,ny_in+2) = arrayin(i,ny_in)           y_in(j-1) = -2.*yPole - y_in(1)
145        enddo  #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  C--   For tracer (method=1,2) set to northernmost zonal-mean value
222  C     at 90N to avoid sharp zonal gradients near the Pole.  C     at 90N to avoid sharp zonal gradients near the Pole.
223  C     For U (method=11,12) set to zero at 90N to minimize velocity  C     For vector component, cannot do much without the other component;
224  C     gradient at North Pole  C     averaging properly done if uvInterp=T in S/R EXF_INTERP_UV
225  C     For V (method=11,12) set to northernmost zonal value at 90N,  #ifdef EXF_USE_OLD_INTERP_POLE
226  C     as is already done above in order to allow cross-PoleArctic flow        IF ( .TRUE. ) THEN
227        do j=ny_in,ny_in+2         DO l= 3,4
228         if (y_in(j).eq.ninety) then  #else
229          if (method.eq.1 .or. method.eq.2) then        IF ( method.LT.10 ) THEN
230           NorthValue = 0.         DO l=-1,4
231           do i=1,nx_in  #endif
232            NorthValue = NorthValue + arrayin(i,j)          j = l
233           enddo          IF ( l.GE.2 ) j = nyIn+l-2
234           NorthValue = NorthValue / nx_in          IF ( ABS(y_in(j)).EQ.yPole ) THEN
235           do i=-1,nx_in+2           IF (method.EQ.1 .OR. method.EQ.2) THEN
236            arrayin(i,j) = NorthValue            poleValue = 0.
237           enddo            DO i=1,nxIn
238          elseif (method.eq.11 .or. method.eq.12) then             poleValue = poleValue + arrayin(i,j)
239           do i=-1,nx_in+2            ENDDO
240            arrayin(i,j) = 0.            poleValue = poleValue / nxIn
241           enddo            DO i=-1,nxIn+2
242          endif             arrayin(i,j) = poleValue
243         endif            ENDDO
244        enddo  #ifdef ALLOW_DEBUG
245              prtPole(l) = prtPole(l) + 0.1
246        do bj = mybylo(mythid), mybyhi(mythid)  #endif
247         do bi = mybxlo(mythid), mybxhi(mythid)  #ifdef EXF_USE_OLD_INTERP_POLE
248             ELSEIF (method.EQ.11 .OR. method.EQ.12) THEN
249  C check validity of input/output coordinates            DO i=-1,nxIn+2
250  #ifdef ALLOW_DEBUG             arrayin(i,j) = 0.
251          if ( debugLevel.GE.debLevC ) then            ENDDO
252           do j=1,sny  #ifdef ALLOW_DEBUG
253            do i=1,snx            prtPole(l) = prtPole(l) + 0.9
254             if ( xG(i,j,bi,bj) .lt. x_in(0)         .or.  #endif
255       &          xG(i,j,bi,bj) .ge. x_in(nx_in+1)   .or.  #endif /* EXF_USE_OLD_INTERP_POLE */
256       &          yG(i,j,bi,bj) .lt. y_in(0)         .or.           ENDIF
257       &          yG(i,j,bi,bj) .ge. y_in(ny_in+1) ) then          ENDIF
258                print*,'ERROR in S/R EXF_INTERP:'         ENDDO
259                print*,'   input grid must encompass output grid.'        ENDIF
260                print*,'i,j,bi,bj'      ,i,j,bi,bj  
261                print*,'xG,yG'          ,xG(i,j,bi,bj),yG(i,j,bi,bj)  #ifdef ALLOW_DEBUG
262                print*,'nx_in,ny_in'    ,nx_in        ,ny_in        debugFlag = ( exf_debugLev.GE.debLevC )
263                print*,'x_in(0,nx_in+1)',x_in(0)      ,x_in(nx_in+1)       &       .OR. ( exf_debugLev.GE.debLevB .AND. myIter.LE.nIter0 )
264                print*,'y_in(0,ny_in+1)',y_in(0)      ,y_in(ny_in+1)  C     prtPole(l)=0 : extended, =1 : changed to pole, =2 : changed to symetric
265                STOP   ' ABNORMAL END: S/R EXF_INTERP'        IF ( debugFlag ) THEN
266             endif          l = ILNBLNK(inFile)
267            enddo          _BEGIN_MASTER(myThid)
268           enddo          WRITE(msgBuf,'(3A,I6,A,2L5)')
269          endif       &   '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 */  #endif /* ALLOW_DEBUG */
284    
285  C compute interpolation indices  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
286          do j=1,sny  C---  Prepare output grid and interpolate for each tile
287           do i=1,snx  
288            if (xG(i,j,bi,bj)-x_in(1) .ge. 0.) then  C--   put xG in interval [ lon_0 , lon_0+360 [
289             w_ind(i,j) = int((xG(i,j,bi,bj)-x_in(1))/lon_inc) + 1        DO bj=myByLo(myThid),myByHi(myThid)
290            else         DO bi=myBxLo(myThid),myBxHi(myThid)
291             w_ind(i,j) = int((xG(i,j,bi,bj)-x_in(1))/lon_inc)          DO j=1-OLy,sNy+OLy
292            endif           DO i=1-OLx,sNx+OLx
293            e_ind(i,j) = w_ind(i,j) + 1            xG(i,j,bi,bj) = xG_in(i,j,bi,bj)-lon_0
294           enddo       &                  + threeSixtyRS*2.
295          enddo            xG(i,j,bi,bj) = lon_0+MOD(xG(i,j,bi,bj),threeSixtyRS)
296  #ifndef TARGET_NEC_SX           ENDDO
297  C     use the original and more readable variant of the algorithm that          ENDDO
298  C     has unvectorizable while-loops for each (i,j)  #ifdef ALLOW_DEBUG
299          do j=1,sny  C--   Check validity of input/output coordinates
300           do i=1,snx          IF ( debugFlag ) THEN
301            js = ny_in*.5           DO j=1,sNy
302            do while (yG(i,j,bi,bj) .lt. y_in(js))            DO i=1,sNx
303             js = (js - 1)*.5             IF ( xG(i,j,bi,bj) .LT. x_in(0)        .OR.
304            enddo       &          xG(i,j,bi,bj) .GE. x_in(nxIn+1)   .OR.
305            do while (yG(i,j,bi,bj) .ge. y_in(js+1))       &          yG(i,j,bi,bj) .LT. y_in(0)        .OR.
306             js = js + 1       &          yG(i,j,bi,bj) .GE. y_in(nyIn+1) ) THEN
307            enddo              l = ILNBLNK(inFile)
308            s_ind(i,j) = js              WRITE(msgBuf,'(3A,I6)')
309           enddo       &        'EXF_INTERP: file="', inFile(1:l), '", rec=', irecord
310          enddo              CALL PRINT_ERROR( msgBuf, myThid )
311  #else /* TARGET_NEC_SX defined */              WRITE(msgBuf,'(A)')
312  C     this variant vectorizes more efficiently than the original one because       &        'EXF_INTERP: input grid must encompass output grid.'
313  C     it moves the while loops out of the i,j loops (loop pushing) but              CALL PRINT_ERROR( msgBuf, myThid )
314  C     it is ugly and incomprehensible              WRITE(msgBuf,'(A,2I8,2I6,A,1P2E14.6)') 'i,j,bi,bj=',
315          icnt = 0       &        i,j,bi,bj, ' , xG,yG=', xG(i,j,bi,bj), yG(i,j,bi,bj)
316          do j=1,sny              CALL PRINT_ERROR( msgBuf, myThid )
317           do i=1,snx              WRITE(msgBuf,'(A,I9,A,1P2E14.6)') 'nxIn=', nxIn,
318            s_ind(i,j) = ny_in*.5       &        ' , x_in(0,nxIn+1)=', x_in(0) ,x_in(nxIn+1)
319            icnt = icnt+1              CALL PRINT_ERROR( msgBuf, myThid )
320            inx(icnt,1) = i              WRITE(msgBuf,'(A,I9,A,1P2E14.6)') 'nyIn=', nyIn,
321            inx(icnt,2) = j       &        ' , y_in(0,nyIn+1)=', y_in(0) ,y_in(nyIn+1)
322           enddo              CALL PRINT_ERROR( msgBuf, myThid )
323          enddo              STOP 'ABNORMAL END: S/R EXF_INTERP'
324          do while (icnt .gt. 0)             ENDIF
325           ii = 0            ENDDO
326  !CDIR NODEP           ENDDO
327           do ic=1,icnt          ENDIF
328            i = inx(ic,1)  #endif /* ALLOW_DEBUG */
329            j = inx(ic,2)         ENDDO
330            if (yG(i,j,bi,bj) .lt. y_in(s_ind(i,j))) then        ENDDO
331             s_ind(i,j) = (s_ind(i,j) - 1)*.5  
332             ii = ii+1        DO bj = myByLo(myThid), myByHi(myThid)
333             inx(ii,1) = i         DO bi = myBxLo(myThid), myBxHi(myThid)
334             inx(ii,2) = j  
335            endif  C--   Compute interpolation lon & lat index mapping
336           enddo  C--     latitude index
337           icnt = ii          DO j=1,sNy
338          enddo           DO i=1,sNx
339          icnt = 0            s_ind(i,j) = 0
340          do j=1,sny            w_ind(i,j) = nyIn+1
341           do i=1,snx           ENDDO
342            icnt = icnt+1          ENDDO
343            inx(icnt,1) = i  C       # of pts = nyIn+2 ; # of interval = nyIn+1 ; evaluate nLoop as
344            inx(icnt,2) = j  C       1 + truncated log2(# interval -1); add epsil=1.e-3 for safey
345           enddo          tmpVar = nyIn + 1. _d -3
346          enddo          nLoop = 1 + INT( LOG(tmpVar)/LOG(2. _d 0) )
347          do while (icnt .gt. 0)          DO l=1,nLoop
348           ii = 0           DO j=1,sNy
349  !CDIR NODEP            DO i=1,sNx
350           do ic=1,icnt             IF ( w_ind(i,j).GT.s_ind(i,j)+1 ) THEN
351            i = inx(ic,1)              k = NINT( (s_ind(i,j)+w_ind(i,j))*0.5 )
352            j = inx(ic,2)              IF ( yG(i,j,bi,bj) .LT. y_in(k) ) THEN
353            if (yG(i,j,bi,bj) .ge. y_in(s_ind(i,j)+1)) then                w_ind(i,j) = k
354             s_ind(i,j) = s_ind(i,j) + 1              ELSE
355             ii = ii+1                s_ind(i,j) = k
356             inx(ii,1) = i              ENDIF
357             inx(ii,2) = j             ENDIF
358            endif            ENDDO
359           enddo           ENDDO
360           icnt = ii          ENDDO
361          enddo  #ifdef ALLOW_DEBUG
362  #endif /* TARGET_NEC_SX defined */          IF ( debugFlag ) THEN
363          do j=1,sny  C-      Check that we found the right lat. index
364           do i=1,snx           DO j=1,sNy
365            n_ind(i,j) = s_ind(i,j) + 1            DO i=1,sNx
366           enddo             IF ( w_ind(i,j).NE.s_ind(i,j)+1 ) THEN
367          enddo              l = ILNBLNK(inFile)
368                WRITE(msgBuf,'(3A,I4,A,I4)')
369          if (method.eq.1 .or. method.eq.11 .or. method.eq.21) then       &        'EXF_INTERP: file="', inFile(1:l), '", rec=', irecord,
370         &        ', nLoop=', nLoop
371  C bilinear interpolation              CALL PRINT_ERROR( msgBuf, myThid )
372           sp = 2              WRITE(msgBuf,'(A)')
373           do j=1,sny       &        'EXF_INTERP: did not find Latitude index for grid-pt:'
374            do i=1,snx              CALL PRINT_ERROR( msgBuf, myThid )
375             arrayout(i,j,bi,bj) = 0.              WRITE(msgBuf,'(A,2I8,2I6,A,1PE16.8)')
376             do l=0,1       &        'EXF_INTERP: i,j,bi,bj=',i,j,bi,bj,' , yG=',yG(i,j,bi,bj)
377              px_ind(l+1) = x_in(w_ind(i,j)+l)              CALL PRINT_ERROR( msgBuf, myThid )
378              py_ind(l+1) = y_in(s_ind(i,j)+l)              WRITE(msgBuf,'(A,I8,A,1PE16.8)')
379             enddo       &        'EXF_INTERP: s_ind=',s_ind(i,j),', lat=',y_in(s_ind(i,j))
380  #ifndef TARGET_NEC_SX              CALL PRINT_ERROR( msgBuf, myThid )
381             do k=1,2              WRITE(msgBuf,'(A,I8,A,1PE16.8)')
382              ew_val(k) = arrayin(w_ind(i,j),s_ind(i,j)+k-1)       &        'EXF_INTERP: n_ind=',w_ind(i,j),', lat=',y_in(w_ind(i,j))
383       &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)              CALL PRINT_ERROR( msgBuf, myThid )
384       &             +arrayin(e_ind(i,j),s_ind(i,j)+k-1)              STOP 'ABNORMAL END: S/R EXF_INTERP'
385       &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)             ENDIF
386              arrayout(i,j,bi,bj)=arrayout(i,j,bi,bj)            ENDDO
387       &             +ew_val(k)*lagran(k,yG(i,j,bi,bj),py_ind,sp)           ENDDO
388             enddo          ENDIF
389  #else  #endif /* ALLOW_DEBUG */
390             ew_val1 = arrayin(w_ind(i,j),s_ind(i,j)+1-1)  C--     longitude index
391       &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)          DO j=1,sNy
392       &             +arrayin(e_ind(i,j),s_ind(i,j)+1-1)           DO i=1,sNx
393       &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)             w_ind(i,j) = INT((xG(i,j,bi,bj)-x_in(-1))/lon_inc) - 1
394             ew_val2 = arrayin(w_ind(i,j),s_ind(i,j)+2-1)           ENDDO
395       &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)          ENDDO
396       &             +arrayin(e_ind(i,j),s_ind(i,j)+2-1)  
397       &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)  C--   Do interpolation using lon & lat index mapping
398             arrayout(i,j,bi,bj)=          CALL EXF_INTERPOLATE(
399       &             +ew_val1*lagran(1,yG(i,j,bi,bj),py_ind,sp)       I                inFile, irecord, method,
400       &             +ew_val2*lagran(2,yG(i,j,bi,bj),py_ind,sp)       I                nxIn, nyIn, x_in, y_in,
401  #endif /* TARGET_NEC_SX defined */       I                arrayin,
402            enddo       O                arrayout,
403           enddo       I                xG, yG,
404          elseif (method .eq. 2 .or. method.eq.12 .or. method.eq.22) then       I                w_ind, s_ind,
405         I                bi, bj, myThid )
406  C bicubic interpolation  
407           sp = 4         ENDDO
408           do j=1,sny        ENDDO
           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  
 #ifndef TARGET_NEC_SX  
            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  
 #else  
            ew_val1 =  
      &             arrayin(w_ind(i,j)-1,s_ind(i,j)+1-2)  
      &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)  
      &             +arrayin(w_ind(i,j)  ,s_ind(i,j)+1-2)  
      &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)  
      &             +arrayin(e_ind(i,j)  ,s_ind(i,j)+1-2)  
      &             *lagran(3,xG(i,j,bi,bj),px_ind,sp)  
      &             +arrayin(e_ind(i,j)+1,s_ind(i,j)+1-2)  
      &             *lagran(4,xG(i,j,bi,bj),px_ind,sp)  
             ew_val2 =  
      &             arrayin(w_ind(i,j)-1,s_ind(i,j)+2-2)  
      &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)  
      &             +arrayin(w_ind(i,j)  ,s_ind(i,j)+2-2)  
      &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)  
      &             +arrayin(e_ind(i,j)  ,s_ind(i,j)+2-2)  
      &             *lagran(3,xG(i,j,bi,bj),px_ind,sp)  
      &             +arrayin(e_ind(i,j)+1,s_ind(i,j)+2-2)  
      &             *lagran(4,xG(i,j,bi,bj),px_ind,sp)  
             ew_val3 =  
      &             arrayin(w_ind(i,j)-1,s_ind(i,j)+3-2)  
      &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)  
      &             +arrayin(w_ind(i,j)  ,s_ind(i,j)+3-2)  
      &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)  
      &             +arrayin(e_ind(i,j)  ,s_ind(i,j)+3-2)  
      &             *lagran(3,xG(i,j,bi,bj),px_ind,sp)  
      &             +arrayin(e_ind(i,j)+1,s_ind(i,j)+3-2)  
      &             *lagran(4,xG(i,j,bi,bj),px_ind,sp)  
             ew_val4 =  
      &             arrayin(w_ind(i,j)-1,s_ind(i,j)+4-2)  
      &             *lagran(1,xG(i,j,bi,bj),px_ind,sp)  
      &             +arrayin(w_ind(i,j)  ,s_ind(i,j)+4-2)  
      &             *lagran(2,xG(i,j,bi,bj),px_ind,sp)  
      &             +arrayin(e_ind(i,j)  ,s_ind(i,j)+4-2)  
      &             *lagran(3,xG(i,j,bi,bj),px_ind,sp)  
      &             +arrayin(e_ind(i,j)+1,s_ind(i,j)+4-2)  
      &             *lagran(4,xG(i,j,bi,bj),px_ind,sp)  
             arrayout(i,j,bi,bj)=  
      &             +ew_val1*lagran(1,yG(i,j,bi,bj),py_ind,sp)  
      &             +ew_val2*lagran(2,yG(i,j,bi,bj),py_ind,sp)  
      &             +ew_val3*lagran(3,yG(i,j,bi,bj),py_ind,sp)  
      &             +ew_val4*lagran(4,yG(i,j,bi,bj),py_ind,sp)  
 #endif /* TARGET_NEC_SX defined */  
           enddo  
          enddo  
         else  
          stop 'stop in exf_interp.F: interpolation method not supported'  
         endif  
        enddo  
       enddo  
409    
410        RETURN        RETURN
411        END        END

Legend:
Removed from v.1.25  
changed lines
  Added in v.1.34

  ViewVC Help
Powered by ViewVC 1.1.22