/[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.9 - (hide annotations) (download)
Fri Sep 10 12:19:30 2004 UTC (19 years, 9 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint55c_post, checkpoint55b_post, checkpoint55, checkpoint54f_post, checkpoint55a_post
Changes since 1.8: +13 -8 lines
 o overhaul of IO so that we now have flags for MDSIO and/or MNC
   - all verification tests compile and run with linux_ia32_g77
   - defaults are compatible with current input files--nothing
     should change if you were not previously using MNC
   - MNC output has been added in numerous places (eg. timeave)
     but there are still a few writes not yet do-able with MNC
     (this is in progress)
   - flags now allow for either/or/both use of MDSIO and MNC and
     documentation will soon follow
   - numerous small formatting cleanups for ProTeX

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

  ViewVC Help
Powered by ViewVC 1.1.22