/[MITgcm]/MITgcm/pkg/exf/exf_check.F
ViewVC logotype

Contents of /MITgcm/pkg/exf/exf_check.F

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


Revision 1.28 - (show annotations) (download)
Fri Jan 27 17:12:08 2017 UTC (7 years, 4 months ago) by jmc
Branch: MAIN
Changes since 1.27: +22 -21 lines
add option ALLOW_READ_TURBFLUXES (and corresponding set of parameters)
 to allow to read-in Sensible & Latent Heat flux.

1 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_check.F,v 1.27 2017/01/11 03:45:34 gforget Exp $
2 C $Name: $
3
4 #include "EXF_OPTIONS.h"
5
6 C-- File exf_check.F: Routines to check EXF settings
7 C-- Contents
8 C-- o EXF_CHECK
9 C-- o EXF_CHECK_INTERP
10
11 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
12 CBOP
13 C !ROUTINE: EXF_CHECK
14 C !INTERFACE:
15
16 SUBROUTINE EXF_CHECK( myThid )
17
18 C !DESCRIPTION: \bv
19 C *==========================================================*
20 C | S/R EXF_CHECK
21 C | o Check parameters and other package dependences
22 C *==========================================================*
23 C \ev
24
25 C !USES:
26 IMPLICIT NONE
27
28 C == Global variables ===
29 #include "EEPARAMS.h"
30 #include "SIZE.h"
31 #include "PARAMS.h"
32
33 #include "EXF_PARAM.h"
34 #include "EXF_CONSTANTS.h"
35
36 C !INPUT/OUTPUT PARAMETERS:
37 C myThid :: my Thread Id number
38 INTEGER myThid
39
40 C !LOCAL VARIABLES:
41 C msgBuf :: Informational/error message buffer
42 CHARACTER*(MAX_LEN_MBUF) msgBuf
43 INTEGER errCount
44 CEOP
45
46 _BEGIN_MASTER(myThid)
47 errCount = 0
48
49 WRITE(msgBuf,'(A)') 'EXF_CHECK: #define ALLOW_EXF'
50 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
51 & SQUEEZE_RIGHT, myThid )
52
53 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
54 C check for consistency
55 IF (.NOT.
56 & (exf_iprec.EQ.precFloat32 .OR. exf_iprec.EQ.precFloat64)
57 & ) THEN
58 WRITE(msgBuf,'(A)')
59 & 'S/R EXF_CHECK: value of exf_iprec not allowed'
60 CALL PRINT_ERROR( msgBuf, myThid )
61 errCount = errCount + 1
62 ENDIF
63
64 IF (repeatPeriod.lt.0.) THEN
65 WRITE(msgBuf,'(A)')
66 & 'S/R EXF_CHECK: repeatPeriod must be positive'
67 CALL PRINT_ERROR( msgBuf, myThid )
68 errCount = errCount + 1
69 ENDIF
70
71 IF (useExfYearlyFields.and.repeatPeriod.ne.0.) THEN
72 WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: The use of ',
73 $ 'useExfYearlyFields AND repeatPeriod is not implemented'
74 CALL PRINT_ERROR( msgBuf, myThid )
75 errCount = errCount + 1
76 ENDIF
77
78 IF ( useAtmWind ) THEN
79 IF ( ustressfile .NE. ' ' .OR. vstressfile .NE. ' ' ) THEN
80 WRITE(msgBuf,'(A)')
81 & 'S/R EXF_CHECK: use u,v_wind components but not wind-stress'
82 CALL PRINT_ERROR( msgBuf, myThid )
83 errCount = errCount + 1
84 ENDIF
85 ENDIF
86
87 IF ( .NOT.useAtmWind ) THEN
88 IF ( uwindfile .NE. ' ' .OR. vwindfile .NE. ' ' ) THEN
89 WRITE(msgBuf,'(A)')
90 & 'S/R EXF_CHECK: read-in wind-stress but not u,v_wind components'
91 CALL PRINT_ERROR( msgBuf, myThid )
92 errCount = errCount + 1
93 ENDIF
94 ENDIF
95
96 #ifdef ALLOW_SALTFLX
97 IF ( useSEAICE .OR. useThSIce ) THEN
98 IF ( saltflxfile .NE. ' ' ) THEN
99 WRITE(msgBuf,'(2A)') 'S/R EXF_CHECK: exf salt flux is not',
100 & ' allowed when using either pkg/seaice or pkg/thsice'
101 CALL PRINT_ERROR( msgBuf, myThid )
102 errCount = errCount + 1
103 ENDIF
104 ENDIF
105 #endif /* ALLOW_SALTFLX */
106
107 #ifndef ALLOW_ZENITHANGLE
108 IF ( useExfZenAlbedo .OR. useExfZenIncoming .OR.
109 & select_ZenAlbedo .NE. 0 ) THEN
110 WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: unsupported option',
111 & ' when ALLOW_ZENITHANGLE is not defined'
112 CALL PRINT_ERROR( msgBuf, myThid )
113 errCount = errCount + 1
114 ENDIF
115 #endif /* ndef ALLOW_ZENITHANGLE */
116
117 #ifdef ALLOW_ZENITHANGLE
118 IF ( usingCartesianGrid .OR. usingCylindricalGrid ) THEN
119 WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ALLOW_ZENITHANGLE does ',
120 & 'not work for carthesian and cylindrical grids'
121 CALL PRINT_ERROR( msgBuf, myThid )
122 errCount = errCount + 1
123 ENDIF
124 IF ( select_ZenAlbedo.LT.0 .OR. select_ZenAlbedo.GT.3 ) THEN
125 WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: unsupported ',
126 & 'select_ZenAlbedo choice'
127 CALL PRINT_ERROR( msgBuf, myThid )
128 errCount = errCount + 1
129 ENDIF
130 IF ( select_ZenAlbedo.EQ.2 .) THEN
131 WRITE(msgBuf,'(A,A)')
132 & 'S/R EXF_CHECK: *** WARNING *** for daily mean albedo, ',
133 & 'it is advised to use select_ZenAlbedo.EQ.1 instead of 2'
134 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
135 & SQUEEZE_RIGHT, myThid )
136 ENDIF
137 IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 21600 ) THEN
138 WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: using diurnal albedo ',
139 & 'formula requires diurnal downward shortwave forcing'
140 CALL PRINT_ERROR( msgBuf, myThid )
141 errCount = errCount + 1
142 ENDIF
143 IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 3600 ) then
144 WRITE(msgBuf,'(A,A,A)')
145 & 'S/R EXF_CHECK: *** WARNING *** ',
146 & 'the diurnal albedo formula is likely not safe for such ',
147 & 'coarse temporal resolution downward shortwave forcing'
148 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
149 & SQUEEZE_RIGHT, myThid )
150 ENDIF
151 #endif /* ALLOW_ZENITHANGLE */
152
153 #ifdef USE_EXF_INTERPOLATION
154 IF ( usingCartesianGrid ) THEN
155 WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
156 & 'USE_EXF_INTERPOLATION assumes latitude/longitude'
157 CALL PRINT_ERROR( msgBuf, myThid )
158 WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
159 & 'input and output coordinates. Trivial to extend to'
160 CALL PRINT_ERROR( msgBuf, myThid )
161 WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
162 & 'cartesian coordinates, but has not yet been done.'
163 CALL PRINT_ERROR( msgBuf, myThid )
164 errCount = errCount + 1
165 ENDIF
166
167 CALL EXF_CHECK_INTERP('ustress',ustressfile,ustress_interpMethod,
168 & ustress_nlat,ustress_lon_inc,errCount,myThid)
169 CALL EXF_CHECK_INTERP('vstress',vstressfile,vstress_interpMethod,
170 & vstress_nlat,vstress_lon_inc,errCount,myThid)
171 CALL EXF_CHECK_INTERP('hflux',hfluxfile,hflux_interpMethod,
172 & hflux_nlat,hflux_lon_inc,errCount,myThid)
173 CALL EXF_CHECK_INTERP('sflux',sfluxfile,sflux_interpMethod,
174 & sflux_nlat,sflux_lon_inc,errCount,myThid)
175 CALL EXF_CHECK_INTERP('swflux',swfluxfile,swflux_interpMethod,
176 & swflux_nlat,swflux_lon_inc,errCount,myThid)
177 CALL EXF_CHECK_INTERP('runoff',runofffile,runoff_interpMethod,
178 & runoff_nlat,runoff_lon_inc,errCount,myThid)
179 CALL EXF_CHECK_INTERP('saltflx',saltflxfile,saltflx_interpMethod,
180 & saltflx_nlat,saltflx_lon_inc,errCount,myThid)
181 CALL EXF_CHECK_INTERP('atemp',atempfile,atemp_interpMethod,
182 & atemp_nlat,atemp_lon_inc,errCount,myThid)
183 CALL EXF_CHECK_INTERP('aqh',aqhfile,aqh_interpMethod,
184 & aqh_nlat,aqh_lon_inc,errCount,myThid)
185 CALL EXF_CHECK_INTERP( 'hs', hs_file, hs_interpMethod,
186 & hs_nlat, hs_lon_inc, errCount, myThid )
187 CALL EXF_CHECK_INTERP( 'hl', hl_file, hl_interpMethod,
188 & hl_nlat, hl_lon_inc, errCount, myThid )
189 CALL EXF_CHECK_INTERP('evap',evapfile,evap_interpMethod,
190 & evap_nlat,evap_lon_inc,errCount,myThid)
191 CALL EXF_CHECK_INTERP('precip',precipfile,precip_interpMethod,
192 & precip_nlat,precip_lon_inc,errCount,myThid)
193 CALL EXF_CHECK_INTERP('snowprecip',
194 & snowprecipfile,snowprecip_interpMethod,
195 & snowprecip_nlat,snowprecip_lon_inc,errCount,myThid)
196 CALL EXF_CHECK_INTERP('uwind',uwindfile,uwind_interpMethod,
197 & uwind_nlat,uwind_lon_inc,errCount,myThid)
198 CALL EXF_CHECK_INTERP('vwind',vwindfile,vwind_interpMethod,
199 & vwind_nlat,vwind_lon_inc,errCount,myThid)
200 CALL EXF_CHECK_INTERP('wspeed',wspeedfile,wspeed_interpMethod,
201 & wspeed_nlat,wspeed_lon_inc,errCount,myThid)
202 CALL EXF_CHECK_INTERP('lwflux',lwfluxfile,lwflux_interpMethod,
203 & lwflux_nlat,lwflux_lon_inc,errCount,myThid)
204 CALL EXF_CHECK_INTERP('swdown',swdownfile,swdown_interpMethod,
205 & swdown_nlat,swdown_lon_inc,errCount,myThid)
206 CALL EXF_CHECK_INTERP('lwdown',lwdownfile,lwdown_interpMethod,
207 & lwdown_nlat,lwdown_lon_inc,errCount,myThid)
208 CALL EXF_CHECK_INTERP('apressure',
209 & apressurefile,apressure_interpMethod,
210 & apressure_nlat,apressure_lon_inc,errCount,myThid)
211 CALL EXF_CHECK_INTERP('areamask',
212 & areamaskfile,areamask_interpMethod,
213 & areamask_nlat,areamask_lon_inc,errCount,myThid)
214 CALL EXF_CHECK_INTERP('climsst',climsstfile,climsst_interpMethod,
215 & climsst_nlat,climsst_lon_inc,errCount,myThid)
216 CALL EXF_CHECK_INTERP('climsss',climsssfile,climsss_interpMethod,
217 & climsss_nlat,climsss_lon_inc,errCount,myThid)
218 CALL EXF_CHECK_INTERP('climustr',
219 & climustrfile,climustr_interpMethod,
220 & climustr_nlat,climustr_lon_inc,errCount,myThid)
221 CALL EXF_CHECK_INTERP('climvstr',
222 & climvstrfile,climvstr_interpMethod,
223 & climvstr_nlat,climvstr_lon_inc,errCount,myThid)
224
225 C- some restrictions on 2-component vector field (might be relaxed later on)
226 IF ( ( uwind_interpMethod.GE.1 .AND. uwindfile.NE.' ' ) .OR.
227 & ( vwind_interpMethod.GE.1 .AND. vwindfile.NE.' ' ) ) THEN
228 IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
229 IF ( uwind_interpMethod.EQ.0 .OR. uwindfile.EQ.' ' .OR.
230 & vwind_interpMethod.EQ.0 .OR. vwindfile.EQ.' ' ) THEN
231 C- stop if one expects interp+rotation (Curvilin-G) which will not happen
232 WRITE(msgBuf,'(A)')
233 & 'S/R EXF_CHECK: interp. needs 2 components (wind)'
234 CALL PRINT_ERROR( msgBuf, myThid )
235 errCount = errCount + 1
236 ENDIF
237 IF ( uwindstartdate .NE. vwindstartdate .OR.
238 & uwindperiod .NE. vwindperiod ) THEN
239 WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
240 & 'For CurvilinearGrid/RotatedGrid, the u and v wind '
241 CALL PRINT_ERROR( msgBuf, myThid )
242 WRITE(msgBuf,'(A,A,A)') 'S/R EXF_CHECK: ',
243 & 'files have to have the same startdate and period, ',
244 & 'because S/R EXF_SET_UV assumes that.'
245 CALL PRINT_ERROR( msgBuf, myThid )
246 errCount = errCount + 1
247 ENDIF
248 ENDIF
249 ENDIF
250 IF ( (ustress_interpMethod.GE.1 .AND. ustressfile.NE.' ') .OR.
251 & (vstress_interpMethod.GE.1 .AND. vstressfile.NE.' ') ) THEN
252 IF ( readStressOnCgrid ) THEN
253 WRITE(msgBuf,'(A,A)')
254 & 'S/R EXF_CHECK: readStressOnCgrid=.TRUE. ',
255 & 'and interp wind-stress (=A-grid) are not compatible'
256 CALL PRINT_ERROR( msgBuf, myThid )
257 errCount = errCount + 1
258 ENDIF
259 IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
260 IF ( ustress_interpMethod.EQ.0 .OR. ustressfile.EQ.' ' .OR.
261 & vstress_interpMethod.EQ.0 .OR. vstressfile.EQ.' ' ) THEN
262 C- stop if one expects interp+rotation (Curvilin-G) which will not happen
263 WRITE(msgBuf,'(A)')
264 & 'S/R EXF_CHECK: interp. needs 2 components (wind-stress)'
265 CALL PRINT_ERROR( msgBuf, myThid )
266 errCount = errCount + 1
267 ENDIF
268 IF ( ustressstartdate .NE. vstressstartdate .OR.
269 & ustressperiod .NE. vstressperiod ) THEN
270 WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
271 & 'For CurvilinearGrid/RotatedGrid, the u and v wind stress '
272 CALL PRINT_ERROR( msgBuf, myThid )
273 WRITE(msgBuf,'(A,A,A)') 'S/R EXF_CHECK: ',
274 & 'files have to have the same startdate and period, ',
275 & 'because S/R EXF_SET_UV assumes that.'
276 CALL PRINT_ERROR( msgBuf, myThid )
277 errCount = errCount + 1
278 ENDIF
279 ENDIF
280 ENDIF
281
282 IF ( (ustress_interpMethod.EQ.0 .AND. ustressfile.NE.' ') .OR.
283 & (vstress_interpMethod.EQ.0 .AND. vstressfile.NE.' ') ) THEN
284 #else /* ifndef USE_EXF_INTERPOLATION */
285 IF ( ustressfile .NE. ' ' .OR. vstressfile .NE. ' ' ) THEN
286 #endif /* USE_EXF_INTERPOLATION */
287 IF ( (readStressOnAgrid.AND.readStressOnCgrid) .OR.
288 & .NOT.(readStressOnAgrid.OR.readStressOnCgrid) ) THEN
289 WRITE(msgBuf,'(A)')
290 & 'S/R EXF_CHECK: Select 1 wind-stress position: A or C-grid'
291 CALL PRINT_ERROR( msgBuf, myThid )
292 errCount = errCount + 1
293 ENDIF
294 IF (rotateStressOnAgrid.AND..NOT.readStressOnAgrid) THEN
295 WRITE(msgBuf,'(2A)') 'S/R EXF_CHECK: rotateStressOnAgrid ',
296 & 'only applies to cases readStressOnAgrid is true'
297 CALL PRINT_ERROR( msgBuf, myThid )
298 errCount = errCount + 1
299 ENDIF
300
301 ELSE
302 IF ( readStressOnAgrid .OR. readStressOnCgrid .OR.
303 & rotateStressOnAgrid) THEN
304 WRITE(msgBuf,'(A)')
305 & 'S/R EXF_CHECK: wind-stress position irrelevant'
306 CALL PRINT_ERROR( msgBuf, myThid )
307 errCount = errCount + 1
308 ENDIF
309 ENDIF
310
311 #ifdef USE_NO_INTERP_RUNOFF
312 WRITE(msgBuf,'(A)')
313 & 'S/R EXF_CHECK: USE_NO_INTERP_RUNOFF code has been removed;'
314 CALL PRINT_ERROR( msgBuf, myThid )
315 WRITE(msgBuf,'(A,A)')
316 & 'S/R EXF_CHECK: use instead "runoff_interpMethod=0"',
317 & ' in "data.exf" (EXF_NML_04)'
318 CALL PRINT_ERROR( msgBuf, myThid )
319 errCount = errCount + 1
320 #endif /* USE_NO_INTERP_RUNOFF */
321
322 #ifdef ALLOW_CLIMTEMP_RELAXATION
323 WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
324 & 'ALLOW_CLIMTEMP_RELAXATION no longer supported. Use pkg/rbcs'
325 CALL PRINT_ERROR( msgBuf, myThid )
326 errCount = errCount + 1
327 #endif /* ALLOW_CLIMTEMP_RELAXATION */
328
329 #ifdef ALLOW_CLIMSALT_RELAXATION
330 WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
331 & 'ALLOW_CLIMSALT_RELAXATION no longer supported. Use pkg/rbcs'
332 CALL PRINT_ERROR( msgBuf, myThid )
333 errCount = errCount + 1
334 #endif /* ALLOW_CLIMSALT_RELAXATION */
335
336 IF ( climsstTauRelax.NE.0. ) THEN
337 #ifndef ALLOW_CLIMSST_RELAXATION
338 WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsstTauRelax > 0'
339 CALL PRINT_ERROR( msgBuf, myThid )
340 WRITE(msgBuf,'(A)')
341 & 'S/R EXF_CHECK: but ALLOW_CLIMSST_RELAXATION is not defined'
342 CALL PRINT_ERROR( msgBuf, myThid )
343 errCount = errCount + 1
344 #endif /* ndef ALLOW_CLIMSST_RELAXATION */
345 IF ( climsstfile.EQ.' ' ) THEN
346 WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsstTauRelax > 0 but'
347 CALL PRINT_ERROR( msgBuf, myThid )
348 WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsstfile is not set'
349 CALL PRINT_ERROR( msgBuf, myThid )
350 errCount = errCount + 1
351 ENDIf
352 ENDIf
353
354 IF ( climsssTauRelax.NE.0. ) THEN
355 #ifndef ALLOW_CLIMSSS_RELAXATION
356 WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsssTauRelax > 0'
357 CALL PRINT_ERROR( msgBuf, myThid )
358 WRITE(msgBuf,'(A)')
359 & 'S/R EXF_CHECK: but ALLOW_CLIMSSS_RELAXATION is not defined'
360 CALL PRINT_ERROR( msgBuf, myThid )
361 errCount = errCount + 1
362 #endif /* ALLOW_CLIMSSS_RELAXATION */
363 IF ( climsssfile.EQ.' ' ) THEN
364 WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsssTauRelax > 0 but'
365 CALL PRINT_ERROR( msgBuf, myThid )
366 WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsssfile is not set'
367 CALL PRINT_ERROR( msgBuf, myThid )
368 errCount = errCount + 1
369 ENDIF
370 ENDIF
371
372 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
373
374 IF ( errCount.GE.1 ) THEN
375 WRITE(msgBuf,'(A,I3,A)')
376 & 'EXF_CHECK: detected', errCount,' fatal error(s)'
377 CALL PRINT_ERROR( msgBuf, myThid )
378 CALL ALL_PROC_DIE( 0 )
379 STOP 'ABNORMAL END: S/R EXF_CHECK'
380 ENDIF
381
382 _END_MASTER(myThid)
383
384 RETURN
385 END
386
387 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
388
389 CBOP
390 C !ROUTINE: EXF_CHECK_INTERP
391 C !INTERFACE:
392
393 SUBROUTINE EXF_CHECK_INTERP(
394 I loc_name, loc_file,
395 I loc_interpMethod, loc_nlat, loc_lon_inc,
396 U errCount,
397 I myThid )
398
399 C !DESCRIPTION: \bv
400 C *==========================================================*
401 C | S/R EXF_CHECK_INTERP
402 C | o Check parameters for one of the pkg/exf variable
403 C *==========================================================*
404 C \ev
405
406 C !USES:
407 IMPLICIT NONE
408
409 C == Global variables ===
410 #include "EEPARAMS.h"
411 #include "EXF_PARAM.h"
412
413 C !INPUT/OUTPUT PARAMETERS:
414 C myThid :: my Thread Id number
415 CHARACTER*(*) loc_name
416 CHARACTER*(*) loc_file
417 INTEGER loc_interpMethod
418 INTEGER loc_nlat
419 _RL loc_lon_inc
420 INTEGER errCount
421 INTEGER myThid
422
423 C !LOCAL VARIABLES:
424 C msgBuf :: Informational/error message buffer
425 CHARACTER*(MAX_LEN_MBUF) msgBuf
426 CEOP
427
428 IF ( loc_interpMethod.GE.1 .AND. loc_file.NE.' ' ) THEN
429 IF ( loc_nlat .GT. MAX_LAT_INC ) THEN
430 WRITE(msgBuf,'(3A)') 'S/R EXF_CHECK_INTERP: ',loc_name,
431 & '_nlat > MAX_LAT_INC'
432 CALL PRINT_ERROR( msgBuf, myThid )
433 errCount = errCount + 1
434 ENDIF
435 IF ( loc_lon_inc.GT.500. ) THEN
436 WRITE(msgBuf,'(4A,1PE16.8)') 'S/R EXF_CHECK_INTERP: ',
437 & 'Invalid value for: ',loc_name,'_lon_inc =', loc_lon_inc
438 CALL PRINT_ERROR( msgBuf, myThid )
439 WRITE(msgBuf,'(4A)') 'S/R EXF_CHECK_INTERP: Fix it ',
440 & 'or Turn off ',loc_name,'-interp (interpMethod=0)'
441 CALL PRINT_ERROR( msgBuf, myThid )
442 errCount = errCount + 1
443 ENDIF
444 ENDIF
445
446 RETURN
447 END

  ViewVC Help
Powered by ViewVC 1.1.22