/[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.75 - (hide annotations) (download)
Tue Nov 5 18:30:42 2013 UTC (10 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64q, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t
Changes since 1.74: +9 -1 lines
check size of overlap for the unlikely case useSmag3D & useCDscheme

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

  ViewVC Help
Powered by ViewVC 1.1.22