/[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.6 - (hide annotations) (download)
Tue May 18 17:39:21 1999 UTC (25 years, 1 month ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint28, checkpoint29, checkpoint22, checkpoint23, checkpoint24, checkpoint25, checkpoint27, branch-atmos-merge-freeze, branch-atmos-merge-start, checkpoint26, branch-atmos-merge-shapiro, checkpoint33, checkpoint32, checkpoint31, checkpoint30, checkpoint34, branch-atmos-merge-zonalfilt, branch-atmos-merge-phase5, branch-atmos-merge-phase4, branch-atmos-merge-phase7, branch-atmos-merge-phase6, branch-atmos-merge-phase1, branch-atmos-merge-phase3, branch-atmos-merge-phase2
Branch point for: branch-atmos-merge
Changes since 1.5: +9 -8 lines
Added IMPLICIT NONE where missing and changed formatting from 'I' to 'I5'.

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

  ViewVC Help
Powered by ViewVC 1.1.22