/[MITgcm]/MITgcm/pkg/rbcs/rbcs_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/rbcs/rbcs_readparms.F

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


Revision 1.14 - (show annotations) (download)
Wed Nov 15 23:34:31 2017 UTC (6 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, HEAD
Changes since 1.13: +32 -4 lines
- increase size of "relaxMaskFile" to read-in from namelist and save it
  (+check) into new (renamed) "relaxMaskTrFile" array.

1 C $Header: /u/gcmpack/MITgcm/pkg/rbcs/rbcs_readparms.F,v 1.13 2017/08/09 15:23:36 mlosch Exp $
2 C $Name: $
3
4 #include "RBCS_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: RBCS_READPARMS
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE RBCS_READPARMS( myThid )
11
12 C !DESCRIPTION:
13 C Initialize RBCS parameters, read in data.rbcs
14
15 C !USES: ===============================================================
16 IMPLICIT NONE
17 #include "SIZE.h"
18 #include "EEPARAMS.h"
19 #include "PARAMS.h"
20 #ifdef ALLOW_PTRACERS
21 #include "PTRACERS_SIZE.h"
22 #endif
23 #include "RBCS_SIZE.h"
24 #include "RBCS_PARAMS.h"
25
26 C !INPUT PARAMETERS: ===================================================
27 C myThid :: my thread Id. number
28 INTEGER myThid
29
30 C !OUTPUT PARAMETERS: ==================================================
31 C none
32
33 #ifdef ALLOW_RBCS
34
35 C === Local variables ===
36 C msgBuf :: Informational/error message buffer
37 C iUnit :: Work variable for IO unit number
38 C iTracer :: passive tracer index
39 C relaxMaskFile :: local mask-file name to read from namelist
40 CHARACTER*(MAX_LEN_MBUF) msgBuf
41 INTEGER iUnit
42 INTEGER irbc, errCount
43 INTEGER locSize
44 #ifdef ALLOW_PTRACERS
45 INTEGER iTracer
46 PARAMETER( locSize = 10+PTRACERS_num )
47 #else
48 PARAMETER( locSize = 4 )
49 #endif
50 CHARACTER*(MAX_LEN_FNAM) relaxMaskFile(locSize)
51 C-- useRBCptracers is no longer used
52 LOGICAL useRBCptracers
53 INTEGER rbcsIniter
54 CEOP
55
56 C-- RBCS parameters:
57 NAMELIST /RBCS_PARM01/
58 & tauRelaxU,
59 & tauRelaxV,
60 & tauRelaxT,
61 & tauRelaxS,
62 & relaxMaskUFile,
63 & relaxMaskVFile,
64 & relaxMaskFile,
65 & relaxUFile,
66 & relaxVFile,
67 & relaxTFile,
68 & relaxSFile,
69 & useRBCuVel,
70 & useRBCvVel,
71 & useRBCtemp,
72 & useRBCsalt,
73 & useRBCptracers,
74 & rbcsIniter,
75 & rbcsForcingPeriod,
76 & rbcsForcingCycle,
77 & rbcsForcingOffset,
78 & rbcsVanishingTime,
79 & rbcsSingleTimeFiles,
80 & deltaTrbcs,
81 & rbcsIter0
82
83 #ifdef ALLOW_PTRACERS
84 NAMELIST /RBCS_PARM02/
85 & useRBCpTrNum, tauRelaxPTR,
86 & relaxPtracerFile
87 #endif
88
89 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
90
91 IF ( .NOT.useRBCS ) THEN
92 C- pkg RBCS is not used
93 _BEGIN_MASTER(myThid)
94 C- Track pkg activation status:
95 C print a (weak) warning if data.rbcs is found
96 CALL PACKAGES_UNUSED_MSG( 'useRBCS', ' ', ' ' )
97 _END_MASTER(myThid)
98 RETURN
99 ENDIF
100
101 _BEGIN_MASTER(myThid)
102
103 C-- Default values
104 useRBCuVel =.FALSE.
105 useRBCvVel =.FALSE.
106 useRBCtemp =.FALSE.
107 useRBCsalt =.FALSE.
108 tauRelaxU = 0.
109 tauRelaxV = 0.
110 tauRelaxT = 0.
111 tauRelaxS = 0.
112 relaxMaskUFile = ' '
113 relaxMaskVFile = ' '
114 DO irbc=1,locSize
115 relaxMaskFile(irbc) = ' '
116 ENDDO
117 relaxUFile = ' '
118 relaxVFile = ' '
119 relaxTFile = ' '
120 relaxSFile = ' '
121 rbcsIniter = 0
122 rbcsForcingPeriod = 0. _d 0
123 rbcsForcingCycle = 0. _d 0
124 rbcsForcingOffset = 0. _d 0
125 rbcsVanishingTime = 0. _d 0
126 rbcsSingleTimeFiles = .FALSE.
127 deltaTrbcs = deltaTclock
128 rbcsIter0 = 0
129 #ifdef ALLOW_PTRACERS
130 DO iTracer=1,PTRACERS_num
131 useRBCpTrNum(iTracer)=.FALSE.
132 tauRelaxPTR(iTracer) = 0.
133 relaxPtracerFile(iTracer) = ' '
134 ENDDO
135 #endif
136 useRBCptracers=.FALSE.
137
138 C-- Open and read the data.rbcs file
139
140 WRITE(msgBuf,'(A)') ' RBCS_READPARMS: opening data.rbcs'
141 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
142 & SQUEEZE_RIGHT , 1)
143 CALL OPEN_COPY_DATA_FILE(
144 I 'data.rbcs', 'RBCS_READPARMS',
145 O iUnit,
146 I myThid )
147 READ(UNIT=iUnit,NML=RBCS_PARM01)
148 #ifdef ALLOW_PTRACERS
149 READ(UNIT=iUnit,NML=RBCS_PARM02)
150 #endif
151 WRITE(msgBuf,'(A)')
152 & ' RBCS_READPARMS: finished reading data.rbcs'
153 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
154 & SQUEEZE_RIGHT , 1)
155
156 C-- Close the open data file
157 #ifdef SINGLE_DISK_IO
158 CLOSE(iUnit)
159 #else
160 CLOSE(iUnit,STATUS='DELETE')
161 #endif /* SINGLE_DISK_IO */
162
163 C- save local mask-file name into relaxMaskTrFile (stored in common block)
164 DO irbc=1,maskLEN
165 relaxMaskTrFile(irbc) = ' '
166 ENDDO
167 errCount = 0
168 DO irbc=1,locSize
169 IF ( irbc.LE.maskLEN ) THEN
170 relaxMaskTrFile(irbc) = relaxMaskFile(irbc)
171 ELSEIF ( relaxMaskFile(irbc).NE.' ' ) THEN
172 errCount = errCount + 1
173 ENDIF
174 ENDDO
175 IF ( errCount.GT.0 ) THEN
176 WRITE(msgBuf,'(2A,I6)')' RBCS_READPARAMS: ',
177 & 'Too many "relaxMaskFile" are set ! exceeds maskLEN=', maskLEN
178 CALL PRINT_ERROR( msgBuf, myThid )
179 WRITE(msgBuf,'(2A)')' RBCS_READPARAMS: ',
180 & '==> Increase maskLEN (in RBCS_SIZE.h) and recompile'
181 CALL PRINT_ERROR( msgBuf, myThid )
182 ENDIF
183
184 C--- Check RBCS config and params:
185 #ifdef DISABLE_RBCS_MOM
186 IF ( useRBCuVel .OR. useRBCvVel ) THEN
187 WRITE(msgBuf,'(2A,2(L2,A))') 'RBCS_READPARMS: ',
188 & 'cannot use RBC for U,V (useRBCuVel=',useRBCuVel,
189 & ', useRBCvVel=',useRBCvVel,')'
190 CALL PRINT_ERROR( msgBuf, myThid )
191 WRITE(msgBuf,'(2A)') 'RBCS_READPARMS: ',
192 & 'when DISABLE_RBCS_MOM is defined (in RBCS_OPTIONS.h)'
193 CALL PRINT_ERROR( msgBuf, myThid )
194 STOP 'ABNORMAL END: S/R RBCS_READPARMS'
195 ENDIF
196 #endif /* DISABLE_RBCS_MOM */
197 IF (rbcsIniter.NE.0) THEN
198 WRITE(msgBuf,'(2A)')' RBCS_READPARAMS: ',
199 & 'rbcsIniter has been replaced by rbcsForcingOffset '
200 CALL PRINT_ERROR( msgBuf, myThid )
201 WRITE(msgBuf,'(2A)')' RBCS_READPARAMS: ',
202 & 'which is in seconds. Please change your data.rbcs'
203 CALL PRINT_ERROR( msgBuf, myThid )
204 STOP 'ABNORMAL END: S/R RBCS_READPARAMS'
205 ENDIF
206 IF (startTime.LT.rbcsForcingOffset+0.5*rbcsForcingPeriod .AND.
207 & .NOT. rbcsSingleTimeFiles) THEN
208 IF (rbcsForcingCycle.GT.0) THEN
209 WRITE(msgBuf,'(2A)')' RBCS_READPARAMS: ',
210 & 'startTime before rbcsForcingOffset+0.5*rbcsForcingPeriod '
211 CALL PRINT_ERROR( msgBuf, myThid )
212 WRITE(msgBuf,'(2A)')' RBCS_READPARAMS: ',
213 & 'will use last record'
214 CALL PRINT_ERROR( msgBuf, myThid )
215 ELSE
216 WRITE(msgBuf,'(2A)')' RBCS_READPARAMS: ',
217 & 'startTime before rbcsForcingOffset+0.5*rbcsForcingPeriod '
218 CALL PRINT_ERROR( msgBuf, myThid )
219 WRITE(msgBuf,'(2A)')' RBCS_READPARAMS: ',
220 & 'not allowed with rbcsForcingCycle=0 unless rbcsSingleTimeFiles'
221 CALL PRINT_ERROR( msgBuf, myThid )
222 STOP 'ABNORMAL END: S/R RBCS_READPARAMS'
223 ENDIF
224 ENDIF
225 IF ( useRBCuVel .AND. tauRelaxU.LE.0. ) THEN
226 WRITE(msgBuf,'(2A)') 'RBCS_READPARMS: ',
227 & 'tauRelaxU cannot be zero with useRBCuVel'
228 CALL PRINT_ERROR( msgBuf, myThid )
229 STOP 'ABNORMAL END: S/R RBCS_READPARMS'
230 ENDIF
231 IF ( useRBCvVel .AND. tauRelaxV.LE.0. ) THEN
232 WRITE(msgBuf,'(2A)') 'RBCS_READPARMS: ',
233 & 'tauRelaxV cannot be zero with useRBCvVel'
234 CALL PRINT_ERROR( msgBuf, myThid )
235 STOP 'ABNORMAL END: S/R RBCS_READPARMS'
236 ENDIF
237 IF ( useRBCtemp .AND. tauRelaxT.LE.0. ) THEN
238 WRITE(msgBuf,'(2A)') 'RBCS_READPARMS: ',
239 & 'tauRelaxT cannot be zero with useRBCtemp'
240 CALL PRINT_ERROR( msgBuf, myThid )
241 STOP 'ABNORMAL END: S/R RBCS_READPARMS'
242 ENDIF
243 IF ( useRBCsalt .AND. tauRelaxS.LE.0. ) THEN
244 WRITE(msgBuf,'(2A)') 'RBCS_READPARMS: ',
245 & 'tauRelaxS cannot be zero with useRBCsalt'
246 CALL PRINT_ERROR( msgBuf, myThid )
247 STOP 'ABNORMAL END: S/R RBCS_READPARMS'
248 ENDIF
249 #ifdef ALLOW_PTRACERS
250 DO iTracer=1,PTRACERS_num
251 IF ( useRBCpTrNum(iTracer) ) THEN
252 IF ( .NOT.usePTRACERS ) THEN
253 WRITE(msgBuf,'(2A,I6,A)') 'RBCS_READPARMS: ',
254 & 'usePTRACERS=F => cannot use RBCS for tracer:', iTracer
255 CALL PRINT_ERROR( msgBuf, myThid )
256 STOP 'ABNORMAL END: S/R RBCS_READPARMS'
257 ENDIF
258 c IF ( iTracer.GT.PTRACERS_numInUse ) THEN
259 c STOP 'ABNORMAL END: S/R RBCS_READPARMS'
260 c ENDIF
261 IF ( tauRelaxPTR(iTracer).LE.0. ) THEN
262 WRITE(msgBuf,'(2A,I6,A)') 'RBCS_READPARMS: ',
263 & 'tauRelaxPTR(itr=', iTracer, ' ) = 0. is'
264 CALL PRINT_ERROR( msgBuf, myThid )
265 WRITE(msgBuf,'(2A,I6,A)') 'RBCS_READPARMS: ',
266 & 'not allowed with useRBCptr(itr)=T'
267 CALL PRINT_ERROR( msgBuf, myThid )
268 STOP 'ABNORMAL END: S/R RBCS_READPARMS'
269 ENDIF
270 ENDIF
271 ENDDO
272 #endif
273 _END_MASTER(myThid)
274
275 C Everyone else must wait for the parameters to be loaded
276 _BARRIER
277
278 #endif /* ALLOW_RBCS */
279
280 RETURN
281 END

  ViewVC Help
Powered by ViewVC 1.1.22