/[MITgcm]/MITgcm_contrib/ESMF/global_ocean.128x64x15/code/eeset_parms.F
ViewVC logotype

Annotation of /MITgcm_contrib/ESMF/global_ocean.128x64x15/code/eeset_parms.F

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


Revision 1.1.1.1 - (hide annotations) (download) (vendor branch)
Sun Feb 15 22:28:19 2004 UTC (21 years, 5 months ago) by cnh
Branch: Initial
CVS Tags: Baseline
Changes since 1.1: +0 -0 lines
Initial checkin

1 cnh 1.1 C $Header: /u/u0/gcmpack/MITgcm/eesupp/src/eeset_parms.F,v 1.15 2003/12/15 02:02:39 jmc Exp $
2     C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: EESET_PARMS
8    
9     C !INTERFACE:
10     SUBROUTINE EESET_PARMS
11     IMPLICIT NONE
12    
13     C !DESCRIPTION:
14     C *==========================================================*
15     C | SUBROUTINE EESET_PARMS
16     C | o Routine to set model "parameters"
17     C *==========================================================*
18     C | This routine is called from the high-level wrapper
19     C | after multi-process paralle processing has started but
20     C | before multi-threaded parallelism. THe routine reads an
21     C | an "execution environment" input parameter file holding
22     C | information about the number of threads at run-time.
23     C *==========================================================*
24    
25     C !USES:
26     C == Global variables ==
27     #include "SIZE.h"
28     #include "EEPARAMS.h"
29     #include "EESUPPORT.h"
30     INTEGER IFNBLNK
31     EXTERNAL IFNBLNK
32     INTEGER ILNBLNK
33     EXTERNAL ILNBLNK
34    
35     C !LOCAL VARIABLES:
36     C == Local variables ==
37     C iUnit :: Work variable for IO unit number
38     C errIO :: IO unit error flag
39     C IL :: Temp. for index strings
40     C msgBuf :: Temp. for textual I/O
41     C record :: Temp. for textual I/O
42     INTEGER IL
43     INTEGER errIO
44     INTEGER iUnit
45     CHARACTER*(MAX_LEN_MBUF) msgBuf
46     CHARACTER*(MAX_LEN_PREC) record
47     NAMELIST /EEPARMS/
48     & nTx, nTy, usingMPI, useCoupler, useCubedSphereExchange
49     CEOP
50    
51    
52     C-- For now these options are fixed as the code does
53     C not fully support features for overlapping communication
54     C and computation.
55     usingSyncMessages = .TRUE.
56    
57     C-- Text map plots of fields ignore exact zero values
58     printMapIncludesZeros = .FALSE.
59    
60     C-- The remaining parameters here are set to default values.
61     C-- and then any different values are read from an input
62     C-- file called "eedata".
63     C The defaults set here are for serial execution.
64     C
65     C nTx and nTy are the number of threads in the X and Y
66     C directions.
67     C nSx/nTx and nSy/nTy be whole numbers at present.
68     C
69     C notUsingXPeriodicity and notUsingYPeriodicity affect
70     C the identifying of neighbor processes in a multi-process
71     C mode. On the whole the numerical model code should not
72     C customise itself based on these numbers as they may be
73     C removed if they do not prove useful.
74     C
75     C usingMPI is a flag which controls whether MPI message
76     C passing library calls are actually made. Note that under
77     C MPI it is necessary to start a program a special way -
78     C normally using a command of the form
79     C % mpirun program_name
80     C If usingMPI is set to TRUE but % mpirun .... was not
81     C used to launch the program then an internal MPI error
82     C may be generated when the first MPI call ( CALL MPI_Init )
83     C is made.
84     C
85     C useCoupler is a flag which controls communications with other
86     C model components through a coupler interface.
87     C
88     notUsingXPeriodicity = .FALSE.
89     notUsingYPeriodicity = .FALSE.
90     useCubedSphereExchange = .FALSE.
91     usingMPI = .FALSE.
92     useCoupler = .FALSE.
93     useCoupler = .TRUE.
94     nTx = 1
95     nTy = 1
96    
97     C-- Read in data from eedata file
98     C We really ought to be using our environment file reading
99     C package - but we have not written it yet.
100    
101     C Make scratch copies of input data file with and without comments
102     OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
103     OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
104     OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',
105     & err=1,IOSTAT=errIO)
106     IF ( errIO .GE. 0 ) GOTO 2
107     1 CONTINUE
108     WRITE(msgBuf,'(A)')
109     & 'S/R EESET_PARMS'
110     CALL PRINT_ERROR( msgBuf , 1)
111     WRITE(msgBuf,'(A)')
112     & 'Unable to open execution environment'
113     CALL PRINT_ERROR( msgBuf , 1)
114     WRITE(msgBuf,'(A)')
115     & 'parameter file "eedata"'
116     CALL PRINT_ERROR( msgBuf , 1)
117     CALL EEDATA_EXAMPLE
118     STOP 'ABNORMAL END: S/R EESET_PARMS'
119     2 CONTINUE
120     1000 CONTINUE
121     READ(eeDataUnit,FMT='(A)',END=1001) RECORD
122     IL = MAX(ILNBLNK(RECORD),1)
123     IF ( RECORD(1:1) .NE. commentCharacter )
124     & WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
125     WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
126     GOTO 1000
127     1001 CONTINUE
128     CLOSE(eeDataUnit)
129     C-- Report contents of parameter file
130     WRITE(msgBuf,'(A)')
131     & '// ======================================================='
132     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
133     WRITE(msgBuf,'(A)')
134     & '// Execution Environment parameter file "eedata"'
135     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
136     WRITE(msgBuf,'(A)')
137     & '// ======================================================='
138     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
139     & SQUEEZE_RIGHT , 1)
140    
141     iUnit = scrUnit2
142     REWIND(iUnit)
143     2000 CONTINUE
144     READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
145     IL = MAX(ILNBLNK(RECORD),1)
146     WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
147     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit, SQUEEZE_RIGHT , 1)
148     GOTO 2000
149     2001 CONTINUE
150     CLOSE(iUnit)
151    
152     WRITE(msgBuf,'(A)') ' '
153     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
154     & SQUEEZE_RIGHT , 1)
155    
156     iUnit = scrUnit1
157     REWIND(iUnit)
158     READ(UNIT=iUnit,NML=EEPARMS,IOSTAT=errIO,err=3)
159     IF ( errIO .GE. 0 ) GOTO 4
160     3 CONTINUE
161     #ifndef TARGET_PWR3
162     WRITE(msgBuf,'(A)')
163     & 'S/R EESET_PARMS'
164     CALL PRINT_ERROR( msgBuf , 1)
165     WRITE(msgBuf,'(A)')
166     & 'Error reading execution environment '
167     CALL PRINT_ERROR( msgBuf , 1)
168     WRITE(msgBuf,'(A)')
169     & 'parameter file "eedata"'
170     CALL PRINT_ERROR( msgBuf , 1)
171     CALL EEDATA_EXAMPLE
172     STOP 'ABNORMAL END: S/R EESET_PARMS'
173     #endif
174     4 CONTINUE
175    
176     C-- Execution Environment parameter file read
177     CLOSE(iUnit)
178    
179     Cdbg eeDataUnit = 42
180     Cdbg OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',IOSTAT=errIO)
181     Cdbg IF ( errIO .LT. 0 ) GOTO 11
182     Cdbg DO K=1, 10
183     Cdbg READ(eedataUnit,IOSTAT=errIO)
184     Cdbg IF ( errIO .LT. 0 ) GOTO 11
185     Cdbg ENDDO
186     Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingXPeriodicity
187     Cdbg IF ( errIO .LT. 0 ) GOTO 11
188     Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingYPeriodicity
189     Cdbg IF ( errIO .LT. 0 ) GOTO 11
190     Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) usingMPI
191     Cdbg IF ( errIO .LT. 0 ) GOTO 11
192     Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTx
193     Cdbg IF ( errIO .LT. 0 ) GOTO 11
194     Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTy
195    
196    
197     Cdbg IF (errIO .LT. 0 ) eeBootError = .TRUE.
198     Cdbg CLOSE(eeDataUnit,IOSTAT=errIO)
199     Cdbg IF ( eeBootError .OR. errIO .LT. 0 ) THEN
200     C-- Report that an error occured
201     Cdbg eeBootError = .TRUE.
202     Cdbg WRITE(msgBuf,'(A)' )
203     Cdbg & 'S/R EESET_PARMS: Error reading "eedata" execution environment file'
204     Cdbg CALL PRINT_ERROR( msgBuf , 1)
205     Cdbg ELSE
206     C-- Write summary of settings that were selected
207     Cdbg ENDIF
208     C
209     C
210     RETURN
211     END

  ViewVC Help
Powered by ViewVC 1.1.22