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

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

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


Revision 1.5 - (hide annotations) (download)
Mon Mar 22 17:37:42 1999 UTC (25 years, 3 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint20, checkpoint21
Changes since 1.4: +11 -4 lines
Modified MPI calls to allow use in "coupled" context.
 o created COMMON block to contain MPI communicator MPI_COMM_MODEL
 o globally replaced MPI_COMM_World with MPI_COMM_MODEL
 o set MPI_COMM_MODEL equal to MPI_COMM_World in eeboot_minimal.F

1 adcroft 1.5 C $Header: /u/gcmpack/models/MITgcmUV/eesupp/src/eeboot_minimal.F,v 1.4 1998/10/28 03:11:34 cnh Exp $
2 cnh 1.1
3     #include "CPP_EEOPTIONS.h"
4    
5     CStartOfInterface
6     SUBROUTINE EEBOOT_MINIMAL
7     C /==========================================================\
8     C | SUBROUTINE EEBOOT_MINIMAL |
9     C | o Set an initial environment that is predictable i.e. |
10     C | behaves in a similar way on all machines and stable. |
11     C |==========================================================|
12     C | Under MPI this routine calls MPI_INIT to setup the |
13     C | mpi environment ( on some systems the code is running as |
14     C | a single process prior to MPI_INIT, on others the mpirun |
15     C | script has already created multiple processes). Until |
16     C | MPI_Init is called it is unclear what state the |
17     C | application is in. Once this routine has been run it is |
18     C | "safe" to do things like I/O to report erros and to get |
19     C | run parameters. |
20     C | Note: This routine can also be compiled with CPP |
21     C | directives set so that no multi-processing is initialise.|
22     C | This is OK and should work fine. |
23     C \==========================================================/
24    
25     C === Global data ===
26     #include "SIZE.h"
27     #include "EEPARAMS.h"
28     #include "EESUPPORT.h"
29    
30     CEndOfInterface
31    
32     C === Local variables ===
33     INTEGER myThid
34     #ifdef ALLOW_USE_MPI
35     C mpiRC - Error code reporting variable used
36     C with MPI.
37     C fNam - Used to build name of file for standard
38     C output and error output.
39     C msgBuffer - Used to build messages for printing.
40     CHARACTER*(MAX_LEN_MBUF) msgBuffer
41     INTEGER mpiRC
42     CHARACTER*13 fNam
43     #endif /* ALLOW_USE_MPI */
44    
45     C-- Default values set to single processor case
46     numberOfProcs = 1
47     myProcId = 0
48     pidIO = myProcId
49     myProcessStr = '??????'
50 cnh 1.4 C Set a dummy value for myThid because we are not multi-threading
51 cnh 1.1 C yet.
52     myThid = 1
53     #ifdef ALLOW_USE_MPI
54     C--
55     C-- MPI style multiple-process initialisation
56     C-- =========================================
57     #ifndef ALWAYS_USE_MPI
58     IF ( usingMPI ) THEN
59     #endif
60     C-- Initialise MPI multi-process parallel environment.
61     C On some systems program forks at this point. Others have already
62     C forked within mpirun - now thats an open standard!
63     CALL MPI_INIT( mpiRC )
64     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
65     eeBootError = .TRUE.
66     WRITE(msgBuffer,'(A,I)')
67     & 'S/R INI_PROCS: MPI_INIT return code',
68     & mpiRC
69     CALL PRINT_ERROR( msgBuffer , myThid)
70     GOTO 999
71     ENDIF
72 adcroft 1.5 C-- MPI has now been initialized but now we need to either
73     C ask for a communicator or pretend that we have:
74     C Ask coupler interface for a communicator
75     c call MITCOMPONENT_init( 'MITgcmUV', MPI_COMM_MODEL )
76     C Pretend that we have asked for a communicator
77     MPI_COMM_MODEL = MPI_COMM_WORLD
78    
79 cnh 1.1 C-- Get my process number
80 adcroft 1.5 CALL MPI_COMM_RANK( MPI_COMM_MODEL, mpiMyId, mpiRC )
81 cnh 1.1 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
82     eeBootError = .TRUE.
83     WRITE(msgBuffer,'(A,I)')
84     & 'S/R INI_PROCS: MPI_COMM_RANK return code',
85     & mpiRC
86     CALL PRINT_ERROR( msgBuffer , myThid)
87     GOTO 999
88     ENDIF
89     myProcId = mpiMyId
90     WRITE(myProcessStr,'(I4.4)') myProcId
91     mpiPidIo = myProcId
92     pidIO = mpiPidIo
93     IF ( mpiPidIo .EQ. myProcId ) THEN
94     WRITE(fNam,'(A,A)') 'STDERR.', myProcessStr(1:4)
95     OPEN(errorMessageUnit,FILE=fNam,STATUS='unknown')
96     WRITE(fNam,'(A,A)') 'STDOUT.', myProcessStr(1:4)
97     OPEN(standardMessageUnit,FILE=fNam,STATUS='unknown')
98     ENDIF
99    
100     C-- Synchronise all processes
101     C Strictly this is superfluous, but by using it we can guarantee to
102 cnh 1.4 C find out about processes that did not start up.
103 adcroft 1.5 CALL MPI_BARRIER( MPI_COMM_MODEL, mpiRC )
104 cnh 1.1 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
105     eeBootError = .TRUE.
106     WRITE(msgBuffer,'(A,I)')
107     & 'S/R INI_PROCS: MPI_BARRIER return code',
108     & mpiRC
109     CALL PRINT_ERROR( msgBuffer , myThid)
110     GOTO 999
111     ENDIF
112    
113     C-- Get number of MPI processes
114 adcroft 1.5 CALL MPI_COMM_SIZE ( MPI_COMM_MODEL, mpiNProcs, mpiRC )
115 cnh 1.1 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
116     eeBootError = .TRUE.
117     WRITE(msgBuffer,'(A,I)')
118     & 'S/R INI_PROCS: MPI_COMM_SIZE return code',
119     & mpiRC
120     CALL PRINT_ERROR( msgBuffer , myThid)
121     GOTO 999
122     ENDIF
123     numberOfProcs = mpiNProcs
124    
125 cnh 1.4 C-- Can not have more processes than compile time MAX_NO_PROCS
126 cnh 1.1 IF ( numberOfProcs .GT. MAX_NO_PROCS ) THEN
127     eeBootError = .TRUE.
128     WRITE(msgBuffer,'(A)')
129     & 'S/R INI_PROCS: No. of processes too large'
130     CALL PRINT_ERROR( msgBuffer , myThid)
131     GOTO 999
132     ENDIF
133     C-- Under MPI only allow same number of processes as proc.
134     C-- grid size.
135     C Strictly we are allowed more procs. but knowing there
136     C is an exact match makes things easier.
137     IF ( numberOfProcs .NE. nPx*nPy ) THEN
138     eeBootError = .TRUE.
139     WRITE(msgBuffer,'(A)')
140     & 'S/R INI_PROCS: No. of processes not equal to nPx*nPy'
141     CALL PRINT_ERROR( msgBuffer , myThid)
142     GOTO 999
143     ENDIF
144    
145     #ifndef ALWAYS_USE_MPI
146     ENDIF
147     #endif
148     #endif /* ALLOW_USE_MPI */
149    
150     999 CONTINUE
151    
152     RETURN
153     END
154    

  ViewVC Help
Powered by ViewVC 1.1.22