/[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.11 - (hide annotations) (download)
Sun Feb 4 14:38:43 2001 UTC (23 years, 3 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint38, c37_adj, checkpoint39, checkpoint37, checkpoint36, checkpoint35
Branch point for: pre38
Changes since 1.10: +2 -1 lines
Made sure each .F and .h file had
the CVS keywords Header and Name at its start.
Most had header but very few currently have Name, so
lots of changes!

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

  ViewVC Help
Powered by ViewVC 1.1.22