/[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.13 - (show annotations) (download)
Tue Jun 6 14:55:53 2006 UTC (18 years ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58h_post, checkpoint58j_post, checkpoint58i_post, checkpoint58g_post
Changes since 1.12: +233 -229 lines
Fixed 72-char-per-line issue and changes indentation to 2.

1 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_set_uv.F,v 1.12 2006/06/06 03:36:14 dimitri 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, offset
97 integer i, j, bi, bj
98 integer il, interp_method
99 parameter(interp_method=2)
100 integer year0, year1
101
102 c == external ==
103
104 integer ilnblnk
105 external ilnblnk
106
107 c == end of interface ==
108
109 IF ( usingCurvilinearGrid ) THEN
110
111 if ( uvecfile .NE. ' ' .and. vvecfile .NE. ' ' ) then
112
113 c get record numbers and interpolation factor
114 call exf_GetFFieldRec(
115 I uvecstartdate, uvecperiod
116 I , uvecstartdate1, uvecstartdate2
117 I , useExfYearlyFields
118 O , fac, first, changed
119 O , count0, count1, year0, year1
120 I , mycurrenttime, mycurrentiter, mythid
121 & )
122
123 if ( first ) then
124 if (useExfYearlyFields) then
125 C Complete filenames with YR or _YEAR extension
126 il = ilnblnk( uvecfile )
127 if (twoDigitYear) then
128 if (year0.ge.2000) then
129 write(uvecfile0(1:128),'(a,i2.2)')
130 & uvecfile(1:il),year0-2000
131 else
132 write(uvecfile0(1:128),'(a,i2.2)')
133 & uvecfile(1:il),year0-1900
134 endif
135 else
136 write(uvecfile0(1:128),'(2a,i4.4)')
137 & uvecfile(1:il),'_',year0
138 endif
139 il = ilnblnk( vvecfile )
140 if (twoDigitYear) then
141 if (year0.ge.2000) then
142 write(vvecfile0(1:128),'(a,i2.2)')
143 & vvecfile(1:il),year0-2000
144 else
145 write(vvecfile0(1:128),'(a,i2.2)')
146 & vvecfile(1:il),year0-1900
147 endif
148 else
149 write(vvecfile0(1:128),'(2a,i4.4)')
150 & vvecfile(1:il),'_',year0
151 endif
152 else
153 uvecfile0 = uvecfile
154 vvecfile0 = vvecfile
155 endif
156 c scalar interpolation to (xC,yC) locations
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 call exf_interp( vvecfile0, exf_iprec
164 & , tmp_v, count0, xC, yC
165 & , vvec_lon0,vvec_lon_inc
166 & , vvec_lat0,vvec_lat_inc
167 & , vvec_nlon,vvec_nlat,interp_method,mythid
168 & )
169 c vector rotation
170 do bj = mybylo(mythid),mybyhi(mythid)
171 do bi = mybxlo(mythid),mybxhi(mythid)
172 do j = 1,sny
173 do i = 1,snx
174 C if yc is within dyc of North Pole then find direction from adjacent values
175 offset=0
176 if ( yC(i,j,bi,bj) .gt.
177 & (90-dyC(i,j,bi,bj)*8.9946e-06) )
178 & offset=2
179 x1=xG(i-offset,j-offset,bi,bj)
180 x2=xG(i-offset+1,j-offset,bi,bj)
181 x3=xG(i-offset,j-offset+1,bi,bj)
182 x4=xG(i-offset+1,j-offset+1,bi,bj)
183 if ((x2-x1).gt.180) x2=x2-360
184 if ((x1-x2).gt.180) x2=x2+360
185 if ((x3-x1).gt.180) x3=x3-360
186 if ((x1-x3).gt.180) x3=x3+360
187 if ((x4-x1).gt.180) x4=x4-360
188 if ((x1-x4).gt.180) x4=x4+360
189 y1=yG(i-offset,j-offset,bi,bj)
190 y2=yG(i-offset+1,j-offset,bi,bj)
191 y3=yG(i-offset,j-offset+1,bi,bj)
192 y4=yG(i-offset+1,j-offset+1,bi,bj)
193 dx=0.5*(x3+x4-x1-x2)
194 dx=dx*
195 & cos(deg2rad*yC(i-offset,j-offset,bi,bj))
196 dy=0.5*(y3+y4-y1-y2)
197 vvec1(i,j,bi,bj)=
198 & (tmp_u(i-offset,j-offset,bi,bj)*dx+
199 & tmp_v(i-offset,j-offset,bi,bj)*dy)/
200 & sqrt(dx*dx+dy*dy)
201 dx=0.5*(x2+x4-x1-x3)
202 dx=dx*
203 & cos(deg2rad*yC(i-offset,j-offset,bi,bj))
204 dy=0.5*(y2+y4-y1-y3)
205 uvec1(i,j,bi,bj)=
206 & (tmp_u(i-offset,j-offset,bi,bj)*dx+
207 & tmp_v(i-offset,j-offset,bi,bj)*dy)/
208 & sqrt(dx*dx+dy*dy)
209 enddo
210 enddo
211 enddo
212 enddo
213 c apply mask
214 if (exf_yftype .eq. 'RL') then
215 call exf_filter_rl( uvec1, uvecmask, mythid )
216 call exf_filter_rl( vvec1, vvecmask, mythid )
217 else
218 call exf_filter_rs( uvec1, uvecmask, mythid )
219 call exf_filter_rs( vvec1, vvecmask, mythid )
220 end if
221 endif
222
223 if (( first ) .or. ( changed )) then
224 call exf_SwapFFields( uvec0, uvec1, mythid )
225 call exf_SwapFFields( vvec0, vvec1, mythid )
226 if (useExfYearlyFields) then
227 C Complete filenames with YR or _YEAR extension
228 il = ilnblnk( uvecfile )
229 if (twoDigitYear) then
230 if (year1.ge.2000) then
231 write(uvecfile1(1:128),'(a,i2.2)')
232 & uvecfile(1:il),year1-2000
233 else
234 write(uvecfile1(1:128),'(a,i2.2)')
235 & uvecfile(1:il),year1-1900
236 endif
237 else
238 write(uvecfile1(1:128),'(2a,i4.4)')
239 & uvecfile(1:il),'_',year1
240 endif
241 il = ilnblnk( vvecfile )
242 if (twoDigitYear) then
243 if (year1.ge.2000) then
244 write(vvecfile1(1:128),'(a,i2.2)')
245 & vvecfile(1:il),year1-2000
246 else
247 write(vvecfile1(1:128),'(a,i2.2)')
248 & vvecfile(1:il),year1-1900
249 endif
250 else
251 write(vvecfile1(1:128),'(2a,i4.4)')
252 & vvecfile(1:il),'_',year1
253 endif
254 else
255 uvecfile1 = uvecfile
256 vvecfile1 = vvecfile
257 endif
258 c scalar interpolation to (xC,yC) locations
259 call exf_interp( uvecfile1, exf_iprec
260 & , tmp_u, count1, xC, yC
261 & , uvec_lon0,uvec_lon_inc
262 & , uvec_lat0,uvec_lat_inc
263 & , uvec_nlon,uvec_nlat,interp_method,mythid
264 & )
265 call exf_interp( vvecfile1, exf_iprec
266 & , tmp_v, count1, xC, yC
267 & , vvec_lon0,vvec_lon_inc
268 & , vvec_lat0,vvec_lat_inc
269 & , vvec_nlon,vvec_nlat,interp_method,mythid
270 & )
271 c vector rotation
272 do bj = mybylo(mythid),mybyhi(mythid)
273 do bi = mybxlo(mythid),mybxhi(mythid)
274 do j = 1,sny
275 do i = 1,snx
276 C if yc is within dyc of North Pole then find direction from adjacent values
277 offset=0
278 if ( yC(i,j,bi,bj) .gt.
279 & (90-dyC(i,j,bi,bj)*8.9946e-06) )
280 & offset=2
281 x1=xG(i-offset,j-offset,bi,bj)
282 x2=xG(i-offset+1,j-offset,bi,bj)
283 x3=xG(i-offset,j-offset+1,bi,bj)
284 x4=xG(i-offset+1,j-offset+1,bi,bj)
285 if ((x2-x1).gt.180) x2=x2-360
286 if ((x1-x2).gt.180) x2=x2+360
287 if ((x3-x1).gt.180) x3=x3-360
288 if ((x1-x3).gt.180) x3=x3+360
289 if ((x4-x1).gt.180) x4=x4-360
290 if ((x1-x4).gt.180) x4=x4+360
291 y1=yG(i-offset,j-offset,bi,bj)
292 y2=yG(i-offset+1,j-offset,bi,bj)
293 y3=yG(i-offset,j-offset+1,bi,bj)
294 y4=yG(i-offset+1,j-offset+1,bi,bj)
295 dx=0.5*(x3+x4-x1-x2)
296 dx=dx*
297 & cos(deg2rad*yC(i-offset,j-offset,bi,bj))
298 dy=0.5*(y3+y4-y1-y2)
299 vvec1(i,j,bi,bj)=
300 & (tmp_u(i-offset,j-offset,bi,bj)*dx+
301 & tmp_v(i-offset,j-offset,bi,bj)*dy)/
302 & sqrt(dx*dx+dy*dy)
303 dx=0.5*(x2+x4-x1-x3)
304 dx=dx*
305 & cos(deg2rad*yC(i-offset,j-offset,bi,bj))
306 dy=0.5*(y2+y4-y1-y3)
307 uvec1(i,j,bi,bj)=
308 & (tmp_u(i-offset,j-offset,bi,bj)*dx+
309 & tmp_v(i-offset,j-offset,bi,bj)*dy)/
310 & sqrt(dx*dx+dy*dy)
311 enddo
312 enddo
313 enddo
314 enddo
315 c apply mask
316 if (exf_yftype .eq. 'RL') then
317 call exf_filter_rl( uvec1, uvecmask, mythid )
318 call exf_filter_rl( vvec1, vvecmask, mythid )
319 else
320 call exf_filter_rs( uvec1, uvecmask, mythid )
321 call exf_filter_rs( vvec1, vvecmask, mythid )
322 end if
323 endif
324
325 c Interpolate linearly onto the current time.
326 do bj = mybylo(mythid),mybyhi(mythid)
327 do bi = mybxlo(mythid),mybxhi(mythid)
328 do j = 1,sny
329 do i = 1,snx
330 uvec(i,j,bi,bj) = exf_inscal_uvec * (
331 & fac * uvec0(i,j,bi,bj) +
332 & (exf_one - fac) * uvec1(i,j,bi,bj) )
333 vvec(i,j,bi,bj) = exf_inscal_vvec * (
334 & fac * vvec0(i,j,bi,bj) +
335 & (exf_one - fac) * vvec1(i,j,bi,bj) )
336 enddo
337 enddo
338 enddo
339 enddo
340
341 endif
342
343 ELSE
344 c IF ( .NOT. useCubedSphereExchange )
345
346 call exf_set_gen(
347 & uvecfile, uvecstartdate, uvecperiod,
348 I uvecstartdate1, uvecstartdate2,
349 & exf_inscal_uvec,
350 & uvec_remove_intercept, uvec_remove_slope,
351 & uvec, uvec0, uvec1, uvecmask,
352 & uvec_lon0, uvec_lon_inc, uvec_lat0, uvec_lat_inc,
353 & uvec_nlon, uvec_nlat, xC, yC, interp_method,
354 & mycurrenttime, mycurrentiter, mythid )
355 call exf_set_gen(
356 & vvecfile, vvecstartdate, vvecperiod,
357 I vvecstartdate1, vvecstartdate2,
358 & exf_inscal_vvec,
359 & vvec_remove_intercept, vvec_remove_slope,
360 & vvec, vvec0, vvec1, vvecmask,
361 & vvec_lon0, vvec_lon_inc, vvec_lat0, vvec_lat_inc,
362 & vvec_nlon, vvec_nlat, xC, yC, interp_method,
363 & mycurrenttime, mycurrentiter, mythid )
364
365 ENDIF
366
367 #endif /* USE_EXF_INTERPOLATION */
368
369 return
370 end

  ViewVC Help
Powered by ViewVC 1.1.22