/[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.29 - (hide annotations) (download)
Tue Oct 5 17:43:40 2010 UTC (13 years, 8 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62w, checkpoint62y, checkpoint62x
Changes since 1.28: +3 -2 lines
move "useOASIS" from PARAMS.h to EEPARAMS.h and read it from "eedata"

1 mlosch 1.29 C $Header: /u/gcmpack/MITgcm/eesupp/src/eeset_parms.F,v 1.28 2010/05/23 01:35:23 jmc Exp $
2 adcroft 1.12 C $Name: $
3 cnh 1.1
4     #include "CPP_EEOPTIONS.h"
5    
6 cnh 1.13 CBOP
7 jmc 1.25 C !ROUTINE: EESET_PARMS
8 cnh 1.13
9     C !INTERFACE:
10 cnh 1.1 SUBROUTINE EESET_PARMS
11 adcroft 1.8 IMPLICIT NONE
12 cnh 1.1
13 cnh 1.13 C !DESCRIPTION:
14     C *==========================================================*
15 jmc 1.25 C | SUBROUTINE EESET\_PARMS
16     C | o Routine to set model "parameters"
17 cnh 1.13 C *==========================================================*
18 jmc 1.25 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 cnh 1.13 C *==========================================================*
24    
25     C !USES:
26     C == Global variables ==
27 cnh 1.1 #include "SIZE.h"
28     #include "EEPARAMS.h"
29     #include "EESUPPORT.h"
30 cnh 1.13 INTEGER IFNBLNK
31     EXTERNAL IFNBLNK
32     INTEGER ILNBLNK
33     EXTERNAL ILNBLNK
34 cnh 1.1
35 cnh 1.13 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 adcroft 1.9 INTEGER IL
43 cnh 1.1 INTEGER errIO
44     INTEGER iUnit
45     CHARACTER*(MAX_LEN_MBUF) msgBuf
46     CHARACTER*(MAX_LEN_PREC) record
47 jmc 1.26 #if defined (TARGET_BGL) || defined (TARGET_CRAYXT)
48     CHARACTER*(MAX_LEN_FNAM) scratchFile1
49     CHARACTER*(MAX_LEN_FNAM) scratchFile2
50     #endif
51     CEOP
52    
53 cnh 1.1 NAMELIST /EEPARMS/
54 jmc 1.27 & nTx, nTy, usingMPI,
55     & useCubedSphereExchange,
56 mlosch 1.29 & useCoupler, useNEST_PARENT, useNEST_CHILD, useOASIS,
57 jmc 1.25 & useSETRLSTK, useSIGREG,
58     & printMapIncludesZeros, maxLengthPrt1D
59 cnh 1.1
60    
61     C-- For now these options are fixed as the code does
62     C not fully support features for overlapping communication
63     C and computation.
64     usingSyncMessages = .TRUE.
65 cnh 1.5
66 cnh 1.1 C-- The remaining parameters here are set to default values.
67     C-- and then any different values are read from an input
68     C-- file called "eedata".
69     C The defaults set here are for serial execution.
70     C
71 jmc 1.25 C nTx and nTy are the number of threads in the X and Y
72 cnh 1.1 C directions.
73     C nSx/nTx and nSy/nTy be whole numbers at present.
74     C
75     C notUsingXPeriodicity and notUsingYPeriodicity affect
76     C the identifying of neighbor processes in a multi-process
77 jmc 1.25 C mode. On the whole the numerical model code should not
78 cnh 1.1 C customise itself based on these numbers as they may be
79     C removed if they do not prove useful.
80     C
81     C usingMPI is a flag which controls whether MPI message
82     C passing library calls are actually made. Note that under
83 jmc 1.25 C MPI it is necessary to start a program a special way -
84 cnh 1.1 C normally using a command of the form
85     C % mpirun program_name
86     C If usingMPI is set to TRUE but % mpirun .... was not
87     C used to launch the program then an internal MPI error
88     C may be generated when the first MPI call ( CALL MPI_Init )
89     C is made.
90     C
91 jmc 1.15 C useCoupler is a flag which controls communications with other
92     C model components through a coupler interface.
93     C
94 jmc 1.25 C useSETRLSTK is a flag which toggles calling a small C routine
95 edhill 1.20 C which sets the stack size to "unlimited" using setrlimit()
96 edhill 1.22
97 cnh 1.1 notUsingXPeriodicity = .FALSE.
98     notUsingYPeriodicity = .FALSE.
99 adcroft 1.12 useCubedSphereExchange = .FALSE.
100 cnh 1.1 usingMPI = .FALSE.
101 jmc 1.15 useCoupler = .FALSE.
102 jmc 1.27 useNEST_PARENT = .FALSE.
103     useNEST_CHILD = .FALSE.
104 mlosch 1.29 useOASIS = .FALSE.
105 adcroft 1.7 nTx = 1
106     nTy = 1
107 edhill 1.20 useSETRLSTK = .FALSE.
108 edhill 1.21 useSIGREG = .FALSE.
109 cnh 1.1
110 jmc 1.25 C-- Parameter for printing (ascii) to Std-Oupt:
111     C Text map plots of fields ignore exact zero values
112     printMapIncludesZeros = .FALSE.
113     C Maximum length for printing (to Std-Msg-Unit) 1-D array
114     maxLengthPrt1D = 65
115    
116 jmc 1.28 C To write output to global-files and from Master MPI process only
117     C NOTE: read from main parameter file "data"
118     useSingleCpuIO = .FALSE.
119    
120 cnh 1.1 C-- Read in data from eedata file
121     C We really ought to be using our environment file reading
122 cnh 1.6 C package - but we have not written it yet.
123 cnh 1.1
124     C Make scratch copies of input data file with and without comments
125 heimbach 1.24 #if defined (TARGET_BGL) || defined (TARGET_CRAYXT)
126 jmc 1.26 WRITE(scratchFile1,'(A,I4.4)') 'scratch1.', myProcId
127     WRITE(scratchFile2,'(A,I4.4)') 'scratch2.', myProcId
128     OPEN(UNIT=scrUnit1, FILE=scratchFile1, STATUS='UNKNOWN')
129     OPEN(UNIT=scrUnit2, FILE=scratchFile2, STATUS='UNKNOWN')
130 ce107 1.19 #else
131 cnh 1.1 OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
132     OPEN(UNIT=scrUnit2,STATUS='SCRATCH')
133 ce107 1.19 #endif
134 cnh 1.6 OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',
135     & err=1,IOSTAT=errIO)
136 cnh 1.1 IF ( errIO .GE. 0 ) GOTO 2
137     1 CONTINUE
138 jmc 1.25 WRITE(msgBuf,'(A)')
139 cnh 1.1 & 'S/R EESET_PARMS'
140     CALL PRINT_ERROR( msgBuf , 1)
141 jmc 1.25 WRITE(msgBuf,'(A)')
142 cnh 1.1 & 'Unable to open execution environment'
143     CALL PRINT_ERROR( msgBuf , 1)
144 jmc 1.25 WRITE(msgBuf,'(A)')
145 cnh 1.1 & 'parameter file "eedata"'
146     CALL PRINT_ERROR( msgBuf , 1)
147     CALL EEDATA_EXAMPLE
148     STOP 'ABNORMAL END: S/R EESET_PARMS'
149     2 CONTINUE
150     1000 CONTINUE
151     READ(eeDataUnit,FMT='(A)',END=1001) RECORD
152     IL = MAX(ILNBLNK(RECORD),1)
153 cnh 1.16 IF ( RECORD(1:1) .NE. commentCharacter ) THEN
154     CALL NML_SET_TERMINATOR( RECORD )
155     WRITE(UNIT=scrUnit1,FMT='(A)') RECORD(:IL)
156     ENDIF
157 cnh 1.1 WRITE(UNIT=scrUnit2,FMT='(A)') RECORD(:IL)
158     GOTO 1000
159     1001 CONTINUE
160     CLOSE(eeDataUnit)
161     C-- Report contents of parameter file
162 jmc 1.25 WRITE(msgBuf,'(A)')
163 cnh 1.6 & '// ======================================================='
164     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
165 jmc 1.25 WRITE(msgBuf,'(A)')
166 cnh 1.6 & '// Execution Environment parameter file "eedata"'
167     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
168 jmc 1.25 WRITE(msgBuf,'(A)')
169 cnh 1.6 & '// ======================================================='
170 cnh 1.1 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
171     & SQUEEZE_RIGHT , 1)
172    
173     iUnit = scrUnit2
174     REWIND(iUnit)
175     2000 CONTINUE
176     READ(UNIT=iUnit,FMT='(A)',END=2001) RECORD
177     IL = MAX(ILNBLNK(RECORD),1)
178     WRITE(msgBuf,'(A,A)') '>',RECORD(:IL)
179 cnh 1.6 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit, SQUEEZE_RIGHT , 1)
180 cnh 1.1 GOTO 2000
181     2001 CONTINUE
182     CLOSE(iUnit)
183    
184     WRITE(msgBuf,'(A)') ' '
185     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
186     & SQUEEZE_RIGHT , 1)
187    
188     iUnit = scrUnit1
189     REWIND(iUnit)
190     READ(UNIT=iUnit,NML=EEPARMS,IOSTAT=errIO,err=3)
191     IF ( errIO .GE. 0 ) GOTO 4
192     3 CONTINUE
193 jamous 1.14 #ifndef TARGET_PWR3
194 jmc 1.25 WRITE(msgBuf,'(A)')
195 cnh 1.1 & 'S/R EESET_PARMS'
196     CALL PRINT_ERROR( msgBuf , 1)
197 jmc 1.25 WRITE(msgBuf,'(A)')
198 cnh 1.1 & 'Error reading execution environment '
199     CALL PRINT_ERROR( msgBuf , 1)
200 jmc 1.25 WRITE(msgBuf,'(A)')
201 cnh 1.1 & 'parameter file "eedata"'
202     CALL PRINT_ERROR( msgBuf , 1)
203     CALL EEDATA_EXAMPLE
204     STOP 'ABNORMAL END: S/R EESET_PARMS'
205 jamous 1.14 #endif
206 cnh 1.1 4 CONTINUE
207 cnh 1.4
208     C-- Execution Environment parameter file read
209     CLOSE(iUnit)
210 cnh 1.1
211     Cdbg eeDataUnit = 42
212     Cdbg OPEN(UNIT=eeDataUnit,FILE='eedata',STATUS='OLD',IOSTAT=errIO)
213     Cdbg IF ( errIO .LT. 0 ) GOTO 11
214     Cdbg DO K=1, 10
215     Cdbg READ(eedataUnit,IOSTAT=errIO)
216     Cdbg IF ( errIO .LT. 0 ) GOTO 11
217 jmc 1.25 Cdbg ENDDO
218 cnh 1.1 Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingXPeriodicity
219     Cdbg IF ( errIO .LT. 0 ) GOTO 11
220     Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) notUsingYPeriodicity
221     Cdbg IF ( errIO .LT. 0 ) GOTO 11
222     Cdbg READ(eedataUnit,FMT='(30X,1X,L23)',IOSTAT=errIO) usingMPI
223     Cdbg IF ( errIO .LT. 0 ) GOTO 11
224 jmc 1.25 Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTx
225 cnh 1.1 Cdbg IF ( errIO .LT. 0 ) GOTO 11
226 jmc 1.25 Cdbg READ(eedataUnit,FMT='(30X,1X,I3)',IOSTAT=errIO) nTy
227 cnh 1.1
228    
229     Cdbg IF (errIO .LT. 0 ) eeBootError = .TRUE.
230     Cdbg CLOSE(eeDataUnit,IOSTAT=errIO)
231     Cdbg IF ( eeBootError .OR. errIO .LT. 0 ) THEN
232     C-- Report that an error occured
233     Cdbg eeBootError = .TRUE.
234 jmc 1.25 Cdbg WRITE(msgBuf,'(A)' )
235 cnh 1.1 Cdbg & 'S/R EESET_PARMS: Error reading "eedata" execution environment file'
236     Cdbg CALL PRINT_ERROR( msgBuf , 1)
237     Cdbg ELSE
238     C-- Write summary of settings that were selected
239     Cdbg ENDIF
240     C
241     C
242     RETURN
243     END

  ViewVC Help
Powered by ViewVC 1.1.22