/[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.24 - (hide annotations) (download)
Wed Jun 7 01:55:14 2006 UTC (18 years ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58n_post, checkpoint58h_post, checkpoint58q_post, checkpoint58j_post, checkpoint58i_post, checkpoint58o_post, checkpoint58k_post, checkpoint58p_post, checkpoint58m_post
Changes since 1.23: +3 -3 lines
Modifications for bottom topography control
o replace hFacC by _hFacC at various places
o replace ALLOW_HFACC_CONTROL by ALLOW_DEPTH_CONTROL
o add non-self-adjoint cg2d_nsa
o update autodiff support routines
o re-initialise hfac after ctrl_depth_ini
o works for 5x5 box, doesnt work for global_ocean.90x40x15

1 edhill 1.5 C
2 heimbach 1.24 C $Header: /u/gcmpack/MITgcm/pkg/ctrl/ctrl_readparms.F,v 1.23 2006/05/27 17:07: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     & xx_theta_file,
74     & xx_salt_file,
75     & xx_hflux_file,
76     & xx_hfluxstartdate1, xx_hfluxstartdate2, xx_hfluxperiod,
77 heimbach 1.22 & xx_hflux_remo_intercept, xx_hflux_remo_slope,
78 heimbach 1.2 & xx_sflux_file,
79     & xx_sfluxstartdate1, xx_sfluxstartdate2, xx_sfluxperiod,
80 heimbach 1.22 & xx_sflux_remo_intercept, xx_sflux_remo_slope,
81 heimbach 1.2 & xx_tauu_file,
82     & xx_tauustartdate1, xx_tauustartdate2, xx_tauuperiod,
83 heimbach 1.22 & xx_tauu_remo_intercept, xx_tauu_remo_slope,
84 heimbach 1.2 & xx_tauv_file,
85     & xx_tauvstartdate1, xx_tauvstartdate2, xx_tauvperiod,
86 heimbach 1.22 & xx_tauv_remo_intercept, xx_tauv_remo_slope,
87 heimbach 1.2 & xx_atemp_file,
88     & xx_atempstartdate1, xx_atempstartdate2, xx_atempperiod,
89 heimbach 1.22 & xx_atemp_remo_intercept, xx_atemp_remo_slope,
90 heimbach 1.2 & xx_aqh_file,
91     & xx_aqhstartdate1, xx_aqhstartdate2, xx_aqhperiod,
92 heimbach 1.22 & xx_aqh_remo_intercept, xx_aqh_remo_slope,
93 heimbach 1.16 & xx_precip_file,
94     & xx_precipstartdate1, xx_precipstartdate2, xx_precipperiod,
95 heimbach 1.22 & xx_precip_remo_intercept, xx_precip_remo_slope,
96 heimbach 1.17 & xx_swflux_file,
97     & xx_swfluxstartdate1, xx_swfluxstartdate2, xx_swfluxperiod,
98 heimbach 1.22 & xx_swflux_remo_intercept, xx_swflux_remo_slope,
99 heimbach 1.18 & xx_swdown_file,
100     & xx_swdownstartdate1, xx_swdownstartdate2, xx_swdownperiod,
101 heimbach 1.22 & xx_swdown_remo_intercept, xx_swdown_remo_slope,
102 heimbach 1.2 & xx_uwind_file,
103     & xx_uwindstartdate1, xx_uwindstartdate2, xx_uwindperiod,
104 heimbach 1.22 & xx_uwind_remo_intercept, xx_uwind_remo_slope,
105 heimbach 1.2 & xx_vwind_file,
106     & xx_vwindstartdate1, xx_vwindstartdate2, xx_vwindperiod,
107 heimbach 1.22 & xx_vwind_remo_intercept, xx_vwind_remo_slope,
108 heimbach 1.2 & xx_obcsn_file,
109     & xx_obcsnstartdate1, xx_obcsnstartdate2, xx_obcsnperiod,
110     & xx_obcss_file,
111     & xx_obcssstartdate1, xx_obcssstartdate2, xx_obcssperiod,
112     & xx_obcsw_file,
113     & xx_obcswstartdate1, xx_obcswstartdate2, xx_obcswperiod,
114     & xx_obcse_file,
115     & xx_obcsestartdate1, xx_obcsestartdate2, xx_obcseperiod,
116     & xx_diffkr_file,
117     & xx_kapgm_file,
118     & xx_tr1_file,
119     & xx_sst_file,
120 heimbach 1.19 & xx_sststartdate1, xx_sststartdate2, xx_sstperiod,
121 heimbach 1.2 & xx_sss_file,
122 heimbach 1.19 & xx_sssstartdate1, xx_sssstartdate2, xx_sssperiod,
123 heimbach 1.24 & xx_depth_file,
124 heimbach 1.2 & xx_efluxy_file,
125     & xx_efluxp_file,
126 heimbach 1.7 & xx_bottomdrag_file,
127 heimbach 1.12 & xx_edtaux_file,
128     & xx_edtauy_file,
129 heimbach 1.14 & xx_uvel_file,
130     & xx_vvel_file,
131     & xx_etan_file,
132 heimbach 1.10 & doInitXX,
133 heimbach 1.11 & doPackDiag,
134     & doZscaleUnpack,
135 heimbach 1.20 & doZscalePack,
136     & doMainUnpack,
137     & doMainPack,
138 heimbach 1.23 & doAdmtlmBypassAD,
139     & delZexp
140 heimbach 1.2
141     namelist /ctrl_packnames/
142 heimbach 1.6 & yadmark, yctrlid, yctrlposunpack, yctrlpospack,
143 heimbach 1.2 & ctrlname, costname, scalname, maskname, metaname
144    
145     _BEGIN_MASTER( myThid )
146    
147     c-- Set default values.
148 heimbach 1.8 doInitXX = .TRUE.
149     #ifdef ALLOW_ADMTLM
150     doAdmTlm = .TRUE.
151     #else
152     doAdmTlm = .FALSE.
153     #endif
154 heimbach 1.10 doPackDiag = .FALSE.
155 heimbach 1.11 doZscaleUnpack = .FALSE.
156     doZscalePack = .FALSE.
157 heimbach 1.20 doMainUnpack = .TRUE.
158     doMainPack = .TRUE.
159 heimbach 1.21 doAdmtlmBypassAD = .FALSE.
160 heimbach 1.8
161 heimbach 1.23 delZexp = 0.
162    
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.2 xx_uwindstartdate1 = 0
230     xx_uwindstartdate2 = 0
231     xx_uwindperiod = 0. _d 0
232 heimbach 1.13 xx_uwind_file = 'xx_uwind'
233 heimbach 1.22 xx_uwind_remo_intercept = 0. _d 0
234     xx_uwind_remo_slope = 0. _d 0
235     c
236 heimbach 1.2 xx_vwindstartdate1 = 0
237     xx_vwindstartdate2 = 0
238     xx_vwindperiod = 0. _d 0
239 heimbach 1.13 xx_vwind_file = 'xx_vwind'
240 heimbach 1.22 xx_vwind_remo_intercept = 0. _d 0
241     xx_vwind_remo_slope = 0. _d 0
242     c
243 heimbach 1.2 xx_obcsnstartdate1 = 0
244     xx_obcsnstartdate2 = 0
245     xx_obcsnperiod = 0. _d 0
246 heimbach 1.13 xx_obcsn_file = 'xx_obcsn'
247 heimbach 1.22 c
248 heimbach 1.2 xx_obcssstartdate1 = 0
249     xx_obcssstartdate2 = 0
250     xx_obcssperiod = 0. _d 0
251 heimbach 1.13 xx_obcss_file = 'xx_obcss'
252 heimbach 1.22 c
253 heimbach 1.2 xx_obcswstartdate1 = 0
254     xx_obcswstartdate2 = 0
255     xx_obcswperiod = 0. _d 0
256 heimbach 1.13 xx_obcsw_file = 'xx_obcsw'
257 heimbach 1.22 c
258 heimbach 1.2 xx_obcsestartdate1 = 0
259     xx_obcsestartdate2 = 0
260     xx_obcseperiod = 0. _d 0
261 heimbach 1.13 xx_obcse_file = 'xx_obcse'
262 heimbach 1.22 c
263 heimbach 1.19 xx_sststartdate1 = 0
264     xx_sststartdate2 = 0
265     xx_sstperiod = 0. _d 0
266 heimbach 1.13 xx_sst_file = 'xx_sst'
267 heimbach 1.22 c
268 heimbach 1.19 xx_sssstartdate1 = 0
269     xx_sssstartdate2 = 0
270     xx_sssperiod = 0. _d 0
271 heimbach 1.13 xx_sss_file = 'xx_sss'
272 heimbach 1.22 c
273     xx_diffkr_file = 'xx_diffkr'
274     xx_kapgm_file = 'xx_kapgm'
275     xx_tr1_file = 'xx_ptr'
276 heimbach 1.24 xx_depth_file = 'xx_depth'
277 heimbach 1.13 xx_efluxy_file = 'xx_efluxy'
278     xx_efluxp_file = 'xx_efluxp'
279     xx_bottomdrag_file = 'xx_bottomdrag'
280     xx_edtaux_file = 'xx_edtaux'
281     xx_edtauy_file = 'xx_edtauy'
282 heimbach 1.14 xx_uvel_file = 'xx_uvel'
283     xx_vvel_file = 'xx_vvel'
284     xx_etan_file = 'xx_etan'
285 heimbach 1.2
286 heimbach 1.4 #ifdef ALLOW_TANGENTLINEAR_RUN
287     yadprefix = 'g_'
288     yadmark = 'g_'
289     #else
290     yadprefix = 'ad'
291 heimbach 1.2 yadmark = 'ad'
292     #endif
293     yctrlid = 'MIT_CE_000'
294 heimbach 1.6 yctrlposunpack = '.opt'
295     yctrlpospack = '.opt'
296 heimbach 1.2 ctrlname = ' '
297     costname = ' '
298     scalname = ' '
299     maskname = ' '
300     metaname = ' '
301    
302 heimbach 1.15 c-- Next, read the cost data file.
303     WRITE(msgBuf,'(A)') 'CTRL_READPARMS: opening data.ctrl'
304     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
305     & SQUEEZE_RIGHT , 1)
306    
307     CALL OPEN_COPY_DATA_FILE(
308     I 'data.ctrl', 'CTRL_READPARMS',
309     O iUnit,
310     I myThid )
311    
312     READ(unit = iUnit, nml = ctrl_nml)
313     READ(unit = iUnit, nml = ctrl_packnames)
314    
315     WRITE(msgBuf,'(A)')
316     & 'CTRL_READPARMS: finished reading data.ctrl'
317     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
318     & SQUEEZE_RIGHT , 1)
319 heimbach 1.2
320 heimbach 1.15 CLOSE( iUnit )
321 heimbach 1.2
322     _END_MASTER( myThid )
323    
324     _BARRIER
325    
326     return
327     end
328    

  ViewVC Help
Powered by ViewVC 1.1.22