/[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.11 - (hide annotations) (download)
Mon Dec 20 23:32:52 2004 UTC (19 years, 6 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint57d_post, checkpoint57c_pre, checkpoint57c_post
Changes since 1.10: +3 -5 lines
o exf_getffields interpolation defaults to bilinear for all scalar forcing
  fields (remains bicubic for wind velocity and stress).  This avoids, e.g.,
  spurious negative numbers for precipitation and humidity.  Will cause
  some small numerical differences for integrations using
  pkg/exf/exf_interp.F.

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     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 heimbach 1.10 call exf_interp( genfile0, exf_iprec
113 dimitri 1.4 & , gen1, count0, gen_xout, gen_yout
114 dimitri 1.3 & , gen_lon0,gen_lon_inc
115     & , gen_lat0,gen_lat_inc
116 dimitri 1.5 & , gen_nlon,gen_nlat,interp_method,mythid
117 dimitri 1.3 & )
118     #else
119 heimbach 1.10 call mdsreadfield( genfile0, exf_iprec, exf_yftype, 1
120 heimbach 1.2 & , gen1, count0, mythid
121     & )
122 dimitri 1.3 #endif
123 heimbach 1.2
124     if (exf_yftype .eq. 'RL') then
125     call exf_filter_rl( gen1, genmask, mythid )
126     else
127     call exf_filter_rs( gen1, genmask, mythid )
128     end if
129     endif
130    
131     if (( first ) .or. ( changed )) then
132     call exf_SwapFFields( gen0, gen1, mythid )
133    
134 heimbach 1.10 if (useExfYearlyFields) then
135     il = ilnblnk( genfile )
136     write(genfile1(1:128),'(2a,i4.4)')
137     & genfile(1:il),'_',year1
138     else
139     genfile1 = genfile
140     endif
141 dimitri 1.3 #ifdef USE_EXF_INTERPOLATION
142 heimbach 1.10 call exf_interp( genfile1, exf_iprec
143 dimitri 1.4 & , gen1, count1, gen_xout, gen_yout
144 dimitri 1.3 & , gen_lon0,gen_lon_inc
145     & , gen_lat0,gen_lat_inc
146 dimitri 1.5 & , gen_nlon,gen_nlat,interp_method,mythid
147 dimitri 1.3 & )
148     #else
149 heimbach 1.10 call mdsreadfield( genfile1, exf_iprec, exf_yftype, 1
150 heimbach 1.2 & , gen1, count1, mythid
151     & )
152 dimitri 1.3 #endif
153 heimbach 1.2
154     if (exf_yftype .eq. 'RL') then
155     call exf_filter_rl( gen1, genmask, mythid )
156     else
157     call exf_filter_rs( gen1, genmask, mythid )
158     end if
159     endif
160    
161     c Loop over tiles.
162     do bj = mybylo(mythid),mybyhi(mythid)
163     do bi = mybxlo(mythid),mybxhi(mythid)
164     do j = 1,sny
165     do i = 1,snx
166    
167     c Interpolate linearly onto the current time.
168    
169     genfld(i,j,bi,bj) = exf_inscal_gen * (
170     & fac * gen0(i,j,bi,bj) +
171     & (exf_one - fac) * gen1(i,j,bi,bj) )
172    
173     enddo
174     enddo
175     enddo
176     enddo
177    
178     endif
179    
180     end
181    
182    
183    
184     subroutine exf_init_gen (
185     & genconst, genfld, gen0, gen1, mythid )
186    
187     c ==================================================================
188     c SUBROUTINE exf_init_gen
189     c ==================================================================
190     c
191     c o
192     c
193     c started: Ralf.Giering@FastOpt.de 25-Mai-2000
194     c changed: heimbach@mit.edu 10-Jan-2002
195     c heimbach@mit.edu: totally re-organized exf_set_...
196     c replaced all routines by one generic routine
197     c
198     c ==================================================================
199     c SUBROUTINE exf_init_gen
200     c ==================================================================
201    
202     implicit none
203    
204     c == global variables ==
205    
206     #include "EEPARAMS.h"
207     #include "SIZE.h"
208    
209     #include "exf_param.h"
210    
211     c == routine arguments ==
212    
213     _RL genconst
214     _RL genfld(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
215     _RL gen0 (1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
216     _RL gen1 (1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
217     integer mythid
218    
219     c == local variables ==
220    
221     integer bi, bj
222     integer i, j
223    
224     c == end of interface ==
225    
226     do bj = mybylo(mythid), mybyhi(mythid)
227     do bi = mybxlo(mythid), mybxhi(mythid)
228 heimbach 1.9 do j = 1-oly, sny+oly
229     do i = 1-olx, snx+olx
230 heimbach 1.2 genfld(i,j,bi,bj) = genconst
231 heimbach 1.9 gen0(i,j,bi,bj) = genconst
232     gen1(i,j,bi,bj) = genconst
233 heimbach 1.2 enddo
234     enddo
235     enddo
236     enddo
237    
238     end

  ViewVC Help
Powered by ViewVC 1.1.22