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

Contents of /MITgcm/eesupp/src/eeboot_minimal.F

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


Revision 1.31 - (show annotations) (download)
Wed Jul 26 21:23:07 2017 UTC (6 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, HEAD
Changes since 1.30: +6 -5 lines
- add argument "procId" to S/R EESET_PARMS to fix  scratchFile1 & 2 setting
  (case TARGET_BGL or TARGET_CRAYXT) for early call (from eeboot_minimal.F):
  called with myProcId in eeboot.F and with mpiMyWId in eeboot_minimal.F

1 C $Header: /u/gcmpack/MITgcm/eesupp/src/eeboot_minimal.F,v 1.30 2017/06/20 11:32:11 mlosch Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_EEOPTIONS.h"
6
7 CBOP
8 C !ROUTINE: EEBOOT_MINIMAL
9
10 C !INTERFACE:
11 SUBROUTINE EEBOOT_MINIMAL( myComm )
12
13 C !DESCRIPTION:
14 C *==========================================================*
15 C | SUBROUTINE EEBOOT\_MINIMAL
16 C | o Set an initial environment that is predictable i.e.
17 C | behaves in a similar way on all machines and stable.
18 C *==========================================================*
19 C | Under MPI this routine calls MPI\_INIT to setup the
20 C | mpi environment ( on some systems the code is running as
21 C | a single process prior to MPI\_INIT, on others the mpirun
22 C | script has already created multiple processes). Until
23 C | MPI\_Init is called it is unclear what state the
24 C | application is in. Once this routine has been run it is
25 C | "safe" to do things like I/O to report erros and to get
26 C | run parameters.
27 C | Note: This routine can also be compiled with CPP
28 C | directives set so that no multi-processing is initialise.
29 C | This is OK and will work fine.
30 C *==========================================================*
31
32 C !USES:
33 IMPLICIT NONE
34 C == Global data ==
35 #include "SIZE.h"
36 #include "EEPARAMS.h"
37 #include "EESUPPORT.h"
38
39 C !ROUTINE ARGUMENTS
40 C == Routine arguments ==
41 C myComm :: Communicator that is passed down from
42 C upper level driver (if there is one).
43 INTEGER myComm
44
45 C !LOCAL VARIABLES:
46 C == Local variables ==
47 C myThid :: Temp. dummy thread number.
48 C fNam :: Used to build file name for standard and error output.
49 C msgBuf :: Used to build messages for printing.
50 INTEGER myThid
51 #ifdef USE_PDAF
52 CHARACTER*18 fNam
53 #else
54 CHARACTER*13 fNam
55 #endif /* USE_PDAF */
56 CHARACTER*(MAX_LEN_MBUF) msgBuf
57 #ifdef ALLOW_USE_MPI
58 C mpiRC :: Error code reporting variable used with MPI.
59 INTEGER mpiRC
60 INTEGER mpiIsInitialized
61 LOGICAL doReport
62 #if defined(ALLOW_OASIS) || defined(COMPONENT_MODULE)
63 INTEGER mpiMyWid
64 #endif
65 #if defined(ALLOW_NEST_PARENT) || defined(ALLOW_NEST_CHILD)
66 INTEGER mpiMyWid, color
67 #endif
68 #ifdef USE_PDAF
69 INTEGER mpi_task_id
70 #endif /* USE_PDAF */
71 #endif /* ALLOW_USE_MPI */
72 CEOP
73
74 C-- Default values set to single processor case
75 numberOfProcs = 1
76 myProcId = 0
77 pidIO = myProcId
78 myProcessStr = '------'
79 C Set a dummy value for myThid because we are not multi-threading yet.
80 myThid = 1
81
82 C Annoyingly there is no universal way to have the usingMPI
83 C parameter work as one might expect. This is because, on some
84 C systems I/O does not work until MPI_Init has been called.
85 C The solution for now is that the parameter below may need to
86 C be changed manually!
87 #ifdef ALLOW_USE_MPI
88 usingMPI = .TRUE.
89 #else
90 usingMPI = .FALSE.
91 #endif
92
93 IF ( .NOT.usingMPI ) THEN
94
95 WRITE(myProcessStr,'(I4.4)') myProcId
96 WRITE(fNam,'(A,A)') 'STDERR.', myProcessStr(1:4)
97 OPEN(errorMessageUnit,FILE=fNam,STATUS='unknown')
98 c WRITE(fNam,'(A,A)') 'STDOUT.', myProcessStr(1:4)
99 c OPEN(standardMessageUnit,FILE=fNam,STATUS='unknown')
100
101 #ifdef ALLOW_USE_MPI
102 ELSE
103 C-- MPI style multiple-process initialisation
104 C-- =========================================
105
106 CALL MPI_Initialized( mpiIsInitialized, mpiRC )
107
108 IF ( mpiIsInitialized .EQ. 0 ) THEN
109 C-- Initialise MPI multi-process parallel environment.
110 C On some systems program forks at this point. Others have already
111 C forked within mpirun - now thats an open standard!
112 CALL MPI_INIT( mpiRC )
113 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
114 eeBootError = .TRUE.
115 WRITE(msgBuf,'(A,I5)')
116 & 'EEBOOT_MINIMAL: MPI_INIT return code', mpiRC
117 CALL PRINT_ERROR( msgBuf, myThid )
118 GOTO 999
119 ENDIF
120
121 C-- MPI has now been initialized ; now we need to either
122 C ask for a communicator or pretend that we have:
123 C Pretend that we have asked for a communicator
124 MPI_COMM_MODEL = MPI_COMM_WORLD
125
126 ELSE
127 C-- MPI was already initialized and communicator has been passed
128 C down from upper level driver
129 MPI_COMM_MODEL = myComm
130
131 ENDIF
132
133 doReport = .FALSE.
134 #ifdef USE_PDAF
135 C initialize PDAF
136 C for more output increase second parameter from 1 to 2
137 CALL INIT_PARALLEL_PDAF(0, 1, MPI_COMM_MODEL, MPI_COMM_MODEL,
138 & mpi_task_id)
139 #endif /* USE_PDAF */
140
141 #ifdef ALLOW_OASIS
142 C add a 1rst preliminary call EESET_PARAMS to set useOASIS
143 C (needed to decide either to call OASIS_INIT or not)
144 CALL MPI_COMM_RANK( MPI_COMM_WORLD, mpiMyWId, mpiRC )
145 CALL EESET_PARMS ( mpiMyWId, doReport )
146 IF ( useOASIS ) CALL OASIS_INIT(MPI_COMM_MODEL)
147 #endif /* ALLOW_OASIS */
148
149 #ifdef COMPONENT_MODULE
150 C-- Set the running directory
151 CALL MPI_COMM_RANK( MPI_COMM_WORLD, mpiMyWId, mpiRC )
152 CALL SETDIR( mpiMyWId )
153
154 C- jmc: test:
155 C add a 1rst preliminary call EESET_PARAMS to set useCoupler
156 C (needed to decide either to call CPL_INIT or not)
157 CALL EESET_PARMS ( mpiMyWId, doReport )
158 C- jmc: test end ; otherwise, uncomment next line:
159 c useCoupler = .TRUE.
160
161 C-- Ask coupler interface for a communicator
162 IF ( useCoupler) CALL CPL_INIT
163 #endif /* COMPONENT_MODULE */
164
165 C-- Case with Nest(ing)
166 #if defined(ALLOW_NEST_PARENT) || defined(ALLOW_NEST_CHILD)
167 C-- Set the running directory
168 CALL MPI_COMM_RANK( MPI_COMM_WORLD, mpiMyWId, mpiRC )
169 CALL SETDIR( mpiMyWId )
170
171 C-- Setup Nesting Execution Environment
172 CALL NEST_EEINIT( mpiMyWId, color )
173 #endif /* ALLOW_NEST_PARENT | ALLOW_NEST_CHILD */
174
175 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
176
177 C-- Get my process number
178 CALL MPI_COMM_RANK( MPI_COMM_MODEL, mpiMyId, mpiRC )
179 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
180 eeBootError = .TRUE.
181 WRITE(msgBuf,'(A,I5)')
182 & 'EEBOOT_MINIMAL: MPI_COMM_RANK return code', mpiRC
183 CALL PRINT_ERROR( msgBuf, myThid )
184 GOTO 999
185 ENDIF
186 myProcId = mpiMyId
187 #ifdef USE_PDAF
188 WRITE(myProcessStr,'(I4.4,A1,I4.4)') mpi_task_id,'.',myProcId
189 #else
190 WRITE(myProcessStr,'(I4.4)') myProcId
191 #endif /* USE_PDAF */
192 mpiPidIo = myProcId
193 pidIO = mpiPidIo
194 IF ( mpiPidIo .EQ. myProcId ) THEN
195 #ifdef SINGLE_DISK_IO
196 IF( myProcId .EQ. 0 ) THEN
197 #endif
198 WRITE(fNam,'(A,A)') 'STDERR.', myProcessStr(1:4)
199 #ifdef USE_PDAF
200 WRITE(fNam,'(A,A)') 'STDERR.', myProcessStr(1:9)
201 #endif
202 OPEN(errorMessageUnit,FILE=fNam,STATUS='unknown')
203 WRITE(fNam,'(A,A)') 'STDOUT.', myProcessStr(1:4)
204 #ifdef USE_PDAF
205 WRITE(fNam,'(A,A)') 'STDOUT.', myProcessStr(1:9)
206 #endif
207 OPEN(standardMessageUnit,FILE=fNam,STATUS='unknown')
208 #ifdef SINGLE_DISK_IO
209 ELSE
210 OPEN(errorMessageUnit,FILE='/dev/null',STATUS='unknown')
211 standardMessageUnit=errorMessageUnit
212 ENDIF
213 IF( myProcId .EQ. 0 ) THEN
214 WRITE(msgBuf,'(2A)') '** WARNING ** EEBOOT_MINIMAL: ',
215 & 'defined SINGLE_DISK_IO will result in losing'
216 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
217 & SQUEEZE_RIGHT, myThid )
218 WRITE(msgBuf,'(2A)') '** WARNING ** EEBOOT_MINIMAL: ',
219 & 'any message (error/warning) from any proc <> 0'
220 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
221 & SQUEEZE_RIGHT, myThid )
222 ENDIF
223 #endif
224 ENDIF
225
226 #if defined(ALLOW_NEST_PARENT) || defined(ALLOW_NEST_CHILD)
227 WRITE(standardMessageUnit,'(2(A,I6))')
228 & ' mpiMyWId =', mpiMyWId, ' , color =',color
229 #endif /* ALLOW_NEST_PARENT | ALLOW_NEST_CHILD */
230
231 C-- Synchronise all processes
232 C Strictly this is superfluous, but by using it we can guarantee to
233 C find out about processes that did not start up.
234 CALL MPI_BARRIER( MPI_COMM_MODEL, mpiRC )
235 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
236 eeBootError = .TRUE.
237 WRITE(msgBuf,'(A,I6)')
238 & 'EEBOOT_MINIMAL: MPI_BARRIER return code', mpiRC
239 CALL PRINT_ERROR( msgBuf, myThid )
240 GOTO 999
241 ENDIF
242
243 C-- Get number of MPI processes
244 CALL MPI_COMM_SIZE ( MPI_COMM_MODEL, mpiNProcs, mpiRC )
245 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
246 eeBootError = .TRUE.
247 WRITE(msgBuf,'(A,I6)')
248 & 'EEBOOT_MINIMAL: MPI_COMM_SIZE return code', mpiRC
249 CALL PRINT_ERROR( msgBuf, myThid )
250 GOTO 999
251 ENDIF
252 numberOfProcs = mpiNProcs
253
254 #endif /* ALLOW_USE_MPI */
255 ENDIF
256
257 C-- Under MPI only allow same number of processes as proc grid size.
258 C Strictly we are allowed more procs but knowing there
259 C is an exact match makes things easier.
260 IF ( numberOfProcs .NE. nPx*nPy ) THEN
261 eeBootError = .TRUE.
262 WRITE(msgBuf,'(2(A,I6))')
263 & 'EEBOOT_MINIMAL: No. of procs=', numberOfProcs,
264 & ' not equal to nPx*nPy=', nPx*nPy
265 CALL PRINT_ERROR( msgBuf, myThid )
266 GOTO 999
267 ENDIF
268
269 #ifdef USE_LIBHPM
270 CALL F_HPMINIT(myProcId, "mitgcmuv")
271 #endif
272
273 999 CONTINUE
274 RETURN
275 END

  ViewVC Help
Powered by ViewVC 1.1.22