/[MITgcm]/MITgcm/pkg/mnc/mnc_readparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/mnc/mnc_readparms.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.13 - (hide annotations) (download)
Mon Oct 18 16:04:20 2004 UTC (19 years, 7 months ago) by edhill
Branch: MAIN
Changes since 1.12: +12 -12 lines
 o remove all the *_ioinc flags and replace them with the single global
   outputTypesInclusive flag

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

  ViewVC Help
Powered by ViewVC 1.1.22