/[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.1 - (show annotations) (download)
Thu Aug 7 02:31:29 2003 UTC (20 years, 10 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint51f_pre
o Added on-the-fly spatial interpolation capability
    "USE_EXF_INTERPOLATION" to pkg/exf.
  - This is a temporary Cartesian-grid hack until
    the super-duper ESMF coupler becomes available.
  - See verification/global_with_exf/README for usage example.
  - Removed obsolete EXFwindOnBgrid and SEAICEwindOnCgrid
    flags and modified pkg/seaice accordingly.
o Bug fix to pkg/ptracers, pkg/generic_advdiff/gad_calc_rhs.F,
    and pkg/kpp/kpp_transport_ptr.F for dealing with tracer
    non-local transport term.

1 #include "EXF_CPPOPTIONS.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)
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
23 #ifdef BICUBIC
24 sp = 4
25 #else
26 sp = 2
27 #endif
28 do k=1,sp
29 if ( k .ne. i) then
30 denom = denom*(a(i) - a(k))
31 numer = numer*(x - a(k))
32 endif
33 enddo
34
35 lagran = numer/denom
36
37 return
38 end
39
40
41 SUBROUTINE exf_interp(
42 I infile,
43 I filePrec,
44 O arrayout,
45 I irecord, xG, yG,
46 I lon_0,lon_inc,
47 I lat_0,lat_inc,
48 I nx_in,ny_in,mythid)
49
50 C
51 C *** infile = name of the input file (global binary, before interp.)
52 C filePrec = file precicision
53 C arrout = output arrays (different for each processor)
54 C irecord = record number in global file
55 C xG,yG = coordinates for output grid
56 C lon_0, lat_0 = lon and lat of sw corner of global input grid
57 C lon_inc = scalar x-grid increment
58 C lat_inc = vector y-grid increments
59 C nx_in, ny_in = input x-grid and y-grid size
60 C
61
62 #include "SIZE.h"
63 #include "EEPARAMS.h"
64 #include "EESUPPORT.h"
65 #include "exf_param.h"
66
67 C local variables
68
69 integer ierr
70 integer nx_in, ny_in
71 integer irecord, filePrec
72 _RL arrayout(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nsx,nsy)
73
74 real*8 ne_fac,nw_fac,se_fac,sw_fac
75 integer e_ind(snx),w_ind(snx)
76 integer n_ind(sny),s_ind(sny)
77
78 real*8 px_ind(4), py_ind(4)
79 real*8 ew_val(4)
80 external lagran
81 real*8 lagran
82
83 _RL lon_0,lon_inc
84 _RL lat_0,lat_inc(ny_in-1)
85 real*4 arrayin(-1:nx_in+2,-1:ny_in+2)
86 real*8 x_in(-1:nx_in+2),y_in(-1:ny_in+2)
87
88 _RS xG(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
89 _RS yG(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90
91 character*(*) infile
92 integer i, j, k, l, js
93 integer bi,bj,mythid
94 integer interp_unit
95
96 C read in input data
97
98 call mdsfindunit( interp_unit, mythid)
99 open(interp_unit,file=infile,status='old',access='direct',
100 & recl=nx_in*ny_in*4)
101 read(interp_unit,rec=irecord) ((arrayin(i,j),i=1,nx_in),j=1,ny_in)
102 #ifdef _BYTESWAPIO
103 call MDS_BYTESWAPR4((nx_in+4)*(ny_in+4), arrayin )
104 #endif
105 close(interp_unit)
106
107 C setup input grid
108
109 do i=-1,nx_in+2
110 x_in(i) = lon_0 + (i-1.)*lon_inc
111 enddo
112
113 y_in(0) = lat_0 - lat_inc(1)
114 y_in(-1)= lat_0 - 2.*lat_inc(1)
115
116 y_in(1) = lat_0
117 do j=2,ny_in
118 y_in(j) = y_in(j-1) + lat_inc(j-1)
119 enddo
120
121 y_in(ny_in+1) = y_in(ny_in) + lat_inc(ny_in-1)
122 y_in(ny_in+2) = y_in(ny_in) + 2.*lat_inc(ny_in-1)
123
124 C check validity of input/output parameters
125
126 if ( xG(1,1) .le. x_in(0) .or.
127 & xG(snx,1) .ge. x_in(nx_in+1) .or.
128 & yG(1,1) .lt. y_in(1) .or.
129 & yG(1,sny) .gt. y_in(ny_in) ) then
130 print*,'ERROR in S/R EXF_INTERP:'
131 print*,' input grid must encompass output grid.'
132 STOP ' ABNORMAL END: S/R EXF_INTERP'
133 endif
134
135 C enlarge boundary
136
137 do j=1,ny_in
138 arrayin(0,j) = arrayin(nx_in,j)
139 arrayin(-1,j) = arrayin(nx_in-1,j)
140 arrayin(nx_in+1,j) = arrayin(1,j)
141 arrayin(nx_in+2,j) = arrayin(2,j)
142 enddo
143
144 do i=-1,nx_in+2
145 arrayin(i,0) = arrayin(i,1)
146 arrayin(i,-1) = arrayin(i,1)
147 arrayin(i,ny_in+1) = arrayin(i,ny_in)
148 arrayin(i,ny_in+2) = arrayin(i,ny_in)
149 enddo
150
151 C compute interpolation indices
152
153 do i=1,snx
154 if (xG(i,1)-x_in(1) .ge. 0.) then
155 w_ind(i) = int((xG(i,1)-x_in(1))/lon_inc) + 1
156 else
157 w_ind(i) = int((xG(i,1)-x_in(1))/lon_inc)
158 endif
159 e_ind(i) = w_ind(i) + 1
160 enddo
161
162 js = ny_in/2
163 do j=1,sny
164 do while (yG(1,j) .lt. y_in(js))
165 js = (js + 1)/2
166 enddo
167 do while (yG(1,j) .ge. y_in(js+1))
168 js = js + 1
169 enddo
170 s_ind(j) = js
171 n_ind(j) = js + 1
172 enddo
173
174 C interpolate
175
176 do bj = mybylo(mythid), mybyhi(mythid)
177 do bi = mybxlo(mythid), mybxhi(mythid)
178
179 #ifdef BICUBIC
180 do j=1,sny
181 do i=1,snx
182
183 arrayout(i,j,bi,bj) = 0.
184
185 do l=-1,2
186 px_ind(l+2) = x_in(w_ind(i)+l)
187 py_ind(l+2) = y_in(s_ind(j)+l)
188 enddo
189
190 do k=1,4
191 ew_val(k) =
192 & arrayin(w_ind(i)-1,s_ind(j)+k-2)*lagran(1,xG(i,1),px_ind)
193 & + arrayin(w_ind(i) ,s_ind(j)+k-2)*lagran(2,xG(i,1),px_ind)
194 & + arrayin(e_ind(i) ,s_ind(j)+k-2)*lagran(3,xG(i,1),px_ind)
195 & + arrayin(e_ind(i)+1,s_ind(j)+k-2)*lagran(4,xG(i,1),px_ind)
196 arrayout(i,j,bi,bj)=arrayout(i,j,bi,bj)
197 & + ew_val(k)*lagran(k,yG(1,j),py_ind)
198 enddo
199
200 enddo
201 enddo
202 #else
203 do j=1,sny
204 do i=1,snx
205
206 arrayout(i,j,bi,bj) = 0.
207
208 do l=0,1
209 px_ind(l+1) = x_in(w_ind(i)+l)
210 py_ind(l+1) = y_in(s_ind(j)+l)
211 enddo
212
213 do k=1,2
214 ew_val(k) =
215 & arrayin(w_ind(i),s_ind(j)+k-1)*lagran(1,xG(i,1),px_ind)
216 & + arrayin(e_ind(i),s_ind(j)+k-1)*lagran(2,xG(i,1),px_ind)
217
218 arrayout(i,j,bi,bj)=arrayout(i,j,bi,bj)
219 & + ew_val(k)*lagran(k,yG(1,j),py_ind)
220 enddo
221
222 enddo
223 enddo
224 #endif
225 enddo
226 enddo
227
228 END
229 C ***

  ViewVC Help
Powered by ViewVC 1.1.22