/[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.9 - (show annotations) (download)
Mon Mar 27 22:25:40 2000 UTC (24 years, 1 month ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint28, checkpoint29, checkpoint27, branch-atmos-merge-freeze, branch-atmos-merge-start, checkpoint26, branch-atmos-merge-shapiro, checkpoint33, checkpoint32, checkpoint31, checkpoint30, branch-atmos-merge-zonalfilt, branch-atmos-merge-phase5, branch-atmos-merge-phase4, branch-atmos-merge-phase7, branch-atmos-merge-phase6, branch-atmos-merge-phase1, branch-atmos-merge-phase3, branch-atmos-merge-phase2
Branch point for: branch-atmos-merge
Changes since 1.8: +2 -3 lines
Removed unused variables and fixed some unitialized variables.

1 C $Header: /u/gcmpack/models/MITgcmUV/eesupp/src/eeset_parms.F,v 1.8 1999/05/18 17:39:21 adcroft 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 IMPLICIT NONE
18
19 C === Global variables ===
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "EESUPPORT.h"
23 CEndOfInterface
24
25 C === Local variables ===
26 C iUnit - Work variable for IO unit number
27 C errIO - IO unit error flag
28 INTEGER 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 = 1
78 nTy = 1
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 have not 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',
88 & err=1,IOSTAT=errIO)
89 IF ( errIO .GE. 0 ) GOTO 2
90 1 CONTINUE
91 WRITE(msgBuf,'(A)')
92 & 'S/R EESET_PARMS'
93 CALL PRINT_ERROR( msgBuf , 1)
94 WRITE(msgBuf,'(A)')
95 & 'Unable to open execution environment'
96 CALL PRINT_ERROR( msgBuf , 1)
97 WRITE(msgBuf,'(A)')
98 & 'parameter file "eedata"'
99 CALL PRINT_ERROR( msgBuf , 1)
100 CALL EEDATA_EXAMPLE
101 STOP 'ABNORMAL END: S/R EESET_PARMS'
102 2 CONTINUE
103 1000 CONTINUE
104 READ(eeDataUnit,FMT='(A)',END=1001) RECORD
105 IL = MAX(ILNBLNK(RECORD),1)
106 IF ( RECORD(1:1) .NE. commentCharacter )
107 & WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
108 WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
109 GOTO 1000
110 1001 CONTINUE
111 CLOSE(eeDataUnit)
112 C-- Report contents of parameter file
113 WRITE(msgBuf,'(A)')
114 & '// ======================================================='
115 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
116 WRITE(msgBuf,'(A)')
117 & '// Execution Environment parameter file "eedata"'
118 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
119 WRITE(msgBuf,'(A)')
120 & '// ======================================================='
121 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
122 & SQUEEZE_RIGHT , 1)
123
124 iUnit = scrUnit2
125 REWIND(iUnit)
126 2000 CONTINUE
127 READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
128 IL = MAX(ILNBLNK(RECORD),1)
129 WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
130 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit, SQUEEZE_RIGHT , 1)
131 GOTO 2000
132 2001 CONTINUE
133 CLOSE(iUnit)
134
135 WRITE(msgBuf,'(A)') ' '
136 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
137 & SQUEEZE_RIGHT , 1)
138
139 iUnit = scrUnit1
140 REWIND(iUnit)
141 READ(UNIT=iUnit,NML=EEPARMS,IOSTAT=errIO,err=3)
142 IF ( errIO .GE. 0 ) GOTO 4
143 3 CONTINUE
144 WRITE(msgBuf,'(A)')
145 & 'S/R EESET_PARMS'
146 CALL PRINT_ERROR( msgBuf , 1)
147 WRITE(msgBuf,'(A)')
148 & 'Error reading execution environment '
149 CALL PRINT_ERROR( msgBuf , 1)
150 WRITE(msgBuf,'(A)')
151 & 'parameter file "eedata"'
152 CALL PRINT_ERROR( msgBuf , 1)
153 CALL EEDATA_EXAMPLE
154 STOP 'ABNORMAL END: S/R EESET_PARMS'
155 4 CONTINUE
156
157 C-- Execution Environment parameter file read
158 CLOSE(iUnit)
159
160 Cdbg eeDataUnit = 42
161 Cdbg OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',IOSTAT=errIO)
162 Cdbg IF ( errIO .LT. 0 ) GOTO 11
163 Cdbg DO K=1, 10
164 Cdbg READ(eedataUnit,IOSTAT=errIO)
165 Cdbg IF ( errIO .LT. 0 ) GOTO 11
166 Cdbg ENDDO
167 Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingXPeriodicity
168 Cdbg IF ( errIO .LT. 0 ) GOTO 11
169 Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingYPeriodicity
170 Cdbg IF ( errIO .LT. 0 ) GOTO 11
171 Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) usingMPI
172 Cdbg IF ( errIO .LT. 0 ) GOTO 11
173 Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTx
174 Cdbg IF ( errIO .LT. 0 ) GOTO 11
175 Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTy
176
177
178 Cdbg IF (errIO .LT. 0 ) eeBootError = .TRUE.
179 Cdbg CLOSE(eeDataUnit,IOSTAT=errIO)
180 Cdbg IF ( eeBootError .OR. errIO .LT. 0 ) THEN
181 C-- Report that an error occured
182 Cdbg eeBootError = .TRUE.
183 Cdbg WRITE(msgBuf,'(A)' )
184 Cdbg & 'S/R EESET_PARMS: Error reading "eedata" execution environment file'
185 Cdbg CALL PRINT_ERROR( msgBuf , 1)
186 Cdbg ELSE
187 C-- Write summary of settings that were selected
188 Cdbg ENDIF
189 C
190 C
191 RETURN
192 END

  ViewVC Help
Powered by ViewVC 1.1.22