/[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.5 - (show annotations) (download)
Wed Dec 10 19:37:25 2003 UTC (20 years, 6 months ago) by dimitri
Branch: MAIN
Branch point for: netcdf-sm0
Changes since 1.4: +37 -37 lines
o changes to permit hi-res, cubed-sphere, configuration
  - added useSingleCpuIO capability to mdsio_readfield.F and exf_interp.F
  - added "#undef ALLOW_USE_MPI" support to eesupp/src/scatter_2d.F
  - added pkg/exf/exf_set_uv.F for on-the-fly interpolation and rotation
    of surface winds for the cube
  (A verification experiment, based on global_ocean.cs32x15, but with
   pkg/seaice turned on and with on-the-fly interpolation from the NCEP
   Gaussian grid is described in MITgcm_contrib/high_res_cube/README_ice,
   complete with example surface forcing files and matlab scripts to look
   at the output and compare it with that of global_ocean.cs32x15.)

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 # include "PARAMS.h"
64 #endif /* ALLOW_USE_MPI */
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 if ( xG(1,1 ,bi,bj) .le. x_in(0) .or.
170 & xG(snx,1,bi,bj) .ge. x_in(nx_in+1) .or.
171 & yG(1,1 ,bi,bj) .lt. y_in(1) .or.
172 & yG(1,sny,bi,bj) .gt. y_in(ny_in) ) then
173 print*,'ERROR in S/R EXF_INTERP:'
174 print*,' input grid must encompass output grid.'
175 STOP ' ABNORMAL END: S/R EXF_INTERP'
176 endif
177
178 C compute interpolation indices
179 do i=1,snx
180 do j=1,sny
181 if (xG(i,j,bi,bj)-x_in(1) .ge. 0.) then
182 w_ind(i,j) = int((xG(i,j,bi,bj)-x_in(1))/lon_inc) + 1
183 else
184 w_ind(i,j) = int((xG(i,j,bi,bj)-x_in(1))/lon_inc)
185 endif
186 e_ind(i,j) = w_ind(i,j) + 1
187 js = ny_in/2
188 do while (yG(i,j,bi,bj) .lt. y_in(js))
189 js = (js + 1)/2
190 enddo
191 do while (yG(i,j,bi,bj) .ge. y_in(js+1))
192 js = js + 1
193 enddo
194 s_ind(i,j) = js
195 n_ind(i,j) = js + 1
196 enddo
197 enddo
198
199 if (method .eq. 1) then
200
201 C bilinear interpolation
202 sp = 2
203 do j=1,sny
204 do i=1,snx
205 arrayout(i,j,bi,bj) = 0.
206 do l=0,1
207 px_ind(l+1) = x_in(w_ind(i,j)+l)
208 py_ind(l+1) = y_in(s_ind(i,j)+l)
209 enddo
210 do k=1,2
211 ew_val(k) = arrayin(w_ind(i,j),s_ind(i,j)+k-1)
212 & *lagran(1,xG(i,j,bi,bj),px_ind,sp)
213 & +arrayin(e_ind(i,j),s_ind(i,j)+k-1)
214 & *lagran(2,xG(i,j,bi,bj),px_ind,sp)
215 arrayout(i,j,bi,bj)=arrayout(i,j,bi,bj)
216 & +ew_val(k)*lagran(k,yG(i,j,bi,bj),py_ind,sp)
217 enddo
218 enddo
219 enddo
220 elseif (method .eq. 2) then
221
222 C bicubic interpolation
223 sp = 4
224 do j=1,sny
225 do i=1,snx
226 arrayout(i,j,bi,bj) = 0.
227 do l=-1,2
228 px_ind(l+2) = x_in(w_ind(i,j)+l)
229 py_ind(l+2) = y_in(s_ind(i,j)+l)
230 enddo
231 do k=1,4
232 ew_val(k) =
233 & arrayin(w_ind(i,j)-1,s_ind(i,j)+k-2)
234 & *lagran(1,xG(i,j,bi,bj),px_ind,sp)
235 & +arrayin(w_ind(i,j) ,s_ind(i,j)+k-2)
236 & *lagran(2,xG(i,j,bi,bj),px_ind,sp)
237 & +arrayin(e_ind(i,j) ,s_ind(i,j)+k-2)
238 & *lagran(3,xG(i,j,bi,bj),px_ind,sp)
239 & +arrayin(e_ind(i,j)+1,s_ind(i,j)+k-2)
240 & *lagran(4,xG(i,j,bi,bj),px_ind,sp)
241 arrayout(i,j,bi,bj)=arrayout(i,j,bi,bj)
242 & +ew_val(k)*lagran(k,yG(i,j,bi,bj),py_ind,sp)
243 enddo
244 enddo
245 enddo
246 else
247 stop 'stop in exf_interp.F: interpolation method not supported'
248 endif
249 enddo
250 enddo
251
252 END

  ViewVC Help
Powered by ViewVC 1.1.22