/[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.34 - (show annotations) (download)
Tue Mar 16 00:16:50 2010 UTC (14 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64x, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.33: +2 -2 lines
avoid unbalanced quote (single or double) in commented line

1 C $Header: /u/gcmpack/MITgcm/pkg/mnc/mnc_readparms.F,v 1.33 2009/06/14 15:36:01 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 !LOCAL VARIABLES:
37 integer i, nl, ku
38 character*(MAX_LEN_MBUF) data_file
39 character*(MAX_LEN_MBUF) msgBuf
40 NAMELIST /MNC_01/
41 & mnc_use_indir, mnc_use_outdir, mnc_outdir_date,
42 & mnc_outdir_num, mnc_use_name_ni0, mnc_echo_gvtypes,
43 & pickup_write_mnc, pickup_read_mnc,
44 & timeave_mnc, snapshot_mnc, monitor_mnc, autodiff_mnc,
45 & writegrid_mnc, readgrid_mnc,
46 & mnc_outdir_str, mnc_indir_str, mnc_max_fsize,
47 & mnc_filefreq,
48 & mnc_read_bathy, mnc_read_salt, mnc_read_theta
49
50 C Functions
51 integer ILNBLNK
52
53 C-----
54 C Need some work to make MNC multi-threaded safe.
55 C For now, switch it off (otherwise, it is hanging up somewhere)
56 IF ( nThreads.GT.1 ) THEN
57 _BARRIER
58 _BEGIN_MASTER( myThid )
59 WRITE(msgBuf,'(2A)') '**WARNING** MNC_READPARMS: ',
60 & 'useMNC unsafe with multi-threads'
61 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
62 & SQUEEZE_RIGHT , myThid )
63 WRITE(msgBuf,'(2A)') '**WARNING** MNC_READPARMS: ',
64 & 'for now, switch useMNC to FALSE'
65 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
66 & SQUEEZE_RIGHT , myThid )
67 useMNC = .FALSE.
68 _END_MASTER( myThid )
69 _BARRIER
70 RETURN
71 ENDIF
72 C-----
73
74 C Set default values for MNC run-time parameters
75 DO i = 1,MAX_LEN_FNAM
76 mnc_outdir_str(i:i) = ' '
77 mnc_indir_str(i:i) = ' '
78 ENDDO
79 mnc_echo_gvtypes = .FALSE.
80 mnc_use_outdir = .FALSE.
81 mnc_outdir_str(1:4) = 'mnc_'
82 mnc_outdir_date = .FALSE.
83 mnc_outdir_num = .TRUE.
84 mnc_use_name_ni0 = .FALSE.
85 pickup_write_mnc = .TRUE.
86 pickup_read_mnc = .TRUE.
87 mnc_use_indir = .FALSE.
88 mnc_indir_str(1:4) = ' '
89 monitor_mnc = .TRUE.
90 timeave_mnc = .TRUE.
91 snapshot_mnc = .TRUE.
92 autodiff_mnc = .TRUE.
93 writegrid_mnc = .TRUE.
94 C 2GB is 2147483648 bytes or approx: 2.1475e+09
95 mnc_max_fsize = 2.1 _d 9
96 readgrid_mnc = .FALSE.
97
98 C New parms for initial files
99 mnc_read_bathy = .FALSE.
100 mnc_read_salt = .FALSE.
101 mnc_read_theta = .FALSE.
102
103 C Temporary hack for Baylor
104 mnc_filefreq = -1
105
106 C Set the file name
107 DO i=1,MAX_LEN_MBUF
108 data_file(i:i) = ' '
109 ENDDO
110 WRITE(data_file,'(a)') 'data.mnc'
111 nl = ILNBLNK(data_file)
112
113 WRITE(msgbuf,'(3a)') ' MNC_READPARMS: opening file ''',
114 & data_file(1:nl), ''''
115 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
116 & SQUEEZE_RIGHT,mythid)
117
118 CALL OPEN_COPY_DATA_FILE(data_file(1:nl),'MNC_READPARMS',
119 & ku, myThid )
120 READ(ku,NML=MNC_01)
121 CLOSE(ku)
122
123 WRITE(msgBuf,'(a)') ' MNC_READPARMS: finished reading data.mnc'
124 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
125 & SQUEEZE_RIGHT,mythid)
126
127 C Pickups must always be read in an EXCLUSIVE fashion
128 IF (pickup_read_mnc) pickup_read_mdsio = .FALSE.
129
130 C IO handling is done in one of two senses:
131 C (1) outputTypesInclusive=.TRUE. is an "inclusive-or" meaning that
132 C one or more write methods can occur simultaneously or
133 C (2) outputTypesInclusive=.FALSE. is an "exclusive-or" meaning that
134 C only one write method can occur in a given run
135 C
136 C Since all the *_mdsio flags default to .TRUE. and
137 C outputTypesInclusive defaults to .FALSE., the logic here is
138 C simple:
139 IF ( (.NOT. outputTypesInclusive)
140 & .AND. pickup_write_mnc ) pickup_write_mdsio = .FALSE.
141 IF ( (.NOT. outputTypesInclusive)
142 & .AND. timeave_mnc ) timeave_mdsio = .FALSE.
143 IF ( (.NOT. outputTypesInclusive)
144 & .AND. snapshot_mnc ) snapshot_mdsio = .FALSE.
145 IF ( (.NOT. outputTypesInclusive)
146 & .AND. monitor_mnc ) monitor_stdio = .FALSE.
147
148 C Reads are always an exclusive relationship
149 IF (pickup_read_mnc) pickup_read_mdsio = .FALSE.
150
151 C Create and/or set the MNC output directory
152 IF (mnc_use_outdir) THEN
153 IF ( mnc_outdir_num .OR. mnc_outdir_date ) THEN
154 CALL MNC_SET_OUTDIR(myThid)
155 ELSE
156 DO i = 1,MNC_MAX_CHAR
157 mnc_out_path(i:i) = ' '
158 ENDDO
159 write(mnc_out_path,'(2A)')
160 & mnc_outdir_str(1:ILNBLNK(mnc_outdir_str)), '/'
161 ENDIF
162 ENDIF
163
164 RETURN
165 END
166
167 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
168 CBOP 1
169 C !ROUTINE: MNC_SET_OUTDIR
170
171 C !INTERFACE:
172 SUBROUTINE MNC_SET_OUTDIR( myThid )
173
174 C !DESCRIPTION:
175 C Create the output (sub--)directory for the MNC output files.
176
177 C !USES:
178 implicit none
179 #include "MNC_COMMON.h"
180 #include "SIZE.h"
181 #include "EEPARAMS.h"
182 #include "PARAMS.h"
183 #include "MNC_PARAMS.h"
184
185 C !INPUT PARAMETERS:
186 integer myThid
187 CEOP
188
189 C !LOCAL VARIABLES:
190 integer i,j,k, ntot, npathd, idate
191 character*(MNC_MAX_PATH) pathd
192 character*(100) cenc
193 integer ienc(MNC_MAX_PATH)
194 integer ncenc
195
196 C Functions
197 integer ILNBLNK
198
199 cenc(1:26) = 'abcdefghijklmnopqrstuvwxyz'
200 cenc(27:52) = 'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
201 cenc(53:70) = '0123456789_.,+-=/~'
202 ncenc = 70
203 npathd = 100
204 IF (mnc_outdir_date) THEN
205 idate = 1
206 ELSE
207 idate = 0
208 ENDIF
209 DO i = 1,MNC_MAX_PATH
210 pathd(i:i) = ' '
211 ENDDO
212 k = ILNBLNK(mnc_outdir_str)
213 IF (k .GT. MNC_MAX_PATH) k = MNC_MAX_PATH
214 pathd(1:k) = mnc_outdir_str(1:k)
215 ntot = 0
216 DO i = 1,k
217 DO j = 1,ncenc
218 IF (pathd(i:i) .EQ. cenc(j:j)) THEN
219 ntot = ntot + 1
220 ienc(ntot) = j
221 GOTO 20
222 ENDIF
223 ENDDO
224 20 CONTINUE
225 ENDDO
226
227 CALL mnccdir(ntot, ienc, idate)
228
229 DO i = 1,MNC_MAX_PATH
230 mnc_out_path(i:i) = ' '
231 ENDDO
232 IF (ntot .GT. 0) THEN
233 IF (ntot .GT. (MNC_MAX_PATH-40)) THEN
234 ntot = MNC_MAX_PATH - 40
235 ENDIF
236 DO i = 1,ntot
237 j = ienc(i)
238 mnc_out_path(i:i) = cenc(j:j)
239 ENDDO
240 mnc_out_path((ntot+1):(ntot+1)) = '/'
241 ENDIF
242
243 RETURN
244 END
245
246 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22