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

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

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


Revision 1.12 - (hide annotations) (download)
Tue May 29 14:01:36 2001 UTC (22 years, 11 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, checkpoint40pre2, checkpoint40pre4, checkpoint40pre5, checkpoint40
Changes since 1.11: +4 -3 lines
Merge from branch pre38:
 o essential mods for cubed sphere
 o debugged atmosphere, dynamcis + physics (aim)
 o new packages (mom_vecinv, mom_fluxform, ...)

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

  ViewVC Help
Powered by ViewVC 1.1.22