/[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.14 - (show annotations) (download)
Fri Jun 30 12:05:42 2006 UTC (17 years, 11 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58q_post, checkpoint58o_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58m_post
Changes since 1.13: +18 -12 lines
o pkg/exf modifications to interpolation and rotation routines for more
   reasonable treatment of North Pole singularity: for tracers North Pole
   value is set to northernmost zonal-mean value, for zonal velocity it is
   set to zero, and for meridional velocity it is set to northernmost value.

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

  ViewVC Help
Powered by ViewVC 1.1.22