/[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.6 - (hide annotations) (download)
Tue Sep 23 04:34:25 2003 UTC (20 years, 8 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint51j_post, checkpoint51f_post, branchpoint-genmake2, checkpoint51h_pre, checkpoint51g_post, checkpoint51i_pre
Branch point for: branch-genmake2
Changes since 1.5: +1 -0 lines
o Mods and bug fixes to pkg/cal and pkg/exf needed for computation
  of tracer Green's fucntions for ocean inversion project.

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

  ViewVC Help
Powered by ViewVC 1.1.22