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

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

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


Revision 1.13 - (show annotations) (download)
Fri Sep 21 03:54:34 2001 UTC (22 years, 8 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint44e_post, release1_p13_pre, checkpoint44f_post, checkpoint43a-release1mods, release1_p13, chkpt44d_post, release1_p8, release1_p9, release1_p1, release1_p2, release1_p3, release1_p4, release1_p5, release1_p6, release1_p7, checkpoint44e_pre, release1_b1, checkpoint43, release1_chkpt44d_post, release1_p11, icebear5, icebear4, icebear3, icebear2, release1-branch_tutorials, chkpt44a_post, checkpoint44h_pre, chkpt44c_pre, ecco_c44_e19, ecco_c44_e18, ecco_c44_e17, ecco_c44_e16, release1_p12, release1_p10, release1_p16, release1_p17, release1_p14, release1_p15, checkpoint44g_post, release1-branch-end, release1_final_v1, checkpoint44b_post, ecco_ice2, ecco_ice1, checkpoint44h_post, release1_p12_pre, ecco_c44_e22, ecco_c44_e25, chkpt44a_pre, ecco_c44_e23, ecco_c44_e20, ecco_c44_e21, ecco_c44_e26, ecco_c44_e27, ecco_c44_e24, ecco-branch-mod1, ecco-branch-mod2, ecco-branch-mod3, ecco-branch-mod4, ecco-branch-mod5, release1_beta1, checkpoint44b_pre, checkpoint42, checkpoint41, checkpoint44, checkpoint45, chkpt44c_post, checkpoint44f_pre, release1-branch_branchpoint
Branch point for: c24_e25_ice, release1_final, release1-branch, release1, ecco-branch, release1_50yr, icebear, release1_coupled
Changes since 1.12: +31 -21 lines
Starting to bring comments up to date and format comments
for document extraction of "prototypes".

1 C $Header: /u/gcmpack/models/MITgcmUV/eesupp/src/eeset_parms.F,v 1.12 2001/05/29 14:01:36 adcroft 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,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 notUsingXPeriodicity = .FALSE.
86 notUsingYPeriodicity = .FALSE.
87 useCubedSphereExchange = .FALSE.
88 usingMPI = .FALSE.
89 nTx = 1
90 nTy = 1
91
92 C-- Read in data from eedata file
93 C We really ought to be using our environment file reading
94 C package - but we have not written it yet.
95
96 C Make scratch copies of input data file with and without comments
97 OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
98 OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
99 OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',
100 & err=1,IOSTAT=errIO)
101 IF ( errIO .GE. 0 ) GOTO 2
102 1 CONTINUE
103 WRITE(msgBuf,'(A)')
104 & 'S/R EESET_PARMS'
105 CALL PRINT_ERROR( msgBuf , 1)
106 WRITE(msgBuf,'(A)')
107 & 'Unable to open execution environment'
108 CALL PRINT_ERROR( msgBuf , 1)
109 WRITE(msgBuf,'(A)')
110 & 'parameter file "eedata"'
111 CALL PRINT_ERROR( msgBuf , 1)
112 CALL EEDATA_EXAMPLE
113 STOP 'ABNORMAL END: S/R EESET_PARMS'
114 2 CONTINUE
115 1000 CONTINUE
116 READ(eeDataUnit,FMT='(A)',END=1001) RECORD
117 IL = MAX(ILNBLNK(RECORD),1)
118 IF ( RECORD(1:1) .NE. commentCharacter )
119 & WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
120 WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
121 GOTO 1000
122 1001 CONTINUE
123 CLOSE(eeDataUnit)
124 C-- Report contents of parameter file
125 WRITE(msgBuf,'(A)')
126 & '// ======================================================='
127 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
128 WRITE(msgBuf,'(A)')
129 & '// Execution Environment parameter file "eedata"'
130 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
131 WRITE(msgBuf,'(A)')
132 & '// ======================================================='
133 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
134 & SQUEEZE_RIGHT , 1)
135
136 iUnit = scrUnit2
137 REWIND(iUnit)
138 2000 CONTINUE
139 READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
140 IL = MAX(ILNBLNK(RECORD),1)
141 WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
142 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit, SQUEEZE_RIGHT , 1)
143 GOTO 2000
144 2001 CONTINUE
145 CLOSE(iUnit)
146
147 WRITE(msgBuf,'(A)') ' '
148 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
149 & SQUEEZE_RIGHT , 1)
150
151 iUnit = scrUnit1
152 REWIND(iUnit)
153 READ(UNIT=iUnit,NML=EEPARMS,IOSTAT=errIO,err=3)
154 IF ( errIO .GE. 0 ) GOTO 4
155 3 CONTINUE
156 WRITE(msgBuf,'(A)')
157 & 'S/R EESET_PARMS'
158 CALL PRINT_ERROR( msgBuf , 1)
159 WRITE(msgBuf,'(A)')
160 & 'Error reading execution environment '
161 CALL PRINT_ERROR( msgBuf , 1)
162 WRITE(msgBuf,'(A)')
163 & 'parameter file "eedata"'
164 CALL PRINT_ERROR( msgBuf , 1)
165 CALL EEDATA_EXAMPLE
166 STOP 'ABNORMAL END: S/R EESET_PARMS'
167 4 CONTINUE
168
169 C-- Execution Environment parameter file read
170 CLOSE(iUnit)
171
172 Cdbg eeDataUnit = 42
173 Cdbg OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',IOSTAT=errIO)
174 Cdbg IF ( errIO .LT. 0 ) GOTO 11
175 Cdbg DO K=1, 10
176 Cdbg READ(eedataUnit,IOSTAT=errIO)
177 Cdbg IF ( errIO .LT. 0 ) GOTO 11
178 Cdbg ENDDO
179 Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingXPeriodicity
180 Cdbg IF ( errIO .LT. 0 ) GOTO 11
181 Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingYPeriodicity
182 Cdbg IF ( errIO .LT. 0 ) GOTO 11
183 Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) usingMPI
184 Cdbg IF ( errIO .LT. 0 ) GOTO 11
185 Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTx
186 Cdbg IF ( errIO .LT. 0 ) GOTO 11
187 Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTy
188
189
190 Cdbg IF (errIO .LT. 0 ) eeBootError = .TRUE.
191 Cdbg CLOSE(eeDataUnit,IOSTAT=errIO)
192 Cdbg IF ( eeBootError .OR. errIO .LT. 0 ) THEN
193 C-- Report that an error occured
194 Cdbg eeBootError = .TRUE.
195 Cdbg WRITE(msgBuf,'(A)' )
196 Cdbg & 'S/R EESET_PARMS: Error reading "eedata" execution environment file'
197 Cdbg CALL PRINT_ERROR( msgBuf , 1)
198 Cdbg ELSE
199 C-- Write summary of settings that were selected
200 Cdbg ENDIF
201 C
202 C
203 RETURN
204 END

  ViewVC Help
Powered by ViewVC 1.1.22