/[MITgcm]/MITgcm/pkg/ctrl/ctrl_readparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/ctrl/ctrl_readparms.F

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


Revision 1.31 - (hide annotations) (download)
Fri Feb 13 15:02:00 2009 UTC (15 years, 3 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q
Changes since 1.30: +3 -1 lines
Add flag to reduce all tapelev I/O to single-prec.
In data.ctrl set
 doSinglePrecTapelev = .TRUE.

1 edhill 1.5 C
2 heimbach 1.31 C $Header: /u/gcmpack/MITgcm/pkg/ctrl/ctrl_readparms.F,v 1.30 2008/06/26 18:11:53 heimbach Exp $
3 heimbach 1.10 C $Name: $
4 heimbach 1.2
5 edhill 1.5 #include "AD_CONFIG.h"
6 heimbach 1.2 #include "CTRL_CPPOPTIONS.h"
7    
8    
9     subroutine ctrl_readparms( mythid )
10    
11     c ==================================================================
12     c SUBROUTINE ctrl_readparms
13     c ==================================================================
14     c
15     c o read ctrl parameters
16     c split from ctrl_init
17     c
18     c started: heimbach@mit.edu 12-Jun-2003
19     c
20     c ==================================================================
21     c SUBROUTINE ctrl_readparms
22     c ==================================================================
23    
24     implicit none
25    
26     c == global variables ==
27    
28     #include "EEPARAMS.h"
29     #include "SIZE.h"
30     #include "PARAMS.h"
31     #include "GRID.h"
32     #include "ctrl.h"
33    
34     #ifdef ALLOW_OBCS_CONTROL
35     # include "OBCS.h"
36     #endif
37    
38     c == routine arguments ==
39    
40     integer mythid
41    
42     c == local variables ==
43    
44     integer bi,bj
45     integer i,j,k
46     integer ntmp
47     integer ivarindex
48 heimbach 1.15 integer iUnit
49 heimbach 1.2 integer iobcs
50     integer il
51     integer errio
52     integer startrec
53     integer endrec
54     integer difftime(4)
55     _RL diffsecs
56     _RL dummy
57    
58     character*(80) ymaskobcs
59     character*(max_len_prec) record
60     character*(max_len_mbuf) msgbuf
61    
62     integer nwetc3d
63    
64     c == external ==
65    
66     integer ilnblnk
67     external ilnblnk
68    
69     c == end of interface ==
70    
71     c-- Read the namelist input.
72     namelist /ctrl_nml/
73 heimbach 1.25 & xx_theta_file, xx_salt_file,
74     & xx_hflux_file, xx_hflux_remo_intercept, xx_hflux_remo_slope,
75 heimbach 1.2 & xx_hfluxstartdate1, xx_hfluxstartdate2, xx_hfluxperiod,
76 heimbach 1.25 & xx_sflux_file, xx_sflux_remo_intercept, xx_sflux_remo_slope,
77 heimbach 1.2 & xx_sfluxstartdate1, xx_sfluxstartdate2, xx_sfluxperiod,
78 heimbach 1.25 & xx_tauu_file, xx_tauu_remo_intercept, xx_tauu_remo_slope,
79 heimbach 1.2 & xx_tauustartdate1, xx_tauustartdate2, xx_tauuperiod,
80 heimbach 1.25 & xx_tauv_file, xx_tauv_remo_intercept, xx_tauv_remo_slope,
81 heimbach 1.2 & xx_tauvstartdate1, xx_tauvstartdate2, xx_tauvperiod,
82 heimbach 1.25 & xx_atemp_file, xx_atemp_remo_intercept, xx_atemp_remo_slope,
83 heimbach 1.2 & xx_atempstartdate1, xx_atempstartdate2, xx_atempperiod,
84 heimbach 1.25 & xx_aqh_file, xx_aqh_remo_intercept, xx_aqh_remo_slope,
85 heimbach 1.2 & xx_aqhstartdate1, xx_aqhstartdate2, xx_aqhperiod,
86 heimbach 1.25 & xx_precip_file, xx_precip_remo_intercept, xx_precip_remo_slope,
87 heimbach 1.16 & xx_precipstartdate1, xx_precipstartdate2, xx_precipperiod,
88 heimbach 1.25 & xx_swflux_file, xx_swflux_remo_intercept, xx_swflux_remo_slope,
89 heimbach 1.17 & xx_swfluxstartdate1, xx_swfluxstartdate2, xx_swfluxperiod,
90 heimbach 1.25 & xx_swdown_file, xx_swdown_remo_intercept, xx_swdown_remo_slope,
91 heimbach 1.18 & xx_swdownstartdate1, xx_swdownstartdate2, xx_swdownperiod,
92 heimbach 1.25 & xx_lwflux_file, xx_lwflux_remo_intercept, xx_lwflux_remo_slope,
93     & xx_lwfluxstartdate1, xx_lwfluxstartdate2, xx_lwfluxperiod,
94     & xx_lwdown_file, xx_lwdown_remo_intercept, xx_lwdown_remo_slope,
95     & xx_lwdownstartdate1, xx_lwdownstartdate2, xx_lwdownperiod,
96     & xx_evap_file, xx_evap_remo_intercept, xx_evap_remo_slope,
97     & xx_evapstartdate1, xx_evapstartdate2, xx_evapperiod,
98     & xx_snowprecip_file, xx_snowprecip_remo_intercept,
99     & xx_snowprecip_remo_slope, xx_snowprecipperiod,
100     & xx_snowprecipstartdate1, xx_snowprecipstartdate2,
101     & xx_apressure_file, xx_apressure_remo_intercept,
102     & xx_apressure_remo_slope, xx_apressureperiod,
103     & xx_apressurestartdate1, xx_apressurestartdate2,
104     & xx_runoff_file, xx_runoff_remo_intercept, xx_runoff_remo_slope,
105     & xx_runoffstartdate1, xx_runoffstartdate2, xx_runoffperiod,
106     & xx_uwind_file, xx_uwind_remo_intercept, xx_uwind_remo_slope,
107 heimbach 1.2 & xx_uwindstartdate1, xx_uwindstartdate2, xx_uwindperiod,
108 heimbach 1.25 & xx_vwind_file, xx_vwind_remo_intercept, xx_vwind_remo_slope,
109 heimbach 1.2 & xx_vwindstartdate1, xx_vwindstartdate2, xx_vwindperiod,
110     & xx_obcsn_file,
111     & xx_obcsnstartdate1, xx_obcsnstartdate2, xx_obcsnperiod,
112     & xx_obcss_file,
113     & xx_obcssstartdate1, xx_obcssstartdate2, xx_obcssperiod,
114     & xx_obcsw_file,
115     & xx_obcswstartdate1, xx_obcswstartdate2, xx_obcswperiod,
116     & xx_obcse_file,
117     & xx_obcsestartdate1, xx_obcsestartdate2, xx_obcseperiod,
118 gforget 1.29 & xx_diffkr_file, xx_kapgm_file, xx_kapredi_file, xx_tr1_file,
119 heimbach 1.25 & xx_sst_file, xx_sss_file,
120 heimbach 1.19 & xx_sststartdate1, xx_sststartdate2, xx_sstperiod,
121     & xx_sssstartdate1, xx_sssstartdate2, xx_sssperiod,
122 heimbach 1.24 & xx_depth_file,
123 heimbach 1.25 & xx_efluxy_file, xx_efluxp_file,
124 heimbach 1.7 & xx_bottomdrag_file,
125 heimbach 1.25 & xx_edtaux_file, xx_edtauy_file,
126     & xx_uvel_file, xx_vvel_file, xx_etan_file,
127 heimbach 1.27 & xx_siarea_file, xx_siheff_file, xx_sihsnow_file,
128 heimbach 1.10 & doInitXX,
129 heimbach 1.11 & doPackDiag,
130 heimbach 1.25 & doZscaleUnpack, doZscalePack,
131     & doMainUnpack, doMainPack,
132 heimbach 1.31 & doSinglePrecTapelev,
133 heimbach 1.23 & doAdmtlmBypassAD,
134 gforget 1.26 & delZexp, forcingPrecond
135 dfer 1.28 cHFLUXM_CONTROL
136     & ,xx_hfluxm_file
137     cHFLUXM_CONTROL
138 heimbach 1.2
139     namelist /ctrl_packnames/
140 heimbach 1.6 & yadmark, yctrlid, yctrlposunpack, yctrlpospack,
141 heimbach 1.2 & ctrlname, costname, scalname, maskname, metaname
142    
143     _BEGIN_MASTER( myThid )
144    
145     c-- Set default values.
146 heimbach 1.8 doInitXX = .TRUE.
147     #ifdef ALLOW_ADMTLM
148     doAdmTlm = .TRUE.
149     #else
150     doAdmTlm = .FALSE.
151     #endif
152 heimbach 1.10 doPackDiag = .FALSE.
153 heimbach 1.11 doZscaleUnpack = .FALSE.
154     doZscalePack = .FALSE.
155 heimbach 1.20 doMainUnpack = .TRUE.
156     doMainPack = .TRUE.
157 heimbach 1.31 doSinglePrecTapelev = .FALSE.
158 heimbach 1.21 doAdmtlmBypassAD = .FALSE.
159 heimbach 1.8
160 heimbach 1.23 delZexp = 0.
161 gforget 1.26 forcingPrecond = 1. _d 0
162 heimbach 1.23
163 heimbach 1.13 xx_theta_file = 'xx_theta'
164     xx_salt_file = 'xx_salt'
165 heimbach 1.22 c
166 heimbach 1.2 xx_hfluxstartdate1 = 0
167     xx_hfluxstartdate2 = 0
168     xx_hfluxperiod = 0. _d 0
169 heimbach 1.13 xx_hflux_file = 'xx_hfl'
170 heimbach 1.22 xx_hflux_remo_intercept = 0. _d 0
171     xx_hflux_remo_slope = 0. _d 0
172     c
173 heimbach 1.2 xx_sfluxstartdate1 = 0
174     xx_sfluxstartdate2 = 0
175     xx_sfluxperiod = 0. _d 0
176 heimbach 1.13 xx_sflux_file = 'xx_sfl'
177 heimbach 1.22 xx_sflux_remo_intercept = 0. _d 0
178     xx_sflux_remo_slope = 0. _d 0
179     c
180 heimbach 1.2 xx_tauustartdate1 = 0
181     xx_tauustartdate2 = 0
182     xx_tauuperiod = 0. _d 0
183 heimbach 1.13 xx_tauu_file = 'xx_tauu'
184 heimbach 1.22 xx_tauu_remo_intercept = 0. _d 0
185     xx_tauu_remo_slope = 0. _d 0
186     c
187 heimbach 1.2 xx_tauvstartdate1 = 0
188     xx_tauvstartdate2 = 0
189     xx_tauvperiod = 0. _d 0
190 heimbach 1.13 xx_tauv_file = 'xx_tauv'
191 heimbach 1.22 xx_tauv_remo_intercept = 0. _d 0
192     xx_tauv_remo_slope = 0. _d 0
193     c
194 heimbach 1.2 xx_atempstartdate1 = 0
195     xx_atempstartdate2 = 0
196     xx_atempperiod = 0. _d 0
197 heimbach 1.13 xx_atemp_file = 'xx_atemp'
198 heimbach 1.22 xx_atemp_remo_intercept = 0. _d 0
199     xx_atemp_remo_slope = 0. _d 0
200     c
201 heimbach 1.2 xx_aqhstartdate1 = 0
202     xx_aqhstartdate2 = 0
203     xx_aqhperiod = 0. _d 0
204 heimbach 1.13 xx_aqh_file = 'xx_aqh'
205 heimbach 1.22 xx_aqh_remo_intercept = 0. _d 0
206     xx_aqh_remo_slope = 0. _d 0
207     c
208 heimbach 1.16 xx_precipstartdate1 = 0
209     xx_precipstartdate2 = 0
210     xx_precipperiod = 0. _d 0
211     xx_precip_file = 'xx_precip'
212 heimbach 1.22 xx_precip_remo_intercept = 0. _d 0
213     xx_precip_remo_slope = 0. _d 0
214     c
215 heimbach 1.17 xx_swfluxstartdate1 = 0
216     xx_swfluxstartdate2 = 0
217     xx_swfluxperiod = 0. _d 0
218     xx_swflux_file = 'xx_swflux'
219 heimbach 1.22 xx_swflux_remo_intercept = 0. _d 0
220     xx_swflux_remo_slope = 0. _d 0
221     c
222 heimbach 1.18 xx_swdownstartdate1 = 0
223     xx_swdownstartdate2 = 0
224     xx_swdownperiod = 0. _d 0
225     xx_swdown_file = 'xx_swdown'
226 heimbach 1.22 xx_swdown_remo_intercept = 0. _d 0
227     xx_swdown_remo_slope = 0. _d 0
228     c
229 heimbach 1.25 xx_lwfluxstartdate1 = 0
230     xx_lwfluxstartdate2 = 0
231     xx_lwfluxperiod = 0. _d 0
232     xx_lwflux_file = 'xx_lwflux'
233     xx_lwflux_remo_intercept = 0. _d 0
234     xx_lwflux_remo_slope = 0. _d 0
235     c
236     xx_lwdownstartdate1 = 0
237     xx_lwdownstartdate2 = 0
238     xx_lwdownperiod = 0. _d 0
239     xx_lwdown_file = 'xx_lwdown'
240     xx_lwdown_remo_intercept = 0. _d 0
241     xx_lwdown_remo_slope = 0. _d 0
242     c
243     xx_evapstartdate1 = 0
244     xx_evapstartdate2 = 0
245     xx_evapperiod = 0. _d 0
246     xx_evap_file = 'xx_evap'
247     xx_evap_remo_intercept = 0. _d 0
248     xx_evap_remo_slope = 0. _d 0
249     c
250     xx_snowprecipstartdate1 = 0
251     xx_snowprecipstartdate2 = 0
252     xx_snowprecipperiod = 0. _d 0
253     xx_snowprecip_file = 'xx_snowprecip'
254     xx_snowprecip_remo_intercept = 0. _d 0
255     xx_snowprecip_remo_slope = 0. _d 0
256     c
257     xx_apressurestartdate1 = 0
258     xx_apressurestartdate2 = 0
259     xx_apressureperiod = 0. _d 0
260     xx_apressure_file = 'xx_apressure'
261     xx_apressure_remo_intercept = 0. _d 0
262     xx_apressure_remo_slope = 0. _d 0
263     c
264     xx_runoffstartdate1 = 0
265     xx_runoffstartdate2 = 0
266     xx_runoffperiod = 0. _d 0
267     xx_runoff_file = 'xx_runoff'
268     xx_runoff_remo_intercept = 0. _d 0
269     xx_runoff_remo_slope = 0. _d 0
270     c
271 heimbach 1.2 xx_uwindstartdate1 = 0
272     xx_uwindstartdate2 = 0
273     xx_uwindperiod = 0. _d 0
274 heimbach 1.13 xx_uwind_file = 'xx_uwind'
275 heimbach 1.22 xx_uwind_remo_intercept = 0. _d 0
276     xx_uwind_remo_slope = 0. _d 0
277     c
278 heimbach 1.2 xx_vwindstartdate1 = 0
279     xx_vwindstartdate2 = 0
280     xx_vwindperiod = 0. _d 0
281 heimbach 1.13 xx_vwind_file = 'xx_vwind'
282 heimbach 1.22 xx_vwind_remo_intercept = 0. _d 0
283     xx_vwind_remo_slope = 0. _d 0
284     c
285 heimbach 1.2 xx_obcsnstartdate1 = 0
286     xx_obcsnstartdate2 = 0
287     xx_obcsnperiod = 0. _d 0
288 heimbach 1.13 xx_obcsn_file = 'xx_obcsn'
289 heimbach 1.22 c
290 heimbach 1.2 xx_obcssstartdate1 = 0
291     xx_obcssstartdate2 = 0
292     xx_obcssperiod = 0. _d 0
293 heimbach 1.13 xx_obcss_file = 'xx_obcss'
294 heimbach 1.22 c
295 heimbach 1.2 xx_obcswstartdate1 = 0
296     xx_obcswstartdate2 = 0
297     xx_obcswperiod = 0. _d 0
298 heimbach 1.13 xx_obcsw_file = 'xx_obcsw'
299 heimbach 1.22 c
300 heimbach 1.2 xx_obcsestartdate1 = 0
301     xx_obcsestartdate2 = 0
302     xx_obcseperiod = 0. _d 0
303 heimbach 1.13 xx_obcse_file = 'xx_obcse'
304 heimbach 1.22 c
305 heimbach 1.19 xx_sststartdate1 = 0
306     xx_sststartdate2 = 0
307     xx_sstperiod = 0. _d 0
308 heimbach 1.13 xx_sst_file = 'xx_sst'
309 heimbach 1.22 c
310 heimbach 1.19 xx_sssstartdate1 = 0
311     xx_sssstartdate2 = 0
312     xx_sssperiod = 0. _d 0
313 heimbach 1.13 xx_sss_file = 'xx_sss'
314 heimbach 1.22 c
315     xx_diffkr_file = 'xx_diffkr'
316     xx_kapgm_file = 'xx_kapgm'
317 gforget 1.29 xx_kapredi_file = 'xx_kapredi'
318 heimbach 1.22 xx_tr1_file = 'xx_ptr'
319 heimbach 1.24 xx_depth_file = 'xx_depth'
320 heimbach 1.13 xx_efluxy_file = 'xx_efluxy'
321     xx_efluxp_file = 'xx_efluxp'
322     xx_bottomdrag_file = 'xx_bottomdrag'
323     xx_edtaux_file = 'xx_edtaux'
324     xx_edtauy_file = 'xx_edtauy'
325 heimbach 1.14 xx_uvel_file = 'xx_uvel'
326     xx_vvel_file = 'xx_vvel'
327     xx_etan_file = 'xx_etan'
328 heimbach 1.27 xx_siarea_file = 'xx_siarea'
329     xx_siheff_file = 'xx_siheff'
330     xx_sihsnow_file = 'xx_sihsnow'
331 dfer 1.28 cHFLUXM_CONTROL
332     xx_hfluxm_file = 'xx_hfluxm'
333     cHFLUXM_CONTROL
334 heimbach 1.2
335 heimbach 1.4 #ifdef ALLOW_TANGENTLINEAR_RUN
336     yadprefix = 'g_'
337     yadmark = 'g_'
338     #else
339     yadprefix = 'ad'
340 heimbach 1.2 yadmark = 'ad'
341     #endif
342     yctrlid = 'MIT_CE_000'
343 heimbach 1.6 yctrlposunpack = '.opt'
344     yctrlpospack = '.opt'
345 heimbach 1.30 ctrlname = 'ecco_ctrl'
346     costname = 'ecco_cost'
347 heimbach 1.2 scalname = ' '
348     maskname = ' '
349     metaname = ' '
350    
351 heimbach 1.15 c-- Next, read the cost data file.
352     WRITE(msgBuf,'(A)') 'CTRL_READPARMS: opening data.ctrl'
353     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
354     & SQUEEZE_RIGHT , 1)
355    
356     CALL OPEN_COPY_DATA_FILE(
357     I 'data.ctrl', 'CTRL_READPARMS',
358     O iUnit,
359     I myThid )
360    
361     READ(unit = iUnit, nml = ctrl_nml)
362     READ(unit = iUnit, nml = ctrl_packnames)
363    
364     WRITE(msgBuf,'(A)')
365     & 'CTRL_READPARMS: finished reading data.ctrl'
366     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
367     & SQUEEZE_RIGHT , 1)
368 heimbach 1.2
369 heimbach 1.15 CLOSE( iUnit )
370 heimbach 1.2
371     _END_MASTER( myThid )
372    
373     _BARRIER
374    
375     return
376     end
377    

  ViewVC Help
Powered by ViewVC 1.1.22