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

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

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


Revision 1.48 - (show annotations) (download)
Thu Aug 10 15:30:19 2017 UTC (6 years, 8 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, HEAD
Changes since 1.47: +2 -3 lines
remove
#define FMT_PROC_ID 'I9.9'
(now in CPP_EEMARCROS.h) and fix a close statement (srcUnit1->iUnit)
for SINGLE_DISK_IO

1 C $Header: /u/gcmpack/MITgcm/eesupp/src/eeset_parms.F,v 1.47 2017/08/08 15:42:43 mlosch Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5
6 CBOP
7 C !ROUTINE: EESET_PARMS
8
9 C !INTERFACE:
10 SUBROUTINE EESET_PARMS ( procId, doReport )
11
12 C !DESCRIPTION:
13 C *==========================================================*
14 C | SUBROUTINE EESET\_PARMS
15 C | o Routine to set model "parameters"
16 C *==========================================================*
17 C | This routine is called from the high-level wrapper
18 C | after multi-process paralle processing has started but
19 C | before multi-threaded parallelism. THe routine reads an
20 C | an "execution environment" input parameter file holding
21 C | information about the number of threads at run-time.
22 C *==========================================================*
23
24 C !USES:
25 IMPLICIT NONE
26
27 C == Global variables ==
28 #include "SIZE.h"
29 #include "EEPARAMS.h"
30 #include "EESUPPORT.h"
31 #include "EXCH.h"
32
33 C !INPUT PARAMETERS:
34 C procId :: this process id. number (either in World or in Model)
35 C doReport :: if false, skip error stop and any report to std-out/err
36 INTEGER procId
37 LOGICAL doReport
38
39 C !FUNCTIONS:
40 INTEGER IFNBLNK
41 EXTERNAL IFNBLNK
42 INTEGER ILNBLNK
43 EXTERNAL ILNBLNK
44
45 C !LOCAL VARIABLES:
46 C == Local variables ==
47 C iUnit :: Work variable for IO unit number
48 C errIO :: IO unit error flag
49 C IL :: Temp. for index strings
50 C msgBuf :: Temp. for textual I/O
51 C record :: Temp. for textual I/O
52 INTEGER IL
53 INTEGER errIO
54 INTEGER iUnit
55 CHARACTER*(MAX_LEN_MBUF) msgBuf
56 CHARACTER*(MAX_LEN_PREC) record
57 # if !defined(USE_FORTRAN_SCRATCH_FILES) || defined(SINGLE_DISK_IO)
58 CHARACTER*(MAX_LEN_FNAM) scratchFile1
59 CHARACTER*(MAX_LEN_FNAM) scratchFile2
60 #endif
61 #ifdef SINGLE_DISK_IO
62 C mpiRC :: Error code reporting variable used with MPI.
63 INTEGER mpiRC
64 #endif
65 CEOP
66
67 NAMELIST /EEPARMS/
68 & nTx, nTy, usingMPI,
69 & useCubedSphereExchange,
70 & useCoupler, useNEST_PARENT, useNEST_CHILD, useOASIS,
71 & useSETRLSTK, useSIGREG,
72 & debugMode, printMapIncludesZeros, maxLengthPrt1D
73
74 C-- For now these options are fixed as the code does not fully support
75 C features for overlapping communication and computation.
76 usingSyncMessages = .TRUE.
77
78 C-- The remaining parameters here are set to default values; and then
79 C-- any different values are read from an input file called "eedata".
80 C The defaults set here are for serial execution.
81 C
82 C nTx and nTy are the number of threads in the X and Y directions.
83 C nSx/nTx and nSy/nTy be whole numbers at present.
84 C
85 C notUsingXPeriodicity and notUsingYPeriodicity affect the identifying
86 C of neighbor processes in a multi-process mode.
87 C On the whole the numerical model code should not customise itself based
88 C on these numbers as they may be removed if they do not prove useful.
89 C
90 C usingMPI is a flag which controls whether MPI message passing library
91 C calls are actually made. Note that under MPI it is necessary to start
92 C a program a special way - normally using a command of the form
93 C % mpirun program_name
94 C If usingMPI is set to TRUE but % mpirun .... was not used to launch
95 C the program then an internal MPI error may be generated when the first
96 C MPI call ( CALL MPI_Init ) is made.
97 C
98 C useCoupler is a flag which controls communications with other
99 C model components through a coupler interface.
100 C
101 C useSETRLSTK is a flag which toggles calling a small C routine
102 C which sets the stack size to "unlimited" using setrlimit()
103
104 notUsingXPeriodicity = .FALSE.
105 notUsingYPeriodicity = .FALSE.
106 useCubedSphereExchange = .FALSE.
107 #ifdef ALLOW_USE_MPI
108 usingMPI = .TRUE.
109 #else
110 usingMPI = .FALSE.
111 #endif
112 useCoupler = .FALSE.
113 useNEST_PARENT = .FALSE.
114 useNEST_CHILD = .FALSE.
115 useOASIS = .FALSE.
116 nTx = 1
117 nTy = 1
118 useSETRLSTK = .FALSE.
119 useSIGREG = .FALSE.
120
121 C-- Parameter for printing (ascii) to Std-Oupt:
122 C Print debug msg (sequence of S/R calls)
123 debugMode = .FALSE.
124 C Text map plots of fields ignore exact zero values
125 printMapIncludesZeros = .FALSE.
126 C Maximum length for printing (to Std-Msg-Unit) 1-D array
127 maxLengthPrt1D = 65
128
129 C To write output to global-files and from Master MPI process only
130 C NOTE: read from main parameter file "data"
131 useSingleCpuIO = .FALSE.
132
133 C-- Read in data from eedata file
134 C We really ought to be using our environment file reading
135 C package - but we have not written it yet.
136
137 C Make scratch copies of input data file with and without comments
138 #ifdef SINGLE_DISK_IO
139 C Stop if called from eeboot_minimal.F before myProcId is set
140 IF ( .NOT.doReport )
141 & STOP 'ABNORMAL END: S/R EESET_PARMS: myProcId unset'
142 WRITE(scratchFile1,'(A)') 'scratch1'
143 WRITE(scratchFile2,'(A)') 'scratch2'
144 IF( myProcId .EQ. 0 ) THEN
145 OPEN(UNIT=scrUnit1, FILE=scratchFile1, STATUS='UNKNOWN')
146 OPEN(UNIT=scrUnit2, FILE=scratchFile2, STATUS='UNKNOWN')
147 ENDIF
148 #else /* ifndef SINGLE_DISK_IO */
149 # ifdef USE_FORTRAN_SCRATCH_FILES
150 C this is the old default, which can cause filename conflicts on some
151 C multi-node/multi-processor systems
152 OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
153 OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
154 # else
155 C this definition will go into CPP_EEMACROS.h, once this method is
156 C properly established
157 C After opening regular files here, they are closed with STATUS='DELETE'
158 WRITE(scratchFile1,'(A,'//FMT_PROC_ID//')') 'scratch1.', procId
159 WRITE(scratchFile2,'(A,'//FMT_PROC_ID//')') 'scratch2.', procId
160 OPEN(UNIT=scrUnit1, FILE=scratchFile1, STATUS='UNKNOWN')
161 OPEN(UNIT=scrUnit2, FILE=scratchFile2, STATUS='UNKNOWN')
162 # endif
163 #endif /* SINGLE_DISK_IO */
164
165 #ifdef SINGLE_DISK_IO
166 IF( myProcId .EQ. 0 ) THEN
167 #endif
168
169 OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',
170 & err=1,IOSTAT=errIO)
171 IF ( errIO .GE. 0 ) GOTO 2
172 1 CONTINUE
173 IF ( doReport ) THEN
174 WRITE(msgBuf,'(2A)') 'EESET_PARMS: ',
175 & 'Unable to open parameter file "eedata"'
176 CALL PRINT_ERROR( msgBuf, 1 )
177 CALL EEDATA_EXAMPLE
178 C note: At this early stage, MPI might not be yet fully set-up; for this reason
179 C set error flag and return (to avoid a call to ALL_PROC_DIE before stop)
180 c STOP 'ABNORMAL END: S/R EESET_PARMS'
181 eeBootError = .TRUE.
182 ELSE
183 RETURN
184 ENDIF
185 2 CONTINUE
186 1000 CONTINUE
187 READ(eeDataUnit,FMT='(A)',END=1001) RECORD
188 IL = MAX(ILNBLNK(RECORD),1)
189 IF ( RECORD(1:1) .NE. commentCharacter ) THEN
190 CALL NML_SET_TERMINATOR( RECORD )
191 WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
192 ENDIF
193 WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
194 GOTO 1000
195 1001 CONTINUE
196 CLOSE(eeDataUnit)
197
198 C-- Report contents of parameter file
199 iUnit = scrUnit2
200 IF ( doReport ) THEN
201 WRITE(msgBuf,'(A)')
202 & '// ======================================================='
203 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT, 1)
204 WRITE(msgBuf,'(A)')
205 & '// Execution Environment parameter file "eedata"'
206 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT, 1)
207 WRITE(msgBuf,'(A)')
208 & '// ======================================================='
209 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT, 1)
210
211 REWIND(iUnit)
212 2000 CONTINUE
213 READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
214 IL = MAX(ILNBLNK(RECORD),1)
215 WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
216 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit, SQUEEZE_RIGHT, 1)
217 GOTO 2000
218 2001 CONTINUE
219
220 WRITE(msgBuf,'(A)') ' '
221 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit, SQUEEZE_RIGHT, 1)
222 ENDIF
223 CLOSE(iUnit,STATUS='DELETE')
224
225 #ifdef SINGLE_DISK_IO
226 CALL FLUSH(scrUnit1)
227 CLOSE(scrUnit1)
228 ENDIF
229 # ifdef ALLOW_USE_MPI
230 C-- all processes must wait for process 0 to complete
231 C writing scratchFile1 before opening it
232 IF ( usingMPI ) THEN
233 CALL MPI_BARRIER( MPI_COMM_MODEL, mpiRC )
234 ENDIF
235 # endif
236 #ifdef HAVE_SYSTEM
237 CALL SYSTEM('sleep 1')
238 #endif
239 OPEN(UNIT=scrUnit1, FILE=scratchFile1, STATUS='OLD')
240 #endif /* SINGLE_DISK_IO */
241
242 C-- Read namelist
243 iUnit = scrUnit1
244 REWIND(iUnit)
245 READ(UNIT=iUnit,NML=EEPARMS,IOSTAT=errIO,err=3)
246 IF ( errIO .GE. 0 ) GOTO 4
247 3 CONTINUE
248 #ifndef TARGET_PWR3
249 IF ( doReport ) THEN
250 WRITE(msgBuf,'(2A)') 'EESET_PARMS: ',
251 & 'Error reading parameter file "eedata"'
252 CALL PRINT_ERROR( msgBuf, 1 )
253 CALL EEDATA_EXAMPLE
254 eeBootError = .TRUE.
255 ENDIF
256 #endif
257 4 CONTINUE
258
259 C-- Execution Environment parameter file read
260 #ifdef SINGLE_DISK_IO
261 CLOSE(iUnit)
262 #else
263 CLOSE(iUnit,STATUS='DELETE')
264 #endif /* SINGLE_DISK_IO */
265
266 #ifdef ALLOW_USE_MPI
267 #ifdef ALWAYS_USE_MPI
268 IF ( doReport .AND. .NOT.usingMPI ) THEN
269 WRITE(msgBuf,'(2A)') 'EESET_PARMS: ',
270 & 'in eedata: usingMPI=F conflicts'
271 CALL PRINT_ERROR( msgBuf, 1 )
272 WRITE(msgBuf,'(A)') 'EESET_PARMS: with #define ALWAYS_USE_MPI'
273 CALL PRINT_ERROR( msgBuf, 1 )
274 eeBootError = .TRUE.
275 ENDIF
276 usingMPI = .TRUE.
277 #endif
278 #else /* ALLOW_USE_MPI */
279 IF ( doReport .AND. usingMPI ) THEN
280 WRITE(msgBuf,'(2A)') 'EESET_PARMS: ',
281 & 'in eedata: usingMPI=T conflicts'
282 CALL PRINT_ERROR( msgBuf, 1 )
283 WRITE(msgBuf,'(A)') 'EESET_PARMS: with #undef ALLOW_USE_MPI'
284 CALL PRINT_ERROR( msgBuf, 1 )
285 eeBootError = .TRUE.
286 ENDIF
287 usingMPI = .FALSE.
288 #endif /* ALLOW_USE_MPI */
289
290 Cdbg eeDataUnit = 42
291 Cdbg OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',IOSTAT=errIO)
292 Cdbg IF ( errIO .LT. 0 ) GOTO 11
293 Cdbg DO K=1, 10
294 Cdbg READ(eedataUnit,IOSTAT=errIO)
295 Cdbg IF ( errIO .LT. 0 ) GOTO 11
296 Cdbg ENDDO
297 Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingXPeriodicity
298 Cdbg IF ( errIO .LT. 0 ) GOTO 11
299 Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingYPeriodicity
300 Cdbg IF ( errIO .LT. 0 ) GOTO 11
301 Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) usingMPI
302 Cdbg IF ( errIO .LT. 0 ) GOTO 11
303 Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTx
304 Cdbg IF ( errIO .LT. 0 ) GOTO 11
305 Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTy
306
307 Cdbg IF (errIO .LT. 0 ) eeBootError = .TRUE.
308 Cdbg CLOSE(eeDataUnit,IOSTAT=errIO)
309 Cdbg IF ( eeBootError .OR. errIO .LT. 0 ) THEN
310 C-- Report that an error occured
311 Cdbg eeBootError = .TRUE.
312 Cdbg WRITE(msgBuf,'(A)' )
313 Cdbg & 'S/R EESET_PARMS: Error reading "eedata" execution environment file'
314 Cdbg CALL PRINT_ERROR( msgBuf , 1)
315 Cdbg ELSE
316 C-- Write summary of settings that were selected
317 Cdbg ENDIF
318
319 IF ( doReport ) THEN
320 C-- Set parameters for EXCH communication routines
321 C Note: only done once when called with doReport=T
322
323 exchCollectStatistics = .TRUE.
324 C-- Turn off memsync by default (e.g. needed for threads on SUNs)
325 exchNeedsMemsync = .TRUE.
326 exchUsesBarrier = .TRUE.
327 IF ( usingMPI ) THEN
328 C-- ... except that MPI needs this until some counter problem is fixed.
329 exchNeedsMemsync = .FALSE.
330 exchUsesBarrier = .FALSE.
331 ENDIF
332
333 C-- End setting parameters for EXCH communication routines
334 ENDIF
335
336 RETURN
337 END

  ViewVC Help
Powered by ViewVC 1.1.22