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

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

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


Revision 1.16 - (show annotations) (download)
Fri Jan 25 02:43:19 2008 UTC (16 years, 5 months ago) by dimitri
Branch: MAIN
Changes since 1.15: +31 -42 lines
changed comments

1 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_set_uv.F,v 1.15 2007/04/16 23:27:21 jmc Exp $
2 C $Name: $
3
4 #include "EXF_OPTIONS.h"
5
6 subroutine exf_set_uv(
7 & uvecfile, uvecstartdate, uvecperiod,
8 & uvecstartdate1, uvecstartdate2,
9 & exf_inscal_uvec, uvec, uvec0, uvec1, uvecmask,
10 & uvec_lon0, uvec_lon_inc, uvec_lat0, uvec_lat_inc,
11 & uvec_nlon, uvec_nlat,
12 & uvec_remove_intercept, uvec_remove_slope,
13 & vvecfile, vvecstartdate, vvecperiod,
14 & vvecstartdate1, vvecstartdate2,
15 & exf_inscal_vvec, vvec, vvec0, vvec1, vvecmask,
16 & vvec_lon0, vvec_lon_inc, vvec_lat0, vvec_lat_inc,
17 & vvec_nlon, vvec_nlat,
18 & vvec_remove_intercept, vvec_remove_slope,
19 & mycurrenttime, mycurrentiter, mythid )
20
21 c ==================================================================
22 c SUBROUTINE exf_set_uv
23 c ==================================================================
24 c
25 c o Read-in, interpolate, and rotate wind or wind stress vectors
26 c from a spherical-polar input grid to an arbitrary output grid.
27 c
28 c menemenlis@jpl.nasa.gov, 8-Dec-2003
29 c
30 c ==================================================================
31 c SUBROUTINE exf_set_uv
32 c ==================================================================
33
34 implicit none
35
36 c == global variables ==
37
38 #include "EEPARAMS.h"
39 #include "SIZE.h"
40 #include "PARAMS.h"
41 #include "DYNVARS.h"
42 #include "GRID.h"
43
44 #include "EXF_PARAM.h"
45 #include "EXF_FIELDS.h"
46 #include "EXF_CONSTANTS.h"
47
48 #ifdef ALLOW_AUTODIFF
49 # include "ctrl.h"
50 # include "ctrl_dummy.h"
51 #endif
52
53 c == routine arguments ==
54
55 c *vec_lon_0, :: longitude and latitude of SouthWest
56 c *vec_lat_0 corner of global input grid for *vec
57 c *vec_nlon, *vec_nlat :: input x-grid and y-grid size for *vec
58 c *vec_lon_inc :: scalar x-grid increment for *vec
59 c *vec_lat_inc :: vector y-grid increments for *vec
60
61 character*(128) uvecfile, uvecfile0, uvecfile1
62 _RL uvecstartdate, uvecperiod
63 integer uvecstartdate1, uvecstartdate2
64 _RL exf_inscal_uvec
65 _RL uvec_remove_intercept, uvec_remove_slope
66 _RL uvec (1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
67 _RL uvec0 (1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
68 _RL uvec1 (1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
69 character*1 uvecmask
70 _RL uvec_lon0, uvec_lon_inc
71 _RL uvec_lat0, uvec_lat_inc(MAX_LAT_INC)
72 INTEGER uvec_nlon, uvec_nlat
73 character*(128) vvecfile, vvecfile0, vvecfile1
74 _RL vvecstartdate, vvecperiod
75 integer vvecstartdate1, vvecstartdate2
76 _RL exf_inscal_vvec
77 _RL vvec_remove_intercept, vvec_remove_slope
78 _RL vvec (1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
79 _RL vvec0 (1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
80 _RL vvec1 (1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
81 character*1 vvecmask
82 _RL vvec_lon0, vvec_lon_inc
83 _RL vvec_lat0, vvec_lat_inc(MAX_LAT_INC)
84 INTEGER vvec_nlon, vvec_nlat
85 _RL mycurrenttime
86 integer mycurrentiter
87 integer mythid
88
89 #ifdef USE_EXF_INTERPOLATION
90 c == local variables ==
91
92 logical first, changed
93 _RL fac, x1, x2, x3, x4, y1, y2, y3, y4, dx, dy
94 _RL tmp_u (1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
95 _RL tmp_v (1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
96 integer count0, count1
97 integer i, j, bi, bj
98 integer il, interp_method
99 integer year0, year1
100
101 c == external ==
102
103 integer ilnblnk
104 external ilnblnk
105
106 c == end of interface ==
107
108 IF ( usingCurvilinearGrid ) THEN
109
110 if ( uvecfile .NE. ' ' .and. vvecfile .NE. ' ' ) then
111
112 c get record numbers and interpolation factor
113 call exf_GetFFieldRec(
114 I uvecstartdate, uvecperiod
115 I , uvecstartdate1, uvecstartdate2
116 I , useExfYearlyFields
117 O , fac, first, changed
118 O , count0, count1, year0, year1
119 I , mycurrenttime, mycurrentiter, mythid
120 & )
121
122 if ( first ) then
123 if (useExfYearlyFields) then
124 C Complete filenames with YR or _YEAR extension
125 il = ilnblnk( uvecfile )
126 if (twoDigitYear) then
127 if (year0.ge.2000) then
128 write(uvecfile0(1:128),'(a,i2.2)')
129 & uvecfile(1:il),year0-2000
130 else
131 write(uvecfile0(1:128),'(a,i2.2)')
132 & uvecfile(1:il),year0-1900
133 endif
134 else
135 write(uvecfile0(1:128),'(2a,i4.4)')
136 & uvecfile(1:il),'_',year0
137 endif
138 il = ilnblnk( vvecfile )
139 if (twoDigitYear) then
140 if (year0.ge.2000) then
141 write(vvecfile0(1:128),'(a,i2.2)')
142 & vvecfile(1:il),year0-2000
143 else
144 write(vvecfile0(1:128),'(a,i2.2)')
145 & vvecfile(1:il),year0-1900
146 endif
147 else
148 write(vvecfile0(1:128),'(2a,i4.4)')
149 & vvecfile(1:il),'_',year0
150 endif
151 else
152 uvecfile0 = uvecfile
153 vvecfile0 = vvecfile
154 endif
155 c scalar interpolation to (xC,yC) locations
156 interp_method=12
157 call exf_interp( uvecfile0, exf_iprec
158 & , tmp_u, count0, xC, yC
159 & , uvec_lon0,uvec_lon_inc
160 & , uvec_lat0,uvec_lat_inc
161 & , uvec_nlon,uvec_nlat,interp_method,mythid
162 & )
163 interp_method=22
164 call exf_interp( vvecfile0, exf_iprec
165 & , tmp_v, count0, xC, yC
166 & , vvec_lon0,vvec_lon_inc
167 & , vvec_lat0,vvec_lat_inc
168 & , vvec_nlon,vvec_nlat,interp_method,mythid
169 & )
170 c vector rotation
171 do bj = mybylo(mythid),mybyhi(mythid)
172 do bi = mybxlo(mythid),mybxhi(mythid)
173 do j = 1,sny
174 do i = 1,snx
175 x1=xG(i,j,bi,bj)
176 x2=xG(i+1,j,bi,bj)
177 x3=xG(i,j+1,bi,bj)
178 x4=xG(i+1,j+1,bi,bj)
179 if ((x2-x1).gt.180) x2=x2-360
180 if ((x1-x2).gt.180) x2=x2+360
181 if ((x3-x1).gt.180) x3=x3-360
182 if ((x1-x3).gt.180) x3=x3+360
183 if ((x4-x1).gt.180) x4=x4-360
184 if ((x1-x4).gt.180) x4=x4+360
185 y1=yG(i,j,bi,bj)
186 y2=yG(i+1,j,bi,bj)
187 y3=yG(i,j+1,bi,bj)
188 y4=yG(i+1,j+1,bi,bj)
189 dx=0.5*(x3+x4-x1-x2)
190 dx=dx*
191 & cos(deg2rad*yC(i,j,bi,bj))
192 dy=0.5*(y3+y4-y1-y2)
193 vvec1(i,j,bi,bj)=
194 & (tmp_u(i,j,bi,bj)*dx+
195 & tmp_v(i,j,bi,bj)*dy)/
196 & sqrt(dx*dx+dy*dy)
197 dx=0.5*(x2+x4-x1-x3)
198 dx=dx*
199 & cos(deg2rad*yC(i,j,bi,bj))
200 dy=0.5*(y2+y4-y1-y3)
201 uvec1(i,j,bi,bj)=
202 & (tmp_u(i,j,bi,bj)*dx+
203 & tmp_v(i,j,bi,bj)*dy)/
204 & sqrt(dx*dx+dy*dy)
205 enddo
206 enddo
207 enddo
208 enddo
209 c apply mask
210 if (exf_yftype .eq. 'RL') then
211 call exf_filter_rl( uvec1, uvecmask, mythid )
212 call exf_filter_rl( vvec1, vvecmask, mythid )
213 else
214 call exf_filter_rs( uvec1, uvecmask, mythid )
215 call exf_filter_rs( vvec1, vvecmask, mythid )
216 end if
217 endif
218
219 if (( first ) .or. ( changed )) then
220 call exf_SwapFFields( uvec0, uvec1, mythid )
221 call exf_SwapFFields( vvec0, vvec1, mythid )
222 if (useExfYearlyFields) then
223 C Complete filenames with YR or _YEAR extension
224 il = ilnblnk( uvecfile )
225 if (twoDigitYear) then
226 if (year1.ge.2000) then
227 write(uvecfile1(1:128),'(a,i2.2)')
228 & uvecfile(1:il),year1-2000
229 else
230 write(uvecfile1(1:128),'(a,i2.2)')
231 & uvecfile(1:il),year1-1900
232 endif
233 else
234 write(uvecfile1(1:128),'(2a,i4.4)')
235 & uvecfile(1:il),'_',year1
236 endif
237 il = ilnblnk( vvecfile )
238 if (twoDigitYear) then
239 if (year1.ge.2000) then
240 write(vvecfile1(1:128),'(a,i2.2)')
241 & vvecfile(1:il),year1-2000
242 else
243 write(vvecfile1(1:128),'(a,i2.2)')
244 & vvecfile(1:il),year1-1900
245 endif
246 else
247 write(vvecfile1(1:128),'(2a,i4.4)')
248 & vvecfile(1:il),'_',year1
249 endif
250 else
251 uvecfile1 = uvecfile
252 vvecfile1 = vvecfile
253 endif
254 c scalar interpolation to (xC,yC) locations
255 interp_method=12
256 call exf_interp( uvecfile1, exf_iprec
257 & , tmp_u, count1, xC, yC
258 & , uvec_lon0,uvec_lon_inc
259 & , uvec_lat0,uvec_lat_inc
260 & , uvec_nlon,uvec_nlat,interp_method,mythid
261 & )
262 interp_method=22
263 call exf_interp( vvecfile1, exf_iprec
264 & , tmp_v, count1, xC, yC
265 & , vvec_lon0,vvec_lon_inc
266 & , vvec_lat0,vvec_lat_inc
267 & , vvec_nlon,vvec_nlat,interp_method,mythid
268 & )
269 c vector rotation
270 do bj = mybylo(mythid),mybyhi(mythid)
271 do bi = mybxlo(mythid),mybxhi(mythid)
272 do j = 1,sny
273 do i = 1,snx
274 x1=xG(i,j,bi,bj)
275 x2=xG(i+1,j,bi,bj)
276 x3=xG(i,j+1,bi,bj)
277 x4=xG(i+1,j+1,bi,bj)
278 if ((x2-x1).gt.180) x2=x2-360
279 if ((x1-x2).gt.180) x2=x2+360
280 if ((x3-x1).gt.180) x3=x3-360
281 if ((x1-x3).gt.180) x3=x3+360
282 if ((x4-x1).gt.180) x4=x4-360
283 if ((x1-x4).gt.180) x4=x4+360
284 y1=yG(i,j,bi,bj)
285 y2=yG(i+1,j,bi,bj)
286 y3=yG(i,j+1,bi,bj)
287 y4=yG(i+1,j+1,bi,bj)
288 dx=0.5*(x3+x4-x1-x2)
289 dx=dx*
290 & cos(deg2rad*yC(i,j,bi,bj))
291 dy=0.5*(y3+y4-y1-y2)
292 vvec1(i,j,bi,bj)=
293 & (tmp_u(i,j,bi,bj)*dx+
294 & tmp_v(i,j,bi,bj)*dy)/
295 & sqrt(dx*dx+dy*dy)
296 dx=0.5*(x2+x4-x1-x3)
297 dx=dx*
298 & cos(deg2rad*yC(i,j,bi,bj))
299 dy=0.5*(y2+y4-y1-y3)
300 uvec1(i,j,bi,bj)=
301 & (tmp_u(i,j,bi,bj)*dx+
302 & tmp_v(i,j,bi,bj)*dy)/
303 & sqrt(dx*dx+dy*dy)
304 enddo
305 enddo
306 enddo
307 enddo
308 c apply mask
309 if (exf_yftype .eq. 'RL') then
310 call exf_filter_rl( uvec1, uvecmask, mythid )
311 call exf_filter_rl( vvec1, vvecmask, mythid )
312 else
313 call exf_filter_rs( uvec1, uvecmask, mythid )
314 call exf_filter_rs( vvec1, vvecmask, mythid )
315 end if
316 endif
317
318 c Interpolate linearly onto the current time.
319 do bj = mybylo(mythid),mybyhi(mythid)
320 do bi = mybxlo(mythid),mybxhi(mythid)
321 do j = 1,sny
322 do i = 1,snx
323 uvec(i,j,bi,bj) = exf_inscal_uvec * (
324 & fac * uvec0(i,j,bi,bj) +
325 & (exf_one - fac) * uvec1(i,j,bi,bj) )
326 vvec(i,j,bi,bj) = exf_inscal_vvec * (
327 & fac * vvec0(i,j,bi,bj) +
328 & (exf_one - fac) * vvec1(i,j,bi,bj) )
329 enddo
330 enddo
331 enddo
332 enddo
333
334 endif
335
336 ELSE
337 c IF ( .NOT. usingCurvilinearGrid )
338
339 interp_method=12
340 call exf_set_gen(
341 & uvecfile, uvecstartdate, uvecperiod,
342 I uvecstartdate1, uvecstartdate2,
343 & exf_inscal_uvec,
344 & uvec_remove_intercept, uvec_remove_slope,
345 & uvec, uvec0, uvec1, uvecmask,
346 & uvec_lon0, uvec_lon_inc, uvec_lat0, uvec_lat_inc,
347 & uvec_nlon, uvec_nlat, xC, yC, interp_method,
348 & mycurrenttime, mycurrentiter, mythid )
349 interp_method=22
350 call exf_set_gen(
351 & vvecfile, vvecstartdate, vvecperiod,
352 I vvecstartdate1, vvecstartdate2,
353 & exf_inscal_vvec,
354 & vvec_remove_intercept, vvec_remove_slope,
355 & vvec, vvec0, vvec1, vvecmask,
356 & vvec_lon0, vvec_lon_inc, vvec_lat0, vvec_lat_inc,
357 & vvec_nlon, vvec_nlat, xC, yC, interp_method,
358 & mycurrenttime, mycurrentiter, mythid )
359
360 ENDIF
361
362 #endif /* USE_EXF_INTERPOLATION */
363
364 return
365 end

  ViewVC Help
Powered by ViewVC 1.1.22