/[MITgcm]/MITgcm/eesupp/src/eeset_parms.F
ViewVC logotype

Annotation of /MITgcm/eesupp/src/eeset_parms.F

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


Revision 1.4 - (hide annotations) (download)
Wed Aug 19 13:57:42 1998 UTC (25 years, 9 months ago) by cnh
Branch: MAIN
Changes since 1.3: +4 -1 lines
Added close statement for unit from which eedata is read

1 cnh 1.4 C $Header: /u/gcmpack/models/MITgcmUV/eesupp/src/eeset_parms.F,v 1.3 1998/04/23 20:56:54 cnh Exp $
2 cnh 1.1
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-- The remaining parameters here are set to default values.
47     C-- and then any different values are read from an input
48     C-- file called "eedata".
49     C The defaults set here are for serial execution.
50     C
51     C nTx and nTy are the number of threads in the X and Y
52     C directions.
53     C nSx/nTx and nSy/nTy be whole numbers at present.
54     C
55     C notUsingXPeriodicity and notUsingYPeriodicity affect
56     C the identifying of neighbor processes in a multi-process
57     C mode. On the whole the numerical model code should not
58     C customise itself based on these numbers as they may be
59     C removed if they do not prove useful.
60     C
61     C usingMPI is a flag which controls whether MPI message
62     C passing library calls are actually made. Note that under
63     C MPI it is necessary to start a program a special way -
64     C normally using a command of the form
65     C % mpirun program_name
66     C If usingMPI is set to TRUE but % mpirun .... was not
67     C used to launch the program then an internal MPI error
68     C may be generated when the first MPI call ( CALL MPI_Init )
69     C is made.
70     C
71     notUsingXPeriodicity = .FALSE.
72     notUsingYPeriodicity = .FALSE.
73     usingMPI = .FALSE.
74     nTx = 2
75     nTy = 2
76    
77     C-- Read in data from eedata file
78     C We really ought to be using our environment file reading
79     C package - but we haven't written it yet.
80    
81     C Make scratch copies of input data file with and without comments
82     OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
83     OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
84     OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',err=1,IOSTAT=errIO)
85     IF ( errIO .GE. 0 ) GOTO 2
86     1 CONTINUE
87     WRITE(msgBuf,'(A)')
88     & 'S/R EESET_PARMS'
89     CALL PRINT_ERROR( msgBuf , 1)
90     WRITE(msgBuf,'(A)')
91     & 'Unable to open execution environment'
92     CALL PRINT_ERROR( msgBuf , 1)
93     WRITE(msgBuf,'(A)')
94     & 'parameter file "eedata"'
95     CALL PRINT_ERROR( msgBuf , 1)
96     CALL EEDATA_EXAMPLE
97     STOP 'ABNORMAL END: S/R EESET_PARMS'
98     2 CONTINUE
99     1000 CONTINUE
100     READ(eeDataUnit,FMT='(A)',END=1001) RECORD
101     IL = MAX(ILNBLNK(RECORD),1)
102     IF ( RECORD(1:1) .NE. commentCharacter )
103     & WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
104     WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
105     GOTO 1000
106     1001 CONTINUE
107     CLOSE(eeDataUnit)
108     C-- Report contents of parameter file
109     WRITE(msgBuf,'(A)') '// ======================================================='
110     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
111     WRITE(msgBuf,'(A)') '// Execution Environment parameter file "eedata"'
112     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
113     WRITE(msgBuf,'(A)') '// ======================================================='
114     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
115     & SQUEEZE_RIGHT , 1)
116    
117     iUnit = scrUnit2
118     REWIND(iUnit)
119     2000 CONTINUE
120     READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
121     IL = MAX(ILNBLNK(RECORD),1)
122     WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
123     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
124     GOTO 2000
125     2001 CONTINUE
126     CLOSE(iUnit)
127    
128     WRITE(msgBuf,'(A)') ' '
129     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
130     & SQUEEZE_RIGHT , 1)
131    
132     iUnit = scrUnit1
133     REWIND(iUnit)
134     READ(UNIT=iUnit,NML=EEPARMS,IOSTAT=errIO,err=3)
135     IF ( errIO .GE. 0 ) GOTO 4
136     3 CONTINUE
137     WRITE(msgBuf,'(A)')
138     & 'S/R EESET_PARMS'
139     CALL PRINT_ERROR( msgBuf , 1)
140     WRITE(msgBuf,'(A)')
141     & 'Error reading execution environment '
142     CALL PRINT_ERROR( msgBuf , 1)
143     WRITE(msgBuf,'(A)')
144     & 'parameter file "eedata"'
145     CALL PRINT_ERROR( msgBuf , 1)
146     CALL EEDATA_EXAMPLE
147     STOP 'ABNORMAL END: S/R EESET_PARMS'
148     4 CONTINUE
149 cnh 1.4
150     C-- Execution Environment parameter file read
151     CLOSE(iUnit)
152 cnh 1.1
153     Cdbg eeDataUnit = 42
154     Cdbg OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',IOSTAT=errIO)
155     Cdbg IF ( errIO .LT. 0 ) GOTO 11
156     Cdbg DO K=1, 10
157     Cdbg READ(eedataUnit,IOSTAT=errIO)
158     Cdbg IF ( errIO .LT. 0 ) GOTO 11
159     Cdbg ENDDO
160     Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingXPeriodicity
161     Cdbg IF ( errIO .LT. 0 ) GOTO 11
162     Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingYPeriodicity
163     Cdbg IF ( errIO .LT. 0 ) GOTO 11
164     Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) usingMPI
165     Cdbg IF ( errIO .LT. 0 ) GOTO 11
166     Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTx
167     Cdbg IF ( errIO .LT. 0 ) GOTO 11
168     Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTy
169    
170    
171     Cdbg IF (errIO .LT. 0 ) eeBootError = .TRUE.
172     Cdbg CLOSE(eeDataUnit,IOSTAT=errIO)
173     Cdbg IF ( eeBootError .OR. errIO .LT. 0 ) THEN
174     C-- Report that an error occured
175     Cdbg eeBootError = .TRUE.
176     Cdbg WRITE(msgBuf,'(A)' )
177     Cdbg & 'S/R EESET_PARMS: Error reading "eedata" execution environment file'
178     Cdbg CALL PRINT_ERROR( msgBuf , 1)
179     Cdbg ELSE
180     C-- Write summary of settings that were selected
181     Cdbg ENDIF
182     C
183     C
184     RETURN
185     END

  ViewVC Help
Powered by ViewVC 1.1.22