/[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.32 - (hide annotations) (download)
Wed Oct 14 20:09:40 2009 UTC (14 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.31: +5 -2 lines
Complete implementation for xx_gen2d, xx_gen3d

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

  ViewVC Help
Powered by ViewVC 1.1.22