/[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.7 - (hide annotations) (download)
Sun Feb 4 14:38:42 2001 UTC (23 years, 3 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, checkpoint38, checkpoint40pre2, checkpoint40pre4, pre38tag1, c37_adj, pre38-close, checkpoint39, checkpoint37, checkpoint36, checkpoint35, checkpoint40pre5, checkpoint40
Branch point for: pre38
Changes since 1.6: +2 -1 lines
Made sure each .F and .h file had
the CVS keywords Header and Name at its start.
Most had header but very few currently have Name, so
lots of changes!

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

  ViewVC Help
Powered by ViewVC 1.1.22