/[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.21 - (show annotations) (download)
Wed Sep 2 19:18:39 2009 UTC (14 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint62, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61v, checkpoint61w, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.20: +10 -8 lines
comment out wrong exf_yftype calls

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

  ViewVC Help
Powered by ViewVC 1.1.22