/[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.22 - (hide annotations) (download)
Thu Mar 2 02:53:23 2006 UTC (18 years, 3 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58e_post, checkpoint58d_post, checkpoint58c_post, checkpoint58b_post
Changes since 1.21: +55 -4 lines
Adding parameter to remove on-the-fly global mean and trend from
exf forcing and ctrl control adjustments

1 edhill 1.5 C
2 heimbach 1.22 C $Header: /u/gcmpack/MITgcm/pkg/ctrl/ctrl_readparms.F,v 1.21 2005/12/19 23:37:14 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.2 & xx_hfacc_file,
124     & 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.21 & doAdmtlmBypassAD
139 heimbach 1.2
140     namelist /ctrl_packnames/
141 heimbach 1.6 & yadmark, yctrlid, yctrlposunpack, yctrlpospack,
142 heimbach 1.2 & ctrlname, costname, scalname, maskname, metaname
143    
144     _BEGIN_MASTER( myThid )
145    
146     c-- Set default values.
147 heimbach 1.8 doInitXX = .TRUE.
148     #ifdef ALLOW_ADMTLM
149     doAdmTlm = .TRUE.
150     #else
151     doAdmTlm = .FALSE.
152     #endif
153 heimbach 1.10 doPackDiag = .FALSE.
154 heimbach 1.11 doZscaleUnpack = .FALSE.
155     doZscalePack = .FALSE.
156 heimbach 1.20 doMainUnpack = .TRUE.
157     doMainPack = .TRUE.
158 heimbach 1.21 doAdmtlmBypassAD = .FALSE.
159 heimbach 1.8
160 heimbach 1.13 xx_theta_file = 'xx_theta'
161     xx_salt_file = 'xx_salt'
162 heimbach 1.22 c
163 heimbach 1.2 xx_hfluxstartdate1 = 0
164     xx_hfluxstartdate2 = 0
165     xx_hfluxperiod = 0. _d 0
166 heimbach 1.13 xx_hflux_file = 'xx_hfl'
167 heimbach 1.22 xx_hflux_remo_intercept = 0. _d 0
168     xx_hflux_remo_slope = 0. _d 0
169     c
170 heimbach 1.2 xx_sfluxstartdate1 = 0
171     xx_sfluxstartdate2 = 0
172     xx_sfluxperiod = 0. _d 0
173 heimbach 1.13 xx_sflux_file = 'xx_sfl'
174 heimbach 1.22 xx_sflux_remo_intercept = 0. _d 0
175     xx_sflux_remo_slope = 0. _d 0
176     c
177 heimbach 1.2 xx_tauustartdate1 = 0
178     xx_tauustartdate2 = 0
179     xx_tauuperiod = 0. _d 0
180 heimbach 1.13 xx_tauu_file = 'xx_tauu'
181 heimbach 1.22 xx_tauu_remo_intercept = 0. _d 0
182     xx_tauu_remo_slope = 0. _d 0
183     c
184 heimbach 1.2 xx_tauvstartdate1 = 0
185     xx_tauvstartdate2 = 0
186     xx_tauvperiod = 0. _d 0
187 heimbach 1.13 xx_tauv_file = 'xx_tauv'
188 heimbach 1.22 xx_tauv_remo_intercept = 0. _d 0
189     xx_tauv_remo_slope = 0. _d 0
190     c
191 heimbach 1.2 xx_atempstartdate1 = 0
192     xx_atempstartdate2 = 0
193     xx_atempperiod = 0. _d 0
194 heimbach 1.13 xx_atemp_file = 'xx_atemp'
195 heimbach 1.22 xx_atemp_remo_intercept = 0. _d 0
196     xx_atemp_remo_slope = 0. _d 0
197     c
198 heimbach 1.2 xx_aqhstartdate1 = 0
199     xx_aqhstartdate2 = 0
200     xx_aqhperiod = 0. _d 0
201 heimbach 1.13 xx_aqh_file = 'xx_aqh'
202 heimbach 1.22 xx_aqh_remo_intercept = 0. _d 0
203     xx_aqh_remo_slope = 0. _d 0
204     c
205 heimbach 1.16 xx_precipstartdate1 = 0
206     xx_precipstartdate2 = 0
207     xx_precipperiod = 0. _d 0
208     xx_precip_file = 'xx_precip'
209 heimbach 1.22 xx_precip_remo_intercept = 0. _d 0
210     xx_precip_remo_slope = 0. _d 0
211     c
212 heimbach 1.17 xx_swfluxstartdate1 = 0
213     xx_swfluxstartdate2 = 0
214     xx_swfluxperiod = 0. _d 0
215     xx_swflux_file = 'xx_swflux'
216 heimbach 1.22 xx_swflux_remo_intercept = 0. _d 0
217     xx_swflux_remo_slope = 0. _d 0
218     c
219 heimbach 1.18 xx_swdownstartdate1 = 0
220     xx_swdownstartdate2 = 0
221     xx_swdownperiod = 0. _d 0
222     xx_swdown_file = 'xx_swdown'
223 heimbach 1.22 xx_swdown_remo_intercept = 0. _d 0
224     xx_swdown_remo_slope = 0. _d 0
225     c
226 heimbach 1.2 xx_uwindstartdate1 = 0
227     xx_uwindstartdate2 = 0
228     xx_uwindperiod = 0. _d 0
229 heimbach 1.13 xx_uwind_file = 'xx_uwind'
230 heimbach 1.22 xx_uwind_remo_intercept = 0. _d 0
231     xx_uwind_remo_slope = 0. _d 0
232     c
233 heimbach 1.2 xx_vwindstartdate1 = 0
234     xx_vwindstartdate2 = 0
235     xx_vwindperiod = 0. _d 0
236 heimbach 1.13 xx_vwind_file = 'xx_vwind'
237 heimbach 1.22 xx_vwind_remo_intercept = 0. _d 0
238     xx_vwind_remo_slope = 0. _d 0
239     c
240 heimbach 1.2 xx_obcsnstartdate1 = 0
241     xx_obcsnstartdate2 = 0
242     xx_obcsnperiod = 0. _d 0
243 heimbach 1.13 xx_obcsn_file = 'xx_obcsn'
244 heimbach 1.22 c
245 heimbach 1.2 xx_obcssstartdate1 = 0
246     xx_obcssstartdate2 = 0
247     xx_obcssperiod = 0. _d 0
248 heimbach 1.13 xx_obcss_file = 'xx_obcss'
249 heimbach 1.22 c
250 heimbach 1.2 xx_obcswstartdate1 = 0
251     xx_obcswstartdate2 = 0
252     xx_obcswperiod = 0. _d 0
253 heimbach 1.13 xx_obcsw_file = 'xx_obcsw'
254 heimbach 1.22 c
255 heimbach 1.2 xx_obcsestartdate1 = 0
256     xx_obcsestartdate2 = 0
257     xx_obcseperiod = 0. _d 0
258 heimbach 1.13 xx_obcse_file = 'xx_obcse'
259 heimbach 1.22 c
260 heimbach 1.19 xx_sststartdate1 = 0
261     xx_sststartdate2 = 0
262     xx_sstperiod = 0. _d 0
263 heimbach 1.13 xx_sst_file = 'xx_sst'
264 heimbach 1.22 c
265 heimbach 1.19 xx_sssstartdate1 = 0
266     xx_sssstartdate2 = 0
267     xx_sssperiod = 0. _d 0
268 heimbach 1.13 xx_sss_file = 'xx_sss'
269 heimbach 1.22 c
270     xx_diffkr_file = 'xx_diffkr'
271     xx_kapgm_file = 'xx_kapgm'
272     xx_tr1_file = 'xx_ptr'
273 heimbach 1.13 xx_hfacc_file = 'xx_hfacc'
274     xx_efluxy_file = 'xx_efluxy'
275     xx_efluxp_file = 'xx_efluxp'
276     xx_bottomdrag_file = 'xx_bottomdrag'
277     xx_edtaux_file = 'xx_edtaux'
278     xx_edtauy_file = 'xx_edtauy'
279 heimbach 1.14 xx_uvel_file = 'xx_uvel'
280     xx_vvel_file = 'xx_vvel'
281     xx_etan_file = 'xx_etan'
282 heimbach 1.2
283 heimbach 1.4 #ifdef ALLOW_TANGENTLINEAR_RUN
284     yadprefix = 'g_'
285     yadmark = 'g_'
286     #else
287     yadprefix = 'ad'
288 heimbach 1.2 yadmark = 'ad'
289     #endif
290     yctrlid = 'MIT_CE_000'
291 heimbach 1.6 yctrlposunpack = '.opt'
292     yctrlpospack = '.opt'
293 heimbach 1.2 ctrlname = ' '
294     costname = ' '
295     scalname = ' '
296     maskname = ' '
297     metaname = ' '
298    
299 heimbach 1.15 c-- Next, read the cost data file.
300     WRITE(msgBuf,'(A)') 'CTRL_READPARMS: opening data.ctrl'
301     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
302     & SQUEEZE_RIGHT , 1)
303    
304     CALL OPEN_COPY_DATA_FILE(
305     I 'data.ctrl', 'CTRL_READPARMS',
306     O iUnit,
307     I myThid )
308    
309     READ(unit = iUnit, nml = ctrl_nml)
310     READ(unit = iUnit, nml = ctrl_packnames)
311    
312     WRITE(msgBuf,'(A)')
313     & 'CTRL_READPARMS: finished reading data.ctrl'
314     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
315     & SQUEEZE_RIGHT , 1)
316 heimbach 1.2
317 heimbach 1.15 CLOSE( iUnit )
318 heimbach 1.2
319     _END_MASTER( myThid )
320    
321     _BARRIER
322    
323     return
324     end
325    

  ViewVC Help
Powered by ViewVC 1.1.22