/[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.16 - (hide annotations) (download)
Tue Feb 24 16:54:46 2004 UTC (20 years, 3 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube5, checkpoint52l_post
Changes since 1.15: +5 -3 lines
Added compile time flag to set namelist terminator __everywhere__ . This allows lf95
to work with appropriate optfile.
Tested on faulks, but this could break on other compilers platforms.

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

  ViewVC Help
Powered by ViewVC 1.1.22