/[MITgcm]/MITgcm_contrib/sannino/OASIS_3.0_Coupler/pkg/oasis_set_gen.F
ViewVC logotype

Annotation of /MITgcm_contrib/sannino/OASIS_3.0_Coupler/pkg/oasis_set_gen.F

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


Revision 1.1 - (hide annotations) (download)
Thu Jul 20 21:08:16 2006 UTC (19 years ago) by sannino
Branch: MAIN
CVS Tags: HEAD
o Adding OASIS package
o Adding grid refinement package

1 sannino 1.1 #include "EXF_OPTIONS.h"
2    
3     subroutine oasis_set_gen(
4     & genfile, genstartdate, genperiod,
5     & genstartdate1, genstartdate2,
6     & exf_inscal_gen,
7     & genfld, gen0, gen1, genmask,
8     #ifdef USE_EXF_INTERPOLATION
9     & gen_lon0, gen_lon_inc, gen_lat0, gen_lat_inc,
10     & gen_nlon, gen_nlat, gen_xout, gen_yout, interp_method,
11     #endif
12     & mycurrenttime, mycurrentiter, mythid,
13     & idFieldOASIS )
14    
15     c ==================================================================
16     c SUBROUTINE oasis_set_gen
17     c ==================================================================
18     c
19     c o set external forcing gen
20     c
21     c started: Ralf.Giering@FastOpt.de 25-Mai-2000
22     c changed: heimbach@mit.edu 10-Jan-2002
23     c 20-Dec-2002: mods for pkg/seaice, menemenlis@jpl.nasa.gov
24     c heimbach@mit.edu: totally re-organized exf_set_...
25     c replaced all routines by one generic routine
26     c 5-Aug-2003: added USE_EXF_INTERPOLATION for arbitrary
27     c input grid capability
28    
29     c ==================================================================
30     c SUBROUTINE exf_set_gen
31     c ==================================================================
32    
33     implicit none
34    
35     c == global variables ==
36    
37     #include "EEPARAMS.h"
38     #include "SIZE.h"
39     #include "GRID.h"
40    
41     #include "exf_param.h"
42     #include "exf_constants.h"
43    
44     c == routine arguments ==
45    
46     integer genstartdate1, genstartdate2
47     _RL genstartdate, genperiod
48     _RL exf_inscal_gen
49     _RL genfld(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
50     _RL gen0 (1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
51     _RL gen1 (1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
52     character*1 genmask
53     character*(128) genfile, genfile0, genfile1
54     _RL mycurrenttime
55     integer mycurrentiter
56     integer mythid
57     integer idFieldOASIS
58     #ifdef USE_EXF_INTERPOLATION
59     c gen_lon_0 ,gen_lat_0 :: longitude and latitude of SouthWest
60     c corner of global input grid
61     c gen_nlon, gen_nlat :: input x-grid and y-grid size
62     c gen_lon_inc :: scalar x-grid increment
63     c gen_lat_inc :: vector y-grid increments
64     c gen_xout, gen_yout :: coordinates for output grid
65     _RL gen_lon0, gen_lon_inc
66     _RL gen_lat0, gen_lat_inc(MAX_LAT_INC)
67     INTEGER gen_nlon, gen_nlat
68     _RS gen_xout (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
69     _RS gen_yout (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
70     integer interp_method
71     #endif
72    
73     c == local variables ==
74    
75     logical first, changed
76     integer count0, count1
77     integer year0, year1
78     cgmCALENDARIO(
79     integer year0_MY,year1_MY
80     cgmCALENDARIO)
81    
82     _RL fac
83    
84     integer bi, bj
85     integer i, j, il
86    
87     c == external ==
88    
89     integer ilnblnk
90     external ilnblnk
91    
92     c == end of interface ==
93    
94     if ( genfile .NE. ' ' ) then
95    
96     cph(
97     cph-exf-print if (genfile .EQ. hfluxfile) year0 = 3000
98     cph)
99     c get record numbers and interpolation factor for gen
100     call exf_GetFFieldRec(
101     I genstartdate, genperiod
102     I , genstartdate1, genstartdate2
103     I , useExfYearlyFields
104     O , fac, first, changed
105     O , count0, count1, year0, year1
106     I , mycurrenttime, mycurrentiter, mythid
107     & )
108    
109     if ( first ) then
110     if (useExfYearlyFields) then
111     cgmCALENDARIO(
112     cgm(
113     year0_MY = 1 + (year0 - 2000)
114     year0_MY = 2000 + mod(year0_MY-1,1)
115     cgm)
116     cgmCALENDARIO)
117    
118    
119     C Complete filename with YR or _YEAR extension
120     il = ilnblnk( genfile )
121     cgm if (twoDigitYear) then
122     cgm if (year0.ge.2000) then
123     cgm write(genfile0(1:128),'(a,i2.2)')
124     cgm & genfile(1:il),year0-2000
125     cgm else
126     cgm write(genfile0(1:128),'(a,i2.2)')
127     cgm & genfile(1:il),year0-1900
128     cgm endif
129     cgm else
130     cgm write(genfile0(1:128),'(2a,i4.4)')
131     cgm & genfile(1:il),'_',year0
132     cgm endif
133     cgm(
134     write(genfile0(1:128),'(2a,i4.4)')
135     & genfile(1:il),'_',year0_MY
136     c print*,genfile0
137     cgm)
138     else
139     genfile0 = genfile
140     endif
141     #ifdef USE_EXF_INTERPOLATION
142     call exf_interp( genfile0, exf_iprec
143     & , gen1, count0, gen_xout, gen_yout
144     & , gen_lon0,gen_lon_inc
145     & , gen_lat0,gen_lat_inc
146     & , gen_nlon,gen_nlat,interp_method,mythid
147     & )
148     #else
149     c call mdsreadfield( genfile0, exf_iprec, exf_yftype, 1
150     c & , gen1, count0, mythid
151     c & )
152    
153     CALL OASIS_GET (
154     & gen1,idFieldOASIS , mycurrentTime
155     & , mycurrentIter, myThid )
156     #endif
157    
158     if (exf_yftype .eq. 'RL') then
159     call exf_filter_rl( gen1, genmask, mythid )
160     else
161     call exf_filter_rs( gen1, genmask, mythid )
162     end if
163     endif
164    
165     if (( first ) .or. ( changed )) then
166     call exf_SwapFFields( gen0, gen1, mythid )
167    
168     if (useExfYearlyFields) then
169     cgmCALENDARIO(
170     year1_MY = 1 + (year1 - 2000)
171     year1_MY = 2000 + mod(year1_MY-1,1)
172     cgm)
173    
174    
175     C Complete filename with YR or _YEAR extension
176     il = ilnblnk( genfile )
177     c if (twoDigitYear) then
178     c if (year1.ge.2000) then
179     c write(genfile1(1:128),'(a,i2.2)')
180     c & genfile(1:il),year1-2000
181     c else
182     c write(genfile1(1:128),'(a,i2.2)')
183     c & genfile(1:il),year1-1900
184     c endif
185     c else
186     c write(genfile1(1:128),'(2a,i4.4)')
187     c & genfile(1:il),'_',year1
188     c endif
189     cgm(
190     write(genfile1(1:128),'(2a,i4.4)')
191     & genfile(1:il),'_',year1_MY
192     cgm)
193     else
194     genfile1 = genfile
195     endif
196     #ifdef USE_EXF_INTERPOLATION
197     call exf_interp( genfile1, exf_iprec
198     & , gen1, count1, gen_xout, gen_yout
199     & , gen_lon0,gen_lon_inc
200     & , gen_lat0,gen_lat_inc
201     & , gen_nlon,gen_nlat,interp_method,mythid
202     & )
203     #else
204     call mdsreadfield( genfile1, exf_iprec, exf_yftype, 1
205     & , gen1, count1, mythid
206     & )
207     #endif
208    
209     if (exf_yftype .eq. 'RL') then
210     call exf_filter_rl( gen1, genmask, mythid )
211     else
212     call exf_filter_rs( gen1, genmask, mythid )
213     end if
214     endif
215    
216     c Loop over tiles.
217     do bj = mybylo(mythid),mybyhi(mythid)
218     do bi = mybxlo(mythid),mybxhi(mythid)
219     do j = 1,sny
220     do i = 1,snx
221    
222     c Interpolate linearly onto the current time.
223    
224     genfld(i,j,bi,bj) = exf_inscal_gen * (
225     & fac * gen0(i,j,bi,bj) +
226     & (exf_one - fac) * gen1(i,j,bi,bj) )
227    
228     enddo
229     enddo
230     enddo
231     enddo
232    
233     endif
234    
235     end
236    
237    
238    
239    

  ViewVC Help
Powered by ViewVC 1.1.22