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

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

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


Revision 1.12 - (hide annotations) (download)
Mon Feb 21 05:32:55 2005 UTC (19 years, 3 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint57o_post, checkpoint57v_post, checkpoint57m_post, checkpoint57s_post, checkpoint57k_post, checkpoint57g_post, checkpoint57i_post, checkpoint57y_post, checkpoint57e_post, checkpoint57g_pre, checkpoint57y_pre, checkpoint57f_pre, checkpoint57r_post, checkpoint58, eckpoint57e_pre, checkpoint57h_done, checkpoint57x_post, checkpoint57n_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint57f_post, checkpoint58a_post, checkpoint57q_post, checkpoint57z_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint57h_post
Branch point for: release1_50yr
Changes since 1.11: +26 -4 lines
pkg/exf: added twoDigitYear to useExfYearlyFields

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

  ViewVC Help
Powered by ViewVC 1.1.22