/[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.30 - (show annotations) (download)
Sun Nov 5 18:36:06 2006 UTC (17 years, 7 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58x_post, checkpoint58t_post, checkpoint59q, checkpoint59p, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint59, checkpoint58y_post, checkpoint58v_post, checkpoint58s_post
Changes since 1.29: +8 -2 lines
add ability to read bathy, salt, and theta using MNC (off by def)
  -- and this can be readily extended to most of the other files
  in PARM05 of the main "data" namelist file

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

  ViewVC Help
Powered by ViewVC 1.1.22