/[MITgcm]/MITgcm_contrib/eh3_spgr/hs94.cs-32x32x5/code_v2/eeset_parms.F
ViewVC logotype

Contents of /MITgcm_contrib/eh3_spgr/hs94.cs-32x32x5/code_v2/eeset_parms.F

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


Revision 1.1 - (show annotations) (download)
Fri Sep 23 20:52:00 2005 UTC (19 years, 10 months ago) by edhill
Branch: MAIN
CVS Tags: HEAD
 o initial working version

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

  ViewVC Help
Powered by ViewVC 1.1.22