/[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.20 - (hide annotations) (download)
Sun Sep 11 18:52:26 2005 UTC (18 years, 8 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint57s_post, checkpoint57t_post, checkpoint57v_post, checkpint57u_post, checkpoint57w_post
Changes since 1.19: +6 -2 lines
 o add HAVE_SETRLSTK define and useSETRLSTK flag (eedata) which calls
   a C routine to unlimit the stack size
   - very helpful on clusters of workstations since the ulimit/limit
     behavior can (otherwise) only be inherited from parent processes
     which is difficult with some MPI-over-ssh/rsh implementations

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

  ViewVC Help
Powered by ViewVC 1.1.22