/[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.28 - (hide annotations) (download)
Tue Jan 15 19:56:27 2008 UTC (16 years, 4 months ago) by dfer
Branch: MAIN
Changes since 1.27: +7 -1 lines
Bit of tutorial_global_oce_optim

1 edhill 1.5 C
2 dfer 1.28 C $Header: /u/gcmpack/MITgcm/pkg/ctrl/ctrl_readparms.F,v 1.27 2007/06/21 04:06:21 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 heimbach 1.25 & xx_diffkr_file, xx_kapgm_file, xx_tr1_file,
119     & 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.23 & doAdmtlmBypassAD,
133 gforget 1.26 & delZexp, forcingPrecond
134 dfer 1.28 cHFLUXM_CONTROL
135     & ,xx_hfluxm_file
136     cHFLUXM_CONTROL
137 heimbach 1.2
138     namelist /ctrl_packnames/
139 heimbach 1.6 & yadmark, yctrlid, yctrlposunpack, yctrlpospack,
140 heimbach 1.2 & ctrlname, costname, scalname, maskname, metaname
141    
142     _BEGIN_MASTER( myThid )
143    
144     c-- Set default values.
145 heimbach 1.8 doInitXX = .TRUE.
146     #ifdef ALLOW_ADMTLM
147     doAdmTlm = .TRUE.
148     #else
149     doAdmTlm = .FALSE.
150     #endif
151 heimbach 1.10 doPackDiag = .FALSE.
152 heimbach 1.11 doZscaleUnpack = .FALSE.
153     doZscalePack = .FALSE.
154 heimbach 1.20 doMainUnpack = .TRUE.
155     doMainPack = .TRUE.
156 heimbach 1.21 doAdmtlmBypassAD = .FALSE.
157 heimbach 1.8
158 heimbach 1.23 delZexp = 0.
159 gforget 1.26 forcingPrecond = 1. _d 0
160 heimbach 1.23
161 heimbach 1.13 xx_theta_file = 'xx_theta'
162     xx_salt_file = 'xx_salt'
163 heimbach 1.22 c
164 heimbach 1.2 xx_hfluxstartdate1 = 0
165     xx_hfluxstartdate2 = 0
166     xx_hfluxperiod = 0. _d 0
167 heimbach 1.13 xx_hflux_file = 'xx_hfl'
168 heimbach 1.22 xx_hflux_remo_intercept = 0. _d 0
169     xx_hflux_remo_slope = 0. _d 0
170     c
171 heimbach 1.2 xx_sfluxstartdate1 = 0
172     xx_sfluxstartdate2 = 0
173     xx_sfluxperiod = 0. _d 0
174 heimbach 1.13 xx_sflux_file = 'xx_sfl'
175 heimbach 1.22 xx_sflux_remo_intercept = 0. _d 0
176     xx_sflux_remo_slope = 0. _d 0
177     c
178 heimbach 1.2 xx_tauustartdate1 = 0
179     xx_tauustartdate2 = 0
180     xx_tauuperiod = 0. _d 0
181 heimbach 1.13 xx_tauu_file = 'xx_tauu'
182 heimbach 1.22 xx_tauu_remo_intercept = 0. _d 0
183     xx_tauu_remo_slope = 0. _d 0
184     c
185 heimbach 1.2 xx_tauvstartdate1 = 0
186     xx_tauvstartdate2 = 0
187     xx_tauvperiod = 0. _d 0
188 heimbach 1.13 xx_tauv_file = 'xx_tauv'
189 heimbach 1.22 xx_tauv_remo_intercept = 0. _d 0
190     xx_tauv_remo_slope = 0. _d 0
191     c
192 heimbach 1.2 xx_atempstartdate1 = 0
193     xx_atempstartdate2 = 0
194     xx_atempperiod = 0. _d 0
195 heimbach 1.13 xx_atemp_file = 'xx_atemp'
196 heimbach 1.22 xx_atemp_remo_intercept = 0. _d 0
197     xx_atemp_remo_slope = 0. _d 0
198     c
199 heimbach 1.2 xx_aqhstartdate1 = 0
200     xx_aqhstartdate2 = 0
201     xx_aqhperiod = 0. _d 0
202 heimbach 1.13 xx_aqh_file = 'xx_aqh'
203 heimbach 1.22 xx_aqh_remo_intercept = 0. _d 0
204     xx_aqh_remo_slope = 0. _d 0
205     c
206 heimbach 1.16 xx_precipstartdate1 = 0
207     xx_precipstartdate2 = 0
208     xx_precipperiod = 0. _d 0
209     xx_precip_file = 'xx_precip'
210 heimbach 1.22 xx_precip_remo_intercept = 0. _d 0
211     xx_precip_remo_slope = 0. _d 0
212     c
213 heimbach 1.17 xx_swfluxstartdate1 = 0
214     xx_swfluxstartdate2 = 0
215     xx_swfluxperiod = 0. _d 0
216     xx_swflux_file = 'xx_swflux'
217 heimbach 1.22 xx_swflux_remo_intercept = 0. _d 0
218     xx_swflux_remo_slope = 0. _d 0
219     c
220 heimbach 1.18 xx_swdownstartdate1 = 0
221     xx_swdownstartdate2 = 0
222     xx_swdownperiod = 0. _d 0
223     xx_swdown_file = 'xx_swdown'
224 heimbach 1.22 xx_swdown_remo_intercept = 0. _d 0
225     xx_swdown_remo_slope = 0. _d 0
226     c
227 heimbach 1.25 xx_lwfluxstartdate1 = 0
228     xx_lwfluxstartdate2 = 0
229     xx_lwfluxperiod = 0. _d 0
230     xx_lwflux_file = 'xx_lwflux'
231     xx_lwflux_remo_intercept = 0. _d 0
232     xx_lwflux_remo_slope = 0. _d 0
233     c
234     xx_lwdownstartdate1 = 0
235     xx_lwdownstartdate2 = 0
236     xx_lwdownperiod = 0. _d 0
237     xx_lwdown_file = 'xx_lwdown'
238     xx_lwdown_remo_intercept = 0. _d 0
239     xx_lwdown_remo_slope = 0. _d 0
240     c
241     xx_evapstartdate1 = 0
242     xx_evapstartdate2 = 0
243     xx_evapperiod = 0. _d 0
244     xx_evap_file = 'xx_evap'
245     xx_evap_remo_intercept = 0. _d 0
246     xx_evap_remo_slope = 0. _d 0
247     c
248     xx_snowprecipstartdate1 = 0
249     xx_snowprecipstartdate2 = 0
250     xx_snowprecipperiod = 0. _d 0
251     xx_snowprecip_file = 'xx_snowprecip'
252     xx_snowprecip_remo_intercept = 0. _d 0
253     xx_snowprecip_remo_slope = 0. _d 0
254     c
255     xx_apressurestartdate1 = 0
256     xx_apressurestartdate2 = 0
257     xx_apressureperiod = 0. _d 0
258     xx_apressure_file = 'xx_apressure'
259     xx_apressure_remo_intercept = 0. _d 0
260     xx_apressure_remo_slope = 0. _d 0
261     c
262     xx_runoffstartdate1 = 0
263     xx_runoffstartdate2 = 0
264     xx_runoffperiod = 0. _d 0
265     xx_runoff_file = 'xx_runoff'
266     xx_runoff_remo_intercept = 0. _d 0
267     xx_runoff_remo_slope = 0. _d 0
268     c
269 heimbach 1.2 xx_uwindstartdate1 = 0
270     xx_uwindstartdate2 = 0
271     xx_uwindperiod = 0. _d 0
272 heimbach 1.13 xx_uwind_file = 'xx_uwind'
273 heimbach 1.22 xx_uwind_remo_intercept = 0. _d 0
274     xx_uwind_remo_slope = 0. _d 0
275     c
276 heimbach 1.2 xx_vwindstartdate1 = 0
277     xx_vwindstartdate2 = 0
278     xx_vwindperiod = 0. _d 0
279 heimbach 1.13 xx_vwind_file = 'xx_vwind'
280 heimbach 1.22 xx_vwind_remo_intercept = 0. _d 0
281     xx_vwind_remo_slope = 0. _d 0
282     c
283 heimbach 1.2 xx_obcsnstartdate1 = 0
284     xx_obcsnstartdate2 = 0
285     xx_obcsnperiod = 0. _d 0
286 heimbach 1.13 xx_obcsn_file = 'xx_obcsn'
287 heimbach 1.22 c
288 heimbach 1.2 xx_obcssstartdate1 = 0
289     xx_obcssstartdate2 = 0
290     xx_obcssperiod = 0. _d 0
291 heimbach 1.13 xx_obcss_file = 'xx_obcss'
292 heimbach 1.22 c
293 heimbach 1.2 xx_obcswstartdate1 = 0
294     xx_obcswstartdate2 = 0
295     xx_obcswperiod = 0. _d 0
296 heimbach 1.13 xx_obcsw_file = 'xx_obcsw'
297 heimbach 1.22 c
298 heimbach 1.2 xx_obcsestartdate1 = 0
299     xx_obcsestartdate2 = 0
300     xx_obcseperiod = 0. _d 0
301 heimbach 1.13 xx_obcse_file = 'xx_obcse'
302 heimbach 1.22 c
303 heimbach 1.19 xx_sststartdate1 = 0
304     xx_sststartdate2 = 0
305     xx_sstperiod = 0. _d 0
306 heimbach 1.13 xx_sst_file = 'xx_sst'
307 heimbach 1.22 c
308 heimbach 1.19 xx_sssstartdate1 = 0
309     xx_sssstartdate2 = 0
310     xx_sssperiod = 0. _d 0
311 heimbach 1.13 xx_sss_file = 'xx_sss'
312 heimbach 1.22 c
313     xx_diffkr_file = 'xx_diffkr'
314     xx_kapgm_file = 'xx_kapgm'
315     xx_tr1_file = 'xx_ptr'
316 heimbach 1.24 xx_depth_file = 'xx_depth'
317 heimbach 1.13 xx_efluxy_file = 'xx_efluxy'
318     xx_efluxp_file = 'xx_efluxp'
319     xx_bottomdrag_file = 'xx_bottomdrag'
320     xx_edtaux_file = 'xx_edtaux'
321     xx_edtauy_file = 'xx_edtauy'
322 heimbach 1.14 xx_uvel_file = 'xx_uvel'
323     xx_vvel_file = 'xx_vvel'
324     xx_etan_file = 'xx_etan'
325 heimbach 1.27 xx_siarea_file = 'xx_siarea'
326     xx_siheff_file = 'xx_siheff'
327     xx_sihsnow_file = 'xx_sihsnow'
328 dfer 1.28 cHFLUXM_CONTROL
329     xx_hfluxm_file = 'xx_hfluxm'
330     cHFLUXM_CONTROL
331 heimbach 1.2
332 heimbach 1.4 #ifdef ALLOW_TANGENTLINEAR_RUN
333     yadprefix = 'g_'
334     yadmark = 'g_'
335     #else
336     yadprefix = 'ad'
337 heimbach 1.2 yadmark = 'ad'
338     #endif
339     yctrlid = 'MIT_CE_000'
340 heimbach 1.6 yctrlposunpack = '.opt'
341     yctrlpospack = '.opt'
342 heimbach 1.2 ctrlname = ' '
343     costname = ' '
344     scalname = ' '
345     maskname = ' '
346     metaname = ' '
347    
348 heimbach 1.15 c-- Next, read the cost data file.
349     WRITE(msgBuf,'(A)') 'CTRL_READPARMS: opening data.ctrl'
350     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
351     & SQUEEZE_RIGHT , 1)
352    
353     CALL OPEN_COPY_DATA_FILE(
354     I 'data.ctrl', 'CTRL_READPARMS',
355     O iUnit,
356     I myThid )
357    
358     READ(unit = iUnit, nml = ctrl_nml)
359     READ(unit = iUnit, nml = ctrl_packnames)
360    
361     WRITE(msgBuf,'(A)')
362     & 'CTRL_READPARMS: finished reading data.ctrl'
363     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
364     & SQUEEZE_RIGHT , 1)
365 heimbach 1.2
366 heimbach 1.15 CLOSE( iUnit )
367 heimbach 1.2
368     _END_MASTER( myThid )
369    
370     _BARRIER
371    
372     return
373     end
374    

  ViewVC Help
Powered by ViewVC 1.1.22