/[MITgcm]/MITgcm_contrib/nesting_sannino/code_nest_merged/eeset_parms.F
ViewVC logotype

Contents of /MITgcm_contrib/nesting_sannino/code_nest_merged/eeset_parms.F

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


Revision 1.3 - (show annotations) (download)
Tue Nov 24 18:05:40 2009 UTC (16 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: HEAD
Changes since 1.2: +1 -1 lines
FILE REMOVED
specific version no longer needed after merging into main code.

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

  ViewVC Help
Powered by ViewVC 1.1.22