/[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.30 - (show annotations) (download)
Wed Jun 8 01:39:54 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62z, checkpoint63g, checkpoint63, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c
Changes since 1.29: +6 -4 lines
switch reading of debugMode from S/R INI_PARMS, file "data"
 to S/R EESET_PARMS, file "eedata".

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

  ViewVC Help
Powered by ViewVC 1.1.22