/[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.52 - (hide annotations) (download)
Tue Nov 24 09:06:29 2009 UTC (14 years, 6 months ago) by mlosch
Branch: MAIN
Changes since 1.51: +14 -1 lines
forgot to include output of new parameter useSRCGSolver and a test

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

  ViewVC Help
Powered by ViewVC 1.1.22