/[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.23 - (show annotations) (download)
Thu Jan 24 08:29:51 2008 UTC (16 years, 4 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint62, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59o, checkpoint59n, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62d, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.22: +60 -1 lines
o finish vectorization of exf_interp for TARGET_NEC_SX
  by unrolling short inner k-loops by hand (arghhh!)

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

  ViewVC Help
Powered by ViewVC 1.1.22