/[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.38 - (show annotations) (download)
Wed Aug 9 15:23:37 2017 UTC (6 years, 9 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, HEAD
Changes since 1.37: +6 -2 lines
replace CLOSE(nmlfileUnit) with CLOSE(nmlfileUnit,STATUS='DELETE') to remove
scratchfiles after closing, except for SINGLE_DISK_IO, when everything
stays the same

1 C $Header: /u/gcmpack/MITgcm/pkg/mnc/mnc_readparms.F,v 1.37 2015/02/24 19:59:22 jmc Exp $
2 C $Name: BASE $
3
4 #include "MNC_OPTIONS.h"
5
6 C-- File mnc_readparms.F
7 C-- Contents
8 C-- o MNC_READPARMS
9 C-- o MNC_SET_OUTDIR
10
11 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
12 CBOP 0
13 C !ROUTINE: MNC_READPARMS
14
15 C !INTERFACE:
16 SUBROUTINE MNC_READPARMS( myThid )
17
18 C !DESCRIPTION:
19 C Read the MNC run-time parameters file. IF the file does not
20 C exist, MNC will assume that it is not needed (that is, some other
21 C IO routines such as MDSIO will be used) and will not issue any
22 C errors.
23
24 C !USES:
25 IMPLICIT NONE
26 #include "SIZE.h"
27 #include "MNC_COMMON.h"
28 #include "EEPARAMS.h"
29 #include "PARAMS.h"
30 #include "MNC_PARAMS.h"
31
32 C !INPUT PARAMETERS:
33 INTEGER myThid
34 CEOP
35
36 C !FUNCTIONS:
37 INTEGER ILNBLNK
38
39 C !LOCAL VARIABLES:
40 INTEGER i, nl, ku
41 CHARACTER*(MAX_LEN_MBUF) data_file
42 CHARACTER*(MAX_LEN_MBUF) msgBuf
43
44 NAMELIST /MNC_01/
45 & mnc_use_indir, mnc_use_outdir, mnc_outdir_date,
46 & mnc_outdir_num, mnc_use_name_ni0, mnc_echo_gvtypes,
47 & pickup_write_mnc, pickup_read_mnc,
48 & timeave_mnc, snapshot_mnc, monitor_mnc, autodiff_mnc,
49 & writegrid_mnc, readgrid_mnc,
50 & mnc_outdir_str, mnc_indir_str, mnc_max_fsize,
51 & mnc_filefreq,
52 & mnc_read_bathy, mnc_read_salt, mnc_read_theta
53
54 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
55
56 IF ( .NOT.useMNC ) THEN
57 C- pkg MNC is not used
58 _BEGIN_MASTER(myThid)
59 C- Track pkg activation status:
60 C print a (weak) warning if data.mnc is found
61 CALL PACKAGES_UNUSED_MSG( 'useMNC', ' ', ' ' )
62 _END_MASTER(myThid)
63 RETURN
64 ENDIF
65
66 C-----
67 C Need some work to make MNC multi-threaded safe.
68 C For now, switch it off (otherwise, it is hanging up somewhere)
69 IF ( nThreads.GT.1 ) THEN
70 _BARRIER
71 _BEGIN_MASTER( myThid )
72 WRITE(msgBuf,'(2A)') '** WARNING ** MNC_READPARMS: ',
73 & 'useMNC unsafe with multi-threads'
74 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
75 & SQUEEZE_RIGHT , myThid )
76 WRITE(msgBuf,'(2A)') '** WARNING ** MNC_READPARMS: ',
77 & 'for now, switch useMNC to FALSE'
78 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
79 & SQUEEZE_RIGHT , myThid )
80 useMNC = .FALSE.
81 _END_MASTER( myThid )
82 _BARRIER
83 RETURN
84 ENDIF
85 C-----
86
87 C Set default values for MNC run-time parameters
88 DO i = 1,MAX_LEN_FNAM
89 mnc_outdir_str(i:i) = ' '
90 mnc_indir_str(i:i) = ' '
91 ENDDO
92 mnc_echo_gvtypes = .FALSE.
93 mnc_use_outdir = .FALSE.
94 mnc_outdir_str(1:4) = 'mnc_'
95 mnc_outdir_date = .FALSE.
96 mnc_outdir_num = .TRUE.
97 mnc_use_name_ni0 = .FALSE.
98 pickup_write_mnc = .FALSE.
99 pickup_read_mnc = .FALSE.
100 mnc_use_indir = .FALSE.
101 mnc_indir_str(1:4) = ' '
102 monitor_mnc = .TRUE.
103 timeave_mnc = .TRUE.
104 snapshot_mnc = .TRUE.
105 autodiff_mnc = .TRUE.
106 writegrid_mnc = .TRUE.
107 C 2GB is 2147483648 bytes or approx: 2.1475e+09
108 mnc_max_fsize = 2.1 _d 9
109 readgrid_mnc = .FALSE.
110
111 C New parms for initial files
112 mnc_read_bathy = .FALSE.
113 mnc_read_salt = .FALSE.
114 mnc_read_theta = .FALSE.
115
116 C Temporary hack for Baylor
117 mnc_filefreq = -1
118
119 C Set the file name
120 DO i=1,MAX_LEN_MBUF
121 data_file(i:i) = ' '
122 ENDDO
123 WRITE(data_file,'(a)') 'data.mnc'
124 nl = ILNBLNK(data_file)
125
126 WRITE(msgbuf,'(3a)') ' MNC_READPARMS: opening file ''',
127 & data_file(1:nl), ''''
128 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
129 & SQUEEZE_RIGHT,myThid)
130
131 CALL OPEN_COPY_DATA_FILE(data_file(1:nl),'MNC_READPARMS',
132 & ku, myThid )
133 READ(ku,NML=MNC_01)
134 #ifdef SINGLE_DISK_IO
135 CLOSE(ku)
136 #else
137 CLOSE(ku,STATUS='DELETE')
138 #endif /* SINGLE_DISK_IO */
139
140 WRITE(msgBuf,'(a)') ' MNC_READPARMS: finished reading data.mnc'
141 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
142 & SQUEEZE_RIGHT,myThid)
143
144 C Pickups must always be read in an EXCLUSIVE fashion
145 IF (pickup_read_mnc) pickup_read_mdsio = .FALSE.
146
147 C IO handling is done in one of two senses:
148 C (1) outputTypesInclusive=.TRUE. is an "inclusive-or" meaning that
149 C one or more write methods can occur simultaneously or
150 C (2) outputTypesInclusive=.FALSE. is an "exclusive-or" meaning that
151 C only one write method can occur in a given run
152 C
153 C Since all the *_mdsio flags default to .TRUE. and
154 C outputTypesInclusive defaults to .FALSE., the logic here is
155 C simple:
156 IF ( (.NOT. outputTypesInclusive)
157 & .AND. pickup_write_mnc ) pickup_write_mdsio = .FALSE.
158 IF ( (.NOT. outputTypesInclusive)
159 & .AND. timeave_mnc ) timeave_mdsio = .FALSE.
160 IF ( (.NOT. outputTypesInclusive)
161 & .AND. snapshot_mnc ) snapshot_mdsio = .FALSE.
162 IF ( (.NOT. outputTypesInclusive)
163 & .AND. monitor_mnc ) monitor_stdio = .FALSE.
164
165 C Reads are always an exclusive relationship
166 IF (pickup_read_mnc) pickup_read_mdsio = .FALSE.
167
168 C Create and/or set the MNC output directory
169 IF (mnc_use_outdir) THEN
170 IF ( mnc_outdir_num .OR. mnc_outdir_date ) THEN
171 CALL MNC_SET_OUTDIR(myThid)
172 ELSE
173 DO i = 1,MNC_MAX_CHAR
174 mnc_out_path(i:i) = ' '
175 ENDDO
176 write(mnc_out_path,'(2A)')
177 & mnc_outdir_str(1:ILNBLNK(mnc_outdir_str)), '/'
178 ENDIF
179 ENDIF
180
181 C-- print out some kee parameters :
182
183 C-- Check the parameters :
184 IF ( pickup_write_mnc .OR. pickup_read_mnc ) THEN
185 WRITE(msgBuf,'(2A)') '** WARNING ** MNC_READPARMS: ',
186 & 'incomplete MNC pickup files implementation'
187 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
188 & SQUEEZE_RIGHT, myThid )
189 ENDIF
190 IF ( pickup_write_mnc ) THEN
191 WRITE(msgBuf,'(2A)') '** WARNING ** MNC_READPARMS: ',
192 & '=> pickup_write_mnc=T not recommanded'
193 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
194 & SQUEEZE_RIGHT, myThid )
195 ENDIF
196 IF ( pickup_read_mnc ) THEN
197 WRITE(msgBuf,'(2A)') '** WARNING ** MNC_READPARMS: ',
198 & '=> pickup_read_mnc=T not working for some set-up'
199 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
200 & SQUEEZE_RIGHT, myThid )
201 ENDIF
202
203 RETURN
204 END
205
206 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
207 CBOP 1
208 C !ROUTINE: MNC_SET_OUTDIR
209
210 C !INTERFACE:
211 SUBROUTINE MNC_SET_OUTDIR( myThid )
212
213 C !DESCRIPTION:
214 C Create the output (sub--)directory for the MNC output files.
215
216 C !USES:
217 implicit none
218 #include "MNC_COMMON.h"
219 #include "SIZE.h"
220 #include "EEPARAMS.h"
221 #include "PARAMS.h"
222 #include "MNC_PARAMS.h"
223
224 C !INPUT PARAMETERS:
225 integer myThid
226 CEOP
227
228 C !LOCAL VARIABLES:
229 integer i,j,k, ntot, npathd, idate
230 character*(MNC_MAX_PATH) pathd
231 character*(100) cenc
232 integer ienc(MNC_MAX_PATH)
233 integer ncenc
234
235 C Functions
236 integer ILNBLNK
237
238 cenc(1:26) = 'abcdefghijklmnopqrstuvwxyz'
239 cenc(27:52) = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
240 cenc(53:70) = '0123456789_.,+-=/~'
241 ncenc = 70
242 npathd = 100
243 IF (mnc_outdir_date) THEN
244 idate = 1
245 ELSE
246 idate = 0
247 ENDIF
248 DO i = 1,MNC_MAX_PATH
249 pathd(i:i) = ' '
250 ENDDO
251 k = ILNBLNK(mnc_outdir_str)
252 IF (k .GT. MNC_MAX_PATH) k = MNC_MAX_PATH
253 pathd(1:k) = mnc_outdir_str(1:k)
254 ntot = 0
255 DO i = 1,k
256 DO j = 1,ncenc
257 IF (pathd(i:i) .EQ. cenc(j:j)) THEN
258 ntot = ntot + 1
259 ienc(ntot) = j
260 GOTO 20
261 ENDIF
262 ENDDO
263 20 CONTINUE
264 ENDDO
265
266 CALL mnccdir(ntot, ienc, idate)
267
268 DO i = 1,MNC_MAX_PATH
269 mnc_out_path(i:i) = ' '
270 ENDDO
271 IF (ntot .GT. 0) THEN
272 IF (ntot .GT. (MNC_MAX_PATH-40)) THEN
273 ntot = MNC_MAX_PATH - 40
274 ENDIF
275 DO i = 1,ntot
276 j = ienc(i)
277 mnc_out_path(i:i) = cenc(j:j)
278 ENDDO
279 mnc_out_path((ntot+1):(ntot+1)) = '/'
280 ENDIF
281
282 RETURN
283 END

  ViewVC Help
Powered by ViewVC 1.1.22