/[MITgcm]/MITgcm/eesupp/src/open_copy_data_file.F
ViewVC logotype

Contents of /MITgcm/eesupp/src/open_copy_data_file.F

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


Revision 1.11 - (show annotations) (download)
Thu Aug 10 15:31:02 2017 UTC (6 years, 9 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, HEAD
Changes since 1.10: +13 -10 lines
  - change default for opening scratch files to avoid STATUS='SCRATCH'
  - close scratch files with STATUS='DELELTE'
  - you can revert to old default by setting USE_FORTRAN_SCRATCH_FILES
    in CPP_EEOPTIONS.h (tested in lab_sea/code_ad)

1 C $Header: /u/gcmpack/MITgcm/eesupp/src/open_copy_data_file.F,v 1.10 2017/01/10 23:02:52 jmc Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5
6 CBOP
7 C !ROUTINE: OPEN_COPY_DATA_FILE
8 C !INTERFACE:
9 SUBROUTINE OPEN_COPY_DATA_FILE(
10 I data_file, caller_sub,
11 O iUnit,
12 I myThid )
13 C !DESCRIPTION: \bv
14 C *==========================================================*
15 C | SUBROUTINE OPEN_COPY_DATA_FILE
16 C | o Routine to open and copy a data.* file to STDOUT
17 C | and return the open unit in iUnit
18 C *==========================================================*
19 C \ev
20
21 C !USES:
22 IMPLICIT NONE
23 C === Global variables ===
24 #include "SIZE.h"
25 #include "EEPARAMS.h"
26 #ifdef SINGLE_DISK_IO
27 # include "EESUPPORT.h"
28 #endif
29
30 C !INPUT/OUTPUT PARAMETERS:
31 C === Routine arguments ===
32 C data_file :: parameter file to open and copy
33 C caller_sub :: name of subroutine which is calling this S/R
34 C iUnit :: IO unit of parameter-file copy (already opened)
35 C myThid :: my Thread Id number
36 CHARACTER*(*) data_file
37 CHARACTER*(*) caller_sub
38 INTEGER iUnit
39 INTEGER myThid
40
41 C !FUNCTIONS:
42 INTEGER ILNBLNK
43 EXTERNAL ILNBLNK
44
45 C !LOCAL VARIABLES:
46 C === Local variables ===
47 C msgBuf :: Informational/error message buffer
48 CHARACTER*(MAX_LEN_MBUF) msgBuf
49 CHARACTER*(MAX_LEN_PREC) record
50 #if !defined(USE_FORTRAN_SCRATCH_FILES) || defined(SINGLE_DISK_IO)
51 CHARACTER*(MAX_LEN_FNAM) scratchFile1
52 CHARACTER*(MAX_LEN_FNAM) scratchFile2
53 #endif
54 INTEGER errIO,IL
55 LOGICAL exst
56 #ifdef SINGLE_DISK_IO
57 C mpiRC :: Error code reporting variable used with MPI.
58 INTEGER mpiRC
59 #endif
60 CEOP
61
62 _BEGIN_MASTER(myThid)
63
64 C-- Open the parameter file
65 INQUIRE( FILE=data_file, EXIST=exst )
66 IF (exst) THEN
67 WRITE(msgBuf,'(A,A)')
68 & ' OPEN_COPY_DATA_FILE: opening file ',data_file
69 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
70 & SQUEEZE_RIGHT, myThid )
71 ELSE
72 WRITE(msgBuf,'(A,A,A)')
73 & 'File ',data_file,' does not exist!'
74 CALL PRINT_ERROR( msgBuf, myThid )
75 WRITE(msgBuf,'(A,A)') 'S/R CALLED BY ',caller_sub
76 CALL PRINT_ERROR( msgBuf, myThid )
77 STOP 'ABNORMAL END: S/R OPEN_COPY_DATA_FILE'
78 ENDIF
79
80 C Make scratch copies of eedata with and without comments
81 #ifdef SINGLE_DISK_IO
82 WRITE(scratchFile1,'(A,A)') 'scratch1_', data_file
83 WRITE(scratchFile2,'(A,A)') 'scratch2_', data_file
84 IF ( myProcId .EQ. 0 ) THEN
85 OPEN(UNIT=scrUnit1, FILE=scratchFile1, STATUS='UNKNOWN')
86 OPEN(UNIT=scrUnit2, FILE=scratchFile2, STATUS='UNKNOWN')
87 ENDIF
88 #else /* ifndef SINGLE_DISK_IO */
89 #ifdef USE_FORTRAN_SCRATCH_FILES
90 C this is the old default, which can cause filename conflicts on some
91 C multi-node/multi-processor systems
92 OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
93 OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
94 #else
95 C After opening regular files here, they are closed with STATUS='DELETE'
96 WRITE(scratchFile1,'(A,'//FMT_PROC_ID//')') 'scratch1.', myProcId
97 WRITE(scratchFile2,'(A,'//FMT_PROC_ID//')') 'scratch2.', myProcId
98 OPEN(UNIT=scrUnit1, FILE=scratchFile1, STATUS='UNKNOWN')
99 OPEN(UNIT=scrUnit2, FILE=scratchFile2, STATUS='UNKNOWN')
100 #endif /* USE_FORTRAN_SCRATCH_FILES */
101 #endif /* SINGLE_DISK_IO */
102
103 #ifdef SINGLE_DISK_IO
104 IF ( myProcId .EQ. 0 ) THEN
105 #endif
106
107 OPEN(UNIT=modelDataUnit,FILE=data_file,STATUS='OLD',
108 & IOSTAT=errIO)
109 IF ( errIO .LT. 0 ) THEN
110 WRITE(msgBuf,'(A,A)')
111 & 'Unable to open parameter file: ',data_file
112 CALL PRINT_ERROR( msgBuf, myThid )
113 WRITE(msgBuf,'(A,A)') 'S/R CALLED BY ',caller_sub
114 CALL PRINT_ERROR( msgBuf, myThid )
115 STOP 'ABNORMAL END: S/R OPEN_COPY_DATA_FILE'
116 ENDIF
117
118 DO WHILE ( .TRUE. )
119 READ(modelDataUnit,FMT='(A)',END=1001) RECORD
120 IL = MAX(ILNBLNK(RECORD),1)
121 IF ( RECORD(1:1) .NE. commentCharacter ) THEN
122 c CALL NML_SET_TERMINATOR( RECORD )
123 CALL NML_CHANGE_SYNTAX( RECORD, data_file, myThid )
124 WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
125 ENDIF
126 WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
127 ENDDO
128 1001 CONTINUE
129 CLOSE(modelDataUnit)
130
131 C-- Report contents of model parameter file
132 WRITE(msgBuf,'(A)')
133 &'// ======================================================='
134 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
135 & SQUEEZE_RIGHT, myThid )
136 WRITE(msgBuf,'(A,A,A)') '// Parameter file "',data_file,'"'
137 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
138 & SQUEEZE_RIGHT, myThid )
139 WRITE(msgBuf,'(A)')
140 &'// ======================================================='
141 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
142 & SQUEEZE_RIGHT, myThid )
143 iUnit = scrUnit2
144 REWIND(iUnit)
145 DO WHILE ( .TRUE. )
146 READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
147 IL = MAX(ILNBLNK(RECORD),1)
148 WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
149 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
150 & SQUEEZE_RIGHT, myThid )
151 ENDDO
152 2001 CONTINUE
153 CLOSE(iUnit,STATUS='DELETE')
154 WRITE(msgBuf,'(A)') ' '
155 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
156 & SQUEEZE_RIGHT, myThid )
157
158 #ifdef SINGLE_DISK_IO
159 CALL FLUSH(scrUnit1)
160 CLOSE(scrUnit1)
161 ENDIF
162 # ifdef ALLOW_USE_MPI
163 C-- all processes must wait for process 0 to complete
164 C writing scratchFile1 before opening it
165 IF ( usingMPI ) THEN
166 CALL MPI_BARRIER( MPI_COMM_MODEL, mpiRC )
167 ENDIF
168 # endif
169 #ifdef HAVE_SYSTEM
170 CALL SYSTEM('sleep 1')
171 #endif
172 OPEN(UNIT=scrUnit1, FILE=scratchFile1, STATUS='OLD')
173 #endif /* SINGLE_DISK_IO */
174
175 C-- Return open unit to caller
176 iUnit = scrUnit1
177 REWIND(iUnit)
178
179 _END_MASTER(myThid)
180
181 RETURN
182 END

  ViewVC Help
Powered by ViewVC 1.1.22