/[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.29 - (hide annotations) (download)
Mon Dec 12 20:48:58 2005 UTC (18 years, 5 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57z_post
Changes since 1.28: +2 -2 lines
Fixed stdout format bug for tauCD

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

  ViewVC Help
Powered by ViewVC 1.1.22