/[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.49 - (hide annotations) (download)
Mon Apr 7 21:15:06 2008 UTC (16 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint61b, checkpoint61a
Changes since 1.48: +15 -4 lines
print a message to std-output (since calling order has changed)

1 jmc 1.49 C $Header: /u/gcmpack/MITgcm/model/src/config_check.F,v 1.48 2008/04/05 21:24:08 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     C msgBuf :: Informational/error meesage buffer
38     CHARACTER*(MAX_LEN_MBUF) msgBuf
39     CEOP
40    
41     C- check that CPP option is "defined" when running-flag parameter is on:
42    
43 dimitri 1.43 C o If diffKrFile is set, then we should make sure the corresponing
44     C code is being compiled
45     #if !(defined ALLOW_3D_DIFFKR || \
46     (defined (ALLOW_AUTODIFF_TAMC) && defined (ALLOW_DIFFKR_CONTROL)))
47     IF (diffKrFile.NE.' ') THEN
48     WRITE(msgBuf,'(A)')
49     & 'CONFIG_CHECK: diffKrFile is set but never used.'
50     CALL PRINT_ERROR( msgBuf , myThid)
51     WRITE(msgBuf,'(A)')
52     & 'Re-compile with: #define ALLOW_3D_DIFFKR'
53     CALL PRINT_ERROR( msgBuf , myThid)
54     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
55     ENDIF
56     #endif
57    
58 jmc 1.1 #ifndef ALLOW_NONHYDROSTATIC
59 jmc 1.40 IF (use3Dsolver) THEN
60     WRITE(msgBuf,'(A)')
61 jmc 1.1 & 'CONFIG_CHECK: #undef ALLOW_NONHYDROSTATIC and'
62 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
63 jmc 1.32 IF ( implicitIntGravWave ) WRITE(msgBuf,'(A)')
64     & 'CONFIG_CHECK: implicitIntGravWave is TRUE'
65     IF ( nonHydrostatic ) WRITE(msgBuf,'(A)')
66 jmc 1.1 & 'CONFIG_CHECK: nonHydrostatic is TRUE'
67 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
68 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
69     ENDIF
70     #endif
71    
72 jmc 1.22 #ifndef ALLOW_ADAMSBASHFORTH_3
73     IF ( alph_AB.NE.UNSET_RL .OR. beta_AB.NE.UNSET_RL ) THEN
74     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
75     & '#undef ALLOW_ADAMSBASHFORTH_3 but alph_AB,beta_AB'
76     CALL PRINT_ERROR( msgBuf , myThid)
77     WRITE(msgBuf,'(A,1P2E20.7)')
78     & 'CONFIG_CHECK: are set to:',alph_AB,beta_AB
79     CALL PRINT_ERROR( msgBuf , myThid)
80     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
81     ENDIF
82     #endif
83    
84 jmc 1.13 #ifndef INCLUDE_IMPLVERTADV_CODE
85 jmc 1.40 IF ( momImplVertAdv ) THEN
86     WRITE(msgBuf,'(A)')
87 jmc 1.13 & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
88     CALL PRINT_ERROR( msgBuf , myThid)
89     WRITE(msgBuf,'(A)')
90     & 'CONFIG_CHECK: but momImplVertAdv is TRUE'
91     CALL PRINT_ERROR( msgBuf , myThid)
92     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
93     ENDIF
94 jmc 1.40 IF ( tempImplVertAdv ) THEN
95     WRITE(msgBuf,'(A)')
96 jmc 1.13 & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
97     CALL PRINT_ERROR( msgBuf , myThid)
98     WRITE(msgBuf,'(A)')
99     & 'CONFIG_CHECK: but tempImplVertAdv is TRUE'
100     CALL PRINT_ERROR( msgBuf , myThid)
101     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
102     ENDIF
103 jmc 1.40 IF ( saltImplVertAdv ) THEN
104     WRITE(msgBuf,'(A)')
105 jmc 1.13 & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
106     CALL PRINT_ERROR( msgBuf , myThid)
107     WRITE(msgBuf,'(A)')
108     & 'CONFIG_CHECK: but saltImplVertAdv is TRUE'
109     CALL PRINT_ERROR( msgBuf , myThid)
110     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
111     ENDIF
112 jmc 1.19 IF ( dTtracerLev(1).NE.dTtracerLev(Nr) .AND. implicitDiffusion
113 jmc 1.40 & .AND. ( saltStepping .OR. tempStepping .OR. usePTRACERS )
114 jmc 1.19 & ) THEN
115 jmc 1.40 WRITE(msgBuf,'(A)')
116 jmc 1.19 & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
117     CALL PRINT_ERROR( msgBuf , myThid)
118     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
119     & 'but implicitDiffusion=T with non-uniform dTtracerLev'
120     CALL PRINT_ERROR( msgBuf , myThid)
121     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
122     ENDIF
123 jmc 1.13 #endif
124    
125 jmc 1.1 #ifndef EXACT_CONSERV
126 jmc 1.40 IF (exactConserv) THEN
127     WRITE(msgBuf,'(A)')
128 jmc 1.1 & 'CONFIG_CHECK: #undef EXACT_CONSERV and'
129 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
130 jmc 1.1 WRITE(msgBuf,'(A)')
131     & 'CONFIG_CHECK: exactConserv is TRUE'
132 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
133 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
134     ENDIF
135     #endif
136    
137     #ifndef NONLIN_FRSURF
138 jmc 1.40 IF (nonlinFreeSurf.NE.0) THEN
139     WRITE(msgBuf,'(A)')
140 jmc 1.1 & 'CONFIG_CHECK: #undef NONLIN_FRSURF and'
141 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
142 jmc 1.1 WRITE(msgBuf,'(A)')
143     & 'CONFIG_CHECK: nonlinFreeSurf is non-zero'
144 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
145 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
146     ENDIF
147     #endif
148    
149 jmc 1.9 #ifndef NONLIN_FRSURF
150     IF (select_rStar .NE. 0) THEN
151 jmc 1.40 WRITE(msgBuf,'(A)')
152 jmc 1.9 & 'CONFIG_CHECK: rStar is part of NonLin-FS '
153 jmc 1.33 CALL PRINT_ERROR( msgBuf, myThid)
154 jmc 1.9 WRITE(msgBuf,'(A)')
155     & 'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to use it'
156 jmc 1.33 CALL PRINT_ERROR( msgBuf, myThid)
157 jmc 1.9 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
158     ENDIF
159     #endif /* NONLIN_FRSURF */
160    
161 jmc 1.1 #ifdef USE_NATURAL_BCS
162 jmc 1.40 WRITE(msgBuf,'(A)')
163 jmc 1.3 & 'CONFIG_CHECK: USE_NATURAL_BCS option has been replaced'
164     CALL PRINT_ERROR( msgBuf , myThid)
165 jmc 1.1 WRITE(msgBuf,'(A)')
166 jmc 1.3 & 'CONFIG_CHECK: by useRealFreshWaterFlux=TRUE in data file'
167     CALL PRINT_ERROR( msgBuf , myThid)
168 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
169 jmc 1.3 #endif
170    
171 jmc 1.4 C o If pLoadFile is set, then we should make sure the corresponing
172     C code is being compiled
173     #ifndef ATMOSPHERIC_LOADING
174     IF (pLoadFile.NE.' ') THEN
175     WRITE(msgBuf,'(A)')
176     & 'CONFIG_CHECK: pLoadFile is set but you have not'
177     CALL PRINT_ERROR( msgBuf , myThid)
178     WRITE(msgBuf,'(A)')
179     & 'compiled the model with the pressure loading code.'
180     CALL PRINT_ERROR( msgBuf , myThid)
181 jmc 1.15 WRITE(msgBuf,'(A)')
182     & 'Re-compile with: #define ATMOSPHERIC_LOADING'
183     CALL PRINT_ERROR( msgBuf , myThid)
184     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
185     ENDIF
186     IF ( useRealFreshWaterFlux .AND. useThSIce ) THEN
187     WRITE(msgBuf,'(A)')
188     & 'CONFIG_CHECK: sIceLoad is computed but'
189     CALL PRINT_ERROR( msgBuf , myThid)
190     WRITE(msgBuf,'(A)')
191     & 'pressure loading code is not compiled.'
192     CALL PRINT_ERROR( msgBuf , myThid)
193     WRITE(msgBuf,'(A)')
194     & 'Re-compile with: #define ATMOSPHERIC_LOADING'
195 jmc 1.4 CALL PRINT_ERROR( msgBuf , myThid)
196     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
197     ENDIF
198     #endif
199    
200 mlosch 1.31 #ifndef ALLOW_BALANCE_FLUXES
201     IF (balanceEmPmR .OR. balanceQnet) THEN
202     WRITE(msgBuf,'(A,A)')
203     & 'CONFIG_CHECK: balanceEmPmR/Qnet is set but balance code ',
204     & 'is not compiled.'
205     CALL PRINT_ERROR( msgBuf , 1)
206     WRITE(msgBuf,'(A)')
207     & 'Re-compile with ALLOW_BALANCE_FLUXES defined'
208     CALL PRINT_ERROR( msgBuf , 1)
209     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
210     ENDIF
211     #endif
212    
213 jmc 1.3 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
214    
215 jmc 1.48 C-- Check parameter consistency :
216 jmc 1.8
217 jmc 1.17 IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.
218 jmc 1.28 & ( viscC4leithD.NE.0. .OR. viscC4leith.NE.0.
219     & .OR. viscC4smag.NE.0. .OR. viscA4Grid.NE.0.
220     & .OR. viscA4D.NE.0. .OR. viscA4Z.NE.0. ) ) THEN
221 jmc 1.8 WRITE(msgBuf,'(A,A)')
222     & 'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',
223     & ' overlap (Olx,Oly) smaller than 3'
224     CALL PRINT_ERROR( msgBuf , myThid)
225     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
226 jmc 1.33 ENDIF
227 jmc 1.28 IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.
228     & ( viscC2leithD.NE.0. .OR. viscC4leithD.NE.0. )
229     & ) THEN
230     WRITE(msgBuf,'(A,A)')
231     & 'CONFIG_CHECK: cannot use Leith Visc.(div.part) with',
232     & ' overlap (Olx,Oly) smaller than 3'
233     CALL PRINT_ERROR( msgBuf , myThid)
234     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
235 jmc 1.33 ENDIF
236 jmc 1.3
237 jmc 1.48 C-- Deep-Atmosphere & Anelastic limitations:
238 jmc 1.40 IF ( deepAtmosphere .AND.
239     & useRealFreshWaterFlux .AND. usingPCoords ) THEN
240     WRITE(msgBuf,'(A,A)')
241     & 'CONFIG_CHECK: Deep-Atmosphere not yet implemented with',
242     & ' real-Fresh-Water option in P-coordinate'
243     CALL PRINT_ERROR( msgBuf , myThid)
244     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
245     ENDIF
246     IF ( select_rStar.NE.0 .AND.
247     & ( deepAtmosphere .OR.
248     & usingZCoords.AND.rhoRefFile .NE. ' ' ) ) THEN
249     WRITE(msgBuf,'(A,A)')
250     & 'CONFIG_CHECK: Deep-Atmosphere or Anelastic',
251     & ' not yet implemented with rStar'
252     CALL PRINT_ERROR( msgBuf , myThid)
253     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
254     ENDIF
255     IF ( vectorInvariantMomentum .AND.
256     & ( deepAtmosphere .OR.
257     & usingZCoords.AND.rhoRefFile .NE. ' ' ) ) THEN
258     WRITE(msgBuf,'(A,A)')
259     & 'CONFIG_CHECK: Deep-Atmosphere or Anelastic',
260     & ' not yet implemented in Vector-Invariant momentum code'
261     CALL PRINT_ERROR( msgBuf , myThid)
262     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
263     ENDIF
264    
265 jmc 1.48 C-- Free-surface related limitations:
266 jmc 1.3 IF ( rigidLid .AND. implicitFreeSurface ) THEN
267     WRITE(msgBuf,'(A,A)')
268     & 'CONFIG_CHECK: Cannot select both implicitFreeSurface',
269     & ' and rigidLid.'
270     CALL PRINT_ERROR( msgBuf , myThid)
271     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
272 jmc 1.33 ENDIF
273 jmc 1.3
274     IF (rigidLid .AND. exactConserv) THEN
275 jmc 1.40 WRITE(msgBuf,'(A)')
276 jmc 1.3 & 'CONFIG_CHECK: exactConserv not compatible with'
277     CALL PRINT_ERROR( msgBuf , myThid)
278 jmc 1.1 WRITE(msgBuf,'(A)')
279 jmc 1.3 & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
280     CALL PRINT_ERROR( msgBuf , myThid)
281 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
282     ENDIF
283    
284 dfer 1.41 IF ( linFSConserveTr .AND. nonlinFreeSurf.NE.0 ) THEN
285     WRITE(msgBuf,'(A)')
286     & 'CONFIG_CHECK: Cannot select both a Nonlinear Free Surf.'
287     CALL PRINT_ERROR( msgBuf , myThid)
288     WRITE(msgBuf,'(A)')
289     & 'CONFIG_CHECK: and Tracer Correction of Lin. Free Surf.'
290     CALL PRINT_ERROR( msgBuf , myThid)
291     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
292     ENDIF
293    
294 jmc 1.3 IF (rigidLid .AND. useRealFreshWaterFlux) THEN
295 jmc 1.40 WRITE(msgBuf,'(A)')
296 jmc 1.3 & 'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'
297     CALL PRINT_ERROR( msgBuf , myThid)
298 jmc 1.1 WRITE(msgBuf,'(A)')
299     & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
300 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
301     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
302     ENDIF
303    
304     IF ( (implicSurfPress.NE.1. .OR. implicDiv2DFlow.NE.1.)
305     & .AND. nonHydrostatic ) THEN
306     WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: nonHydrostatic',
307     & ' NOT SAFE with non-fully implicit Barotropic solver'
308     CALL PRINT_ERROR( msgBuf , myThid)
309     WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: To by-pass this',
310     & 'STOP, comment this test and re-compile config_check'
311     CALL PRINT_ERROR( msgBuf , myThid)
312 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
313     ENDIF
314    
315     IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN
316 jmc 1.40 WRITE(msgBuf,'(A)')
317 jmc 1.1 & 'CONFIG_CHECK: nonlinFreeSurf cannot be used'
318 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
319 jmc 1.1 WRITE(msgBuf,'(A)')
320     & 'CONFIG_CHECK: without exactConserv'
321 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
322 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
323     ENDIF
324    
325 jmc 1.6 IF (select_rStar.NE.0 .AND. .NOT.exactConserv) THEN
326 jmc 1.40 WRITE(msgBuf,'(A)')
327 jmc 1.6 & 'CONFIG_CHECK: r* Coordinate cannot be used'
328     CALL PRINT_ERROR( msgBuf , myThid)
329     WRITE(msgBuf,'(A)')
330     & 'CONFIG_CHECK: without exactConserv'
331     CALL PRINT_ERROR( msgBuf , myThid)
332     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
333     ENDIF
334    
335 jmc 1.7 C- note : not implemented in checkpoint48b but it's done now (since 01-28-03)
336     c IF (select_rStar.GT.0 .AND. useOBCS ) THEN
337 jmc 1.40 c WRITE(msgBuf,'(A)')
338 jmc 1.7 c & 'CONFIG_CHECK: r* Coordinate not yet implemented'
339     c CALL PRINT_ERROR( msgBuf , 1)
340     c WRITE(msgBuf,'(A)')
341     c & 'CONFIG_CHECK: in OBC package'
342     c CALL PRINT_ERROR( msgBuf , 1)
343     c STOP 'ABNORMAL END: S/R CONFIG_CHECK'
344     c ENDIF
345 jmc 1.1
346 jmc 1.33 c IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN
347     IF (nonlinFreeSurf.NE.0 .AND. use3Dsolver) THEN
348 jmc 1.40 WRITE(msgBuf,'(A)')
349 jmc 1.1 & 'CONFIG_CHECK: nonlinFreeSurf not yet implemented'
350 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
351 jmc 1.1 WRITE(msgBuf,'(A)')
352     & 'CONFIG_CHECK: in nonHydrostatic code'
353 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
354 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
355     ENDIF
356 jmc 1.3
357 jmc 1.40 IF ( nonlinFreeSurf.NE.0 .AND.
358 jmc 1.18 & deltaTfreesurf.NE.dTtracerLev(1) ) THEN
359 jmc 1.40 WRITE(msgBuf,'(A)')
360 jmc 1.4 & 'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'
361     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
362 jmc 1.33 & SQUEEZE_RIGHT , myThid)
363 jmc 1.4 WRITE(msgBuf,'(A)')
364     & 'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'
365     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
366 jmc 1.33 & SQUEEZE_RIGHT , myThid)
367 jmc 1.3 ENDIF
368    
369 jmc 1.15 IF ( useRealFreshWaterFlux .AND. exactConserv
370     & .AND. implicDiv2DFlow.EQ.0. _d 0
371 jmc 1.21 & .AND. startTime.NE.baseTime .AND. usePickupBeforeC54 ) THEN
372 jmc 1.40 WRITE(msgBuf,'(A)')
373 jmc 1.3 & 'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'
374     CALL PRINT_ERROR( msgBuf , myThid)
375     WRITE(msgBuf,'(A)')
376     & 'CONFIG_CHECK: restart not implemented in this config'
377     CALL PRINT_ERROR( msgBuf , myThid)
378     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
379     ENDIF
380    
381 jmc 1.40 IF ( useRealFreshWaterFlux .AND. .NOT.exactConserv
382 jmc 1.15 & .AND. implicDiv2DFlow.NE.1. ) THEN
383     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: **WARNNING** ',
384     & 'RealFreshWater & implicDiv2DFlow < 1'
385     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
386 jmc 1.33 & SQUEEZE_RIGHT , myThid)
387 jmc 1.15 WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: works better',
388     & ' with exactConserv=.T. (+ #define EXACT_CONSERV)'
389     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
390 jmc 1.33 & SQUEEZE_RIGHT , myThid)
391 jmc 1.15 ENDIF
392    
393     #ifdef EXACT_CONSERV
394 jmc 1.4 IF (useRealFreshWaterFlux .AND. .NOT.exactConserv
395     & .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
396 jmc 1.40 WRITE(msgBuf,'(A)')
397 jmc 1.4 & 'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'
398     CALL PRINT_ERROR( msgBuf , myThid)
399     WRITE(msgBuf,'(A)')
400     & 'CONFIG_CHECK: requires exactConserv=T'
401     CALL PRINT_ERROR( msgBuf , myThid)
402     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
403     ENDIF
404     #else
405     IF (useRealFreshWaterFlux
406     & .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
407 jmc 1.40 WRITE(msgBuf,'(A)')
408 jmc 1.4 & 'CONFIG_CHECK: E-P effects on wVel are not included'
409     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
410 jmc 1.33 & SQUEEZE_RIGHT , myThid)
411 jmc 1.4 WRITE(msgBuf,'(A)')
412 jmc 1.15 & 'CONFIG_CHECK: ==> use #define EXACT_CONSERV to fix it'
413 jmc 1.5 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
414 jmc 1.33 & SQUEEZE_RIGHT , myThid)
415 jmc 1.5 ENDIF
416 jmc 1.15 #endif /* EXACT_CONSERV */
417 jmc 1.5
418 jmc 1.48 C-- Momentum related limitations:
419 jmc 1.47 IF ( vectorInvariantMomentum.AND.momStepping ) THEN
420     IF ( highOrderVorticity.AND.upwindVorticity ) THEN
421     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
422     & '"highOrderVorticity" conflicts with "upwindVorticity"'
423     CALL PRINT_ERROR( msgBuf , myThid)
424     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
425     ENDIF
426     ENDIF
427    
428 jmc 1.9 IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN
429 jmc 1.40 C- jmc: since useCDscheme is a new [04-13-03] flag (default=F),
430     C put this WARNING to stress that even if CD-scheme parameters
431     C (tauCD,rCD) are set, CD-scheme is not used without useCDscheme=T
432 jmc 1.9 C- and STOP if using mom_fluxform (following Chris advise).
433     C- jmc: but ultimately, this block can/will be removed.
434     IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN
435 jmc 1.40 WRITE(msgBuf,'(A)')
436 jmc 1.9 & 'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
437     CALL PRINT_ERROR( msgBuf , myThid)
438     WRITE(msgBuf,'(2A)')
439     & 'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
440 jmc 1.40 & ' in "data", namelist PARM01'
441 jmc 1.9 CALL PRINT_ERROR( msgBuf , myThid)
442     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
443     ENDIF
444     WRITE(msgBuf,'(2A)') '**WARNNING** ',
445     & 'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
446 jmc 1.5 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
447 jmc 1.33 & SQUEEZE_RIGHT , myThid)
448 jmc 1.9 WRITE(msgBuf,'(2A)')
449     & 'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
450 jmc 1.40 & ' in "data", namelist PARM01'
451 jmc 1.4 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
452 jmc 1.33 & SQUEEZE_RIGHT , myThid)
453 jmc 1.12 ENDIF
454    
455     IF ( useCDscheme .AND. useCubedSphereExchange ) THEN
456     WRITE(msgBuf,'(2A)')
457     & 'CONFIG_CHECK: CD-scheme not implemented on CubedSphere grid'
458     CALL PRINT_ERROR( msgBuf , myThid)
459     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
460     ENDIF
461    
462 jmc 1.48 C-- Time-stepping limitations
463 jmc 1.40 IF ( momForcingOutAB.NE.0 .AND. momForcingOutAB.NE.1 ) THEN
464 jmc 1.34 WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: momForcingOutAB=',
465     & momForcingOutAB, ' not allowed'
466     CALL PRINT_ERROR( msgBuf , myThid)
467     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: momForcingOutAB ',
468     & 'should be =1 (Out of AB) or =0 (In AB)'
469     CALL PRINT_ERROR( msgBuf , myThid)
470     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
471     ENDIF
472 jmc 1.40 IF ( tracForcingOutAB.NE.0 .AND. tracForcingOutAB.NE.1 ) THEN
473 jmc 1.34 WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: tracForcingOutAB=',
474     & tracForcingOutAB, ' not allowed'
475     CALL PRINT_ERROR( msgBuf , myThid)
476     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: tracForcingOutAB ',
477     & 'should be =1 (Out of AB) or =0 (In AB)'
478 jmc 1.12 CALL PRINT_ERROR( msgBuf , myThid)
479     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
480 jmc 1.4 ENDIF
481 jmc 1.1
482 jmc 1.48 C-- Grid limitations:
483 mlosch 1.44 IF ( rotateGrid ) THEN
484     IF ( .NOT. usingSphericalPolarGrid ) THEN
485     WRITE(msgBuf,'(2A)')
486     & 'CONFIG_CHECK: specifying Euler angles makes only ',
487     & 'sense with usingSphericalGrid=.TRUE.'
488     CALL PRINT_ERROR( msgBuf , myThid)
489     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
490     ENDIF
491     IF ( useFLT .OR. useZonal_Filt .OR. useECCO ) THEN
492     WRITE(msgBuf,'(2A)')
493     & 'CONFIG_CHECK: specifying Euler angles will probably ',
494     & 'not work with pkgs FLT, ZONAL_FLT, ECCO'
495     CALL PRINT_ERROR( msgBuf , myThid)
496     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
497     ENDIF
498     #ifdef ALLOW_PROFILES
499     WRITE(msgBuf,'(2A)')
500     & 'CONFIG_CHECK: specifying Euler angles will probably ',
501     & 'not work with pkg profiles'
502     CALL PRINT_ERROR( msgBuf , myThid)
503     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
504     #endif /* ALLOW_PROFILES */
505     ENDIF
506    
507 jmc 1.48 C-- Packages conflict
508     IF ( useMATRIX .AND. useGCHEM ) THEN
509     WRITE(msgBuf,'(2A)')
510     & 'CONFIG_CHECK: cannot set both: useMATRIX & useGCHEM'
511     CALL PRINT_ERROR( msgBuf , myThid)
512     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
513     ENDIF
514    
515     IF ( useMATRIX .AND. .NOT.usePTRACERS ) THEN
516     WRITE(msgBuf,'(2A)')
517     & 'CONFIG_CHECK: cannot set useMATRIX without ',
518     & 'setting usePTRACERS'
519     CALL PRINT_ERROR( msgBuf , myThid)
520     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
521     ENDIF
522    
523 jmc 1.49 WRITE(msgBuf,'(A)')
524     &'// ======================================================='
525     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
526     & SQUEEZE_RIGHT, myThid )
527     WRITE(msgBuf,'(A)') '// CONFIG_CHECK : Normal End'
528     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
529     & SQUEEZE_RIGHT, myThid )
530     WRITE(msgBuf,'(A)')
531     &'// ======================================================='
532     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
533     & SQUEEZE_RIGHT, myThid )
534     WRITE(msgBuf,'(A)') ' '
535     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
536     & SQUEEZE_RIGHT, myThid )
537 jmc 1.1
538     RETURN
539     END

  ViewVC Help
Powered by ViewVC 1.1.22