/[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.33 - (hide annotations) (download)
Tue Apr 3 00:08:10 2012 UTC (12 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o
Changes since 1.32: +8 -8 lines
set error flag and return ; otherwise would need to call ALL_PROC_DIE
 (but might be too early here) before the STOP.

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

  ViewVC Help
Powered by ViewVC 1.1.22