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

Annotation of /MITgcm_contrib/llc_hires/llc_1080/code-async/eeboot_minimal.F

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


Revision 1.4 - (hide annotations) (download)
Wed Feb 27 20:56:33 2019 UTC (6 years, 5 months ago) by dimitri
Branch: MAIN
CVS Tags: HEAD
Changes since 1.3: +73 -21 lines
updating to more recent asyncio code

1 dimitri 1.4 C $Header: /u/gcmpack/MITgcm_contrib/llc_hires/llc_1080/code-async/eeboot_minimal.F,v 1.3 2014/03/06 02:45:05 dimitri Exp $
2 dimitri 1.1 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 dimitri 1.4 SUBROUTINE EEBOOT_MINIMAL( myComm )
12 dimitri 1.1
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 dimitri 1.4 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 dimitri 1.1 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 dimitri 1.4 #ifdef USE_PDAF
52     CHARACTER*18 fNam
53     #else
54 dimitri 1.1 CHARACTER*13 fNam
55 dimitri 1.4 #endif /* USE_PDAF */
56 dimitri 1.1 CHARACTER*(MAX_LEN_MBUF) msgBuf
57     #ifdef ALLOW_USE_MPI
58     C mpiRC :: Error code reporting variable used with MPI.
59     INTEGER mpiRC
60 dimitri 1.4 INTEGER mpiIsInitialized
61 dimitri 1.1 LOGICAL doReport
62 dimitri 1.4 #if defined(ALLOW_OASIS) || defined(COMPONENT_MODULE)
63 dimitri 1.1 INTEGER mpiMyWid
64     #endif
65     #if defined(ALLOW_NEST_PARENT) || defined(ALLOW_NEST_CHILD)
66     INTEGER mpiMyWid, color
67     #endif
68 dimitri 1.4 #ifdef USE_PDAF
69     INTEGER mpi_task_id
70     #endif /* USE_PDAF */
71 dimitri 1.1 #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 dimitri 1.4 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 dimitri 1.1 & 'EEBOOT_MINIMAL: MPI_INIT return code', mpiRC
117 dimitri 1.4 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 dimitri 1.1 ENDIF
132    
133     doReport = .FALSE.
134 dimitri 1.4 #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 dimitri 1.1
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 dimitri 1.4 CALL MPI_COMM_RANK( MPI_COMM_WORLD, mpiMyWId, mpiRC )
145     CALL EESET_PARMS ( mpiMyWId, doReport )
146 dimitri 1.1 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 dimitri 1.4 CALL EESET_PARMS ( mpiMyWId, doReport )
158 dimitri 1.1 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     #if defined(ALLOW_ASYNCIO)
176     C-- Separate off asynchronous I/O nodes
177     C-- For now this is incompatible with NEST and COMPONENT_MODULE modes
178     CALL ASYNCIO_INIT(MPI_COMM_WORLD,
179     U MPI_COMM_MODEL)
180     #endif /* ALLOW_ASYNCIO */
181    
182     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
183    
184     C-- Get my process number
185     CALL MPI_COMM_RANK( MPI_COMM_MODEL, mpiMyId, mpiRC )
186     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
187     eeBootError = .TRUE.
188     WRITE(msgBuf,'(A,I5)')
189     & 'EEBOOT_MINIMAL: MPI_COMM_RANK return code', mpiRC
190     CALL PRINT_ERROR( msgBuf, myThid )
191     GOTO 999
192     ENDIF
193     myProcId = mpiMyId
194 dimitri 1.4 #ifdef USE_PDAF
195     WRITE(myProcessStr,'(I4.4,A1,I4.4)') mpi_task_id,'.',myProcId
196     #else
197     WRITE(myProcessStr,'(I5.5)') myProcId
198     #endif /* USE_PDAF */
199 dimitri 1.1 mpiPidIo = myProcId
200     pidIO = mpiPidIo
201     IF ( mpiPidIo .EQ. myProcId ) THEN
202 dimitri 1.2 #ifdef SINGLE_DISK_IO
203     IF( myProcId .EQ. 0 ) THEN
204     #endif
205 dimitri 1.4 WRITE(fNam,'(A,A)') 'STDERR.', myProcessStr(1:5)
206     #ifdef USE_PDAF
207     WRITE(fNam,'(A,A)') 'STDERR.', myProcessStr(1:9)
208     #endif
209 dimitri 1.2 OPEN(errorMessageUnit,FILE=fNam,STATUS='unknown')
210 dimitri 1.4 WRITE(fNam,'(A,A)') 'STDOUT.', myProcessStr(1:5)
211     #ifdef USE_PDAF
212     WRITE(fNam,'(A,A)') 'STDOUT.', myProcessStr(1:9)
213     #endif
214 dimitri 1.2 OPEN(standardMessageUnit,FILE=fNam,STATUS='unknown')
215     #ifdef SINGLE_DISK_IO
216     ELSE
217     OPEN(errorMessageUnit,FILE='/dev/null',STATUS='unknown')
218     standardMessageUnit=errorMessageUnit
219     ENDIF
220 dimitri 1.4 IF( myProcId .EQ. 0 ) THEN
221     WRITE(msgBuf,'(2A)') '** WARNING ** EEBOOT_MINIMAL: ',
222     & 'defined SINGLE_DISK_IO will result in losing'
223     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
224     & SQUEEZE_RIGHT, myThid )
225     WRITE(msgBuf,'(2A)') '** WARNING ** EEBOOT_MINIMAL: ',
226     & 'any message (error/warning) from any proc <> 0'
227     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
228     & SQUEEZE_RIGHT, myThid )
229     ENDIF
230 dimitri 1.2 #endif
231 dimitri 1.1 ENDIF
232    
233     #if defined(ALLOW_NEST_PARENT) || defined(ALLOW_NEST_CHILD)
234     WRITE(standardMessageUnit,'(2(A,I6))')
235     & ' mpiMyWId =', mpiMyWId, ' , color =',color
236     #endif /* ALLOW_NEST_PARENT | ALLOW_NEST_CHILD */
237    
238     C-- Synchronise all processes
239     C Strictly this is superfluous, but by using it we can guarantee to
240     C find out about processes that did not start up.
241     CALL MPI_BARRIER( MPI_COMM_MODEL, mpiRC )
242     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
243     eeBootError = .TRUE.
244     WRITE(msgBuf,'(A,I6)')
245     & 'EEBOOT_MINIMAL: MPI_BARRIER return code', mpiRC
246     CALL PRINT_ERROR( msgBuf, myThid )
247     GOTO 999
248     ENDIF
249    
250     C-- Get number of MPI processes
251     CALL MPI_COMM_SIZE ( MPI_COMM_MODEL, mpiNProcs, mpiRC )
252     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
253     eeBootError = .TRUE.
254     WRITE(msgBuf,'(A,I6)')
255     & 'EEBOOT_MINIMAL: MPI_COMM_SIZE return code', mpiRC
256     CALL PRINT_ERROR( msgBuf, myThid )
257     GOTO 999
258     ENDIF
259     numberOfProcs = mpiNProcs
260    
261     #endif /* ALLOW_USE_MPI */
262     ENDIF
263    
264     C-- Under MPI only allow same number of processes as proc grid size.
265     C Strictly we are allowed more procs but knowing there
266     C is an exact match makes things easier.
267     IF ( numberOfProcs .NE. nPx*nPy ) THEN
268     eeBootError = .TRUE.
269     WRITE(msgBuf,'(2(A,I6))')
270     & 'EEBOOT_MINIMAL: No. of procs=', numberOfProcs,
271     & ' not equal to nPx*nPy=', nPx*nPy
272     CALL PRINT_ERROR( msgBuf, myThid )
273     GOTO 999
274     ENDIF
275    
276     #ifdef USE_LIBHPM
277     CALL F_HPMINIT(myProcId, "mitgcmuv")
278     #endif
279    
280     999 CONTINUE
281     RETURN
282     END

  ViewVC Help
Powered by ViewVC 1.1.22