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

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

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


Revision 1.1.6.2 - (hide annotations) (download)
Thu Apr 4 11:08:03 2002 UTC (22 years, 2 months ago) by heimbach
Branch: ecco-branch
CVS Tags: ecco_c44_e22, ecco_c44_e23, ecco_c44_e24
Changes since 1.1.6.1: +17 -3 lines
o added run-off routine
o additional storing needed for ustress,vstess
  because of state-dependent quality check
o added missing initialisations

1 heimbach 1.1.6.2 c $Header: /u/gcmpack/MITgcm/pkg/exf/exf_readparms.F,v 1.1.6.1 2002/02/06 23:18:54 heimbach Exp $
2 heimbach 1.1
3     #include "EXF_CPPOPTIONS.h"
4    
5    
6     subroutine exf_readparms(
7     I mythid
8     & )
9    
10     c ==================================================================
11     c SUBROUTINE exf_readparms
12     c ==================================================================
13     c
14     c o This routine initialises the package that calculates external
15     c forcing fields for a given timestep of the MITgcmUV. Parameters
16     c for this package are set in "data.externalforcing". Some additional
17 heimbach 1.1.6.1 c precompiler switches have to be specified in "EXF_CPPOPTIONS.h".
18 heimbach 1.1 c
19     c started: Christian Eckert eckert@mit.edu 30-Jun-1999
20     c
21     c changed: Christian Eckert eckert@mit.edu 11-Jan-2000
22     c - Restructured the code in order to create a package
23     c for the MITgcmUV.
24     c Christian Eckert eckert@mit.edu 12-Feb-2000
25     c - Changed Routine names (package prefix: exf_)
26 heimbach 1.1.6.1 c changed: Patrick Heimbach, heimbach@mit.edu 04-May-2000
27 heimbach 1.1 c - changed the handling of precip and sflux with respect
28     c to CPP options ALLOW_BULKFORMULAE and ALLOW_ATM_TEMP
29     c changed: Ralf.Giering@FastOpt.de 25-Mai-20000
30 heimbach 1.1.6.1 c - moved relaxation and climatology to extra routines
31 heimbach 1.1 c Patrick Heimbach, heimbach@mit.edu 04-May-2000
32     c - added obcs parameters
33 heimbach 1.1.6.1 c changed: Virginie Thierry, vthierry@ucsd.edu 04-June-2001
34     c - added new obcs parameters (for each boundaries)
35 heimbach 1.1.6.2 c included runoff D. Stammer, Nov. 25, 2001
36 heimbach 1.1 c
37     c ==================================================================
38     c SUBROUTINE exf_readparms
39     c ==================================================================
40    
41     implicit none
42    
43     c == global variables ==
44    
45     #include "EEPARAMS.h"
46     #include "SIZE.h"
47     #include "cal.h"
48     #include "exf.h"
49     #include "exf_param.h"
50     #include "exf_constants.h"
51 heimbach 1.1.6.1 #ifdef ALLOW_OBCS
52     # include "OBCS_OPTIONS.h"
53     #endif
54 heimbach 1.1
55     c == routine arguments ==
56    
57     integer mythid
58    
59     c == local variables ==
60    
61     integer i
62    
63     c == external ==
64    
65     integer ilnblnk
66     external ilnblnk
67    
68     c == end of interface ==
69    
70     c Surface flux data.
71     namelist /exf_nml/
72     & hfluxstartdate1, hfluxstartdate2, hfluxperiod,
73     & atempstartdate1, atempstartdate2, atempperiod,
74     & aqhstartdate1, aqhstartdate2, aqhperiod,
75     & sfluxstartdate1, sfluxstartdate2, sfluxperiod,
76     & precipstartdate1, precipstartdate2, precipperiod,
77 heimbach 1.1.6.2 & runoffstartdate1, runoffstartdate2, runoffperiod,
78 heimbach 1.1 & ustressstartdate1, ustressstartdate2, ustressperiod,
79     & vstressstartdate1, vstressstartdate2, vstressperiod,
80     & uwindstartdate1, uwindstartdate2, uwindperiod,
81     & vwindstartdate1, vwindstartdate2, vwindperiod,
82     & swfluxstartdate1, swfluxstartdate2, swfluxperiod,
83     & lwfluxstartdate1, lwfluxstartdate2, lwfluxperiod,
84 heimbach 1.1.6.1 & obcsNstartdate1, obcsNstartdate2, obcsNperiod,
85     & obcsSstartdate1, obcsSstartdate2, obcsSperiod,
86     & obcsEstartdate1, obcsEstartdate2, obcsEperiod,
87     & obcsWstartdate1, obcsWstartdate2, obcsWperiod,
88 heimbach 1.1 & hfluxfile, atempfile, aqhfile,
89 heimbach 1.1.6.2 & sfluxfile, precipfile, runofffile,
90     & ustressfile, vstressfile,
91     & uwindfile, vwindfile,
92 heimbach 1.1.6.1 & swfluxfile, lwfluxfile,
93 heimbach 1.1 & exf_iprec, exf_yftype
94    
95     _BEGIN_MASTER(mythid)
96    
97     c Set default values.
98    
99     c Calendar data.
100     hfluxstartdate1 = 0
101     hfluxstartdate2 = 0
102     hfluxperiod = 0.0 _d 0
103    
104     atempstartdate1 = 0
105     atempstartdate2 = 0
106     atempperiod = 0.0 _d 0
107    
108     aqhstartdate1 = 0
109     aqhstartdate2 = 0
110     aqhperiod = 0.0 _d 0
111    
112     sfluxstartdate1 = 0
113     sfluxstartdate2 = 0
114     sfluxperiod = 0.0 _d 0
115    
116     precipstartdate1 = 0
117     precipstartdate2 = 0
118     precipperiod = 0.0 _d 0
119    
120 heimbach 1.1.6.2 runoffstartdate1 = 0
121     runoffstartdate2 = 0
122     runoffperiod = 0.0 _d 0
123    
124 heimbach 1.1 ustressstartdate1 = 0
125     ustressstartdate2 = 0
126     ustressperiod = 0.0 _d 0
127    
128     vstressstartdate1 = 0
129     vstressstartdate2 = 0
130     vstressperiod = 0.0 _d 0
131    
132     uwindstartdate1 = 0
133     uwindstartdate2 = 0
134     uwindperiod = 0.0 _d 0
135    
136     vwindstartdate1 = 0
137     vwindstartdate2 = 0
138     vwindperiod = 0.0 _d 0
139    
140     swfluxstartdate1 = 0
141     swfluxstartdate2 = 0
142     swfluxperiod = 0.0 _d 0
143    
144     lwfluxstartdate1 = 0
145     lwfluxstartdate2 = 0
146     lwfluxperiod = 0.0 _d 0
147    
148 heimbach 1.1.6.1 obcsNstartdate1 = 0
149     obcsNstartdate2 = 0
150     obcsNperiod = 0.0 _d 0
151    
152     obcsSstartdate1 = 0
153     obcsSstartdate2 = 0
154     obcsSperiod = 0.0 _d 0
155    
156     obcsEstartdate1 = 0
157     obcsEstartdate2 = 0
158     obcsEperiod = 0.0 _d 0
159    
160     obcsWstartdate1 = 0
161     obcsWstartdate2 = 0
162     obcsWperiod = 0.0 _d 0
163 heimbach 1.1
164     c Data files.
165     hfluxfile = ' '
166     atempfile = ' '
167     aqhfile = ' '
168     precipfile = ' '
169     sfluxfile = ' '
170 heimbach 1.1.6.2 runofffile = ' '
171 heimbach 1.1 ustressfile = ' '
172     vstressfile = ' '
173     uwindfile = ' '
174     vwindfile = ' '
175     swfluxfile = ' '
176     lwfluxfile = ' '
177    
178     c Initialise the date arrays.
179     do i = 1,4
180     hfluxstartdate(i) = 0
181     atempstartdate(i) = 0
182     aqhstartdate(i) = 0
183     precipstartdate(i) = 0
184     sfluxstartdate(i) = 0
185 heimbach 1.1.6.2 runoffstartdate(i) = 0
186 heimbach 1.1 ustressstartdate(i) = 0
187     vstressstartdate(i) = 0
188     uwindstartdate(i) = 0
189     vwindstartdate(i) = 0
190     swfluxstartdate(i) = 0
191     lwfluxstartdate(i) = 0
192 heimbach 1.1.6.1 obcsNstartdate(i) = 0
193     obcsSstartdate(i) = 0
194     obcsEstartdate(i) = 0
195     obcsWstartdate(i) = 0
196 heimbach 1.1 enddo
197    
198     c Initialise file type and field precision
199     exf_iprec = 32
200     exf_yftype = 'RL'
201    
202     c Check for the availability of the right calendar version.
203     if ( calendarversion .ne. usescalendarversion ) then
204     print*,' exf_readparms: You are not using the appropriate'
205     print*,' version of the calendar package.'
206     print*
207     print*,' You are using Calendar version: ', calendarversion
208     print*,' Please use Calendar version: ', usescalendarversion
209     stop ' stopped in exf_readparms.'
210     endif
211    
212     c Next, read the forcing data file.
213     call nml_filter( 'data.exf', scrunit1, myThid )
214     if (scrunit1 .eq. 0) then
215     stop 'exf_readparms: reading namelist failed'
216     end if
217     read( scrunit1, nml = exf_nml )
218     close( scrunit1 )
219    
220     c Complete the start date specifications for the forcing
221     c fields to get a complete calendar date array.
222    
223     c check for consistency
224    
225     if (.NOT.
226     & (exf_iprec .EQ. 32 .OR. exf_iprec .EQ. 64)
227     & ) then
228     stop 'stop in exf_readparms: value of exf_iprec not allowed'
229     else if (.NOT.
230     & (exf_yftype .EQ. 'RS' .OR.
231     & exf_yftype .EQ. 'RL')
232     & ) then
233     stop 'stop in exf_readparms: value of exf_yftype not allowed'
234     end if
235 heimbach 1.1.6.2
236     #ifdef ALLOW_RUNOFF
237     call cal_FullDate( runoffstartdate1, runoffstartdate2,
238     & runoffstartdate, mythid )
239     #endif
240 heimbach 1.1
241     #ifdef ALLOW_BULKFORMULAE
242    
243     #ifdef ALLOW_ATM_TEMP
244     call cal_FullDate( atempstartdate1, atempstartdate2,
245     & atempstartdate, mythid )
246     call cal_FullDate( aqhstartdate1, aqhstartdate2,
247     & aqhstartdate, mythid )
248     call cal_FullDate( swfluxstartdate1, swfluxstartdate2,
249     & swfluxstartdate, mythid )
250     call cal_FullDate( lwfluxstartdate1, lwfluxstartdate2,
251     & lwfluxstartdate, mythid )
252     call cal_FullDate( precipstartdate1, precipstartdate2,
253     & precipstartdate, mythid )
254     #else
255     call cal_FullDate( hfluxstartdate1, hfluxstartdate2,
256     & hfluxstartdate, mythid )
257     call cal_FullDate( sfluxstartdate1, sfluxstartdate2,
258     & sfluxstartdate, mythid )
259     #ifdef ALLOW_KPP
260     call cal_FullDate( swfluxstartdate1, swfluxstartdate2,
261     & swfluxstartdate, mythid )
262     #endif
263    
264     #endif
265    
266     #ifdef ALLOW_ATM_WIND
267     call cal_FullDate( uwindstartdate1, uwindstartdate2,
268     & uwindstartdate, mythid )
269     call cal_FullDate( vwindstartdate1, vwindstartdate2,
270     & vwindstartdate, mythid )
271     #else
272     call cal_FullDate( ustressstartdate1, ustressstartdate2,
273     & ustressstartdate, mythid )
274     call cal_FullDate( vstressstartdate1, vstressstartdate2,
275     & vstressstartdate, mythid )
276     #endif
277    
278     #else
279     call cal_FullDate( hfluxstartdate1, hfluxstartdate2,
280     & hfluxstartdate, mythid )
281     call cal_FullDate( sfluxstartdate1, sfluxstartdate2,
282     & sfluxstartdate, mythid )
283     call cal_FullDate( ustressstartdate1, ustressstartdate2,
284     & ustressstartdate, mythid )
285     call cal_FullDate( vstressstartdate1, vstressstartdate2,
286     & vstressstartdate, mythid )
287     #ifdef ALLOW_KPP
288     call cal_FullDate( swfluxstartdate1, swfluxstartdate2,
289     & swfluxstartdate, mythid )
290     #endif
291    
292     #endif
293    
294     #ifdef ALLOW_OBCS
295 heimbach 1.1.6.1 #ifdef ALLOW_OBCS_NORTH
296     call cal_FullDate( obcsNstartdate1, obcsNstartdate2,
297     & obcsNstartdate, mythid )
298     #endif
299     #ifdef ALLOW_OBCS_SOUTH
300     call cal_FullDate( obcsSstartdate1, obcsSstartdate2,
301     & obcsSstartdate, mythid )
302     #endif
303     #ifdef ALLOW_OBCS_EAST
304     call cal_FullDate( obcsEstartdate1, obcsEstartdate2,
305     & obcsEstartdate, mythid )
306     #endif
307     #ifdef ALLOW_OBCS_WEST
308     call cal_FullDate( obcsWstartdate1, obcsWstartdate2,
309     & obcsWstartdate, mythid )
310     #endif
311 heimbach 1.1 #endif
312    
313     _END_MASTER( mythid )
314    
315     _BARRIER
316    
317     c-- Summarize the External forcing's setup.
318     call exf_summary( mythid )
319    
320    
321     c-- set climatology parameters
322     call exf_clim_readparms( mythid )
323    
324     c-- summarize climatologic forcing configuration
325     call exf_clim_summary( mythid )
326    
327     end

  ViewVC Help
Powered by ViewVC 1.1.22