/[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.37 - (show annotations) (download)
Tue Feb 24 19:59:22 2015 UTC (9 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m
Changes since 1.36: +26 -4 lines
add warnings when using MNC pickup files

1 C $Header: /u/gcmpack/MITgcm/pkg/mnc/mnc_readparms.F,v 1.36 2015/02/23 21:27:49 jmc Exp $
2 C $Name: $
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 CLOSE(ku)
135
136 WRITE(msgBuf,'(a)') ' MNC_READPARMS: finished reading data.mnc'
137 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
138 & SQUEEZE_RIGHT,myThid)
139
140 C Pickups must always be read in an EXCLUSIVE fashion
141 IF (pickup_read_mnc) pickup_read_mdsio = .FALSE.
142
143 C IO handling is done in one of two senses:
144 C (1) outputTypesInclusive=.TRUE. is an "inclusive-or" meaning that
145 C one or more write methods can occur simultaneously or
146 C (2) outputTypesInclusive=.FALSE. is an "exclusive-or" meaning that
147 C only one write method can occur in a given run
148 C
149 C Since all the *_mdsio flags default to .TRUE. and
150 C outputTypesInclusive defaults to .FALSE., the logic here is
151 C simple:
152 IF ( (.NOT. outputTypesInclusive)
153 & .AND. pickup_write_mnc ) pickup_write_mdsio = .FALSE.
154 IF ( (.NOT. outputTypesInclusive)
155 & .AND. timeave_mnc ) timeave_mdsio = .FALSE.
156 IF ( (.NOT. outputTypesInclusive)
157 & .AND. snapshot_mnc ) snapshot_mdsio = .FALSE.
158 IF ( (.NOT. outputTypesInclusive)
159 & .AND. monitor_mnc ) monitor_stdio = .FALSE.
160
161 C Reads are always an exclusive relationship
162 IF (pickup_read_mnc) pickup_read_mdsio = .FALSE.
163
164 C Create and/or set the MNC output directory
165 IF (mnc_use_outdir) THEN
166 IF ( mnc_outdir_num .OR. mnc_outdir_date ) THEN
167 CALL MNC_SET_OUTDIR(myThid)
168 ELSE
169 DO i = 1,MNC_MAX_CHAR
170 mnc_out_path(i:i) = ' '
171 ENDDO
172 write(mnc_out_path,'(2A)')
173 & mnc_outdir_str(1:ILNBLNK(mnc_outdir_str)), '/'
174 ENDIF
175 ENDIF
176
177 C-- print out some kee parameters :
178
179 C-- Check the parameters :
180 IF ( pickup_write_mnc .OR. pickup_read_mnc ) THEN
181 WRITE(msgBuf,'(2A)') '** WARNING ** MNC_READPARMS: ',
182 & 'incomplete MNC pickup files implementation'
183 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
184 & SQUEEZE_RIGHT, myThid )
185 ENDIF
186 IF ( pickup_write_mnc ) THEN
187 WRITE(msgBuf,'(2A)') '** WARNING ** MNC_READPARMS: ',
188 & '=> pickup_write_mnc=T not recommanded'
189 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
190 & SQUEEZE_RIGHT, myThid )
191 ENDIF
192 IF ( pickup_read_mnc ) THEN
193 WRITE(msgBuf,'(2A)') '** WARNING ** MNC_READPARMS: ',
194 & '=> pickup_read_mnc=T not working for some set-up'
195 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
196 & SQUEEZE_RIGHT, myThid )
197 ENDIF
198
199 RETURN
200 END
201
202 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
203 CBOP 1
204 C !ROUTINE: MNC_SET_OUTDIR
205
206 C !INTERFACE:
207 SUBROUTINE MNC_SET_OUTDIR( myThid )
208
209 C !DESCRIPTION:
210 C Create the output (sub--)directory for the MNC output files.
211
212 C !USES:
213 implicit none
214 #include "MNC_COMMON.h"
215 #include "SIZE.h"
216 #include "EEPARAMS.h"
217 #include "PARAMS.h"
218 #include "MNC_PARAMS.h"
219
220 C !INPUT PARAMETERS:
221 integer myThid
222 CEOP
223
224 C !LOCAL VARIABLES:
225 integer i,j,k, ntot, npathd, idate
226 character*(MNC_MAX_PATH) pathd
227 character*(100) cenc
228 integer ienc(MNC_MAX_PATH)
229 integer ncenc
230
231 C Functions
232 integer ILNBLNK
233
234 cenc(1:26) = 'abcdefghijklmnopqrstuvwxyz'
235 cenc(27:52) = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
236 cenc(53:70) = '0123456789_.,+-=/~'
237 ncenc = 70
238 npathd = 100
239 IF (mnc_outdir_date) THEN
240 idate = 1
241 ELSE
242 idate = 0
243 ENDIF
244 DO i = 1,MNC_MAX_PATH
245 pathd(i:i) = ' '
246 ENDDO
247 k = ILNBLNK(mnc_outdir_str)
248 IF (k .GT. MNC_MAX_PATH) k = MNC_MAX_PATH
249 pathd(1:k) = mnc_outdir_str(1:k)
250 ntot = 0
251 DO i = 1,k
252 DO j = 1,ncenc
253 IF (pathd(i:i) .EQ. cenc(j:j)) THEN
254 ntot = ntot + 1
255 ienc(ntot) = j
256 GOTO 20
257 ENDIF
258 ENDDO
259 20 CONTINUE
260 ENDDO
261
262 CALL mnccdir(ntot, ienc, idate)
263
264 DO i = 1,MNC_MAX_PATH
265 mnc_out_path(i:i) = ' '
266 ENDDO
267 IF (ntot .GT. 0) THEN
268 IF (ntot .GT. (MNC_MAX_PATH-40)) THEN
269 ntot = MNC_MAX_PATH - 40
270 ENDIF
271 DO i = 1,ntot
272 j = ienc(i)
273 mnc_out_path(i:i) = cenc(j:j)
274 ENDDO
275 mnc_out_path((ntot+1):(ntot+1)) = '/'
276 ENDIF
277
278 RETURN
279 END

  ViewVC Help
Powered by ViewVC 1.1.22