/[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.58 - (hide annotations) (download)
Tue Mar 15 00:15:23 2011 UTC (13 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c
Changes since 1.57: +10 -1 lines
stop if trying to use OBCS with ALLOW_DEPTH_CONTROL

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

  ViewVC Help
Powered by ViewVC 1.1.22