/[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.18 - (hide annotations) (download)
Thu May 13 21:44:59 2004 UTC (20 years ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint57m_post, checkpoint57g_pre, checkpoint57b_post, checkpoint57g_post, checkpoint56b_post, checkpoint54d_post, checkpoint54e_post, checkpoint57d_post, checkpoint57i_post, checkpoint55, checkpoint54, checkpoint57, checkpoint56, checkpoint57n_post, checkpoint54f_post, checkpoint55i_post, checkpoint57l_post, checkpoint55c_post, checkpoint57f_post, checkpoint53d_post, checkpoint57a_post, checkpoint57h_pre, checkpoint54b_post, checkpoint57h_post, checkpoint55g_post, checkpoint57c_post, checkpoint55d_post, checkpoint54a_pre, checkpoint53c_post, checkpoint55d_pre, checkpoint57c_pre, checkpoint55j_post, checkpoint54a_post, checkpoint55h_post, checkpoint57e_post, checkpoint55b_post, checkpoint55f_post, checkpoint53g_post, checkpoint57p_post, eckpoint57e_pre, checkpoint56a_post, checkpoint53f_post, checkpoint57h_done, checkpoint57j_post, checkpoint57f_pre, checkpoint53b_pre, checkpoint56c_post, checkpoint57a_pre, checkpoint55a_post, checkpoint57o_post, checkpoint57k_post, checkpoint53b_post, checkpoint53d_pre, checkpoint55e_post, checkpoint54c_post
Changes since 1.17: +3 -2 lines
o added printMapIncludesZeros to EEPARMS namelist

1 dimitri 1.18 C $Header: /u/gcmpack/MITgcm/eesupp/src/eeset_parms.F,v 1.17 2004/03/27 03:51:51 edhill 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 edhill 1.17 C | SUBROUTINE EESET\_PARMS
16 cnh 1.13 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 dimitri 1.18 & nTx, nTy, usingMPI, useCoupler, useCubedSphereExchange,
49     & printMapIncludesZeros
50 cnh 1.13 CEOP
51 cnh 1.1
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 cnh 1.5
58     C-- Text map plots of fields ignore exact zero values
59     printMapIncludesZeros = .FALSE.
60 cnh 1.1
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 jmc 1.15 C useCoupler is a flag which controls communications with other
87     C model components through a coupler interface.
88     C
89 cnh 1.1 notUsingXPeriodicity = .FALSE.
90     notUsingYPeriodicity = .FALSE.
91 adcroft 1.12 useCubedSphereExchange = .FALSE.
92 cnh 1.1 usingMPI = .FALSE.
93 jmc 1.15 useCoupler = .FALSE.
94 adcroft 1.7 nTx = 1
95     nTy = 1
96 cnh 1.1
97     C-- Read in data from eedata file
98     C We really ought to be using our environment file reading
99 cnh 1.6 C package - but we have not written it yet.
100 cnh 1.1
101     C Make scratch copies of input data file with and without comments
102     OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
103     OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
104 cnh 1.6 OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',
105     & err=1,IOSTAT=errIO)
106 cnh 1.1 IF ( errIO .GE. 0 ) GOTO 2
107     1 CONTINUE
108     WRITE(msgBuf,'(A)')
109     & 'S/R EESET_PARMS'
110     CALL PRINT_ERROR( msgBuf , 1)
111     WRITE(msgBuf,'(A)')
112     & 'Unable to open execution environment'
113     CALL PRINT_ERROR( msgBuf , 1)
114     WRITE(msgBuf,'(A)')
115     & 'parameter file "eedata"'
116     CALL PRINT_ERROR( msgBuf , 1)
117     CALL EEDATA_EXAMPLE
118     STOP 'ABNORMAL END: S/R EESET_PARMS'
119     2 CONTINUE
120     1000 CONTINUE
121     READ(eeDataUnit,FMT='(A)',END=1001) RECORD
122     IL = MAX(ILNBLNK(RECORD),1)
123 cnh 1.16 IF ( RECORD(1:1) .NE. commentCharacter ) THEN
124     CALL NML_SET_TERMINATOR( RECORD )
125     WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
126     ENDIF
127 cnh 1.1 WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
128     GOTO 1000
129     1001 CONTINUE
130     CLOSE(eeDataUnit)
131     C-- Report contents of parameter file
132 cnh 1.6 WRITE(msgBuf,'(A)')
133     & '// ======================================================='
134     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
135     WRITE(msgBuf,'(A)')
136     & '// Execution Environment parameter file "eedata"'
137     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
138     WRITE(msgBuf,'(A)')
139     & '// ======================================================='
140 cnh 1.1 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
141     & SQUEEZE_RIGHT , 1)
142    
143     iUnit = scrUnit2
144     REWIND(iUnit)
145     2000 CONTINUE
146     READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
147     IL = MAX(ILNBLNK(RECORD),1)
148     WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
149 cnh 1.6 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit, SQUEEZE_RIGHT , 1)
150 cnh 1.1 GOTO 2000
151     2001 CONTINUE
152     CLOSE(iUnit)
153    
154     WRITE(msgBuf,'(A)') ' '
155     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
156     & SQUEEZE_RIGHT , 1)
157    
158     iUnit = scrUnit1
159     REWIND(iUnit)
160     READ(UNIT=iUnit,NML=EEPARMS,IOSTAT=errIO,err=3)
161     IF ( errIO .GE. 0 ) GOTO 4
162     3 CONTINUE
163 jamous 1.14 #ifndef TARGET_PWR3
164 cnh 1.1 WRITE(msgBuf,'(A)')
165     & 'S/R EESET_PARMS'
166     CALL PRINT_ERROR( msgBuf , 1)
167     WRITE(msgBuf,'(A)')
168     & 'Error reading execution environment '
169     CALL PRINT_ERROR( msgBuf , 1)
170     WRITE(msgBuf,'(A)')
171     & 'parameter file "eedata"'
172     CALL PRINT_ERROR( msgBuf , 1)
173     CALL EEDATA_EXAMPLE
174     STOP 'ABNORMAL END: S/R EESET_PARMS'
175 jamous 1.14 #endif
176 cnh 1.1 4 CONTINUE
177 cnh 1.4
178     C-- Execution Environment parameter file read
179     CLOSE(iUnit)
180 cnh 1.1
181     Cdbg eeDataUnit = 42
182     Cdbg OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',IOSTAT=errIO)
183     Cdbg IF ( errIO .LT. 0 ) GOTO 11
184     Cdbg DO K=1, 10
185     Cdbg READ(eedataUnit,IOSTAT=errIO)
186     Cdbg IF ( errIO .LT. 0 ) GOTO 11
187     Cdbg ENDDO
188     Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingXPeriodicity
189     Cdbg IF ( errIO .LT. 0 ) GOTO 11
190     Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingYPeriodicity
191     Cdbg IF ( errIO .LT. 0 ) GOTO 11
192     Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) usingMPI
193     Cdbg IF ( errIO .LT. 0 ) GOTO 11
194     Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTx
195     Cdbg IF ( errIO .LT. 0 ) GOTO 11
196     Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTy
197    
198    
199     Cdbg IF (errIO .LT. 0 ) eeBootError = .TRUE.
200     Cdbg CLOSE(eeDataUnit,IOSTAT=errIO)
201     Cdbg IF ( eeBootError .OR. errIO .LT. 0 ) THEN
202     C-- Report that an error occured
203     Cdbg eeBootError = .TRUE.
204     Cdbg WRITE(msgBuf,'(A)' )
205     Cdbg & 'S/R EESET_PARMS: Error reading "eedata" execution environment file'
206     Cdbg CALL PRINT_ERROR( msgBuf , 1)
207     Cdbg ELSE
208     C-- Write summary of settings that were selected
209     Cdbg ENDIF
210     C
211     C
212     RETURN
213     END

  ViewVC Help
Powered by ViewVC 1.1.22