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

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

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


Revision 1.25 - (show annotations) (download)
Tue Jun 7 22:17:45 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62z
Changes since 1.24: +2 -2 lines
refine debugLevel criteria when printing messages

1 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_interp.F,v 1.24 2010/04/07 20:52:30 jmc Exp $
2 C $Name: $
3
4 #include "EXF_OPTIONS.h"
5
6 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
7 C Flux Coupler using C
8 C Bilinear interpolation of forcing fields C
9 C C
10 C B. Cheng (12/2002) C
11 C C
12 C added Bicubic (bnc 1/2003) C
13 C C
14 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
15
16 _RL FUNCTION LAGRAN(i,x,a,sp)
17
18 INTEGER i
19 _RS x
20 _RL a(4)
21 INTEGER sp
22
23 C- local variables:
24 INTEGER k
25 _RL numer,denom
26
27 numer = 1. _d 0
28 denom = 1. _d 0
29
30 #ifdef TARGET_NEC_SX
31 !CDIR UNROLL=8
32 #endif /* TARGET_NEC_SX */
33 do k=1,sp
34 if ( k .ne. i) then
35 denom = denom*(a(i) - a(k))
36 numer = numer*(x - a(k))
37 endif
38 enddo
39
40 lagran = numer/denom
41
42 RETURN
43 END
44
45 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
46
47 SUBROUTINE exf_interp(
48 I infile,
49 I filePrec,
50 O arrayout,
51 I irecord, xG_in, yG,
52 I lon_0, lon_inc,
53 I lat_0, lat_inc,
54 I nx_in, ny_in, method, mythid)
55
56 implicit none
57
58 C infile (string) :: name of the binary input file (direct access)
59 C filePrec (integer) :: number of bits per word in file (32 or 64)
60 C arrout ( _RL ) :: output array
61 C irecord (integer) :: record number to read
62 C xG,yG :: coordinates for output grid to interpolate to
63 C lon_0, lat_0 :: lon and lat of sw corner of global input grid
64 C lon_inc :: scalar x-grid increment
65 C lat_inc :: vector y-grid increments
66 C nx_in,ny_in (integer) :: size in x & y direction of input file to read
67 C method :: 1,11,21 for bilinear; 2,12,22 for bicubic
68 C :: 1,2 for tracer; 11,12 for U; 21,22 for V
69 C myThid (integer) :: My Thread Id number
70 C
71
72 #include "SIZE.h"
73 #include "EEPARAMS.h"
74 #include "PARAMS.h"
75
76 C subroutine variables
77 character*(*) infile
78 integer filePrec, irecord, nx_in, ny_in
79 _RL arrayout(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
80 _RS xG_in (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
81 _RS yG (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
82 _RL lon_0, lon_inc
83 c _RL lat_0, lat_inc(ny_in-1)
84 _RL lat_0, lat_inc(*)
85 integer method, mythid
86
87 C functions
88 external lagran
89 _RL lagran
90
91 C local variables
92 integer e_ind(snx,sny),w_ind(snx,sny)
93 integer n_ind(snx,sny),s_ind(snx,sny)
94 _RL px_ind(4), py_ind(4), ew_val(4)
95 _RL arrayin(-1:nx_in+2 , -1:ny_in+2)
96 _RL NorthValue
97 _RL x_in (-1:nx_in+2), y_in(-1:ny_in+2)
98 integer i, j, k, l, js, bi, bj, sp, interp_unit
99 #ifdef TARGET_NEC_SX
100 integer ic, ii, icnt
101 integer inx(snx*sny,2)
102 _RL ew_val1, ew_val2, ew_val3, ew_val4
103 #endif
104 _RS xG(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
105 _RL ninety
106 PARAMETER ( ninety = 90. )
107 _RS threeSixtyRS
108 PARAMETER ( threeSixtyRS = 360. )
109
110 C put xG in interval [ lon_0 , lon_0+360 [
111 do bj=myByLo(myThid),myByHi(myThid)
112 do bi=myBxLo(myThid),myBxHi(myThid)
113 do j=1-OLy,sNy+OLy
114 do i=1-OLx,sNx+OLx
115 xG(i,j,bi,bj) = xG_in(i,j,bi,bj)-lon_0
116 & + threeSixtyRS*2.
117 xG(i,j,bi,bj) = lon_0+mod(xG(i,j,bi,bj),threeSixtyRS)
118 enddo
119 enddo
120 enddo
121 enddo
122
123 call exf_interp_read(
124 I infile, filePrec,
125 O arrayin,
126 I irecord, nx_in, ny_in, mythid)
127
128 C setup input longitude grid
129 do i=-1,nx_in+2
130 x_in(i) = lon_0 + (i-1)*lon_inc
131 enddo
132
133 C setup input latitude grid
134 y_in(0) = lat_0 - lat_inc(1)
135 y_in(-1)= lat_0 - 2.*lat_inc(1)
136 y_in(1) = lat_0
137 do j=2,ny_in
138 y_in(j) = y_in(j-1) + lat_inc(j-1)
139 enddo
140 do j=ny_in+1,ny_in+2
141 if (y_in(j-1).eq.ninety) then
142 y_in(j) = 2 * ninety - y_in(j-2)
143 else
144 i = max(1,ny_in-1)
145 y_in(j) = min( y_in(j-1)+lat_inc(i), ninety )
146 endif
147 enddo
148
149 C enlarge boundary
150 do j=1,ny_in
151 arrayin(0,j) = arrayin(nx_in,j)
152 arrayin(-1,j) = arrayin(nx_in-1,j)
153 arrayin(nx_in+1,j) = arrayin(1,j)
154 arrayin(nx_in+2,j) = arrayin(2,j)
155 enddo
156 do i=-1,nx_in+2
157 arrayin(i,0) = arrayin(i,1)
158 arrayin(i,-1) = arrayin(i,1)
159 arrayin(i,ny_in+1) = arrayin(i,ny_in)
160 arrayin(i,ny_in+2) = arrayin(i,ny_in)
161 enddo
162
163 C For tracer (method=1,2) set to northernmost zonal-mean value
164 C at 90N to avoid sharp zonal gradients near the Pole.
165 C For U (method=11,12) set to zero at 90N to minimize velocity
166 C gradient at North Pole
167 C For V (method=11,12) set to northernmost zonal value at 90N,
168 C as is already done above in order to allow cross-PoleArctic flow
169 do j=ny_in,ny_in+2
170 if (y_in(j).eq.ninety) then
171 if (method.eq.1 .or. method.eq.2) then
172 NorthValue = 0.
173 do i=1,nx_in
174 NorthValue = NorthValue + arrayin(i,j)
175 enddo
176 NorthValue = NorthValue / nx_in
177 do i=-1,nx_in+2
178 arrayin(i,j) = NorthValue
179 enddo
180 elseif (method.eq.11 .or. method.eq.12) then
181 do i=-1,nx_in+2
182 arrayin(i,j) = 0.
183 enddo
184 endif
185 endif
186 enddo
187
188 do bj = mybylo(mythid), mybyhi(mythid)
189 do bi = mybxlo(mythid), mybxhi(mythid)
190
191 C check validity of input/output coordinates
192 #ifdef ALLOW_DEBUG
193 if ( debugLevel.GE.debLevC ) then
194 do j=1,sny
195 do i=1,snx
196 if ( xG(i,j,bi,bj) .lt. x_in(0) .or.
197 & xG(i,j,bi,bj) .ge. x_in(nx_in+1) .or.
198 & yG(i,j,bi,bj) .lt. y_in(0) .or.
199 & yG(i,j,bi,bj) .ge. y_in(ny_in+1) ) then
200 print*,'ERROR in S/R EXF_INTERP:'
201 print*,' input grid must encompass output grid.'
202 print*,'i,j,bi,bj' ,i,j,bi,bj
203 print*,'xG,yG' ,xG(i,j,bi,bj),yG(i,j,bi,bj)
204 print*,'nx_in,ny_in' ,nx_in ,ny_in
205 print*,'x_in(0,nx_in+1)',x_in(0) ,x_in(nx_in+1)
206 print*,'y_in(0,ny_in+1)',y_in(0) ,y_in(ny_in+1)
207 STOP ' ABNORMAL END: S/R EXF_INTERP'
208 endif
209 enddo
210 enddo
211 endif
212 #endif /* ALLOW_DEBUG */
213
214 C compute interpolation indices
215 do j=1,sny
216 do i=1,snx
217 if (xG(i,j,bi,bj)-x_in(1) .ge. 0.) then
218 w_ind(i,j) = int((xG(i,j,bi,bj)-x_in(1))/lon_inc) + 1
219 else
220 w_ind(i,j) = int((xG(i,j,bi,bj)-x_in(1))/lon_inc)
221 endif
222 e_ind(i,j) = w_ind(i,j) + 1
223 enddo
224 enddo
225 #ifndef TARGET_NEC_SX
226 C use the original and more readable variant of the algorithm that
227 C has unvectorizable while-loops for each (i,j)
228 do j=1,sny
229 do i=1,snx
230 js = ny_in*.5
231 do while (yG(i,j,bi,bj) .lt. y_in(js))
232 js = (js - 1)*.5
233 enddo
234 do while (yG(i,j,bi,bj) .ge. y_in(js+1))
235 js = js + 1
236 enddo
237 s_ind(i,j) = js
238 enddo
239 enddo
240 #else /* TARGET_NEC_SX defined */
241 C this variant vectorizes more efficiently than the original one because
242 C it moves the while loops out of the i,j loops (loop pushing) but
243 C it is ugly and incomprehensible
244 icnt = 0
245 do j=1,sny
246 do i=1,snx
247 s_ind(i,j) = ny_in*.5
248 icnt = icnt+1
249 inx(icnt,1) = i
250 inx(icnt,2) = j
251 enddo
252 enddo
253 do while (icnt .gt. 0)
254 ii = 0
255 !CDIR NODEP
256 do ic=1,icnt
257 i = inx(ic,1)
258 j = inx(ic,2)
259 if (yG(i,j,bi,bj) .lt. y_in(s_ind(i,j))) then
260 s_ind(i,j) = (s_ind(i,j) - 1)*.5
261 ii = ii+1
262 inx(ii,1) = i
263 inx(ii,2) = j
264 endif
265 enddo
266 icnt = ii
267 enddo
268 icnt = 0
269 do j=1,sny
270 do i=1,snx
271 icnt = icnt+1
272 inx(icnt,1) = i
273 inx(icnt,2) = j
274 enddo
275 enddo
276 do while (icnt .gt. 0)
277 ii = 0
278 !CDIR NODEP
279 do ic=1,icnt
280 i = inx(ic,1)
281 j = inx(ic,2)
282 if (yG(i,j,bi,bj) .ge. y_in(s_ind(i,j)+1)) then
283 s_ind(i,j) = s_ind(i,j) + 1
284 ii = ii+1
285 inx(ii,1) = i
286 inx(ii,2) = j
287 endif
288 enddo
289 icnt = ii
290 enddo
291 #endif /* TARGET_NEC_SX defined */
292 do j=1,sny
293 do i=1,snx
294 n_ind(i,j) = s_ind(i,j) + 1
295 enddo
296 enddo
297
298 if (method.eq.1 .or. method.eq.11 .or. method.eq.21) then
299
300 C bilinear interpolation
301 sp = 2
302 do j=1,sny
303 do i=1,snx
304 arrayout(i,j,bi,bj) = 0.
305 do l=0,1
306 px_ind(l+1) = x_in(w_ind(i,j)+l)
307 py_ind(l+1) = y_in(s_ind(i,j)+l)
308 enddo
309 #ifndef TARGET_NEC_SX
310 do k=1,2
311 ew_val(k) = arrayin(w_ind(i,j),s_ind(i,j)+k-1)
312 & *lagran(1,xG(i,j,bi,bj),px_ind,sp)
313 & +arrayin(e_ind(i,j),s_ind(i,j)+k-1)
314 & *lagran(2,xG(i,j,bi,bj),px_ind,sp)
315 arrayout(i,j,bi,bj)=arrayout(i,j,bi,bj)
316 & +ew_val(k)*lagran(k,yG(i,j,bi,bj),py_ind,sp)
317 enddo
318 #else
319 ew_val1 = arrayin(w_ind(i,j),s_ind(i,j)+1-1)
320 & *lagran(1,xG(i,j,bi,bj),px_ind,sp)
321 & +arrayin(e_ind(i,j),s_ind(i,j)+1-1)
322 & *lagran(2,xG(i,j,bi,bj),px_ind,sp)
323 ew_val2 = arrayin(w_ind(i,j),s_ind(i,j)+2-1)
324 & *lagran(1,xG(i,j,bi,bj),px_ind,sp)
325 & +arrayin(e_ind(i,j),s_ind(i,j)+2-1)
326 & *lagran(2,xG(i,j,bi,bj),px_ind,sp)
327 arrayout(i,j,bi,bj)=
328 & +ew_val1*lagran(1,yG(i,j,bi,bj),py_ind,sp)
329 & +ew_val2*lagran(2,yG(i,j,bi,bj),py_ind,sp)
330 #endif /* TARGET_NEC_SX defined */
331 enddo
332 enddo
333 elseif (method .eq. 2 .or. method.eq.12 .or. method.eq.22) then
334
335 C bicubic interpolation
336 sp = 4
337 do j=1,sny
338 do i=1,snx
339 arrayout(i,j,bi,bj) = 0.
340 do l=-1,2
341 px_ind(l+2) = x_in(w_ind(i,j)+l)
342 py_ind(l+2) = y_in(s_ind(i,j)+l)
343 enddo
344 #ifndef TARGET_NEC_SX
345 do k=1,4
346 ew_val(k) =
347 & arrayin(w_ind(i,j)-1,s_ind(i,j)+k-2)
348 & *lagran(1,xG(i,j,bi,bj),px_ind,sp)
349 & +arrayin(w_ind(i,j) ,s_ind(i,j)+k-2)
350 & *lagran(2,xG(i,j,bi,bj),px_ind,sp)
351 & +arrayin(e_ind(i,j) ,s_ind(i,j)+k-2)
352 & *lagran(3,xG(i,j,bi,bj),px_ind,sp)
353 & +arrayin(e_ind(i,j)+1,s_ind(i,j)+k-2)
354 & *lagran(4,xG(i,j,bi,bj),px_ind,sp)
355 arrayout(i,j,bi,bj)=arrayout(i,j,bi,bj)
356 & +ew_val(k)*lagran(k,yG(i,j,bi,bj),py_ind,sp)
357 enddo
358 #else
359 ew_val1 =
360 & arrayin(w_ind(i,j)-1,s_ind(i,j)+1-2)
361 & *lagran(1,xG(i,j,bi,bj),px_ind,sp)
362 & +arrayin(w_ind(i,j) ,s_ind(i,j)+1-2)
363 & *lagran(2,xG(i,j,bi,bj),px_ind,sp)
364 & +arrayin(e_ind(i,j) ,s_ind(i,j)+1-2)
365 & *lagran(3,xG(i,j,bi,bj),px_ind,sp)
366 & +arrayin(e_ind(i,j)+1,s_ind(i,j)+1-2)
367 & *lagran(4,xG(i,j,bi,bj),px_ind,sp)
368 ew_val2 =
369 & arrayin(w_ind(i,j)-1,s_ind(i,j)+2-2)
370 & *lagran(1,xG(i,j,bi,bj),px_ind,sp)
371 & +arrayin(w_ind(i,j) ,s_ind(i,j)+2-2)
372 & *lagran(2,xG(i,j,bi,bj),px_ind,sp)
373 & +arrayin(e_ind(i,j) ,s_ind(i,j)+2-2)
374 & *lagran(3,xG(i,j,bi,bj),px_ind,sp)
375 & +arrayin(e_ind(i,j)+1,s_ind(i,j)+2-2)
376 & *lagran(4,xG(i,j,bi,bj),px_ind,sp)
377 ew_val3 =
378 & arrayin(w_ind(i,j)-1,s_ind(i,j)+3-2)
379 & *lagran(1,xG(i,j,bi,bj),px_ind,sp)
380 & +arrayin(w_ind(i,j) ,s_ind(i,j)+3-2)
381 & *lagran(2,xG(i,j,bi,bj),px_ind,sp)
382 & +arrayin(e_ind(i,j) ,s_ind(i,j)+3-2)
383 & *lagran(3,xG(i,j,bi,bj),px_ind,sp)
384 & +arrayin(e_ind(i,j)+1,s_ind(i,j)+3-2)
385 & *lagran(4,xG(i,j,bi,bj),px_ind,sp)
386 ew_val4 =
387 & arrayin(w_ind(i,j)-1,s_ind(i,j)+4-2)
388 & *lagran(1,xG(i,j,bi,bj),px_ind,sp)
389 & +arrayin(w_ind(i,j) ,s_ind(i,j)+4-2)
390 & *lagran(2,xG(i,j,bi,bj),px_ind,sp)
391 & +arrayin(e_ind(i,j) ,s_ind(i,j)+4-2)
392 & *lagran(3,xG(i,j,bi,bj),px_ind,sp)
393 & +arrayin(e_ind(i,j)+1,s_ind(i,j)+4-2)
394 & *lagran(4,xG(i,j,bi,bj),px_ind,sp)
395 arrayout(i,j,bi,bj)=
396 & +ew_val1*lagran(1,yG(i,j,bi,bj),py_ind,sp)
397 & +ew_val2*lagran(2,yG(i,j,bi,bj),py_ind,sp)
398 & +ew_val3*lagran(3,yG(i,j,bi,bj),py_ind,sp)
399 & +ew_val4*lagran(4,yG(i,j,bi,bj),py_ind,sp)
400 #endif /* TARGET_NEC_SX defined */
401 enddo
402 enddo
403 else
404 stop 'stop in exf_interp.F: interpolation method not supported'
405 endif
406 enddo
407 enddo
408
409 RETURN
410 END

  ViewVC Help
Powered by ViewVC 1.1.22