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

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

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


Revision 1.36 - (hide annotations) (download)
Sun Sep 29 06:19:38 2013 UTC (10 years, 8 months ago) by dimitri
Branch: MAIN
Changes since 1.35: +13 -9 lines
some fixes to SINGLE_DISK_IO after testing llc_1080 config on pleiades

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

  ViewVC Help
Powered by ViewVC 1.1.22