/[MITgcm]/MITgcm/model/src/config_check.F
ViewVC logotype

Annotation of /MITgcm/model/src/config_check.F

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


Revision 1.72 - (hide annotations) (download)
Sun Dec 30 18:32:52 2012 UTC (11 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64c, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f
Changes since 1.71: +10 -1 lines
add a warning if select_rStar=2 with nonlinFreeSurf <> 4
 (not consistent to account for the slope of the coordinate when
 ignoring the variations of level-thickness in PhiHyd calculation)

1 jmc 1.72 C $Header: /u/gcmpack/MITgcm/model/src/config_check.F,v 1.71 2012/12/22 00:38:35 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4 edhill 1.10 #include "PACKAGES_CONFIG.h"
5 jmc 1.1 #include "CPP_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: CONFIG_CHECK
9     C !INTERFACE:
10     SUBROUTINE CONFIG_CHECK( myThid )
11     C !DESCRIPTION: \bv
12     C *=========================================================*
13     C | SUBROUTINE CONFIG_CHECK
14     C | o Check model parameter settings.
15     C *=========================================================*
16     C | This routine help to prevent the use of parameters
17     C | that are not compatible with the model configuration.
18     C *=========================================================*
19 jmc 1.33 C \ev
20 jmc 1.1
21     C !USES:
22     IMPLICIT NONE
23     C === Global variables ===
24     #include "SIZE.h"
25     #include "EEPARAMS.h"
26     #include "PARAMS.h"
27     c #include "GRID.h"
28    
29     C !INPUT/OUTPUT PARAMETERS:
30     C === Routine arguments ===
31     C myThid - Number of this instances of CONFIG_CHECK
32     INTEGER myThid
33     CEndOfInterface
34    
35     C !LOCAL VARIABLES:
36     C == Local variables ==
37 jmc 1.53 C msgBuf :: Informational/error message buffer
38 jmc 1.1 CHARACTER*(MAX_LEN_MBUF) msgBuf
39 jmc 1.61 INTEGER errCount
40 jmc 1.1 CEOP
41    
42 jmc 1.69 _BEGIN_MASTER(myThid)
43     WRITE(msgBuf,'(A)')
44     &'// ======================================================='
45     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
46     & SQUEEZE_RIGHT, myThid )
47     WRITE(msgBuf,'(A)') '// Check Model config. (CONFIG_CHECK):'
48     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
49     & SQUEEZE_RIGHT, myThid )
50     _END_MASTER(myThid)
51    
52 jmc 1.61 C-- MPI + multi-threads: seems to be OK to let master-thread check & stop
53     C (as long as all procs finish cleanly by calling ALL_PROC_DIE)
54     _BEGIN_MASTER(myThid)
55     errCount = 0
56    
57 jmc 1.1 C- check that CPP option is "defined" when running-flag parameter is on:
58    
59 dimitri 1.43 C o If diffKrFile is set, then we should make sure the corresponing
60     C code is being compiled
61 jmc 1.50 #ifndef ALLOW_3D_DIFFKR
62 dimitri 1.43 IF (diffKrFile.NE.' ') THEN
63     WRITE(msgBuf,'(A)')
64     & 'CONFIG_CHECK: diffKrFile is set but never used.'
65 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
66 jmc 1.70 WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
67     & 'Re-compile with: "#define ALLOW_3D_DIFFKR"'
68 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
69 jmc 1.61 errCount = errCount + 1
70 dimitri 1.43 ENDIF
71     #endif
72    
73 jmc 1.1 #ifndef ALLOW_NONHYDROSTATIC
74 jmc 1.40 IF (use3Dsolver) THEN
75     WRITE(msgBuf,'(A)')
76 jmc 1.1 & 'CONFIG_CHECK: #undef ALLOW_NONHYDROSTATIC and'
77 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
78 jmc 1.32 IF ( implicitIntGravWave ) WRITE(msgBuf,'(A)')
79     & 'CONFIG_CHECK: implicitIntGravWave is TRUE'
80     IF ( nonHydrostatic ) WRITE(msgBuf,'(A)')
81 jmc 1.1 & 'CONFIG_CHECK: nonHydrostatic is TRUE'
82 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
83 jmc 1.61 errCount = errCount + 1
84 jmc 1.1 ENDIF
85     #endif
86    
87 jmc 1.22 #ifndef ALLOW_ADAMSBASHFORTH_3
88     IF ( alph_AB.NE.UNSET_RL .OR. beta_AB.NE.UNSET_RL ) THEN
89     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
90     & '#undef ALLOW_ADAMSBASHFORTH_3 but alph_AB,beta_AB'
91 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
92 jmc 1.22 WRITE(msgBuf,'(A,1P2E20.7)')
93     & 'CONFIG_CHECK: are set to:',alph_AB,beta_AB
94 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
95 jmc 1.61 errCount = errCount + 1
96 jmc 1.22 ENDIF
97     #endif
98    
99 jmc 1.13 #ifndef INCLUDE_IMPLVERTADV_CODE
100 jmc 1.40 IF ( momImplVertAdv ) THEN
101     WRITE(msgBuf,'(A)')
102 jmc 1.13 & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
103 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
104 jmc 1.13 WRITE(msgBuf,'(A)')
105     & 'CONFIG_CHECK: but momImplVertAdv is TRUE'
106 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
107 jmc 1.61 errCount = errCount + 1
108 jmc 1.13 ENDIF
109 jmc 1.40 IF ( tempImplVertAdv ) THEN
110     WRITE(msgBuf,'(A)')
111 jmc 1.13 & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
112 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
113 jmc 1.13 WRITE(msgBuf,'(A)')
114     & 'CONFIG_CHECK: but tempImplVertAdv is TRUE'
115 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
116 jmc 1.61 errCount = errCount + 1
117 jmc 1.13 ENDIF
118 jmc 1.40 IF ( saltImplVertAdv ) THEN
119     WRITE(msgBuf,'(A)')
120 jmc 1.13 & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
121 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
122 jmc 1.13 WRITE(msgBuf,'(A)')
123     & 'CONFIG_CHECK: but saltImplVertAdv is TRUE'
124 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
125 jmc 1.61 errCount = errCount + 1
126 jmc 1.13 ENDIF
127 jmc 1.19 IF ( dTtracerLev(1).NE.dTtracerLev(Nr) .AND. implicitDiffusion
128 jmc 1.40 & .AND. ( saltStepping .OR. tempStepping .OR. usePTRACERS )
129 jmc 1.19 & ) THEN
130 jmc 1.40 WRITE(msgBuf,'(A)')
131 jmc 1.19 & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
132 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
133 jmc 1.19 WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
134     & 'but implicitDiffusion=T with non-uniform dTtracerLev'
135 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
136 jmc 1.61 errCount = errCount + 1
137 jmc 1.19 ENDIF
138 jmc 1.13 #endif
139    
140 gforget 1.55 #ifdef ALLOW_AUTODIFF_TAMC
141     IF ( momImplVertAdv ) THEN
142     WRITE(msgBuf,'(A)')
143     & 'CONFIG_CHECK: momImplVertAdv is not yet'
144     CALL PRINT_ERROR( msgBuf, myThid )
145     WRITE(msgBuf,'(A)')
146     & 'CONFIG_CHECK: supported in adjoint mode'
147     CALL PRINT_ERROR( msgBuf, myThid )
148 jmc 1.61 errCount = errCount + 1
149 gforget 1.55 ENDIF
150     #endif
151    
152 jmc 1.58 #ifdef ALLOW_DEPTH_CONTROL
153     IF ( useOBCS ) THEN
154     WRITE(msgBuf,'(A)')
155     & 'CONFIG_CHECK: DEPTH_CONTROL code not compatible with OBCS'
156     CALL PRINT_ERROR( msgBuf, myThid )
157 jmc 1.61 errCount = errCount + 1
158 jmc 1.58 ENDIF
159     #endif
160    
161 jmc 1.1 #ifndef EXACT_CONSERV
162 jmc 1.40 IF (exactConserv) THEN
163     WRITE(msgBuf,'(A)')
164 jmc 1.1 & 'CONFIG_CHECK: #undef EXACT_CONSERV and'
165 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
166 jmc 1.1 WRITE(msgBuf,'(A)')
167     & 'CONFIG_CHECK: exactConserv is TRUE'
168 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
169 jmc 1.61 errCount = errCount + 1
170 jmc 1.1 ENDIF
171     #endif
172    
173     #ifndef NONLIN_FRSURF
174 jmc 1.40 IF (nonlinFreeSurf.NE.0) THEN
175     WRITE(msgBuf,'(A)')
176 jmc 1.1 & 'CONFIG_CHECK: #undef NONLIN_FRSURF and'
177 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
178 jmc 1.1 WRITE(msgBuf,'(A)')
179     & 'CONFIG_CHECK: nonlinFreeSurf is non-zero'
180 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
181 jmc 1.61 errCount = errCount + 1
182 jmc 1.1 ENDIF
183     #endif
184    
185 jmc 1.9 #ifndef NONLIN_FRSURF
186     IF (select_rStar .NE. 0) THEN
187 jmc 1.40 WRITE(msgBuf,'(A)')
188 jmc 1.9 & 'CONFIG_CHECK: rStar is part of NonLin-FS '
189 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
190 jmc 1.9 WRITE(msgBuf,'(A)')
191 jmc 1.56 & 'CONFIG_CHECK: ==> set #define NONLIN_FRSURF to use it'
192 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
193 jmc 1.61 errCount = errCount + 1
194 jmc 1.9 ENDIF
195     #endif /* NONLIN_FRSURF */
196    
197 jmc 1.56 #ifdef DISABLE_RSTAR_CODE
198     IF ( select_rStar.NE.0 ) THEN
199     WRITE(msgBuf,'(A)')
200     & 'CONFIG_CHECK: rStar code disable (DISABLE_RSTAR_CODE defined)'
201     CALL PRINT_ERROR( msgBuf, myThid )
202     WRITE(msgBuf,'(A)')
203     & 'CONFIG_CHECK: ==> set #undef DISABLE_RSTAR_CODE to use it'
204     CALL PRINT_ERROR( msgBuf, myThid )
205 jmc 1.61 errCount = errCount + 1
206 jmc 1.56 ENDIF
207     #endif /* DISABLE_RSTAR_CODE */
208    
209     #ifdef DISABLE_SIGMA_CODE
210     IF ( selectSigmaCoord.NE.0 ) THEN
211     WRITE(msgBuf,'(A)')
212     & 'CONFIG_CHECK: Sigma code disable (DISABLE_SIGMA_CODE defined)'
213     CALL PRINT_ERROR( msgBuf, myThid )
214     WRITE(msgBuf,'(A)')
215     & 'CONFIG_CHECK: ==> set #undef DISABLE_SIGMA_CODE to use it'
216     CALL PRINT_ERROR( msgBuf, myThid )
217 jmc 1.61 errCount = errCount + 1
218 jmc 1.56 ENDIF
219     #endif /* DISABLE_SIGMA_CODE */
220    
221 jmc 1.1 #ifdef USE_NATURAL_BCS
222 jmc 1.40 WRITE(msgBuf,'(A)')
223 jmc 1.3 & 'CONFIG_CHECK: USE_NATURAL_BCS option has been replaced'
224 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
225 jmc 1.1 WRITE(msgBuf,'(A)')
226 jmc 1.3 & 'CONFIG_CHECK: by useRealFreshWaterFlux=TRUE in data file'
227 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
228 jmc 1.61 errCount = errCount + 1
229 jmc 1.3 #endif
230    
231 jmc 1.50 #ifndef ALLOW_ADDFLUID
232     IF ( selectAddFluid.NE.0 ) THEN
233     WRITE(msgBuf,'(A)')
234 jmc 1.70 & 'CONFIG_CHECK: #undef ALLOW_ADDFLUID (CPP_OPTIONS.h) and'
235 jmc 1.50 CALL PRINT_ERROR( msgBuf, myThid )
236     WRITE(msgBuf,'(A,I4,A)') 'CONFIG_CHECK: selectAddFluid=',
237     & selectAddFluid, ' is not zero'
238     CALL PRINT_ERROR( msgBuf, myThid )
239 jmc 1.61 errCount = errCount + 1
240 jmc 1.50 ENDIF
241     #endif /* ALLOW_ADDFLUID */
242    
243 jmc 1.4 C o If pLoadFile is set, then we should make sure the corresponing
244     C code is being compiled
245     #ifndef ATMOSPHERIC_LOADING
246     IF (pLoadFile.NE.' ') THEN
247     WRITE(msgBuf,'(A)')
248     & 'CONFIG_CHECK: pLoadFile is set but you have not'
249 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
250 jmc 1.4 WRITE(msgBuf,'(A)')
251 jmc 1.70 & ' compiled the model with the pressure loading code.'
252 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
253 jmc 1.15 WRITE(msgBuf,'(A)')
254 jmc 1.70 & ' Re-compile with: "#define ATMOSPHERIC_LOADING"'
255 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
256 jmc 1.61 errCount = errCount + 1
257 jmc 1.15 ENDIF
258     IF ( useRealFreshWaterFlux .AND. useThSIce ) THEN
259     WRITE(msgBuf,'(A)')
260     & 'CONFIG_CHECK: sIceLoad is computed but'
261 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
262 jmc 1.15 WRITE(msgBuf,'(A)')
263 jmc 1.70 & ' pressure loading code is not compiled.'
264 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
265 jmc 1.15 WRITE(msgBuf,'(A)')
266 jmc 1.70 & ' Re-compile with: "#define ATMOSPHERIC_LOADING"'
267     CALL PRINT_ERROR( msgBuf, myThid )
268     errCount = errCount + 1
269     ENDIF
270     #endif
271    
272     #ifndef ALLOW_FRICTION_HEATING
273     IF ( addFrictionHeating ) THEN
274     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: addFrictionHeating=T',
275     & ' but FRICTIONAL_HEATING code is not compiled.'
276     CALL PRINT_ERROR( msgBuf, myThid )
277     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: Re-compile with:',
278     & ' "#define ALLOW_FRICTION_HEATING" (CPP_OPTIONS.h)'
279 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
280 jmc 1.61 errCount = errCount + 1
281 jmc 1.4 ENDIF
282     #endif
283    
284 mlosch 1.31 #ifndef ALLOW_BALANCE_FLUXES
285     IF (balanceEmPmR .OR. balanceQnet) THEN
286     WRITE(msgBuf,'(A,A)')
287     & 'CONFIG_CHECK: balanceEmPmR/Qnet is set but balance code ',
288     & 'is not compiled.'
289 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
290 jmc 1.70 WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
291     & 'Re-compile with: ALLOW_BALANCE_FLUXES defined'
292 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
293 jmc 1.61 errCount = errCount + 1
294 mlosch 1.31 ENDIF
295     #endif
296    
297 gforget 1.66 #ifndef ALLOW_BALANCE_RELAX
298     IF (balanceThetaClimRelax .OR. balanceSaltClimRelax) THEN
299     WRITE(msgBuf,'(A,A)')
300     & 'CONFIG_CHECK: balanceTheta/SaltClimRelax is set ',
301     & 'but balance code is not compiled.'
302     CALL PRINT_ERROR( msgBuf, myThid )
303 jmc 1.70 WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
304 gforget 1.66 & 'Re-compile with ALLOW_BALANCE_RELAX defined'
305     CALL PRINT_ERROR( msgBuf, myThid )
306     errCount = errCount + 1
307     ENDIF
308     #endif
309    
310 mlosch 1.52 #ifndef ALLOW_SRCG
311     IF (useSRCGSolver) THEN
312     WRITE(msgBuf,'(A,A)')
313     & 'CONFIG_CHECK: useSRCGSolver = .TRUE., but single reduction ',
314     & 'code is not compiled.'
315 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
316 mlosch 1.52 WRITE(msgBuf,'(A)')
317     & 'CONFIG_CHECK: Re-compile with ALLOW_SRCG defined'
318 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
319 jmc 1.61 errCount = errCount + 1
320 mlosch 1.52 ENDIF
321     #endif /* ALLOW_SRCG */
322    
323 jmc 1.3 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
324    
325 jmc 1.48 C-- Check parameter consistency :
326 jmc 1.8
327 jmc 1.59 IF ( ( OLx.LT.3 .OR. OLy.LT.3 ) .AND.
328 jmc 1.28 & ( viscC4leithD.NE.0. .OR. viscC4leith.NE.0.
329     & .OR. viscC4smag.NE.0. .OR. viscA4Grid.NE.0.
330     & .OR. viscA4D.NE.0. .OR. viscA4Z.NE.0. ) ) THEN
331 jmc 1.8 WRITE(msgBuf,'(A,A)')
332     & 'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',
333 jmc 1.59 & ' overlap (OLx,OLy) smaller than 3'
334 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
335 jmc 1.61 errCount = errCount + 1
336 jmc 1.33 ENDIF
337 jmc 1.59 IF ( ( OLx.LT.3 .OR. OLy.LT.3 ) .AND.
338 jmc 1.28 & ( viscC2leithD.NE.0. .OR. viscC4leithD.NE.0. )
339     & ) THEN
340     WRITE(msgBuf,'(A,A)')
341     & 'CONFIG_CHECK: cannot use Leith Visc.(div.part) with',
342 jmc 1.59 & ' overlap (OLx,OLy) smaller than 3'
343 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
344 jmc 1.61 errCount = errCount + 1
345 jmc 1.33 ENDIF
346 jmc 1.3
347 jmc 1.62 #ifndef DISCONNECTED_TILES
348     C Overlaps cannot be larger than interior tile except for special cases
349 mlosch 1.60 IF ( sNx.LT.OLx ) THEN
350     #ifdef ALLOW_EXCH2
351     WRITE(msgBuf,'(A)')
352     & 'CONFIG_CHECK: sNx<OLx not allowed with ALLOW_EXCH2 defined'
353     CALL PRINT_ERROR( msgBuf, myThid )
354 jmc 1.61 errCount = errCount + 1
355 mlosch 1.60 #endif /* ALLOW_EXCH2 */
356     IF ( Nx.NE.1 ) THEN
357     WRITE(msgBuf,'(A)')
358     & 'CONFIG_CHECK: sNx<OLx not allowed unless Nx=1'
359     CALL PRINT_ERROR( msgBuf, myThid )
360 jmc 1.61 errCount = errCount + 1
361 mlosch 1.60 ENDIF
362     ENDIF
363     IF ( sNy.LT.OLy ) THEN
364     #ifdef ALLOW_EXCH2
365     WRITE(msgBuf,'(A)')
366     & 'CONFIG_CHECK: sNy<OLy not allowed with ALLOW_EXCH2 defined'
367     CALL PRINT_ERROR( msgBuf, myThid )
368 jmc 1.61 errCount = errCount + 1
369 mlosch 1.60 #endif /* ALLOW_EXCH2 */
370     IF ( Ny.NE.1 ) THEN
371     WRITE(msgBuf,'(A)')
372     & 'CONFIG_CHECK: sNy<OLy not allowed unless Ny=1'
373     CALL PRINT_ERROR( msgBuf, myThid )
374 jmc 1.61 errCount = errCount + 1
375 mlosch 1.60 ENDIF
376     ENDIF
377 jmc 1.62 #endif /* ndef DISCONNECTED_TILES */
378 mlosch 1.60
379 jmc 1.48 C-- Deep-Atmosphere & Anelastic limitations:
380 jmc 1.40 IF ( deepAtmosphere .AND.
381     & useRealFreshWaterFlux .AND. usingPCoords ) THEN
382     WRITE(msgBuf,'(A,A)')
383     & 'CONFIG_CHECK: Deep-Atmosphere not yet implemented with',
384     & ' real-Fresh-Water option in P-coordinate'
385 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
386 jmc 1.61 errCount = errCount + 1
387 jmc 1.40 ENDIF
388     IF ( select_rStar.NE.0 .AND.
389     & ( deepAtmosphere .OR.
390     & usingZCoords.AND.rhoRefFile .NE. ' ' ) ) THEN
391     WRITE(msgBuf,'(A,A)')
392     & 'CONFIG_CHECK: Deep-Atmosphere or Anelastic',
393     & ' not yet implemented with rStar'
394 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
395 jmc 1.61 errCount = errCount + 1
396 jmc 1.40 ENDIF
397     IF ( vectorInvariantMomentum .AND.
398     & ( deepAtmosphere .OR.
399     & usingZCoords.AND.rhoRefFile .NE. ' ' ) ) THEN
400     WRITE(msgBuf,'(A,A)')
401     & 'CONFIG_CHECK: Deep-Atmosphere or Anelastic',
402     & ' not yet implemented in Vector-Invariant momentum code'
403 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
404 jmc 1.61 errCount = errCount + 1
405 jmc 1.40 ENDIF
406    
407 jmc 1.48 C-- Free-surface related limitations:
408 jmc 1.71 IF ( cg2dUseMinResSol.LT.0 .OR. cg2dUseMinResSol.GT.1 ) THEN
409     WRITE(msgBuf,'(A,I10,A)')
410     & 'CONFIG_CHECK: cg2dUseMinResSol set to unvalid value(=',
411     & cg2dUseMinResSol, ')'
412     CALL PRINT_ERROR( msgBuf, myThid )
413     errCount = errCount + 1
414     ENDIF
415    
416 jmc 1.3 IF ( rigidLid .AND. implicitFreeSurface ) THEN
417     WRITE(msgBuf,'(A,A)')
418     & 'CONFIG_CHECK: Cannot select both implicitFreeSurface',
419     & ' and rigidLid.'
420 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
421 jmc 1.61 errCount = errCount + 1
422 jmc 1.33 ENDIF
423 jmc 1.3
424     IF (rigidLid .AND. exactConserv) THEN
425 jmc 1.40 WRITE(msgBuf,'(A)')
426 jmc 1.3 & 'CONFIG_CHECK: exactConserv not compatible with'
427 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
428 jmc 1.1 WRITE(msgBuf,'(A)')
429 jmc 1.3 & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
430 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
431 jmc 1.61 errCount = errCount + 1
432 jmc 1.1 ENDIF
433    
434 dfer 1.41 IF ( linFSConserveTr .AND. nonlinFreeSurf.NE.0 ) THEN
435     WRITE(msgBuf,'(A)')
436     & 'CONFIG_CHECK: Cannot select both a Nonlinear Free Surf.'
437 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
438 dfer 1.41 WRITE(msgBuf,'(A)')
439     & 'CONFIG_CHECK: and Tracer Correction of Lin. Free Surf.'
440 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
441 jmc 1.61 errCount = errCount + 1
442 dfer 1.41 ENDIF
443    
444 jmc 1.3 IF (rigidLid .AND. useRealFreshWaterFlux) THEN
445 jmc 1.40 WRITE(msgBuf,'(A)')
446 jmc 1.3 & 'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'
447 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
448 jmc 1.1 WRITE(msgBuf,'(A)')
449     & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
450 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
451 jmc 1.61 errCount = errCount + 1
452 jmc 1.1 ENDIF
453    
454     IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN
455 jmc 1.40 WRITE(msgBuf,'(A)')
456 jmc 1.1 & 'CONFIG_CHECK: nonlinFreeSurf cannot be used'
457 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
458 jmc 1.1 WRITE(msgBuf,'(A)')
459     & 'CONFIG_CHECK: without exactConserv'
460 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
461 jmc 1.61 errCount = errCount + 1
462 jmc 1.1 ENDIF
463    
464 jmc 1.6 IF (select_rStar.NE.0 .AND. .NOT.exactConserv) THEN
465 jmc 1.40 WRITE(msgBuf,'(A)')
466 jmc 1.6 & 'CONFIG_CHECK: r* Coordinate cannot be used'
467 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
468 jmc 1.6 WRITE(msgBuf,'(A)')
469     & 'CONFIG_CHECK: without exactConserv'
470 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
471 jmc 1.61 errCount = errCount + 1
472 jmc 1.6 ENDIF
473    
474 jmc 1.67 IF ( select_rStar.GE.1 .AND. nonlinFreeSurf.LE.0 ) THEN
475     WRITE(msgBuf,'(2A,I3,A)') 'CONFIG_CHECK: r* Coordinate',
476     & ' (select_rStar=', select_rStar, ' ) cannot be used'
477     CALL PRINT_ERROR( msgBuf, myThid )
478     WRITE(msgBuf,'(2A,I3,A)') 'CONFIG_CHECK: ',
479     & ' with Linear FreeSurf (nonlinFreeSurf=', nonlinFreeSurf,' )'
480     CALL PRINT_ERROR( msgBuf, myThid )
481     errCount = errCount + 1
482     ENDIF
483 jmc 1.72 IF ( select_rStar.EQ.2 .AND. nonlinFreeSurf.NE.4 ) THEN
484     C- not consistent to account for the slope of the coordinate when
485     C ignoring the variations of level-thickness in PhiHyd calculation;
486     C for now, issue a warning (but might change the code later on):
487     WRITE(msgBuf,'(2A,I3)') '** WARNING ** CONFIG_CHECK: ',
488     & 'select_rStar=2 not right with nonlinFreeSurf=', nonlinFreeSurf
489     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
490     & SQUEEZE_RIGHT, myThid )
491     ENDIF
492 jmc 1.67
493 jmc 1.56 IF ( selectSigmaCoord.NE.0 ) THEN
494     IF ( fluidIsWater ) THEN
495     WRITE(msgBuf,'(A)')
496     & 'CONFIG_CHECK: Sigma-Coords not yet coded for Oceanic set-up'
497     CALL PRINT_ERROR( msgBuf, myThid )
498 jmc 1.61 errCount = errCount + 1
499 jmc 1.56 ENDIF
500     IF ( nonlinFreeSurf.LE.0 ) THEN
501     WRITE(msgBuf,'(A)')
502     & 'CONFIG_CHECK: Sigma-Coords not coded for Lin-FreeSurf'
503     CALL PRINT_ERROR( msgBuf, myThid )
504 jmc 1.61 errCount = errCount + 1
505 jmc 1.56 ENDIF
506     IF (select_rStar.NE.0 ) THEN
507     WRITE(msgBuf,'(A)')
508     & 'CONFIG_CHECK: Sigma-Coords and rStar are not compatible'
509     CALL PRINT_ERROR( msgBuf, myThid )
510 jmc 1.61 errCount = errCount + 1
511 jmc 1.56 ENDIF
512     WRITE(msgBuf,'(A)')
513     & 'CONFIG_CHECK: Sigma-Coords code neither complete nor tested'
514     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
515     & SQUEEZE_RIGHT, myThid )
516     ENDIF
517    
518 jmc 1.54 C- note : not implemented in checkpoint48b but it is done now (since 01-28-03)
519 jmc 1.7 c IF (select_rStar.GT.0 .AND. useOBCS ) THEN
520     c STOP 'ABNORMAL END: S/R CONFIG_CHECK'
521     c ENDIF
522 jmc 1.1
523 jmc 1.40 IF ( nonlinFreeSurf.NE.0 .AND.
524 jmc 1.70 & deltaTFreeSurf.NE.dTtracerLev(1) ) THEN
525 jmc 1.53 WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
526     & 'nonlinFreeSurf might cause problems'
527 jmc 1.4 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
528 jmc 1.53 & SQUEEZE_RIGHT, myThid )
529     WRITE(msgBuf,'(2A)') '** WARNING ** ',
530     & 'with different FreeSurf & Tracer time-steps'
531 jmc 1.4 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
532 jmc 1.53 & SQUEEZE_RIGHT, myThid )
533 jmc 1.3 ENDIF
534    
535 jmc 1.15 IF ( useRealFreshWaterFlux .AND. exactConserv
536 jmc 1.50 & .AND. implicDiv2Dflow.EQ.0. _d 0
537 jmc 1.21 & .AND. startTime.NE.baseTime .AND. usePickupBeforeC54 ) THEN
538 jmc 1.40 WRITE(msgBuf,'(A)')
539 jmc 1.3 & 'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'
540 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
541 jmc 1.3 WRITE(msgBuf,'(A)')
542     & 'CONFIG_CHECK: restart not implemented in this config'
543 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
544 jmc 1.61 errCount = errCount + 1
545 jmc 1.3 ENDIF
546    
547 jmc 1.40 IF ( useRealFreshWaterFlux .AND. .NOT.exactConserv
548 jmc 1.50 & .AND. implicDiv2Dflow.NE.1. ) THEN
549 jmc 1.53 WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
550 jmc 1.50 & 'RealFreshWater & implicDiv2Dflow < 1'
551 jmc 1.15 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
552 jmc 1.53 & SQUEEZE_RIGHT, myThid )
553     WRITE(msgBuf,'(2A)') '** WARNING ** works better',
554 jmc 1.15 & ' with exactConserv=.T. (+ #define EXACT_CONSERV)'
555     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
556 jmc 1.53 & SQUEEZE_RIGHT, myThid )
557 jmc 1.15 ENDIF
558    
559     #ifdef EXACT_CONSERV
560 jmc 1.4 IF (useRealFreshWaterFlux .AND. .NOT.exactConserv
561     & .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
562 jmc 1.40 WRITE(msgBuf,'(A)')
563 jmc 1.4 & 'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'
564 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
565 jmc 1.4 WRITE(msgBuf,'(A)')
566     & 'CONFIG_CHECK: requires exactConserv=T'
567 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
568 jmc 1.61 errCount = errCount + 1
569 jmc 1.4 ENDIF
570     #else
571     IF (useRealFreshWaterFlux
572     & .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
573 jmc 1.53 WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
574     & 'E-P effects on wVel are not included'
575 jmc 1.4 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
576 jmc 1.53 & SQUEEZE_RIGHT, myThid )
577     WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
578     & '==> use #define EXACT_CONSERV to fix it'
579 jmc 1.5 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
580 jmc 1.53 & SQUEEZE_RIGHT, myThid )
581 jmc 1.5 ENDIF
582 jmc 1.15 #endif /* EXACT_CONSERV */
583 jmc 1.5
584 jmc 1.50 IF ( selectAddFluid.LT.-1 .OR. selectAddFluid.GT.2 ) THEN
585     WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: selectAddFluid=',
586     & selectAddFluid, ' not allowed'
587 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
588 jmc 1.50 WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
589     & 'should be =0 (Off), 1,2 (Add Mass) or -1 (Virtual Flux)'
590 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
591 jmc 1.61 errCount = errCount + 1
592 jmc 1.50 ENDIF
593     IF ( selectAddFluid.GE.1 .AND. rigidLid ) THEN
594     WRITE(msgBuf,'(A)')
595     & 'CONFIG_CHECK: selectAddFluid > 0 not compatible with'
596 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
597 jmc 1.50 WRITE(msgBuf,'(A)')
598     & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
599 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
600 jmc 1.61 errCount = errCount + 1
601 jmc 1.50 ENDIF
602     IF ( selectAddFluid.GE.1 .AND. .NOT.staggerTimeStep ) THEN
603 jmc 1.53 WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
604     & 'synchronous time-stepping =>'
605 jmc 1.50 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
606 jmc 1.53 & SQUEEZE_RIGHT, myThid )
607     WRITE(msgBuf,'(2A)') '** WARNING ** ',
608 jmc 1.50 & '1 time-step mismatch in AddFluid effects on T & S'
609     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
610 jmc 1.53 & SQUEEZE_RIGHT, myThid )
611     ENDIF
612    
613     C-- Non-hydrostatic and 3-D solver related limitations:
614     IF (nonlinFreeSurf.NE.0 .AND. use3Dsolver) THEN
615     WRITE(msgBuf,'(A)')
616     & 'CONFIG_CHECK: nonlinFreeSurf not yet implemented'
617     CALL PRINT_ERROR( msgBuf, myThid )
618     WRITE(msgBuf,'(A)')
619     & 'CONFIG_CHECK: in nonHydrostatic code'
620     CALL PRINT_ERROR( msgBuf, myThid )
621 jmc 1.61 errCount = errCount + 1
622 jmc 1.53 ENDIF
623    
624     IF ( implicitNHPress*implicSurfPress*implicDiv2Dflow.NE.1.
625     & .AND. implicitIntGravWave ) THEN
626     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: implicitIntGravWave',
627     & ' NOT SAFE with non-fully implicit solver'
628     CALL PRINT_ERROR( msgBuf, myThid )
629     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: To by-pass this',
630     & 'STOP, comment this test and re-compile config_check'
631     CALL PRINT_ERROR( msgBuf, myThid )
632 jmc 1.61 errCount = errCount + 1
633 jmc 1.53 ENDIF
634     IF ( nonHydrostatic .AND. .NOT.exactConserv
635     & .AND. implicDiv2Dflow.NE.1. ) THEN
636     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: Needs exactConserv=T',
637     & ' for nonHydrostatic with implicDiv2Dflow < 1'
638     CALL PRINT_ERROR( msgBuf, myThid )
639 jmc 1.61 errCount = errCount + 1
640 jmc 1.53 ENDIF
641     IF ( nonHydrostatic .AND.
642     & implicitNHPress.NE.implicSurfPress ) THEN
643     WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
644     & ' nonHydrostatic might cause problems with'
645     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
646     & SQUEEZE_RIGHT, myThid )
647     WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
648     & 'different implicitNHPress & implicSurfPress'
649     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
650     & SQUEEZE_RIGHT, myThid )
651     ENDIF
652    
653     IF ( implicitViscosity .AND. use3Dsolver ) THEN
654     WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
655     & 'Implicit viscosity applies to provisional u,vVel'
656     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
657     & SQUEEZE_RIGHT, myThid )
658     WRITE(msgBuf,'(2A)') '** WARNING ** => not consistent with',
659     & 'final vertical shear (after appling 3-D solver solution'
660     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
661     & SQUEEZE_RIGHT, myThid )
662     ENDIF
663     IF ( implicitViscosity .AND. nonHydrostatic ) THEN
664     WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
665     & 'Implicit viscosity not implemented in CALC_GW'
666     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
667     & SQUEEZE_RIGHT, myThid )
668     WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
669     & 'Explicit viscosity might become unstable if too large'
670     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
671     & SQUEEZE_RIGHT, myThid )
672 jmc 1.50 ENDIF
673    
674 jmc 1.48 C-- Momentum related limitations:
675 jmc 1.47 IF ( vectorInvariantMomentum.AND.momStepping ) THEN
676     IF ( highOrderVorticity.AND.upwindVorticity ) THEN
677     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
678     & '"highOrderVorticity" conflicts with "upwindVorticity"'
679 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
680 jmc 1.61 errCount = errCount + 1
681 jmc 1.47 ENDIF
682     ENDIF
683 jmc 1.69 IF ( .NOT.vectorInvariantMomentum .AND. momAdvection ) THEN
684     IF ( usingCurvilinearGrid ) THEN
685     WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
686     & 'missing metric-terms for CurvilinearGrid'
687     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
688     & SQUEEZE_RIGHT, myThid )
689     ENDIF
690     IF ( hasWetCSCorners ) THEN
691     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: momAdvection ',
692     & 'in flux-form is wrong on CubedSphere grid (corners)'
693     CALL PRINT_ERROR( msgBuf, myThid )
694     errCount = errCount + 1
695     ENDIF
696     ENDIF
697 jmc 1.57 IF ( selectCoriMap.LT.0 .OR. selectCoriMap.GT.3 ) THEN
698     WRITE(msgBuf,'(2A,I4)') 'CONFIG_CHECK: ',
699     & 'Invalid option: selectCoriMap=', selectCoriMap
700     CALL PRINT_ERROR( msgBuf, myThid )
701 jmc 1.61 errCount = errCount + 1
702 jmc 1.57 ENDIF
703 jmc 1.47
704 jmc 1.9 IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN
705 jmc 1.40 C- jmc: since useCDscheme is a new [04-13-03] flag (default=F),
706     C put this WARNING to stress that even if CD-scheme parameters
707     C (tauCD,rCD) are set, CD-scheme is not used without useCDscheme=T
708 jmc 1.9 C- and STOP if using mom_fluxform (following Chris advise).
709     C- jmc: but ultimately, this block can/will be removed.
710     IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN
711 jmc 1.40 WRITE(msgBuf,'(A)')
712 jmc 1.9 & 'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
713 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
714 jmc 1.9 WRITE(msgBuf,'(2A)')
715     & 'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
716 jmc 1.40 & ' in "data", namelist PARM01'
717 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
718 jmc 1.61 errCount = errCount + 1
719 jmc 1.9 ENDIF
720 jmc 1.53 WRITE(msgBuf,'(2A)') '** WARNING ** CONFIG_CHECK: ',
721     & 'CD-scheme is OFF but params(tauCD,rCD) are set'
722 jmc 1.5 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
723 jmc 1.53 & SQUEEZE_RIGHT, myThid )
724     WRITE(msgBuf,'(3A)') '** WARNING ** to turn ON CD-scheme:',
725     & ' => "useCDscheme=.TRUE." in "data", namelist PARM01'
726 jmc 1.4 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
727 jmc 1.53 & SQUEEZE_RIGHT, myThid )
728 jmc 1.12 ENDIF
729    
730 jmc 1.69 IF ( useCDscheme .AND. hasWetCSCorners ) THEN
731 jmc 1.12 WRITE(msgBuf,'(2A)')
732     & 'CONFIG_CHECK: CD-scheme not implemented on CubedSphere grid'
733 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
734 jmc 1.69 errCount = errCount + 1
735 jmc 1.12 ENDIF
736    
737 jmc 1.48 C-- Time-stepping limitations
738 jmc 1.40 IF ( momForcingOutAB.NE.0 .AND. momForcingOutAB.NE.1 ) THEN
739 jmc 1.34 WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: momForcingOutAB=',
740     & momForcingOutAB, ' not allowed'
741 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
742 jmc 1.34 WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: momForcingOutAB ',
743     & 'should be =1 (Out of AB) or =0 (In AB)'
744 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
745 jmc 1.61 errCount = errCount + 1
746 jmc 1.34 ENDIF
747 jmc 1.40 IF ( tracForcingOutAB.NE.0 .AND. tracForcingOutAB.NE.1 ) THEN
748 jmc 1.34 WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: tracForcingOutAB=',
749     & tracForcingOutAB, ' not allowed'
750 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
751 jmc 1.34 WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: tracForcingOutAB ',
752     & 'should be =1 (Out of AB) or =0 (In AB)'
753 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
754 jmc 1.61 errCount = errCount + 1
755 jmc 1.4 ENDIF
756 jmc 1.71 IF ( addFrictionHeating .AND. .NOT.staggerTimeStep ) THEN
757     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: addFrictionHeating',
758     & ' not yet coded for synchronous time-stepping.'
759     CALL PRINT_ERROR( msgBuf, myThid )
760     errCount = errCount + 1
761     ENDIF
762 jmc 1.1
763 jmc 1.48 C-- Grid limitations:
764 mlosch 1.44 IF ( rotateGrid ) THEN
765     IF ( .NOT. usingSphericalPolarGrid ) THEN
766     WRITE(msgBuf,'(2A)')
767     & 'CONFIG_CHECK: specifying Euler angles makes only ',
768     & 'sense with usingSphericalGrid=.TRUE.'
769 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
770 jmc 1.61 errCount = errCount + 1
771 mlosch 1.44 ENDIF
772 gforget 1.65 IF ( useFLT .OR. useZonal_Filt .OR. useECCO ) THEN
773 mlosch 1.44 WRITE(msgBuf,'(2A)')
774     & 'CONFIG_CHECK: specifying Euler angles will probably ',
775     & 'not work with pkgs FLT, ZONAL_FLT, ECCO'
776 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
777 jmc 1.61 errCount = errCount + 1
778 mlosch 1.44 ENDIF
779     ENDIF
780    
781 jmc 1.48 C-- Packages conflict
782     IF ( useMATRIX .AND. useGCHEM ) THEN
783     WRITE(msgBuf,'(2A)')
784     & 'CONFIG_CHECK: cannot set both: useMATRIX & useGCHEM'
785 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
786 jmc 1.61 errCount = errCount + 1
787 jmc 1.48 ENDIF
788    
789     IF ( useMATRIX .AND. .NOT.usePTRACERS ) THEN
790     WRITE(msgBuf,'(2A)')
791     & 'CONFIG_CHECK: cannot set useMATRIX without ',
792     & 'setting usePTRACERS'
793 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
794 jmc 1.61 errCount = errCount + 1
795 jmc 1.48 ENDIF
796    
797 jmc 1.50 IF ( (useSEAICE .OR. useThSIce) .AND. allowFreezing ) THEN
798     WRITE(msgBuf,'(2A)')
799     & 'CONFIG_CHECK: cannot set allowFreezing',
800     & ' with pkgs SEAICE or THSICE'
801 jmc 1.53 CALL PRINT_ERROR( msgBuf, myThid )
802 jmc 1.61 errCount = errCount + 1
803     ENDIF
804    
805     IF ( errCount.GE.1 ) THEN
806     WRITE(msgBuf,'(A,I3,A)')
807     & 'CONFIG_CHECK: detected', errCount,' fatal error(s)'
808     CALL PRINT_ERROR( msgBuf, myThid )
809     CALL ALL_PROC_DIE( 0 )
810 jmc 1.50 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
811     ENDIF
812 jmc 1.61 _END_MASTER(myThid)
813    
814     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
815 jmc 1.50
816 jmc 1.61 _BEGIN_MASTER(myThid)
817 jmc 1.49 WRITE(msgBuf,'(A)') '// CONFIG_CHECK : Normal End'
818     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
819     & SQUEEZE_RIGHT, myThid )
820     WRITE(msgBuf,'(A)')
821     &'// ======================================================='
822     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
823     & SQUEEZE_RIGHT, myThid )
824     WRITE(msgBuf,'(A)') ' '
825     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
826     & SQUEEZE_RIGHT, myThid )
827 jmc 1.61 _END_MASTER(myThid)
828 jmc 1.1
829     RETURN
830     END

  ViewVC Help
Powered by ViewVC 1.1.22