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

Annotation of /MITgcm_contrib/eh3_spgr/hs94.cs-32x32x5/code/eeset_parms.F

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


Revision 1.1 - (hide annotations) (download)
Sun Aug 28 18:18:09 2005 UTC (19 years, 11 months ago) by edhill
Branch: MAIN
CVS Tags: HEAD
 o initial check-in of an example to test some new exch2 bits

1 edhill 1.1 C $Header: /u/gcmpack/MITgcm/eesupp/src/eeset_parms.F,v 1.19 2005/08/05 23:44:28 ce107 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, useAsciiW2Reader
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     notUsingXPeriodicity = .FALSE.
90     notUsingYPeriodicity = .FALSE.
91     useCubedSphereExchange = .FALSE.
92     usingMPI = .FALSE.
93     useCoupler = .FALSE.
94     nTx = 1
95     nTy = 1
96    
97     C useAsciiW2Reader :: flag to specify ASCII input files instead of
98     C the old-style hard-coded parameters for the exch2 topology
99     C information
100     useAsciiW2Reader = .FALSE.
101    
102     C-- Read in data from eedata file
103     C We really ought to be using our environment file reading
104     C package - but we have not written it yet.
105    
106     C Make scratch copies of input data file with and without comments
107     #ifdef TARGET_BGL
108     OPEN(UNIT=scrUnit1,FILE='scratch1',STATUS='UNKNOWN')
109     OPEN(UNIT=scrUnit2,FILE='scratch2',STATUS='UNKNOWN')
110     #else
111     OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
112     OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
113     #endif
114     OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',
115     & err=1,IOSTAT=errIO)
116     IF ( errIO .GE. 0 ) GOTO 2
117     1 CONTINUE
118     WRITE(msgBuf,'(A)')
119     & 'S/R EESET_PARMS'
120     CALL PRINT_ERROR( msgBuf , 1)
121     WRITE(msgBuf,'(A)')
122     & 'Unable to open execution environment'
123     CALL PRINT_ERROR( msgBuf , 1)
124     WRITE(msgBuf,'(A)')
125     & 'parameter file "eedata"'
126     CALL PRINT_ERROR( msgBuf , 1)
127     CALL EEDATA_EXAMPLE
128     STOP 'ABNORMAL END: S/R EESET_PARMS'
129     2 CONTINUE
130     1000 CONTINUE
131     READ(eeDataUnit,FMT='(A)',END=1001) RECORD
132     IL = MAX(ILNBLNK(RECORD),1)
133     IF ( RECORD(1:1) .NE. commentCharacter ) THEN
134     CALL NML_SET_TERMINATOR( RECORD )
135     WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
136     ENDIF
137     WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
138     GOTO 1000
139     1001 CONTINUE
140     CLOSE(eeDataUnit)
141     C-- Report contents of parameter file
142     WRITE(msgBuf,'(A)')
143     & '// ======================================================='
144     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
145     WRITE(msgBuf,'(A)')
146     & '// Execution Environment parameter file "eedata"'
147     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
148     WRITE(msgBuf,'(A)')
149     & '// ======================================================='
150     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
151     & SQUEEZE_RIGHT , 1)
152    
153     iUnit = scrUnit2
154     REWIND(iUnit)
155     2000 CONTINUE
156     READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
157     IL = MAX(ILNBLNK(RECORD),1)
158     WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
159     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit, SQUEEZE_RIGHT , 1)
160     GOTO 2000
161     2001 CONTINUE
162     CLOSE(iUnit)
163    
164     WRITE(msgBuf,'(A)') ' '
165     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
166     & SQUEEZE_RIGHT , 1)
167    
168     iUnit = scrUnit1
169     REWIND(iUnit)
170     READ(UNIT=iUnit,NML=EEPARMS,IOSTAT=errIO,err=3)
171     IF ( errIO .GE. 0 ) GOTO 4
172     3 CONTINUE
173     #ifndef TARGET_PWR3
174     WRITE(msgBuf,'(A)')
175     & 'S/R EESET_PARMS'
176     CALL PRINT_ERROR( msgBuf , 1)
177     WRITE(msgBuf,'(A)')
178     & 'Error reading execution environment '
179     CALL PRINT_ERROR( msgBuf , 1)
180     WRITE(msgBuf,'(A)')
181     & 'parameter file "eedata"'
182     CALL PRINT_ERROR( msgBuf , 1)
183     CALL EEDATA_EXAMPLE
184     STOP 'ABNORMAL END: S/R EESET_PARMS'
185     #endif
186     4 CONTINUE
187    
188     C-- Execution Environment parameter file read
189     CLOSE(iUnit)
190    
191     Cdbg eeDataUnit = 42
192     Cdbg OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',IOSTAT=errIO)
193     Cdbg IF ( errIO .LT. 0 ) GOTO 11
194     Cdbg DO K=1, 10
195     Cdbg READ(eedataUnit,IOSTAT=errIO)
196     Cdbg IF ( errIO .LT. 0 ) GOTO 11
197     Cdbg ENDDO
198     Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingXPeriodicity
199     Cdbg IF ( errIO .LT. 0 ) GOTO 11
200     Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingYPeriodicity
201     Cdbg IF ( errIO .LT. 0 ) GOTO 11
202     Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) usingMPI
203     Cdbg IF ( errIO .LT. 0 ) GOTO 11
204     Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTx
205     Cdbg IF ( errIO .LT. 0 ) GOTO 11
206     Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTy
207    
208    
209     Cdbg IF (errIO .LT. 0 ) eeBootError = .TRUE.
210     Cdbg CLOSE(eeDataUnit,IOSTAT=errIO)
211     Cdbg IF ( eeBootError .OR. errIO .LT. 0 ) THEN
212     C-- Report that an error occured
213     Cdbg eeBootError = .TRUE.
214     Cdbg WRITE(msgBuf,'(A)' )
215     Cdbg & 'S/R EESET_PARMS: Error reading "eedata" execution environment file'
216     Cdbg CALL PRINT_ERROR( msgBuf , 1)
217     Cdbg ELSE
218     C-- Write summary of settings that were selected
219     Cdbg ENDIF
220     C
221     C
222     RETURN
223     END

  ViewVC Help
Powered by ViewVC 1.1.22