/[MITgcm]/MITgcm/pkg/mnc/mnc_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/mnc/mnc_readparms.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.23 - (show annotations) (download)
Mon Jun 27 20:19:52 2005 UTC (19 years ago) by edhill
Branch: MAIN
CVS Tags: checkpoint57o_post, checkpoint57m_post, checkpoint57k_post, checkpoint57n_post, checkpoint57p_post, checkpoint57j_post, checkpoint57l_post
Changes since 1.22: +3 -2 lines
 o add a flag (off by default) that includes nIter0 in the MNC file names

1 C $Header: /u/gcmpack/MITgcm/pkg/mnc/mnc_readparms.F,v 1.22 2005/05/11 00:43:04 edhill Exp $
2 C $Name: $
3
4 #include "MNC_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP 0
8 C !ROUTINE: MNC_READPARMS
9
10 C !INTERFACE:
11 SUBROUTINE MNC_READPARMS( myThid )
12
13 C !DESCRIPTION:
14 C Read the MNC run-time parameters file. IF the file does not
15 C exist, MNC will assume that it is not needed (that is, some other
16 C IO routines such as MDSIO will be used) and will not issue any
17 C errors.
18
19 C !USES:
20 implicit none
21 #include "SIZE.h"
22 #include "mnc_common.h"
23 #include "EEPARAMS.h"
24 #include "PARAMS.h"
25 #include "MNC_PARAMS.h"
26
27 C !INPUT PARAMETERS:
28 integer myThid
29 CEOP
30
31 C !LOCAL VARIABLES:
32 integer i, iUnit, nl, isu1,isu2,mdu, errio, IL
33 character*(MAX_LEN_MBUF) data_file
34 character*(MAX_LEN_MBUF) msgBuf
35 CHARACTER*(MAX_LEN_PREC) record
36 NAMELIST /MNC_01/
37 & mnc_use_indir, mnc_use_outdir, mnc_outdir_date,
38 & mnc_outdir_num, mnc_use_name_ni0, mnc_echo_gvtypes,
39 & pickup_write_mnc, pickup_read_mnc,
40 & timeave_mnc, snapshot_mnc, monitor_mnc, autodiff_mnc,
41 & readgrid_mnc,
42 & mnc_outdir_str, mnc_indir_str, mnc_max_fsize
43 LOGICAL exst
44
45 C Functions
46 integer ILNBLNK
47
48 C Set default values for MNC run-time parameters
49 DO i = 1,MAX_LEN_FNAM
50 mnc_outdir_str(i:i) = ' '
51 mnc_indir_str(i:i) = ' '
52 ENDDO
53 mnc_echo_gvtypes = .FALSE.
54 mnc_use_outdir = .FALSE.
55 mnc_outdir_str(1:4) = 'mnc_'
56 mnc_outdir_date = .FALSE.
57 mnc_outdir_num = .TRUE.
58 mnc_use_name_ni0 = .FALSE.
59 pickup_write_mnc = .TRUE.
60 pickup_read_mnc = .TRUE.
61 mnc_use_indir = .FALSE.
62 mnc_indir_str(1:4) = ' '
63 monitor_mnc = .TRUE.
64 timeave_mnc = .TRUE.
65 snapshot_mnc = .TRUE.
66 autodiff_mnc = .TRUE.
67 C 2GB is 2147483648 bytes or approx: 2.1475e+09
68 mnc_max_fsize = 2.1 _d 9
69 readgrid_mnc = .FALSE.
70
71 C Set the file name
72 DO i=1,MAX_LEN_MBUF
73 data_file(i:i) = ' '
74 ENDDO
75 WRITE(data_file,'(a)') 'data.mnc'
76 nl = ILNBLNK(data_file)
77
78 C Verify that the file exists and, if not, disable MNC
79 INQUIRE( FILE=data_file, EXIST=exst )
80 IF (exst) THEN
81 WRITE(msgbuf,'(3a)')
82 & ' MNC_READPARMS: opening file ''',
83 & data_file(1:nl), ''''
84 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
85 & SQUEEZE_RIGHT , mythid)
86 ELSE
87 c WRITE(msgBuf,'(3a)')
88 c & 'Data file: ''',data_file(1:nl),
89 c & ''' does not exist so MNC will be disabled'
90 c CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
91 c & SQUEEZE_RIGHT , mythid)
92 c RETURN
93 C- jmc: found strange things when data.mnc is missing:
94 C "MNC will be disabled" is not implemented
95 C => Safer, in this case, to stop the run here.
96 WRITE(msgBuf,'(3a)')
97 & 'Data file: ''',data_file(1:nl),
98 & ''' does not exist ==> STOP'
99 CALL PRINT_ERROR( msgBuf, mythid)
100 STOP 'ABNORMAL END: S/R MNC_READPARMS'
101 ENDIF
102
103 C Open files
104 isu1 = 60
105 isu2 = 61
106 mdu = 62
107 OPEN(UNIT=isu1, STATUS='SCRATCH')
108 OPEN(UNIT=isu2, STATUS='SCRATCH')
109 OPEN(UNIT=mdu, FILE=data_file, STATUS='OLD', IOSTAT=errio)
110 IF ( errio .LT. 0 ) THEN
111 WRITE(msgBuf,'(3a)')
112 & 'Unable to open data file: ''',data_file(1:nl),
113 & ''' so MNC will be disabled'
114 CALL PRINT_ERROR( msgBuf , 1)
115 STOP 'ABNORMAL END: S/R MNC_READPARMS'
116 RETURN
117 ENDIF
118
119 DO WHILE ( .TRUE. )
120 READ(mdu,FMT='(A)',END=1001) RECORD
121 IL = MAX(ILNBLNK(RECORD),1)
122 IF ( RECORD(1:1) .NE. commentCharacter ) THEN
123 CALL NML_SET_TERMINATOR( RECORD )
124 WRITE(UNIT=isu1,FMT='(A)') RECORD(:IL)
125 ENDIF
126 WRITE(UNIT=isu2,FMT='(A)') RECORD(:IL)
127 ENDDO
128 1001 CONTINUE
129 CLOSE(mdu)
130
131 C-- Report contents of model parameter file
132 WRITE(msgBuf,'(A)')
133 & '// ======================================================='
134 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
135 & SQUEEZE_RIGHT , 1)
136 WRITE(msgBuf,'(3a)') '// Parameter file "',data_file(1:nl),'"'
137 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
138 & SQUEEZE_RIGHT , 1)
139 WRITE(msgBuf,'(A)')
140 & '// ======================================================='
141 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
142 & SQUEEZE_RIGHT , 1)
143 iUnit = isu2
144 REWIND(iUnit)
145 DO WHILE ( .TRUE. )
146 READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
147 IL = MAX(ILNBLNK(RECORD),1)
148 WRITE(msgBuf,'(2a)') '>',RECORD(:IL)
149 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
150 & SQUEEZE_RIGHT , 1)
151 ENDDO
152 2001 CONTINUE
153 CLOSE(iUnit)
154 WRITE(msgBuf,'(A)') ' '
155 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
156 & SQUEEZE_RIGHT , 1)
157
158 iUnit = isu1
159 REWIND(iUnit)
160 READ(UNIT=iUnit,NML=MNC_01,IOSTAT=errio,err=3)
161 GOTO 4
162 3 CONTINUE
163 WRITE(msgBuf,'(A,A,A)')
164 & 'ERROR: while reading file ''',data_file(1:nl),
165 & ''' -- please check file contents'
166 CALL PRINT_ERROR( msgBuf , 1)
167 STOP 'ABNORMAL END: S/R MNC_READPARMS'
168 4 CONTINUE
169
170 WRITE(msgBuf,'(a)') ' MNC_READPARMS: finished reading data.mnc'
171 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
172 & SQUEEZE_RIGHT , 1)
173
174 C Pickups must always be read in an EXCLUSIVE fashion
175 IF (pickup_read_mnc) pickup_read_mdsio = .FALSE.
176
177 C IO handling is done in one of two senses:
178 C (1) outputTypesInclusive=.TRUE. is an "inclusive-or" meaning that
179 C one or more write methods can occur simultaneously and
180 C (2) outputTypesInclusive=.FALSE. is an "exclusive-or" meaning that
181 C only one write method can occur in a given run
182 C
183 C Since all the *_mdsio flags default to .TRUE. and
184 C outputTypesInclusive defaults to .FALSE., the logic here is
185 C simple:
186 IF ( (.NOT. outputTypesInclusive)
187 & .AND. pickup_write_mnc ) pickup_write_mdsio = .FALSE.
188 IF ( (.NOT. outputTypesInclusive)
189 & .AND. timeave_mnc ) timeave_mdsio = .FALSE.
190 IF ( (.NOT. outputTypesInclusive)
191 & .AND. snapshot_mnc ) snapshot_mdsio = .FALSE.
192 IF ( (.NOT. outputTypesInclusive)
193 & .AND. monitor_mnc ) monitor_stdio = .FALSE.
194
195 C Reads are always an exclusive relationship
196 IF (pickup_read_mnc) pickup_read_mdsio = .FALSE.
197
198 C Create and/or set the MNC output directory
199 IF (mnc_use_outdir) THEN
200 IF ( mnc_outdir_num .OR. mnc_outdir_date ) THEN
201 CALL MNC_SET_OUTDIR(myThid)
202 ELSE
203 DO i = 1,MNC_MAX_CHAR
204 mnc_out_path(i:i) = ' '
205 ENDDO
206 write(mnc_out_path,'(2A)')
207 & mnc_outdir_str(1:ILNBLNK(mnc_outdir_str)), '/'
208 ENDIF
209 ENDIF
210
211 RETURN
212 END
213
214 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
215 CBOP 1
216 C !ROUTINE: MNC_SET_OUTDIR
217
218 C !INTERFACE:
219 SUBROUTINE MNC_SET_OUTDIR( myThid )
220
221 C !DESCRIPTION:
222 C Create the output (sub--)directory for the MNC output files.
223
224 C !USES:
225 implicit none
226 #include "mnc_common.h"
227 #include "SIZE.h"
228 #include "EEPARAMS.h"
229 #include "PARAMS.h"
230 #include "MNC_PARAMS.h"
231
232 C !INPUT PARAMETERS:
233 integer myThid
234 CEOP
235
236 C !LOCAL VARIABLES:
237 integer i,j,k, ntot, npathd, idate
238 character*(100) pathd
239 character*(100) cenc
240 integer ienc(100)
241 integer ncenc
242
243 C Functions
244 integer ILNBLNK
245
246 cenc(1:26) = 'abcdefghijklmnopqrstuvwxyz'
247 cenc(27:52) = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
248 cenc(53:70) = '0123456789_.,+-=/~'
249 ncenc = 70
250 npathd = 100
251 IF (mnc_outdir_date) THEN
252 idate = 1
253 ELSE
254 idate = 0
255 ENDIF
256 DO i = 1,100
257 pathd(i:i) = ' '
258 ENDDO
259 k = ILNBLNK(mnc_outdir_str)
260 IF (k .GT. 80) k = 80
261 pathd(1:k) = mnc_outdir_str(1:k)
262 ntot = 0
263 DO i = 1,k
264 DO j = 1,ncenc
265 IF (pathd(i:i) .EQ. cenc(j:j)) THEN
266 ntot = ntot + 1
267 ienc(ntot) = j
268 GOTO 20
269 ENDIF
270 ENDDO
271 20 CONTINUE
272 ENDDO
273 C write(*,*) 'ntot,k = ', ntot, ',',k
274 C DO i = 1,ntot
275 C write(*,*) 'ienc = ', ienc(i)
276 C ENDDO
277
278 #define HAVE_MNCCDIR
279 #ifdef HAVE_MNCCDIR
280 CALL mnccdir(ntot, ienc, idate)
281 #else
282 npathd = 0
283 #endif
284
285 DO i = 1,MNC_MAX_CHAR
286 mnc_out_path(i:i) = ' '
287 ENDDO
288 IF (ntot .GT. 0) THEN
289 IF (ntot .GT. (MNC_MAX_CHAR-40)) THEN
290 ntot = MNC_MAX_CHAR - 40
291 ENDIF
292 DO i = 1,ntot
293 j = ienc(i)
294 mnc_out_path(i:i) = cenc(j:j)
295 ENDDO
296 mnc_out_path((ntot+1):(ntot+1)) = '/'
297 ENDIF
298
299 C k = ILNBLNK(mnc_out_path)
300 C write(*,*) 'mnc_out_path = ''', mnc_out_path(1:k), ''''
301 C STOP 'yoyoyo'
302
303 RETURN
304 END
305
306 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22