/[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.34 - (hide annotations) (download)
Sat Sep 1 17:36:24 2012 UTC (11 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64, checkpoint63s, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f
Changes since 1.33: +34 -22 lines
- set exchNeedsMemsync & exchUsesBarrier according to "usingMPI" (instead of
  ALWAYS_USE_MPI) and move it from ini_communication_patterns.F to eeset_parms.F
- move setting of exchCollectStatistics from exch_init.F to eeset_parms.F

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

  ViewVC Help
Powered by ViewVC 1.1.22