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

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

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


Revision 1.19 - (hide annotations) (download)
Tue Jan 29 11:25:53 2008 UTC (16 years, 4 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59o, checkpoint59n, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61h, checkpoint61i
Changes since 1.18: +1 -8 lines
Completed mods to exf_getffieldrec.F to properly deal
with year transitions for useExfYearlyFields.

1 dimitri 1.19 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_set_uv.F,v 1.18 2008/01/28 06:17:01 dimitri Exp $
2 dimitri 1.1 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 heimbach 1.10 & uvec_nlon, uvec_nlat,
11     & uvec_remove_intercept, uvec_remove_slope,
12 dimitri 1.1 & vvecfile, vvecstartdate, vvecperiod,
13     & exf_inscal_vvec, vvec, vvec0, vvec1, vvecmask,
14     & vvec_lon0, vvec_lon_inc, vvec_lat0, vvec_lat_inc,
15 dimitri 1.3 & vvec_nlon, vvec_nlat,
16 heimbach 1.10 & vvec_remove_intercept, vvec_remove_slope,
17 dimitri 1.1 & 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 jmc 1.15 #include "EXF_PARAM.h"
43     #include "EXF_FIELDS.h"
44     #include "EXF_CONSTANTS.h"
45 dimitri 1.1
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 heimbach 1.5 character*(128) uvecfile, uvecfile0, uvecfile1
60 dimitri 1.1 _RL uvecstartdate, uvecperiod
61     _RL exf_inscal_uvec
62 heimbach 1.10 _RL uvec_remove_intercept, uvec_remove_slope
63 dimitri 1.1 _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 heimbach 1.5 character*(128) vvecfile, vvecfile0, vvecfile1
71 dimitri 1.1 _RL vvecstartdate, vvecperiod
72     _RL exf_inscal_vvec
73 heimbach 1.10 _RL vvec_remove_intercept, vvec_remove_slope
74 dimitri 1.1 _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 heimbach 1.4 #ifdef USE_EXF_INTERPOLATION
86 dimitri 1.1 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 dimitri 1.16 integer count0, count1
93 dimitri 1.1 integer i, j, bi, bj
94 heimbach 1.5 integer il, interp_method
95     integer year0, year1
96    
97     c == external ==
98    
99     integer ilnblnk
100     external ilnblnk
101 dimitri 1.1
102     c == end of interface ==
103    
104 dimitri 1.11 IF ( usingCurvilinearGrid ) THEN
105 dimitri 1.1
106 heimbach 1.13 if ( uvecfile .NE. ' ' .and. vvecfile .NE. ' ' ) then
107 dimitri 1.1
108     c get record numbers and interpolation factor
109 heimbach 1.13 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 dimitri 1.1
117 heimbach 1.13 if ( first ) then
118 mlosch 1.17
119     call exf_GetYearlyFieldName(
120     I useExfYearlyFields, twoDigitYear, uvecperiod, year0,
121     I uvecfile,
122     O uvecfile0,
123 dimitri 1.18 I mycurrenttime, mycurrentiter, mythid )
124 mlosch 1.17 call exf_GetYearlyFieldName(
125     I useExfYearlyFields, twoDigitYear, vvecperiod, year0,
126     I vvecfile,
127     O vvecfile0,
128 dimitri 1.18 I mycurrenttime, mycurrentiter, mythid )
129 mlosch 1.17
130 dimitri 1.1 c scalar interpolation to (xC,yC) locations
131 dimitri 1.14 interp_method=12
132 heimbach 1.13 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 dimitri 1.14 interp_method=22
139 heimbach 1.13 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 dimitri 1.1 c vector rotation
146 heimbach 1.13 do bj = mybylo(mythid),mybyhi(mythid)
147     do bi = mybxlo(mythid),mybxhi(mythid)
148     do j = 1,sny
149     do i = 1,snx
150 dimitri 1.16 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 heimbach 1.13 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 dimitri 1.16 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 heimbach 1.13 dx=0.5*(x3+x4-x1-x2)
165     dx=dx*
166 dimitri 1.16 & cos(deg2rad*yC(i,j,bi,bj))
167 heimbach 1.13 dy=0.5*(y3+y4-y1-y2)
168     vvec1(i,j,bi,bj)=
169 dimitri 1.16 & (tmp_u(i,j,bi,bj)*dx+
170     & tmp_v(i,j,bi,bj)*dy)/
171 heimbach 1.13 & sqrt(dx*dx+dy*dy)
172     dx=0.5*(x2+x4-x1-x3)
173     dx=dx*
174 dimitri 1.16 & cos(deg2rad*yC(i,j,bi,bj))
175 heimbach 1.13 dy=0.5*(y2+y4-y1-y3)
176     uvec1(i,j,bi,bj)=
177 dimitri 1.16 & (tmp_u(i,j,bi,bj)*dx+
178     & tmp_v(i,j,bi,bj)*dy)/
179 heimbach 1.13 & sqrt(dx*dx+dy*dy)
180 dimitri 1.1 enddo
181 heimbach 1.13 enddo
182     enddo
183     enddo
184 dimitri 1.1 c apply mask
185 heimbach 1.13 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     call exf_filter_rs( uvec1, uvecmask, mythid )
190     call exf_filter_rs( vvec1, vvecmask, mythid )
191     end if
192     endif
193    
194     if (( first ) .or. ( changed )) then
195     call exf_SwapFFields( uvec0, uvec1, mythid )
196     call exf_SwapFFields( vvec0, vvec1, mythid )
197 mlosch 1.17
198     call exf_GetYearlyFieldName(
199     I useExfYearlyFields, twoDigitYear, uvecperiod, year1,
200     I uvecfile,
201     O uvecfile1,
202 dimitri 1.18 I mycurrenttime, mycurrentiter, mythid )
203 mlosch 1.17 call exf_GetYearlyFieldName(
204     I useExfYearlyFields, twoDigitYear, vvecperiod, year1,
205     I vvecfile,
206     O vvecfile1,
207 dimitri 1.18 I mycurrenttime, mycurrentiter, mythid )
208 mlosch 1.17
209 dimitri 1.1 c scalar interpolation to (xC,yC) locations
210 dimitri 1.14 interp_method=12
211 heimbach 1.13 call exf_interp( uvecfile1, exf_iprec
212     & , tmp_u, count1, xC, yC
213     & , uvec_lon0,uvec_lon_inc
214     & , uvec_lat0,uvec_lat_inc
215     & , uvec_nlon,uvec_nlat,interp_method,mythid
216     & )
217 dimitri 1.14 interp_method=22
218 heimbach 1.13 call exf_interp( vvecfile1, exf_iprec
219     & , tmp_v, count1, xC, yC
220     & , vvec_lon0,vvec_lon_inc
221     & , vvec_lat0,vvec_lat_inc
222     & , vvec_nlon,vvec_nlat,interp_method,mythid
223     & )
224 dimitri 1.1 c vector rotation
225 heimbach 1.13 do bj = mybylo(mythid),mybyhi(mythid)
226     do bi = mybxlo(mythid),mybxhi(mythid)
227     do j = 1,sny
228     do i = 1,snx
229 dimitri 1.16 x1=xG(i,j,bi,bj)
230     x2=xG(i+1,j,bi,bj)
231     x3=xG(i,j+1,bi,bj)
232     x4=xG(i+1,j+1,bi,bj)
233 heimbach 1.13 if ((x2-x1).gt.180) x2=x2-360
234     if ((x1-x2).gt.180) x2=x2+360
235     if ((x3-x1).gt.180) x3=x3-360
236     if ((x1-x3).gt.180) x3=x3+360
237     if ((x4-x1).gt.180) x4=x4-360
238     if ((x1-x4).gt.180) x4=x4+360
239 dimitri 1.16 y1=yG(i,j,bi,bj)
240     y2=yG(i+1,j,bi,bj)
241     y3=yG(i,j+1,bi,bj)
242     y4=yG(i+1,j+1,bi,bj)
243 heimbach 1.13 dx=0.5*(x3+x4-x1-x2)
244     dx=dx*
245 dimitri 1.16 & cos(deg2rad*yC(i,j,bi,bj))
246 heimbach 1.13 dy=0.5*(y3+y4-y1-y2)
247     vvec1(i,j,bi,bj)=
248 dimitri 1.16 & (tmp_u(i,j,bi,bj)*dx+
249     & tmp_v(i,j,bi,bj)*dy)/
250 heimbach 1.13 & sqrt(dx*dx+dy*dy)
251     dx=0.5*(x2+x4-x1-x3)
252     dx=dx*
253 dimitri 1.16 & cos(deg2rad*yC(i,j,bi,bj))
254 heimbach 1.13 dy=0.5*(y2+y4-y1-y3)
255     uvec1(i,j,bi,bj)=
256 dimitri 1.16 & (tmp_u(i,j,bi,bj)*dx+
257     & tmp_v(i,j,bi,bj)*dy)/
258 heimbach 1.13 & sqrt(dx*dx+dy*dy)
259 dimitri 1.1 enddo
260 heimbach 1.13 enddo
261     enddo
262     enddo
263 dimitri 1.1 c apply mask
264 heimbach 1.13 if (exf_yftype .eq. 'RL') then
265     call exf_filter_rl( uvec1, uvecmask, mythid )
266     call exf_filter_rl( vvec1, vvecmask, mythid )
267     else
268     call exf_filter_rs( uvec1, uvecmask, mythid )
269     call exf_filter_rs( vvec1, vvecmask, mythid )
270     end if
271     endif
272 dimitri 1.1
273     c Interpolate linearly onto the current time.
274 heimbach 1.13 do bj = mybylo(mythid),mybyhi(mythid)
275     do bi = mybxlo(mythid),mybxhi(mythid)
276     do j = 1,sny
277     do i = 1,snx
278     uvec(i,j,bi,bj) = exf_inscal_uvec * (
279     & fac * uvec0(i,j,bi,bj) +
280     & (exf_one - fac) * uvec1(i,j,bi,bj) )
281     vvec(i,j,bi,bj) = exf_inscal_vvec * (
282     & fac * vvec0(i,j,bi,bj) +
283     & (exf_one - fac) * vvec1(i,j,bi,bj) )
284     enddo
285     enddo
286 dimitri 1.1 enddo
287 heimbach 1.13 enddo
288    
289     endif
290 dimitri 1.1
291     ELSE
292 dimitri 1.16 c IF ( .NOT. usingCurvilinearGrid )
293 dimitri 1.1
294 dimitri 1.14 interp_method=12
295 heimbach 1.13 call exf_set_gen(
296     & uvecfile, uvecstartdate, uvecperiod,
297     & exf_inscal_uvec,
298     & uvec_remove_intercept, uvec_remove_slope,
299     & uvec, uvec0, uvec1, uvecmask,
300     & uvec_lon0, uvec_lon_inc, uvec_lat0, uvec_lat_inc,
301     & uvec_nlon, uvec_nlat, xC, yC, interp_method,
302     & mycurrenttime, mycurrentiter, mythid )
303 dimitri 1.14 interp_method=22
304 heimbach 1.13 call exf_set_gen(
305     & vvecfile, vvecstartdate, vvecperiod,
306     & exf_inscal_vvec,
307     & vvec_remove_intercept, vvec_remove_slope,
308     & vvec, vvec0, vvec1, vvecmask,
309     & vvec_lon0, vvec_lon_inc, vvec_lat0, vvec_lat_inc,
310     & vvec_nlon, vvec_nlat, xC, yC, interp_method,
311     & mycurrenttime, mycurrentiter, mythid )
312    
313 dimitri 1.1 ENDIF
314    
315 heimbach 1.4 #endif /* USE_EXF_INTERPOLATION */
316    
317 dimitri 1.1 return
318     end

  ViewVC Help
Powered by ViewVC 1.1.22