/[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.3 - (hide annotations) (download)
Thu Nov 28 12:55:43 2002 UTC (21 years, 6 months ago) by heimbach
Branch: ecco-branch
CVS Tags: ecco_ice1, ecco_c44_e25
Branch point for: c24_e25_ice
Changes since 1.1.6.2: +37 -10 lines
o exf:
  updated external forcing package
  - cleaned old exfa stuff
  - bug fixes
    (missing OBCS_OPTIONS.h in two routines)
  - enable easy to use "no forcing".
  - added exf I/O for atmospheric loading
  - added exf I/O for runoff data
  - transfered scaling between exf <-> MITgcm to exf namelist

1 heimbach 1.1.6.3 c $Header: /u/gcmpack/MITgcm/pkg/exf/exf_readparms.F,v 1.1.6.2 2002/04/04 11:08:03 heimbach Exp $
2 heimbach 1.1
3     #include "EXF_CPPOPTIONS.h"
4 heimbach 1.1.6.3 #ifdef ALLOW_OBCS
5     # include "OBCS_OPTIONS.h"
6     #endif
7 heimbach 1.1
8 heimbach 1.1.6.3 subroutine exf_readparms( mythid )
9 heimbach 1.1
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.6.3 c included pressure forcing. heimbach@mit.edu 05-Nov-2002
37 heimbach 1.1 c
38     c ==================================================================
39     c SUBROUTINE exf_readparms
40     c ==================================================================
41    
42     implicit none
43    
44     c == global variables ==
45    
46     #include "EEPARAMS.h"
47     #include "SIZE.h"
48     #include "cal.h"
49     #include "exf.h"
50     #include "exf_param.h"
51     #include "exf_constants.h"
52    
53     c == routine arguments ==
54    
55     integer mythid
56    
57     c == local variables ==
58    
59     integer i
60    
61     c == external ==
62    
63     integer ilnblnk
64     external ilnblnk
65    
66     c == end of interface ==
67    
68     c Surface flux data.
69     namelist /exf_nml/
70     & hfluxstartdate1, hfluxstartdate2, hfluxperiod,
71     & atempstartdate1, atempstartdate2, atempperiod,
72     & aqhstartdate1, aqhstartdate2, aqhperiod,
73     & sfluxstartdate1, sfluxstartdate2, sfluxperiod,
74     & precipstartdate1, precipstartdate2, precipperiod,
75 heimbach 1.1.6.2 & runoffstartdate1, runoffstartdate2, runoffperiod,
76 heimbach 1.1 & ustressstartdate1, ustressstartdate2, ustressperiod,
77     & vstressstartdate1, vstressstartdate2, vstressperiod,
78     & uwindstartdate1, uwindstartdate2, uwindperiod,
79     & vwindstartdate1, vwindstartdate2, vwindperiod,
80     & swfluxstartdate1, swfluxstartdate2, swfluxperiod,
81     & lwfluxstartdate1, lwfluxstartdate2, lwfluxperiod,
82 heimbach 1.1.6.1 & obcsNstartdate1, obcsNstartdate2, obcsNperiod,
83     & obcsSstartdate1, obcsSstartdate2, obcsSperiod,
84     & obcsEstartdate1, obcsEstartdate2, obcsEperiod,
85     & obcsWstartdate1, obcsWstartdate2, obcsWperiod,
86 heimbach 1.1.6.3 &apressurestartdate1,apressurestartdate2,apressureperiod,
87 heimbach 1.1 & hfluxfile, atempfile, aqhfile,
88 heimbach 1.1.6.2 & sfluxfile, precipfile, runofffile,
89     & ustressfile, vstressfile,
90     & uwindfile, vwindfile,
91 heimbach 1.1.6.3 & swfluxfile, lwfluxfile, apressurefile,
92     & exf_iprec, exf_yftype,
93     & scal_hfl, scal_ust, scal_vst,
94     & scal_swf, scal_sst, scal_sss,
95     & scal_apressure, scal_prc, scal_sfl
96 heimbach 1.1
97     _BEGIN_MASTER(mythid)
98    
99     c Set default values.
100    
101     c Calendar data.
102     hfluxstartdate1 = 0
103     hfluxstartdate2 = 0
104     hfluxperiod = 0.0 _d 0
105    
106     atempstartdate1 = 0
107     atempstartdate2 = 0
108     atempperiod = 0.0 _d 0
109    
110     aqhstartdate1 = 0
111     aqhstartdate2 = 0
112     aqhperiod = 0.0 _d 0
113    
114     sfluxstartdate1 = 0
115     sfluxstartdate2 = 0
116     sfluxperiod = 0.0 _d 0
117    
118     precipstartdate1 = 0
119     precipstartdate2 = 0
120     precipperiod = 0.0 _d 0
121    
122 heimbach 1.1.6.2 runoffstartdate1 = 0
123     runoffstartdate2 = 0
124     runoffperiod = 0.0 _d 0
125    
126 heimbach 1.1 ustressstartdate1 = 0
127     ustressstartdate2 = 0
128     ustressperiod = 0.0 _d 0
129    
130     vstressstartdate1 = 0
131     vstressstartdate2 = 0
132     vstressperiod = 0.0 _d 0
133    
134     uwindstartdate1 = 0
135     uwindstartdate2 = 0
136     uwindperiod = 0.0 _d 0
137    
138     vwindstartdate1 = 0
139     vwindstartdate2 = 0
140     vwindperiod = 0.0 _d 0
141    
142     swfluxstartdate1 = 0
143     swfluxstartdate2 = 0
144     swfluxperiod = 0.0 _d 0
145    
146     lwfluxstartdate1 = 0
147     lwfluxstartdate2 = 0
148     lwfluxperiod = 0.0 _d 0
149    
150 heimbach 1.1.6.1 obcsNstartdate1 = 0
151     obcsNstartdate2 = 0
152     obcsNperiod = 0.0 _d 0
153    
154     obcsSstartdate1 = 0
155     obcsSstartdate2 = 0
156     obcsSperiod = 0.0 _d 0
157    
158     obcsEstartdate1 = 0
159     obcsEstartdate2 = 0
160     obcsEperiod = 0.0 _d 0
161    
162     obcsWstartdate1 = 0
163     obcsWstartdate2 = 0
164     obcsWperiod = 0.0 _d 0
165 heimbach 1.1
166 heimbach 1.1.6.3 apressurestartdate1 = 0
167     apressurestartdate2 = 0
168     apressureperiod = 0.0 _d 0
169    
170 heimbach 1.1 c Data files.
171     hfluxfile = ' '
172     atempfile = ' '
173     aqhfile = ' '
174     precipfile = ' '
175     sfluxfile = ' '
176 heimbach 1.1.6.2 runofffile = ' '
177 heimbach 1.1 ustressfile = ' '
178     vstressfile = ' '
179     uwindfile = ' '
180     vwindfile = ' '
181     swfluxfile = ' '
182     lwfluxfile = ' '
183 heimbach 1.1.6.3 apressurefile = ' '
184 heimbach 1.1
185     c Initialise the date arrays.
186     do i = 1,4
187     hfluxstartdate(i) = 0
188     atempstartdate(i) = 0
189     aqhstartdate(i) = 0
190     precipstartdate(i) = 0
191     sfluxstartdate(i) = 0
192 heimbach 1.1.6.2 runoffstartdate(i) = 0
193 heimbach 1.1 ustressstartdate(i) = 0
194     vstressstartdate(i) = 0
195     uwindstartdate(i) = 0
196     vwindstartdate(i) = 0
197     swfluxstartdate(i) = 0
198     lwfluxstartdate(i) = 0
199 heimbach 1.1.6.1 obcsNstartdate(i) = 0
200     obcsSstartdate(i) = 0
201     obcsEstartdate(i) = 0
202     obcsWstartdate(i) = 0
203 heimbach 1.1.6.3 apressurestartdate(i)= 0
204 heimbach 1.1 enddo
205    
206     c Initialise file type and field precision
207     exf_iprec = 32
208     exf_yftype = 'RL'
209    
210 heimbach 1.1.6.3 c scaling between exf units and MITgcm units
211     scal_hfl = 1. _d 0
212     scal_ust = 1. _d 0
213     scal_vst = 1. _d 0
214     scal_swf = 1. _d 0
215     scal_sst = 1. _d 0
216     scal_sss = 1. _d 0
217     scal_apressure = 1. _d 0
218     #if (defined (ALLOW_BULKFORMULAE) && defined (ALLOW_ATM_TEMP))
219     scal_prc = 1. _d 0
220     #else
221     scal_sfl = 1. _d 0
222     #endif
223    
224 heimbach 1.1 c Check for the availability of the right calendar version.
225     if ( calendarversion .ne. usescalendarversion ) then
226     print*,' exf_readparms: You are not using the appropriate'
227     print*,' version of the calendar package.'
228     print*
229     print*,' You are using Calendar version: ', calendarversion
230     print*,' Please use Calendar version: ', usescalendarversion
231     stop ' stopped in exf_readparms.'
232     endif
233    
234     c Next, read the forcing data file.
235     call nml_filter( 'data.exf', scrunit1, myThid )
236     if (scrunit1 .eq. 0) then
237     stop 'exf_readparms: reading namelist failed'
238     end if
239     read( scrunit1, nml = exf_nml )
240     close( scrunit1 )
241    
242     c Complete the start date specifications for the forcing
243     c fields to get a complete calendar date array.
244    
245     c check for consistency
246    
247     if (.NOT.
248     & (exf_iprec .EQ. 32 .OR. exf_iprec .EQ. 64)
249     & ) then
250     stop 'stop in exf_readparms: value of exf_iprec not allowed'
251     else if (.NOT.
252     & (exf_yftype .EQ. 'RS' .OR.
253     & exf_yftype .EQ. 'RL')
254     & ) then
255     stop 'stop in exf_readparms: value of exf_yftype not allowed'
256     end if
257 heimbach 1.1.6.2
258     #ifdef ALLOW_RUNOFF
259     call cal_FullDate( runoffstartdate1, runoffstartdate2,
260     & runoffstartdate, mythid )
261     #endif
262 heimbach 1.1
263     #ifdef ALLOW_BULKFORMULAE
264    
265     #ifdef ALLOW_ATM_TEMP
266     call cal_FullDate( atempstartdate1, atempstartdate2,
267     & atempstartdate, mythid )
268     call cal_FullDate( aqhstartdate1, aqhstartdate2,
269     & aqhstartdate, mythid )
270     call cal_FullDate( swfluxstartdate1, swfluxstartdate2,
271     & swfluxstartdate, mythid )
272     call cal_FullDate( lwfluxstartdate1, lwfluxstartdate2,
273     & lwfluxstartdate, mythid )
274     call cal_FullDate( precipstartdate1, precipstartdate2,
275     & precipstartdate, mythid )
276     #else
277     call cal_FullDate( hfluxstartdate1, hfluxstartdate2,
278     & hfluxstartdate, mythid )
279     call cal_FullDate( sfluxstartdate1, sfluxstartdate2,
280     & sfluxstartdate, mythid )
281     #ifdef ALLOW_KPP
282     call cal_FullDate( swfluxstartdate1, swfluxstartdate2,
283     & swfluxstartdate, mythid )
284     #endif
285    
286     #endif
287    
288     #ifdef ALLOW_ATM_WIND
289     call cal_FullDate( uwindstartdate1, uwindstartdate2,
290     & uwindstartdate, mythid )
291     call cal_FullDate( vwindstartdate1, vwindstartdate2,
292     & vwindstartdate, mythid )
293     #else
294     call cal_FullDate( ustressstartdate1, ustressstartdate2,
295     & ustressstartdate, mythid )
296     call cal_FullDate( vstressstartdate1, vstressstartdate2,
297     & vstressstartdate, mythid )
298     #endif
299    
300     #else
301     call cal_FullDate( hfluxstartdate1, hfluxstartdate2,
302     & hfluxstartdate, mythid )
303     call cal_FullDate( sfluxstartdate1, sfluxstartdate2,
304     & sfluxstartdate, mythid )
305     call cal_FullDate( ustressstartdate1, ustressstartdate2,
306     & ustressstartdate, mythid )
307     call cal_FullDate( vstressstartdate1, vstressstartdate2,
308     & vstressstartdate, mythid )
309     #ifdef ALLOW_KPP
310     call cal_FullDate( swfluxstartdate1, swfluxstartdate2,
311     & swfluxstartdate, mythid )
312     #endif
313    
314     #endif
315    
316     #ifdef ALLOW_OBCS
317 heimbach 1.1.6.1 #ifdef ALLOW_OBCS_NORTH
318     call cal_FullDate( obcsNstartdate1, obcsNstartdate2,
319     & obcsNstartdate, mythid )
320     #endif
321     #ifdef ALLOW_OBCS_SOUTH
322     call cal_FullDate( obcsSstartdate1, obcsSstartdate2,
323     & obcsSstartdate, mythid )
324     #endif
325     #ifdef ALLOW_OBCS_EAST
326     call cal_FullDate( obcsEstartdate1, obcsEstartdate2,
327     & obcsEstartdate, mythid )
328     #endif
329     #ifdef ALLOW_OBCS_WEST
330     call cal_FullDate( obcsWstartdate1, obcsWstartdate2,
331     & obcsWstartdate, mythid )
332     #endif
333 heimbach 1.1.6.3 #endif
334    
335     #ifdef ATMOSPHERIC_LOADING
336     call cal_FullDate( apressurestartdate1, apressurestartdate2,
337     & apressurestartdate, mythid )
338 heimbach 1.1 #endif
339    
340     _END_MASTER( mythid )
341    
342     _BARRIER
343    
344     c-- Summarize the External forcing's setup.
345     call exf_summary( mythid )
346    
347    
348     c-- set climatology parameters
349     call exf_clim_readparms( mythid )
350    
351     c-- summarize climatologic forcing configuration
352     call exf_clim_summary( mythid )
353    
354     end

  ViewVC Help
Powered by ViewVC 1.1.22