/[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.14 - (hide annotations) (download)
Thu Apr 7 23:38:43 2005 UTC (19 years, 2 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57g_post, checkpoint57g_pre, checkpoint57h_done, checkpoint57h_pre, checkpoint57h_post
Changes since 1.13: +7 -1 lines
o separate masks used for ctrl_pack/unpack 'from write_grid' output
  (suggested by G. Forget)
o added new control variables
  * init. uVel, vVel, etanN
  * lambda[Theta,Salt]ClimRelax

1 edhill 1.5 C
2 heimbach 1.14 C $Header: /u/gcmpack/MITgcm/pkg/ctrl/ctrl_readparms.F,v 1.13 2005/03/30 18:40:40 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    
49     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     & xx_sflux_file,
78     & xx_sfluxstartdate1, xx_sfluxstartdate2, xx_sfluxperiod,
79     & xx_tauu_file,
80     & xx_tauustartdate1, xx_tauustartdate2, xx_tauuperiod,
81     & xx_tauv_file,
82     & xx_tauvstartdate1, xx_tauvstartdate2, xx_tauvperiod,
83     & xx_atemp_file,
84     & xx_atempstartdate1, xx_atempstartdate2, xx_atempperiod,
85     & xx_aqh_file,
86     & xx_aqhstartdate1, xx_aqhstartdate2, xx_aqhperiod,
87     & xx_uwind_file,
88     & xx_uwindstartdate1, xx_uwindstartdate2, xx_uwindperiod,
89     & xx_vwind_file,
90     & xx_vwindstartdate1, xx_vwindstartdate2, xx_vwindperiod,
91     & xx_obcsn_file,
92     & xx_obcsnstartdate1, xx_obcsnstartdate2, xx_obcsnperiod,
93     & xx_obcss_file,
94     & xx_obcssstartdate1, xx_obcssstartdate2, xx_obcssperiod,
95     & xx_obcsw_file,
96     & xx_obcswstartdate1, xx_obcswstartdate2, xx_obcswperiod,
97     & xx_obcse_file,
98     & xx_obcsestartdate1, xx_obcsestartdate2, xx_obcseperiod,
99     & xx_diffkr_file,
100     & xx_kapgm_file,
101     & xx_tr1_file,
102     & xx_sst_file,
103     & xx_sss_file,
104     & xx_hfacc_file,
105     & xx_efluxy_file,
106     & xx_efluxp_file,
107 heimbach 1.7 & xx_bottomdrag_file,
108 heimbach 1.12 & xx_edtaux_file,
109     & xx_edtauy_file,
110 heimbach 1.14 & xx_uvel_file,
111     & xx_vvel_file,
112     & xx_etan_file,
113 heimbach 1.10 & doInitXX,
114 heimbach 1.11 & doPackDiag,
115     & doZscaleUnpack,
116     & doZscalePack
117    
118 heimbach 1.2
119     namelist /ctrl_packnames/
120 heimbach 1.6 & yadmark, yctrlid, yctrlposunpack, yctrlpospack,
121 heimbach 1.2 & ctrlname, costname, scalname, maskname, metaname
122    
123     _BEGIN_MASTER( myThid )
124    
125     c-- Set default values.
126 heimbach 1.8 doInitXX = .TRUE.
127     #ifdef ALLOW_ADMTLM
128     doAdmTlm = .TRUE.
129     #else
130     doAdmTlm = .FALSE.
131     #endif
132 heimbach 1.10 doPackDiag = .FALSE.
133 heimbach 1.11 doZscaleUnpack = .FALSE.
134     doZscalePack = .FALSE.
135 heimbach 1.8
136 heimbach 1.13 xx_theta_file = 'xx_theta'
137     xx_salt_file = 'xx_salt'
138 heimbach 1.2 xx_hfluxstartdate1 = 0
139     xx_hfluxstartdate2 = 0
140     xx_hfluxperiod = 0. _d 0
141 heimbach 1.13 xx_hflux_file = 'xx_hfl'
142 heimbach 1.2 xx_sfluxstartdate1 = 0
143     xx_sfluxstartdate2 = 0
144     xx_sfluxperiod = 0. _d 0
145 heimbach 1.13 xx_sflux_file = 'xx_sfl'
146 heimbach 1.2 xx_tauustartdate1 = 0
147     xx_tauustartdate2 = 0
148     xx_tauuperiod = 0. _d 0
149 heimbach 1.13 xx_tauu_file = 'xx_tauu'
150 heimbach 1.2 xx_tauvstartdate1 = 0
151     xx_tauvstartdate2 = 0
152     xx_tauvperiod = 0. _d 0
153 heimbach 1.13 xx_tauv_file = 'xx_tauv'
154 heimbach 1.2 xx_atempstartdate1 = 0
155     xx_atempstartdate2 = 0
156     xx_atempperiod = 0. _d 0
157 heimbach 1.13 xx_atemp_file = 'xx_atemp'
158 heimbach 1.2 xx_aqhstartdate1 = 0
159     xx_aqhstartdate2 = 0
160     xx_aqhperiod = 0. _d 0
161 heimbach 1.13 xx_aqh_file = 'xx_aqh'
162 heimbach 1.2 xx_uwindstartdate1 = 0
163     xx_uwindstartdate2 = 0
164     xx_uwindperiod = 0. _d 0
165 heimbach 1.13 xx_uwind_file = 'xx_uwind'
166 heimbach 1.2 xx_vwindstartdate1 = 0
167     xx_vwindstartdate2 = 0
168     xx_vwindperiod = 0. _d 0
169 heimbach 1.13 xx_vwind_file = 'xx_vwind'
170 heimbach 1.2 xx_obcsnstartdate1 = 0
171     xx_obcsnstartdate2 = 0
172     xx_obcsnperiod = 0. _d 0
173 heimbach 1.13 xx_obcsn_file = 'xx_obcsn'
174 heimbach 1.2 xx_obcssstartdate1 = 0
175     xx_obcssstartdate2 = 0
176     xx_obcssperiod = 0. _d 0
177 heimbach 1.13 xx_obcss_file = 'xx_obcss'
178 heimbach 1.2 xx_obcswstartdate1 = 0
179     xx_obcswstartdate2 = 0
180     xx_obcswperiod = 0. _d 0
181 heimbach 1.13 xx_obcsw_file = 'xx_obcsw'
182 heimbach 1.2 xx_obcsestartdate1 = 0
183     xx_obcsestartdate2 = 0
184     xx_obcseperiod = 0. _d 0
185 heimbach 1.13 xx_obcse_file = 'xx_obcse'
186     xx_diffkr_file = 'xx_diffkr'
187     xx_kapgm_file = 'xx_kapgm'
188     xx_tr1_file = 'xx_ptr'
189     xx_sst_file = 'xx_sst'
190     xx_sss_file = 'xx_sss'
191     xx_hfacc_file = 'xx_hfacc'
192     xx_efluxy_file = 'xx_efluxy'
193     xx_efluxp_file = 'xx_efluxp'
194     xx_bottomdrag_file = 'xx_bottomdrag'
195     xx_edtaux_file = 'xx_edtaux'
196     xx_edtauy_file = 'xx_edtauy'
197 heimbach 1.14 xx_uvel_file = 'xx_uvel'
198     xx_vvel_file = 'xx_vvel'
199     xx_etan_file = 'xx_etan'
200 heimbach 1.2
201 heimbach 1.4 #ifdef ALLOW_TANGENTLINEAR_RUN
202     yadprefix = 'g_'
203     yadmark = 'g_'
204     #else
205     yadprefix = 'ad'
206 heimbach 1.2 yadmark = 'ad'
207     #endif
208     yctrlid = 'MIT_CE_000'
209 heimbach 1.6 yctrlposunpack = '.opt'
210     yctrlpospack = '.opt'
211 heimbach 1.2 ctrlname = ' '
212     costname = ' '
213     scalname = ' '
214     maskname = ' '
215     metaname = ' '
216    
217     c-- Check versions.
218    
219     open(unit=scrunit1,status='scratch')
220    
221     c-- Next, read the ecco data file.
222     open(unit = modeldataunit,file = 'data.ctrl',
223     & status = 'old', iostat = errio)
224     if ( errio .lt. 0 ) then
225     stop ' stopped in ctrl_readparms'
226     endif
227    
228     do while ( .true. )
229     read(modeldataunit, fmt='(a)', end=1001) record
230     il = max(ilnblnk(record),1)
231     if ( record(1:1) .ne. commentcharacter )
232     & write(unit=scrunit1, fmt='(a)') record(:il)
233     enddo
234     1001 continue
235     close( modeldataunit )
236    
237     rewind( scrunit1 )
238     read(unit = scrunit1, nml = ctrl_nml)
239     read(unit = scrunit1, nml = ctrl_packnames)
240     close( scrunit1 )
241    
242     _END_MASTER( myThid )
243    
244     _BARRIER
245    
246     return
247     end
248    

  ViewVC Help
Powered by ViewVC 1.1.22