/[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.10 - (hide annotations) (download)
Mon Oct 11 16:41:01 2004 UTC (19 years, 8 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57b_post, checkpoint55j_post, checkpoint56b_post, checkpoint55h_post, checkpoint56c_post, checkpoint57a_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, checkpoint55e_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.9: +37 -8 lines
o enable to read exf forcing fields as either
  single file or yearly files (flag 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.4 & gen_nlon, gen_nlat, gen_xout, gen_yout,
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.3 #endif
69 heimbach 1.2
70     c == local variables ==
71    
72     logical first, changed
73     integer count0, count1
74 heimbach 1.10 integer year0, year1
75 heimbach 1.2 _RL fac
76    
77     integer bi, bj
78 heimbach 1.10 integer i, j
79     integer il, interp_method
80    
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     il = ilnblnk( genfile )
106     write(genfile0(1:128),'(2a,i4.4)')
107     & genfile(1:il),'_',year0
108     else
109     genfile0 = genfile
110     endif
111 dimitri 1.3 #ifdef USE_EXF_INTERPOLATION
112 dimitri 1.5 interp_method = 2
113 heimbach 1.10 call exf_interp( genfile0, exf_iprec
114 dimitri 1.4 & , gen1, count0, gen_xout, gen_yout
115 dimitri 1.3 & , gen_lon0,gen_lon_inc
116     & , gen_lat0,gen_lat_inc
117 dimitri 1.5 & , gen_nlon,gen_nlat,interp_method,mythid
118 dimitri 1.3 & )
119     #else
120 heimbach 1.10 call mdsreadfield( genfile0, exf_iprec, exf_yftype, 1
121 heimbach 1.2 & , gen1, count0, mythid
122     & )
123 dimitri 1.3 #endif
124 heimbach 1.2
125     if (exf_yftype .eq. 'RL') then
126     call exf_filter_rl( gen1, genmask, mythid )
127     else
128     call exf_filter_rs( gen1, genmask, mythid )
129     end if
130     endif
131    
132     if (( first ) .or. ( changed )) then
133     call exf_SwapFFields( gen0, gen1, mythid )
134    
135 heimbach 1.10 if (useExfYearlyFields) then
136     il = ilnblnk( genfile )
137     write(genfile1(1:128),'(2a,i4.4)')
138     & genfile(1:il),'_',year1
139     else
140     genfile1 = genfile
141     endif
142 dimitri 1.3 #ifdef USE_EXF_INTERPOLATION
143 dimitri 1.6 interp_method = 2
144 heimbach 1.10 call exf_interp( genfile1, exf_iprec
145 dimitri 1.4 & , gen1, count1, gen_xout, gen_yout
146 dimitri 1.3 & , gen_lon0,gen_lon_inc
147     & , gen_lat0,gen_lat_inc
148 dimitri 1.5 & , gen_nlon,gen_nlat,interp_method,mythid
149 dimitri 1.3 & )
150     #else
151 heimbach 1.10 call mdsreadfield( genfile1, exf_iprec, exf_yftype, 1
152 heimbach 1.2 & , gen1, count1, mythid
153     & )
154 dimitri 1.3 #endif
155 heimbach 1.2
156     if (exf_yftype .eq. 'RL') then
157     call exf_filter_rl( gen1, genmask, mythid )
158     else
159     call exf_filter_rs( gen1, genmask, mythid )
160     end if
161     endif
162    
163     c Loop over tiles.
164     do bj = mybylo(mythid),mybyhi(mythid)
165     do bi = mybxlo(mythid),mybxhi(mythid)
166     do j = 1,sny
167     do i = 1,snx
168    
169     c Interpolate linearly onto the current time.
170    
171     genfld(i,j,bi,bj) = exf_inscal_gen * (
172     & fac * gen0(i,j,bi,bj) +
173     & (exf_one - fac) * gen1(i,j,bi,bj) )
174    
175     enddo
176     enddo
177     enddo
178     enddo
179    
180     endif
181    
182     end
183    
184    
185    
186     subroutine exf_init_gen (
187     & genconst, genfld, gen0, gen1, mythid )
188    
189     c ==================================================================
190     c SUBROUTINE exf_init_gen
191     c ==================================================================
192     c
193     c o
194     c
195     c started: Ralf.Giering@FastOpt.de 25-Mai-2000
196     c changed: heimbach@mit.edu 10-Jan-2002
197     c heimbach@mit.edu: totally re-organized exf_set_...
198     c replaced all routines by one generic routine
199     c
200     c ==================================================================
201     c SUBROUTINE exf_init_gen
202     c ==================================================================
203    
204     implicit none
205    
206     c == global variables ==
207    
208     #include "EEPARAMS.h"
209     #include "SIZE.h"
210    
211     #include "exf_param.h"
212    
213     c == routine arguments ==
214    
215     _RL genconst
216     _RL genfld(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
217     _RL gen0 (1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
218     _RL gen1 (1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
219     integer mythid
220    
221     c == local variables ==
222    
223     integer bi, bj
224     integer i, j
225    
226     c == end of interface ==
227    
228     do bj = mybylo(mythid), mybyhi(mythid)
229     do bi = mybxlo(mythid), mybxhi(mythid)
230 heimbach 1.9 do j = 1-oly, sny+oly
231     do i = 1-olx, snx+olx
232 heimbach 1.2 genfld(i,j,bi,bj) = genconst
233 heimbach 1.9 gen0(i,j,bi,bj) = genconst
234     gen1(i,j,bi,bj) = genconst
235 heimbach 1.2 enddo
236     enddo
237     enddo
238     enddo
239    
240     end

  ViewVC Help
Powered by ViewVC 1.1.22