/[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.22 - (show annotations) (download)
Wed Jan 11 06:02:31 2006 UTC (18 years, 5 months ago) by edhill
Branch: MAIN
Changes since 1.21: +6 -2 lines
o add "--embed-source" option to genmake2 which, when the supporting
  tools can be compiled (as determined by genmake2) will turn on the
  embed_files package which then embeds the entire MITgcm source code
  (*.[fFhc] + Makefile) used for the build within the executable
  - requested by CNH but off by default
  - adds a paltry <9MB to the mitgcmuv executable in most cases
  - only writes the output when useEMBEDSRC in eedata is true

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

  ViewVC Help
Powered by ViewVC 1.1.22