/[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.7 - (show annotations) (download)
Fri Dec 12 15:13:37 2003 UTC (20 years, 6 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint52l_pre, checkpoint52e_pre, hrcube4, checkpoint52n_post, checkpoint52j_post, checkpoint53d_post, checkpoint54a_pre, checkpoint55c_post, checkpoint54e_post, checkpoint52e_post, checkpoint54a_post, checkpoint53c_post, hrcube_1, checkpoint52l_post, checkpoint52k_post, checkpoint54b_post, checkpoint53b_pre, checkpoint55b_post, checkpoint54d_post, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint54, checkpoint54f_post, checkpoint53b_post, checkpoint53, checkpoint52d_post, checkpoint53g_post, checkpoint52f_post, hrcube5, checkpoint52i_post, checkpoint52j_pre, checkpoint53f_post, checkpoint55a_post, checkpoint53d_pre, checkpoint54c_post, checkpoint52i_pre, checkpoint52h_pre, checkpoint52f_pre, hrcube_2, hrcube_3
Changes since 1.6: +1 -1 lines
debugLevel is referred to and lives in PARAMS.h so we need to #include it.

1 #include "EXF_OPTIONS.h"
2 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
3 C Flux Coupler using C
4 C Bilinear interpolation of forcing fields C
5 C C
6 C B. Cheng (12/2002) C
7 C C
8 C added Bicubic (bnc 1/2003) C
9 C C
10 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
11
12 real*8 function lagran(i,x,a,sp)
13
14 INTEGER i,k,sp
15 _RS x
16 real*8 a(4)
17 real*8 numer,denom
18
19 numer = 1.D0
20 denom = 1.D0
21
22 do k=1,sp
23 if ( k .ne. i) then
24 denom = denom*(a(i) - a(k))
25 numer = numer*(x - a(k))
26 endif
27 enddo
28
29 lagran = numer/denom
30
31 return
32 end
33
34
35 SUBROUTINE exf_interp(
36 I infile,
37 I filePrec,
38 O arrayout,
39 I irecord, xG, yG,
40 I lon_0, lon_inc,
41 I lat_0, lat_inc,
42 I nx_in, ny_in, method, mythid)
43
44 implicit none
45
46 C infile = name of the input file (direct access binary)
47 C filePrec = file precicision (currently not used, assumes real*4)
48 C arrout = output arrays (different for each processor)
49 C irecord = record number in global file
50 C xG,yG = coordinates for output grid
51 C lon_0, lat_0 = lon and lat of sw corner of global input grid
52 C lon_inc = scalar x-grid increment
53 C lat_inc = vector y-grid increments
54 C nx_in, ny_in = input x-grid and y-grid size
55 C method = 1 for bilinear 2 for bicubic
56 C mythid = thread id
57 C
58
59 #include "SIZE.h"
60 #include "EEPARAMS.h"
61 #ifdef ALLOW_USE_MPI
62 # include "EESUPPORT.h"
63 #endif /* ALLOW_USE_MPI */
64 #include "PARAMS.h"
65
66 C subroutine variables
67 character*(*) infile
68 integer filePrec, irecord, nx_in, ny_in
69 _RL arrayout(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
70 _RS xG (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
71 _RS yG (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
72 _RL lon_0, lon_inc
73 _RL lat_0, lat_inc(ny_in-1)
74 integer method, mythid
75
76 C local variables
77 integer ierr
78 real*8 ne_fac,nw_fac,se_fac,sw_fac
79 integer e_ind(snx,sny),w_ind(snx,sny)
80 integer n_ind(snx,sny),s_ind(snx,sny)
81 real*8 px_ind(4), py_ind(4), ew_val(4)
82 external lagran
83 real*8 lagran
84 real*4 arrayin(-1:nx_in+2 , -1:ny_in+2)
85 real*8 x_in (-1:nx_in+2), y_in(-1:ny_in+2)
86 integer i, j, k, l, js, bi, bj, sp, interp_unit
87 real*4 global(nx_in,ny_in)
88
89 _BEGIN_MASTER( myThid )
90
91 C check input arguments
92 if ( .NOT. (filePrec .EQ. 32) )
93 & stop 'stop in exf_interp.F: value of filePrec not allowed'
94
95 C read in input data
96 #ifdef ALLOW_USE_MPI
97 if (useSingleCPUIO) then
98
99 C master thread of process 0, only, opens a global file
100 IF( mpiMyId .EQ. 0 ) THEN
101 call mdsfindunit( interp_unit, mythid)
102 open(interp_unit,file=infile,status='old',access='direct',
103 & recl=nx_in*ny_in*4)
104 read(interp_unit,rec=irecord)
105 & ((global(i,j),i=1,nx_in),j=1,ny_in)
106 close(interp_unit)
107 ENDIF
108
109 C broadcast to all processes
110 call MPI_BCAST(global,nx_in*ny_in,MPI_REAL,
111 & 0,MPI_COMM_MODEL,ierr)
112 do j=1,ny_in
113 do i=1,nx_in
114 arrayin(i,j)=global(i,j)
115 enddo
116 enddo
117
118 else
119 #endif /* ALLOW_USE_MPI */
120
121 call mdsfindunit( interp_unit, mythid)
122 open(interp_unit,file=infile,status='old',access='direct',
123 & recl=nx_in*ny_in*4)
124 read(interp_unit,rec=irecord)
125 & ((arrayin(i,j),i=1,nx_in),j=1,ny_in)
126 close(interp_unit)
127
128 #ifdef ALLOW_USE_MPI
129 endif
130 #endif /* ALLOW_USE_MPI */
131
132 #ifdef _BYTESWAPIO
133 call MDS_BYTESWAPR4((nx_in+4)*(ny_in+4), arrayin )
134 #endif /* _BYTESWAPIO */
135
136 C setup input grid
137 do i=-1,nx_in+2
138 x_in(i) = lon_0 + (i-1.)*lon_inc
139 enddo
140 y_in(0) = lat_0 - lat_inc(1)
141 y_in(-1)= lat_0 - 2.*lat_inc(1)
142 y_in(1) = lat_0
143 do j=2,ny_in
144 y_in(j) = y_in(j-1) + lat_inc(j-1)
145 enddo
146 y_in(ny_in+1) = y_in(ny_in) + lat_inc(ny_in-1)
147 y_in(ny_in+2) = y_in(ny_in) + 2.*lat_inc(ny_in-1)
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 _END_MASTER( myThid )
164
165 do bj = mybylo(mythid), mybyhi(mythid)
166 do bi = mybxlo(mythid), mybxhi(mythid)
167
168 C check validity of input/output coordinates
169 #ifdef ALLOW_DEBUG
170 if ( debugLevel .ge. debLevB ) then
171 do i=1,snx
172 do j=1,sny
173 if ( xG(i,j,bi,bj) .lt. x_in(0) .or.
174 & xG(i,j,bi,bj) .ge. x_in(nx_in+1) .or.
175 & yG(i,j,bi,bj) .lt. y_in(0) .or.
176 & yG(i,j,bi,bj) .ge. y_in(ny_in+1) ) then
177 print*,'ERROR in S/R EXF_INTERP:'
178 print*,' input grid must encompass output grid.'
179 print*,'i,j,bi,bj' ,i,j,bi,bj
180 print*,'xG,yG' ,xG(i,j,bi,bj),yG(i,j,bi,bj)
181 print*,'nx_in,ny_in' ,nx_in ,ny_in
182 print*,'x_in(0,nx_in+1)',x_in(0) ,x_in(nx_in+1)
183 print*,'y_in(0,ny_in+1)',y_in(0) ,y_in(ny_in+1)
184 STOP ' ABNORMAL END: S/R EXF_INTERP'
185 endif
186 enddo
187 enddo
188 endif
189 #endif /* ALLOW_DEBUG */
190
191 C compute interpolation indices
192 do i=1,snx
193 do j=1,sny
194 if (xG(i,j,bi,bj)-x_in(1) .ge. 0.) then
195 w_ind(i,j) = int((xG(i,j,bi,bj)-x_in(1))/lon_inc) + 1
196 else
197 w_ind(i,j) = int((xG(i,j,bi,bj)-x_in(1))/lon_inc)
198 endif
199 e_ind(i,j) = w_ind(i,j) + 1
200 js = ny_in*.5
201 do while (yG(i,j,bi,bj) .lt. y_in(js))
202 js = (js - 1)*.5
203 enddo
204 do while (yG(i,j,bi,bj) .ge. y_in(js+1))
205 js = js + 1
206 enddo
207 s_ind(i,j) = js
208 n_ind(i,j) = js + 1
209 enddo
210 enddo
211
212 if (method .eq. 1) then
213
214 C bilinear interpolation
215 sp = 2
216 do j=1,sny
217 do i=1,snx
218 arrayout(i,j,bi,bj) = 0.
219 do l=0,1
220 px_ind(l+1) = x_in(w_ind(i,j)+l)
221 py_ind(l+1) = y_in(s_ind(i,j)+l)
222 enddo
223 do k=1,2
224 ew_val(k) = arrayin(w_ind(i,j),s_ind(i,j)+k-1)
225 & *lagran(1,xG(i,j,bi,bj),px_ind,sp)
226 & +arrayin(e_ind(i,j),s_ind(i,j)+k-1)
227 & *lagran(2,xG(i,j,bi,bj),px_ind,sp)
228 arrayout(i,j,bi,bj)=arrayout(i,j,bi,bj)
229 & +ew_val(k)*lagran(k,yG(i,j,bi,bj),py_ind,sp)
230 enddo
231 enddo
232 enddo
233 elseif (method .eq. 2) then
234
235 C bicubic interpolation
236 sp = 4
237 do j=1,sny
238 do i=1,snx
239 arrayout(i,j,bi,bj) = 0.
240 do l=-1,2
241 px_ind(l+2) = x_in(w_ind(i,j)+l)
242 py_ind(l+2) = y_in(s_ind(i,j)+l)
243 enddo
244 do k=1,4
245 ew_val(k) =
246 & arrayin(w_ind(i,j)-1,s_ind(i,j)+k-2)
247 & *lagran(1,xG(i,j,bi,bj),px_ind,sp)
248 & +arrayin(w_ind(i,j) ,s_ind(i,j)+k-2)
249 & *lagran(2,xG(i,j,bi,bj),px_ind,sp)
250 & +arrayin(e_ind(i,j) ,s_ind(i,j)+k-2)
251 & *lagran(3,xG(i,j,bi,bj),px_ind,sp)
252 & +arrayin(e_ind(i,j)+1,s_ind(i,j)+k-2)
253 & *lagran(4,xG(i,j,bi,bj),px_ind,sp)
254 arrayout(i,j,bi,bj)=arrayout(i,j,bi,bj)
255 & +ew_val(k)*lagran(k,yG(i,j,bi,bj),py_ind,sp)
256 enddo
257 enddo
258 enddo
259 else
260 stop 'stop in exf_interp.F: interpolation method not supported'
261 endif
262 enddo
263 enddo
264
265 END

  ViewVC Help
Powered by ViewVC 1.1.22