/[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.20 - (hide annotations) (download)
Sun Apr 3 05:16:43 2005 UTC (19 years, 2 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint57g_post, checkpoint57g_pre, checkpoint57f_pre, checkpoint57f_post
Changes since 1.19: +5 -2 lines
 o mnc-ifying the seaice package

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

  ViewVC Help
Powered by ViewVC 1.1.22