/[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.3 - (hide annotations) (download)
Mon Mar 22 05:10:10 2004 UTC (20 years, 3 months ago) by edhill
Branch: MAIN
Changes since 1.2: +46 -1 lines
 o C code to create a directory (eg. "mnc_20040322_0001") with a name
   based on the creation date and a sequence number

1 edhill 1.3 C $Header: /u/gcmpack/MITgcm/pkg/mnc/mnc_readparms.F,v 1.2 2004/03/20 20:35:21 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    
8     SUBROUTINE MNC_READPARMS( myThid )
9    
10     implicit none
11    
12     #include "SIZE.h"
13     #include "mnc_common.h"
14     #include "EEPARAMS.h"
15     #include "PARAMS.h"
16    
17     C Arguments
18     integer myThid
19    
20     C Functions
21     integer ILNBLNK
22    
23     C Local Variables
24 edhill 1.2 integer i, iUnit, nl, isu1,isu2,mdu, errio, IL
25     character*(MAX_LEN_MBUF) data_file
26 edhill 1.1 character*(MAX_LEN_MBUF) msgBuf
27 edhill 1.2 CHARACTER*(MAX_LEN_PREC) record
28     NAMELIST /MNC_01/
29     & useMNC,
30 edhill 1.1 & mnc_echo_gtypes,
31     & mnc_pickup_create,
32     & mnc_pickup_read
33 edhill 1.2 LOGICAL exst
34 edhill 1.1
35     C Default values MNC
36 edhill 1.2 useMNC = .FALSE.
37     mnc_echo_gtypes = .FALSE.
38 edhill 1.1 mnc_pickup_create = .FALSE.
39     mnc_pickup_read = .FALSE.
40    
41 edhill 1.2 C Set the file name
42     DO i=1,MAX_LEN_MBUF
43     data_file(i:i) = ' '
44     ENDDO
45     WRITE(data_file,'(a)') 'data.mnc'
46     nl = ILNBLNK(data_file)
47    
48     C Verify that the file exists and, if not, disable MNC
49     INQUIRE( FILE=data_file, EXIST=exst )
50     IF (exst) THEN
51     WRITE(msgbuf,'(3a)')
52     & ' MNC_READPARMS: opening file ''',
53     & data_file(1:nl), ''''
54     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
55     & SQUEEZE_RIGHT , mythid)
56     ELSE
57     WRITE(msgBuf,'(3a)')
58     & 'Data file: ''',data_file(1:nl),
59     & ''' does not exist so MNC will be disabled'
60     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
61     & SQUEEZE_RIGHT , mythid)
62     RETURN
63     ENDIF
64    
65     C Open files
66     isu1 = 60
67     isu2 = 61
68     mdu = 62
69     OPEN(UNIT=isu1, STATUS='SCRATCH')
70     OPEN(UNIT=isu2, STATUS='SCRATCH')
71     OPEN(UNIT=mdu, FILE=data_file, STATUS='OLD', IOSTAT=errio)
72     IF ( errio .LT. 0 ) THEN
73     WRITE(msgBuf,'(3a)')
74     & 'Unable to open data file: ''',data_file(1:nl),
75     & ''' so MNC will be disabled'
76     CALL PRINT_ERROR( msgBuf , 1)
77     STOP 'ABNORMAL END: S/R MNC_READPARMS'
78     RETURN
79     ENDIF
80    
81     DO WHILE ( .TRUE. )
82     READ(mdu,FMT='(A)',END=1001) RECORD
83     IL = MAX(ILNBLNK(RECORD),1)
84     IF ( RECORD(1:1) .NE. commentCharacter ) THEN
85     CALL NML_SET_TERMINATOR( RECORD )
86     WRITE(UNIT=isu1,FMT='(A)') RECORD(:IL)
87     ENDIF
88     WRITE(UNIT=isu2,FMT='(A)') RECORD(:IL)
89     ENDDO
90     1001 CONTINUE
91     CLOSE(mdu)
92    
93     C-- Report contents of model parameter file
94     WRITE(msgBuf,'(A)')
95     & '// ======================================================='
96     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
97     & SQUEEZE_RIGHT , 1)
98     WRITE(msgBuf,'(3a)') '// Parameter file "',data_file(1:nl),'"'
99     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
100     & SQUEEZE_RIGHT , 1)
101     WRITE(msgBuf,'(A)')
102     & '// ======================================================='
103     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
104     & SQUEEZE_RIGHT , 1)
105     iUnit = isu2
106     REWIND(iUnit)
107     DO WHILE ( .TRUE. )
108     READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
109     IL = MAX(ILNBLNK(RECORD),1)
110     WRITE(msgBuf,'(2a)') '>',RECORD(:IL)
111     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
112     & SQUEEZE_RIGHT , 1)
113     ENDDO
114     2001 CONTINUE
115     CLOSE(iUnit)
116     WRITE(msgBuf,'(A)') ' '
117 edhill 1.1 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
118     & SQUEEZE_RIGHT , 1)
119    
120 edhill 1.2 iUnit = isu1
121     REWIND(iUnit)
122     READ(UNIT=iUnit,NML=MNC_01,IOSTAT=errio,err=3)
123     GOTO 4
124     3 CONTINUE
125     WRITE(msgBuf,'(A,A,A)')
126     & 'ERROR: while reading file ''',data_file(1:nl),
127     & ''' -- please check file contents'
128     CALL PRINT_ERROR( msgBuf , 1)
129     STOP 'ABNORMAL END: S/R MNC_READPARMS'
130     4 CONTINUE
131 edhill 1.1
132 edhill 1.2 WRITE(msgBuf,'(a)') ' MNC_READPARMS: finished reading data.mnc'
133     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
134     & SQUEEZE_RIGHT , 1)
135 edhill 1.3
136     CALL MNC_SET_OUTDIR(myThid)
137    
138     RETURN
139     END
140    
141     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
142    
143     SUBROUTINE MNC_SET_OUTDIR( myThid )
144    
145     implicit none
146    
147     #include "SIZE.h"
148     #include "mnc_common.h"
149     #include "EEPARAMS.h"
150     #include "PARAMS.h"
151    
152     C Arguments
153     integer myThid
154    
155     C Functions
156     integer ILNBLNK
157    
158     C Local Variables
159     integer i, nstr, iodate, ioseq, num
160    
161     #define HAVE_MNCCDIR
162     #ifdef HAVE_MNCCDIR
163     CALL mnccdir(iodate, ioseq)
164     #else
165     iodate = 1
166     ioseq = 1
167     #endif
168    
169     DO i = 1,MNC_MAX_CHAR
170     mnc_out_path(i:i) = ' '
171     ENDDO
172     WRITE(mnc_out_path,'(a4,i8,a1,i4,a1)')
173     & 'mnc_', iodate, '_', ioseq, '/'
174     nstr = ILNBLNK(mnc_out_path)
175     DO i = 1,nstr
176     IF (mnc_out_path(i:i) .EQ. ' ') mnc_out_path(i:i) = '0'
177     ENDDO
178     num = ILNBLNK(mnc_out_path)
179     write(*,*) 'mnc_out_path = ', mnc_out_path(1:num)
180 edhill 1.1
181     RETURN
182     END
183    
184     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22