/[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.5 - (show annotations) (download)
Sat Sep 5 17:52:13 1998 UTC (25 years, 8 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint15, checkpoint14
Changes since 1.4: +4 -1 lines
Consistent isomorphism changes

1 C $Header: /u/gcmpack/models/MITgcmUV/eesupp/src/eeset_parms.F,v 1.4 1998/08/19 13:57:42 cnh Exp $
2
3 #include "CPP_EEOPTIONS.h"
4
5 CStartOfInterface
6 SUBROUTINE EESET_PARMS
7 C /==========================================================\
8 C | SUBROUTINE EESET_PARMS |
9 C | o Routine to set model "parameters" |
10 C |==========================================================|
11 C | This routine is called from the high-level wrapper |
12 C | after multi-process paralle processing has started but |
13 C | before multi-threaded parallelism. THe routine reads an |
14 C | an "execution environment" input parameter file holding |
15 C | information about the number of threads at run-time. |
16 C \==========================================================/
17
18 C === Global variables ===
19 #include "SIZE.h"
20 #include "EEPARAMS.h"
21 #include "EESUPPORT.h"
22 CEndOfInterface
23
24 C === Local variables ===
25 C K - Loop counter
26 C iUnit - Work variable for IO unit number
27 C errIO - IO unit error flag
28 INTEGER K, IL
29 INTEGER errIO
30 INTEGER iUnit
31 CHARACTER*(MAX_LEN_MBUF) msgBuf
32 CHARACTER*(MAX_LEN_PREC) record
33 INTEGER IFNBLNK
34 EXTERNAL IFNBLNK
35 INTEGER ILNBLNK
36 EXTERNAL ILNBLNK
37 NAMELIST /EEPARMS/
38 & nTx, nTy
39
40
41 C-- For now these options are fixed as the code does
42 C not fully support features for overlapping communication
43 C and computation.
44 usingSyncMessages = .TRUE.
45
46 C-- Text map plots of fields ignore exact zero values
47 printMapIncludesZeros = .FALSE.
48
49 C-- The remaining parameters here are set to default values.
50 C-- and then any different values are read from an input
51 C-- file called "eedata".
52 C The defaults set here are for serial execution.
53 C
54 C nTx and nTy are the number of threads in the X and Y
55 C directions.
56 C nSx/nTx and nSy/nTy be whole numbers at present.
57 C
58 C notUsingXPeriodicity and notUsingYPeriodicity affect
59 C the identifying of neighbor processes in a multi-process
60 C mode. On the whole the numerical model code should not
61 C customise itself based on these numbers as they may be
62 C removed if they do not prove useful.
63 C
64 C usingMPI is a flag which controls whether MPI message
65 C passing library calls are actually made. Note that under
66 C MPI it is necessary to start a program a special way -
67 C normally using a command of the form
68 C % mpirun program_name
69 C If usingMPI is set to TRUE but % mpirun .... was not
70 C used to launch the program then an internal MPI error
71 C may be generated when the first MPI call ( CALL MPI_Init )
72 C is made.
73 C
74 notUsingXPeriodicity = .FALSE.
75 notUsingYPeriodicity = .FALSE.
76 usingMPI = .FALSE.
77 nTx = 2
78 nTy = 2
79
80 C-- Read in data from eedata file
81 C We really ought to be using our environment file reading
82 C package - but we haven't written it yet.
83
84 C Make scratch copies of input data file with and without comments
85 OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
86 OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
87 OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',err=1,IOSTAT=errIO)
88 IF ( errIO .GE. 0 ) GOTO 2
89 1 CONTINUE
90 WRITE(msgBuf,'(A)')
91 & 'S/R EESET_PARMS'
92 CALL PRINT_ERROR( msgBuf , 1)
93 WRITE(msgBuf,'(A)')
94 & 'Unable to open execution environment'
95 CALL PRINT_ERROR( msgBuf , 1)
96 WRITE(msgBuf,'(A)')
97 & 'parameter file "eedata"'
98 CALL PRINT_ERROR( msgBuf , 1)
99 CALL EEDATA_EXAMPLE
100 STOP 'ABNORMAL END: S/R EESET_PARMS'
101 2 CONTINUE
102 1000 CONTINUE
103 READ(eeDataUnit,FMT='(A)',END=1001) RECORD
104 IL = MAX(ILNBLNK(RECORD),1)
105 IF ( RECORD(1:1) .NE. commentCharacter )
106 & WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
107 WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
108 GOTO 1000
109 1001 CONTINUE
110 CLOSE(eeDataUnit)
111 C-- Report contents of parameter file
112 WRITE(msgBuf,'(A)') '// ======================================================='
113 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
114 WRITE(msgBuf,'(A)') '// Execution Environment parameter file "eedata"'
115 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
116 WRITE(msgBuf,'(A)') '// ======================================================='
117 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
118 & SQUEEZE_RIGHT , 1)
119
120 iUnit = scrUnit2
121 REWIND(iUnit)
122 2000 CONTINUE
123 READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
124 IL = MAX(ILNBLNK(RECORD),1)
125 WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
126 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
127 GOTO 2000
128 2001 CONTINUE
129 CLOSE(iUnit)
130
131 WRITE(msgBuf,'(A)') ' '
132 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
133 & SQUEEZE_RIGHT , 1)
134
135 iUnit = scrUnit1
136 REWIND(iUnit)
137 READ(UNIT=iUnit,NML=EEPARMS,IOSTAT=errIO,err=3)
138 IF ( errIO .GE. 0 ) GOTO 4
139 3 CONTINUE
140 WRITE(msgBuf,'(A)')
141 & 'S/R EESET_PARMS'
142 CALL PRINT_ERROR( msgBuf , 1)
143 WRITE(msgBuf,'(A)')
144 & 'Error reading 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 4 CONTINUE
152
153 C-- Execution Environment parameter file read
154 CLOSE(iUnit)
155
156 Cdbg eeDataUnit = 42
157 Cdbg OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',IOSTAT=errIO)
158 Cdbg IF ( errIO .LT. 0 ) GOTO 11
159 Cdbg DO K=1, 10
160 Cdbg READ(eedataUnit,IOSTAT=errIO)
161 Cdbg IF ( errIO .LT. 0 ) GOTO 11
162 Cdbg ENDDO
163 Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingXPeriodicity
164 Cdbg IF ( errIO .LT. 0 ) GOTO 11
165 Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingYPeriodicity
166 Cdbg IF ( errIO .LT. 0 ) GOTO 11
167 Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) usingMPI
168 Cdbg IF ( errIO .LT. 0 ) GOTO 11
169 Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTx
170 Cdbg IF ( errIO .LT. 0 ) GOTO 11
171 Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTy
172
173
174 Cdbg IF (errIO .LT. 0 ) eeBootError = .TRUE.
175 Cdbg CLOSE(eeDataUnit,IOSTAT=errIO)
176 Cdbg IF ( eeBootError .OR. errIO .LT. 0 ) THEN
177 C-- Report that an error occured
178 Cdbg eeBootError = .TRUE.
179 Cdbg WRITE(msgBuf,'(A)' )
180 Cdbg & 'S/R EESET_PARMS: Error reading "eedata" execution environment file'
181 Cdbg CALL PRINT_ERROR( msgBuf , 1)
182 Cdbg ELSE
183 C-- Write summary of settings that were selected
184 Cdbg ENDIF
185 C
186 C
187 RETURN
188 END

  ViewVC Help
Powered by ViewVC 1.1.22