/[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.2 - (hide annotations) (download)
Thu Apr 23 20:37:29 1998 UTC (26 years, 1 month ago) by cnh
Branch: MAIN
Changes since 1.1: +2 -2 lines
Changed $Id to $Header

1 cnh 1.2 C $Header: eeboot_minimal.F,v 1.1.1.1 1998/04/22 19:15:30 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     C Set a dummy value for myThid because we aren't multi-threading
51     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     C-- Get my process number
73     CALL MPI_COMM_RANK( MPI_COMM_WORLD, mpiMyId, mpiRC )
74     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
75     eeBootError = .TRUE.
76     WRITE(msgBuffer,'(A,I)')
77     & 'S/R INI_PROCS: MPI_COMM_RANK return code',
78     & mpiRC
79     CALL PRINT_ERROR( msgBuffer , myThid)
80     GOTO 999
81     ENDIF
82     myProcId = mpiMyId
83     WRITE(myProcessStr,'(I4.4)') myProcId
84     mpiPidIo = myProcId
85     pidIO = mpiPidIo
86     IF ( mpiPidIo .EQ. myProcId ) THEN
87     WRITE(fNam,'(A,A)') 'STDERR.', myProcessStr(1:4)
88     OPEN(errorMessageUnit,FILE=fNam,STATUS='unknown')
89     WRITE(fNam,'(A,A)') 'STDOUT.', myProcessStr(1:4)
90     OPEN(standardMessageUnit,FILE=fNam,STATUS='unknown')
91     ENDIF
92    
93     C-- Synchronise all processes
94     C Strictly this is superfluous, but by using it we can guarantee to
95     C find out about processes that didn't start up.
96     CALL MPI_BARRIER( MPI_COMM_WORLD, mpiRC )
97     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
98     eeBootError = .TRUE.
99     WRITE(msgBuffer,'(A,I)')
100     & 'S/R INI_PROCS: MPI_BARRIER return code',
101     & mpiRC
102     CALL PRINT_ERROR( msgBuffer , myThid)
103     GOTO 999
104     ENDIF
105    
106     C-- Get number of MPI processes
107     CALL MPI_COMM_SIZE ( MPI_COMM_WORLD, mpiNProcs, mpiRC )
108     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
109     eeBootError = .TRUE.
110     WRITE(msgBuffer,'(A,I)')
111     & 'S/R INI_PROCS: MPI_COMM_SIZE return code',
112     & mpiRC
113     CALL PRINT_ERROR( msgBuffer , myThid)
114     GOTO 999
115     ENDIF
116     numberOfProcs = mpiNProcs
117    
118     C-- Can't have more processes than compile time MAX_NO_PROCS
119     IF ( numberOfProcs .GT. MAX_NO_PROCS ) THEN
120     eeBootError = .TRUE.
121     WRITE(msgBuffer,'(A)')
122     & 'S/R INI_PROCS: No. of processes too large'
123     CALL PRINT_ERROR( msgBuffer , myThid)
124     GOTO 999
125     ENDIF
126     C-- Under MPI only allow same number of processes as proc.
127     C-- grid size.
128     C Strictly we are allowed more procs. but knowing there
129     C is an exact match makes things easier.
130     IF ( numberOfProcs .NE. nPx*nPy ) THEN
131     eeBootError = .TRUE.
132     WRITE(msgBuffer,'(A)')
133     & 'S/R INI_PROCS: No. of processes not equal to nPx*nPy'
134     CALL PRINT_ERROR( msgBuffer , myThid)
135     GOTO 999
136     ENDIF
137    
138     #ifndef ALWAYS_USE_MPI
139     ENDIF
140     #endif
141     #endif /* ALLOW_USE_MPI */
142    
143     999 CONTINUE
144    
145     RETURN
146     END
147    
148 cnh 1.2 C $Id: eeboot_minimal.F,v 1.1.1.1 1998/04/22 19:15:30 cnh Exp $

  ViewVC Help
Powered by ViewVC 1.1.22