/[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.42 - (hide annotations) (download)
Wed Mar 7 00:00:06 2007 UTC (17 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58y_post, checkpoint58w_post, checkpoint59e, checkpoint59d, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint58x_post
Changes since 1.41: +1 -78 lines
move checking for un-compiled pkg, from CONFIG_CHECK to PACKAGES_CHECK.

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

  ViewVC Help
Powered by ViewVC 1.1.22