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

Legend:
Removed from v.1.10.2.1  
changed lines
  Added in v.1.38

  ViewVC Help
Powered by ViewVC 1.1.22