/[MITgcm]/MITgcm_contrib/sannino/OASIS_3.0_Coupler/code/eeboot_minimal.F
ViewVC logotype

Contents of /MITgcm_contrib/sannino/OASIS_3.0_Coupler/code/eeboot_minimal.F

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


Revision 1.1 - (show annotations) (download)
Thu Jul 20 21:08:15 2006 UTC (19 years ago) by sannino
Branch: MAIN
CVS Tags: HEAD
o Adding OASIS package
o Adding grid refinement package

1 C $Header: /u/gcmpack/MITgcm/eesupp/src/eeboot_minimal.F,v 1.16 2005/12/22 00:56:49 ce107 Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5
6 CBOP
7 C !ROUTINE: EEBOOT_MINIMAL
8
9 C !INTERFACE:
10 SUBROUTINE EEBOOT_MINIMAL
11 IMPLICIT NONE
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 C == Global data ==
34 #include "SIZE.h"
35 #include "EEPARAMS.h"
36 #include "EESUPPORT.h"
37 cgmNESTING(
38 #ifdef ALLOW_NESTING_FATHER
39 #include "NESTING_FATHER.h"
40 #endif
41 c
42 #ifdef ALLOW_NESTING_SON
43 #include "NESTING_SON.h"
44 #endif
45 #if defined(ALLOW_NESTING_FATHER) || defined(ALLOW_NESTING_SON)
46 INTEGER color
47 INTEGER mpiMyWid
48 INTEGER Count_Lev
49 INTEGER istatus
50 #endif
51 cgmNESTING)
52
53 cgmOASIS(
54 #ifdef ALLOW_OASIS
55 INTEGER MPI_COMM_OASIS
56 #endif
57 cgmOASIS)
58
59
60 C !LOCAL VARIABLES:
61 C == Local variables ==
62 C myThid :: Temp. dummy thread number.
63 C fNam :: Used to build name of file for standard
64 C output and error output.
65 INTEGER myThid
66 CHARACTER*13 fNam
67 #ifdef ALLOW_USE_MPI
68 C mpiRC :: Error code reporting variable used
69 C with MPI.
70 C msgBuffer :: Used to build messages for printing.
71 CHARACTER*(MAX_LEN_MBUF) msgBuffer
72 INTEGER mpiRC
73 INTEGER nptmp
74 #ifdef COMPONENT_MODULE
75 INTEGER mpiMyWid
76 #endif
77 #endif /* ALLOW_USE_MPI */
78 CEOP
79
80 C-- Default values set to single processor case
81 numberOfProcs = 1
82 myProcId = 0
83 pidIO = myProcId
84 myProcessStr = '------'
85 C Set a dummy value for myThid because we are not multi-threading
86 C yet.
87 myThid = 1
88 #ifdef ALLOW_USE_MPI
89 C--
90 C-- MPI style multiple-process initialisation
91 C-- =========================================
92 #ifndef ALWAYS_USE_MPI
93 IF ( usingMPI ) THEN
94 #endif
95 C-- Initialise MPI multi-process parallel environment.
96 C On some systems program forks at this point. Others have already
97 C forked within mpirun - now thats an open standard!
98 CALL MPI_INIT( mpiRC )
99 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
100 eeBootError = .TRUE.
101 WRITE(msgBuffer,'(A,I5)')
102 & 'S/R INI_PROCS: MPI_INIT return code',
103 & mpiRC
104 CALL PRINT_ERROR( msgBuffer , myThid)
105 GOTO 999
106 ENDIF
107
108 C-- MPI has now been initialized but now we need to either
109 C ask for a communicator or pretend that we have:
110 C Pretend that we have asked for a communicator
111 cgmOASIS(
112 #ifdef ALLOW_OASIS
113 CALL OASIS_INIT (MPI_COMM_OASIS)
114 #endif
115 cgmOASIS)
116
117 cgmNESTING(
118 #ifndef ALLOW_NESTING_FATHER
119 #ifndef ALLOW_NESTING_SON
120 cgmOASIS(
121 #ifndef ALLOW_OASIS
122 MPI_COMM_MODEL = MPI_COMM_WORLD
123 #else
124 MPI_COMM_MODEL = MPI_COMM_OASIS
125 #endif
126 cgmOASIS)
127 #endif
128 #endif
129 cgmNESTING)
130 #ifdef COMPONENT_MODULE
131 C-- Set the running directory
132 CALL MPI_COMM_RANK( MPI_COMM_WORLD, mpiMyWId, mpiRC )
133 CALL SETDIR( mpiMyWId )
134
135 C- jmc: test:
136 C add a 1rst preliminary call EESET_PARAMS to set useCoupler
137 C (needed to decide either to call CPL_INIT or not)
138 CALL EESET_PARMS
139 IF ( eeBootError ) GOTO 999
140 C- jmc: test end ; otherwise, uncomment next line:
141 c useCoupler = .TRUE.
142
143 C-- Ask coupler interface for a communicator
144 IF ( useCoupler) CALL CPL_INIT
145 #endif
146
147 C-- Get my process number
148 cgmNESTING(
149 #ifndef ALLOW_NESTING_FATHER
150 #ifndef ALLOW_NESTING_SON
151 CALL MPI_COMM_RANK( MPI_COMM_MODEL, mpiMyId, mpiRC )
152 #endif
153 #endif
154 cgmNESTING)
155 cgmNESTING(
156 #ifdef ALLOW_NESTING_FATHER
157 CALL MPI_COMM_RANK( MPI_COMM_WORLD, mpiMyWId, mpiRC )
158
159 MSTR_DRV_F(1) = 0
160 MSTR_FTH_F(1) = 1
161 MSTR_SON_F(1) = NCPUs_FTH_F + 1
162
163
164 DO Count_Lev = 2, NST_LEV_TOT_F
165 MSTR_DRV_F(Count_Lev) = MSTR_SON_F(Count_Lev-1) + NCPUs_SON_F(Count_Lev - 1)
166 MSTR_SON_F(Count_Lev) = MSTR_DRV_F(Count_Lev) + 1
167 MSTR_FTH_F(Count_Lev) = MSTR_SON_F(Count_Lev-1)
168 ENDDO
169
170
171 IF (NST_LEV_F.EQ.1) THEN
172 IF (mpiMyWId.GE.MSTR_FTH_F(1).AND.mpiMyWId.LT.MSTR_SON_F(1)) color = 1
173 IF (mpiMyWId.GE.MSTR_SON_F(1)) color = 2
174 ENDIF
175
176 IF (NST_LEV_F.GT.1) THEN
177 IF (mpiMyWId.GE.MSTR_SON_F(NST_LEV_F).AND.
178 & mpiMyWId.LT.MSTR_SON_F(NST_LEV_F)+NCPUs_SON_F(NST_LEV_F))
179 & color = (NST_LEV_F + 1)
180 ENDIF
181 #endif /* ALLOW_NESTING_FATHER */
182
183 c==========================================================================
184
185 #ifdef ALLOW_NESTING_SON
186 CALL MPI_COMM_RANK( MPI_COMM_WORLD, mpiMyWId, mpiRC )
187
188 MSTR_DRV_S(1) = 0
189 MSTR_FTH_S(1) = 1
190 MSTR_SON_S(1) = NCPUs_FTH_S + 1
191
192
193 DO Count_Lev = 2, NST_LEV_TOT_S
194 MSTR_DRV_S(Count_Lev) = MSTR_SON_S(Count_Lev-1) + NCPUs_SON_S(Count_Lev - 1)
195 MSTR_SON_S(Count_Lev) = MSTR_DRV_S(Count_Lev) + 1
196 MSTR_FTH_S(Count_Lev) = MSTR_SON_S(Count_Lev-1)
197 ENDDO
198
199
200 IF (NST_LEV_S.EQ.1) THEN
201 IF (mpiMyWId.GE.MSTR_FTH_S(1).AND.mpiMyWId.LT.MSTR_SON_S(1)) color = 1
202 IF (mpiMyWId.GE.MSTR_SON_S(1)) color = 2
203 ENDIF
204
205 IF (NST_LEV_S.GT.1) THEN
206 IF (mpiMyWId.GE.MSTR_SON_S(NST_LEV_S).AND.
207 & mpiMyWId.LT.MSTR_SON_S(NST_LEV_S)+NCPUs_SON_S(NST_LEV_S))
208 & color = (NST_LEV_S + 1)
209 ENDIF
210 write(*,*) 'mpiMyWId=',mpiMyWId,'color=',color
211 #endif /* ALLOW_NESTING_SON */
212
213 #if defined(ALLOW_NESTING_FATHER) || defined(ALLOW_NESTING_SON)
214 call MPI_COMM_SPLIT (MPI_COMM_WORLD, color, 0,
215 & MPI_COMM_MODEL,mpiRC)
216 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
217 write(*,*) 'errore SPLIT'
218 ENDIF
219 C-- Get my process number
220 CALL MPI_COMM_RANK( MPI_COMM_MODEL, mpiMyId, mpiRC )
221
222
223 #endif /* ALLOW_NESTING_FATHER */
224 cgmNESTING)
225
226
227 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
228 eeBootError = .TRUE.
229 WRITE(msgBuffer,'(A,I5)')
230 & 'S/R INI_PROCS: MPI_COMM_RANK return code',
231 & mpiRC
232 CALL PRINT_ERROR( msgBuffer , myThid)
233 GOTO 999
234 ENDIF
235
236
237 myProcId = mpiMyId
238 WRITE(myProcessStr,'(I4.4)') myProcId
239 mpiPidIo = myProcId
240 pidIO = mpiPidIo
241 IF ( mpiPidIo .EQ. myProcId ) THEN
242 WRITE(fNam,'(A,A)') 'STDERR.', myProcessStr(1:4)
243 OPEN(errorMessageUnit,FILE=fNam,STATUS='unknown')
244 WRITE(fNam,'(A,A)') 'STDOUT.', myProcessStr(1:4)
245 cgmCASPUR OPEN(standardMessageUnit,FILE=fNam,STATUS='unknown')
246 ENDIF
247
248
249
250 C-- Synchronise all processes
251 C Strictly this is superfluous, but by using it we can guarantee to
252 C find out about processes that did not start up.
253 CALL MPI_BARRIER( MPI_COMM_MODEL, mpiRC )
254
255
256 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
257 eeBootError = .TRUE.
258 WRITE(msgBuffer,'(A,I5)')
259 & 'S/R INI_PROCS: MPI_BARRIER return code',
260 & mpiRC
261 CALL PRINT_ERROR( msgBuffer , myThid)
262 GOTO 999
263 ENDIF
264
265
266
267 C-- Get number of MPI processes
268 CALL MPI_COMM_SIZE ( MPI_COMM_MODEL, mpiNProcs, mpiRC )
269 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
270 eeBootError = .TRUE.
271 WRITE(msgBuffer,'(A,I5)')
272 & 'S/R INI_PROCS: MPI_COMM_SIZE return code',
273 & mpiRC
274 CALL PRINT_ERROR( msgBuffer , myThid)
275 GOTO 999
276 ENDIF
277
278
279 numberOfProcs = mpiNProcs
280
281 C-- Can not have more processes than compile time MAX_NO_PROCS
282 IF ( numberOfProcs .GT. MAX_NO_PROCS ) THEN
283 eeBootError = .TRUE.
284 WRITE(msgBuffer,'(A)')
285 & 'S/R INI_PROCS: No. of processes too large'
286 CALL PRINT_ERROR( msgBuffer , myThid)
287 GOTO 999
288 ENDIF
289 C-- Under MPI only allow same number of processes as proc.
290 C-- grid size.
291 C Strictly we are allowed more procs. but knowing there
292 C is an exact match makes things easier.
293 IF ( numberOfProcs .NE. nPx*nPy ) THEN
294 eeBootError = .TRUE.
295 nptmp = nPx*nPy
296 WRITE(msgBuffer,'(A,2I5)')
297 & 'S/R INI_PROCS: No. of processes not equal to nPx*nPy',
298 & numberOfProcs, nptmp
299 CALL PRINT_ERROR( msgBuffer , myThid)
300 GOTO 999
301 ENDIF
302
303 #ifndef ALWAYS_USE_MPI
304 ENDIF
305 #endif
306
307 #else /* ALLOW_USE_MPI */
308
309 WRITE(myProcessStr,'(I4.4)') myProcId
310 WRITE(fNam,'(A,A)') 'STDERR.', myProcessStr(1:4)
311 OPEN(errorMessageUnit,FILE=fNam,STATUS='unknown')
312 c WRITE(fNam,'(A,A)') 'STDOUT.', myProcessStr(1:4)
313 c OPEN(standardMessageUnit,FILE=fNam,STATUS='unknown')
314
315 #endif /* ALLOW_USE_MPI */
316 #ifdef USE_LIBHPM
317 CALL F_HPMINIT(myProcId, "mitgcmuv")
318 #endif
319
320
321
322 999 CONTINUE
323
324 RETURN
325 END
326

  ViewVC Help
Powered by ViewVC 1.1.22