/[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.18 - (show annotations) (download)
Tue Feb 8 17:58:24 2005 UTC (19 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57d_post
Changes since 1.17: +7 -7 lines
change the default value of MNC flags: True when useMNC is true.

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

  ViewVC Help
Powered by ViewVC 1.1.22