/[MITgcm]/MITgcm_contrib/llc_hires/llc_4320/code-async/eeboot_minimal.F
ViewVC logotype

Contents of /MITgcm_contrib/llc_hires/llc_4320/code-async/eeboot_minimal.F

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


Revision 1.4 - (show annotations) (download)
Thu Mar 6 02:45:05 2014 UTC (11 years, 5 months ago) by dimitri
Branch: MAIN
CVS Tags: HEAD
Changes since 1.3: +1 -14 lines
updating async-io to latest MITgcm trunk code

1 C $Header: /u/gcmpack/MITgcm_contrib/llc_hires/llc_4320/code-async/eeboot_minimal.F,v 1.3 2013/10/30 06:33:24 dimitri 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
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 !LOCAL VARIABLES:
40 C == Local variables ==
41 C myThid :: Temp. dummy thread number.
42 C fNam :: Used to build file name for standard and error output.
43 C msgBuf :: Used to build messages for printing.
44 INTEGER myThid
45 CHARACTER*13 fNam
46 CHARACTER*(MAX_LEN_MBUF) msgBuf
47 #ifdef ALLOW_USE_MPI
48 C mpiRC :: Error code reporting variable used with MPI.
49 INTEGER mpiRC
50 LOGICAL doReport
51 #ifdef COMPONENT_MODULE
52 INTEGER mpiMyWid
53 #endif
54 #if defined(ALLOW_NEST_PARENT) || defined(ALLOW_NEST_CHILD)
55 INTEGER mpiMyWid, color
56 #endif
57 #endif /* ALLOW_USE_MPI */
58 CEOP
59
60 C-- Default values set to single processor case
61 numberOfProcs = 1
62 myProcId = 0
63 pidIO = myProcId
64 myProcessStr = '------'
65 C Set a dummy value for myThid because we are not multi-threading yet.
66 myThid = 1
67
68 C Annoyingly there is no universal way to have the usingMPI
69 C parameter work as one might expect. This is because, on some
70 C systems I/O does not work until MPI_Init has been called.
71 C The solution for now is that the parameter below may need to
72 C be changed manually!
73 #ifdef ALLOW_USE_MPI
74 usingMPI = .TRUE.
75 #else
76 usingMPI = .FALSE.
77 #endif
78
79 IF ( .NOT.usingMPI ) THEN
80
81 WRITE(myProcessStr,'(I4.4)') myProcId
82 WRITE(fNam,'(A,A)') 'STDERR.', myProcessStr(1:4)
83 OPEN(errorMessageUnit,FILE=fNam,STATUS='unknown')
84 c WRITE(fNam,'(A,A)') 'STDOUT.', myProcessStr(1:4)
85 c OPEN(standardMessageUnit,FILE=fNam,STATUS='unknown')
86
87 #ifdef ALLOW_USE_MPI
88 ELSE
89 C-- MPI style multiple-process initialisation
90 C-- =========================================
91
92 C-- Initialise MPI multi-process parallel environment.
93 C On some systems program forks at this point. Others have already
94 C forked within mpirun - now thats an open standard!
95 CALL MPI_INIT( mpiRC )
96 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
97 eeBootError = .TRUE.
98 WRITE(msgBuf,'(A,I5)')
99 & 'EEBOOT_MINIMAL: MPI_INIT return code', mpiRC
100 CALL PRINT_ERROR( msgBuf, myThid )
101 GOTO 999
102 ENDIF
103
104 C-- MPI has now been initialized but now we need to either
105 C ask for a communicator or pretend that we have:
106 C Pretend that we have asked for a communicator
107 MPI_COMM_MODEL = MPI_COMM_WORLD
108 doReport = .FALSE.
109
110 #ifdef ALLOW_OASIS
111 C add a 1rst preliminary call EESET_PARAMS to set useOASIS
112 C (needed to decide either to call OASIS_INIT or not)
113 CALL EESET_PARMS ( doReport )
114 IF ( useOASIS ) CALL OASIS_INIT(MPI_COMM_MODEL)
115 #endif /* ALLOW_OASIS */
116
117 #ifdef COMPONENT_MODULE
118 C-- Set the running directory
119 CALL MPI_COMM_RANK( MPI_COMM_WORLD, mpiMyWId, mpiRC )
120 CALL SETDIR( mpiMyWId )
121
122 C- jmc: test:
123 C add a 1rst preliminary call EESET_PARAMS to set useCoupler
124 C (needed to decide either to call CPL_INIT or not)
125 CALL EESET_PARMS ( doReport )
126 C- jmc: test end ; otherwise, uncomment next line:
127 c useCoupler = .TRUE.
128
129 C-- Ask coupler interface for a communicator
130 IF ( useCoupler) CALL CPL_INIT
131 #endif /* COMPONENT_MODULE */
132
133 C-- Case with Nest(ing)
134 #if defined(ALLOW_NEST_PARENT) || defined(ALLOW_NEST_CHILD)
135 C-- Set the running directory
136 CALL MPI_COMM_RANK( MPI_COMM_WORLD, mpiMyWId, mpiRC )
137 CALL SETDIR( mpiMyWId )
138
139 C-- Setup Nesting Execution Environment
140 CALL NEST_EEINIT( mpiMyWId, color )
141 #endif /* ALLOW_NEST_PARENT | ALLOW_NEST_CHILD */
142
143 #if defined(ALLOW_ASYNCIO)
144 C-- Separate off asynchronous I/O nodes
145 C-- For now this is incompatible with NEST and COMPONENT_MODULE modes
146 CALL ASYNCIO_INIT(MPI_COMM_WORLD,
147 U MPI_COMM_MODEL)
148 #endif /* ALLOW_ASYNCIO */
149
150 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
151
152 C-- Get my process number
153 CALL MPI_COMM_RANK( MPI_COMM_MODEL, mpiMyId, mpiRC )
154 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
155 eeBootError = .TRUE.
156 WRITE(msgBuf,'(A,I5)')
157 & 'EEBOOT_MINIMAL: MPI_COMM_RANK return code', mpiRC
158 CALL PRINT_ERROR( msgBuf, myThid )
159 GOTO 999
160 ENDIF
161 myProcId = mpiMyId
162 WRITE(myProcessStr,'(I5.5)') myProcId
163 mpiPidIo = myProcId
164 pidIO = mpiPidIo
165 IF ( mpiPidIo .EQ. myProcId ) THEN
166 #ifdef SINGLE_DISK_IO
167 IF( myProcId .EQ. 0 ) THEN
168 #endif
169 WRITE(fNam,'(A,A)') 'STDERR.', myProcessStr(1:5)
170 OPEN(errorMessageUnit,FILE=fNam,STATUS='unknown')
171 WRITE(fNam,'(A,A)') 'STDOUT.', myProcessStr(1:5)
172 OPEN(standardMessageUnit,FILE=fNam,STATUS='unknown')
173 #ifdef SINGLE_DISK_IO
174 ELSE
175 OPEN(errorMessageUnit,FILE='/dev/null',STATUS='unknown')
176 standardMessageUnit=errorMessageUnit
177 ENDIF
178 #endif
179 ENDIF
180
181 #if defined(ALLOW_NEST_PARENT) || defined(ALLOW_NEST_CHILD)
182 WRITE(standardMessageUnit,'(2(A,I6))')
183 & ' mpiMyWId =', mpiMyWId, ' , color =',color
184 #endif /* ALLOW_NEST_PARENT | ALLOW_NEST_CHILD */
185
186 C-- Synchronise all processes
187 C Strictly this is superfluous, but by using it we can guarantee to
188 C find out about processes that did not start up.
189 CALL MPI_BARRIER( MPI_COMM_MODEL, mpiRC )
190 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
191 eeBootError = .TRUE.
192 WRITE(msgBuf,'(A,I6)')
193 & 'EEBOOT_MINIMAL: MPI_BARRIER return code', mpiRC
194 CALL PRINT_ERROR( msgBuf, myThid )
195 GOTO 999
196 ENDIF
197
198 C-- Get number of MPI processes
199 CALL MPI_COMM_SIZE ( MPI_COMM_MODEL, mpiNProcs, mpiRC )
200 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
201 eeBootError = .TRUE.
202 WRITE(msgBuf,'(A,I6)')
203 & 'EEBOOT_MINIMAL: MPI_COMM_SIZE return code', mpiRC
204 CALL PRINT_ERROR( msgBuf, myThid )
205 GOTO 999
206 ENDIF
207 numberOfProcs = mpiNProcs
208
209 #endif /* ALLOW_USE_MPI */
210 ENDIF
211
212 C-- Under MPI only allow same number of processes as proc grid size.
213 C Strictly we are allowed more procs but knowing there
214 C is an exact match makes things easier.
215 IF ( numberOfProcs .NE. nPx*nPy ) THEN
216 eeBootError = .TRUE.
217 WRITE(msgBuf,'(2(A,I6))')
218 & 'EEBOOT_MINIMAL: No. of procs=', numberOfProcs,
219 & ' not equal to nPx*nPy=', nPx*nPy
220 CALL PRINT_ERROR( msgBuf, myThid )
221 GOTO 999
222 ENDIF
223
224 #ifdef USE_LIBHPM
225 CALL F_HPMINIT(myProcId, "mitgcmuv")
226 #endif
227
228 999 CONTINUE
229 RETURN
230 END

  ViewVC Help
Powered by ViewVC 1.1.22