/[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.51 - (hide annotations) (download)
Sat Oct 10 22:36:14 2009 UTC (14 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint61w, checkpoint61x, checkpoint61y
Changes since 1.50: +2 -2 lines
Allow CD-scheme on cubed-sphere topology for now (testing)
assuming that cube corners are on land

1 heimbach 1.51 C $Header: /u/gcmpack/MITgcm/model/src/config_check.F,v 1.50 2008/08/24 21:47:57 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4 edhill 1.10 #include "PACKAGES_CONFIG.h"
5 jmc 1.1 #include "CPP_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: CONFIG_CHECK
9     C !INTERFACE:
10     SUBROUTINE CONFIG_CHECK( myThid )
11     C !DESCRIPTION: \bv
12     C *=========================================================*
13     C | SUBROUTINE CONFIG_CHECK
14     C | o Check model parameter settings.
15     C *=========================================================*
16     C | This routine help to prevent the use of parameters
17     C | that are not compatible with the model configuration.
18     C *=========================================================*
19 jmc 1.33 C \ev
20 jmc 1.1
21     C !USES:
22     IMPLICIT NONE
23     C === Global variables ===
24     #include "SIZE.h"
25     #include "EEPARAMS.h"
26     #include "PARAMS.h"
27     c #include "GRID.h"
28    
29     C !INPUT/OUTPUT PARAMETERS:
30     C === Routine arguments ===
31     C myThid - Number of this instances of CONFIG_CHECK
32     INTEGER myThid
33     CEndOfInterface
34    
35     C !LOCAL VARIABLES:
36     C == Local variables ==
37     C msgBuf :: Informational/error meesage buffer
38     CHARACTER*(MAX_LEN_MBUF) msgBuf
39     CEOP
40    
41     C- check that CPP option is "defined" when running-flag parameter is on:
42    
43 dimitri 1.43 C o If diffKrFile is set, then we should make sure the corresponing
44     C code is being compiled
45 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 jmc 1.3 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
225    
226 jmc 1.48 C-- Check parameter consistency :
227 jmc 1.8
228 jmc 1.17 IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.
229 jmc 1.28 & ( viscC4leithD.NE.0. .OR. viscC4leith.NE.0.
230     & .OR. viscC4smag.NE.0. .OR. viscA4Grid.NE.0.
231     & .OR. viscA4D.NE.0. .OR. viscA4Z.NE.0. ) ) THEN
232 jmc 1.8 WRITE(msgBuf,'(A,A)')
233     & 'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',
234     & ' overlap (Olx,Oly) smaller than 3'
235     CALL PRINT_ERROR( msgBuf , myThid)
236     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
237 jmc 1.33 ENDIF
238 jmc 1.28 IF ( ( Olx.LT.3 .OR. Oly.LT.3 ) .AND.
239     & ( viscC2leithD.NE.0. .OR. viscC4leithD.NE.0. )
240     & ) THEN
241     WRITE(msgBuf,'(A,A)')
242     & 'CONFIG_CHECK: cannot use Leith Visc.(div.part) with',
243     & ' overlap (Olx,Oly) smaller than 3'
244     CALL PRINT_ERROR( msgBuf , myThid)
245     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
246 jmc 1.33 ENDIF
247 jmc 1.3
248 jmc 1.48 C-- Deep-Atmosphere & Anelastic limitations:
249 jmc 1.40 IF ( deepAtmosphere .AND.
250     & useRealFreshWaterFlux .AND. usingPCoords ) THEN
251     WRITE(msgBuf,'(A,A)')
252     & 'CONFIG_CHECK: Deep-Atmosphere not yet implemented with',
253     & ' real-Fresh-Water option in P-coordinate'
254     CALL PRINT_ERROR( msgBuf , myThid)
255     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
256     ENDIF
257     IF ( select_rStar.NE.0 .AND.
258     & ( deepAtmosphere .OR.
259     & usingZCoords.AND.rhoRefFile .NE. ' ' ) ) THEN
260     WRITE(msgBuf,'(A,A)')
261     & 'CONFIG_CHECK: Deep-Atmosphere or Anelastic',
262     & ' not yet implemented with rStar'
263     CALL PRINT_ERROR( msgBuf , myThid)
264     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
265     ENDIF
266     IF ( vectorInvariantMomentum .AND.
267     & ( deepAtmosphere .OR.
268     & usingZCoords.AND.rhoRefFile .NE. ' ' ) ) THEN
269     WRITE(msgBuf,'(A,A)')
270     & 'CONFIG_CHECK: Deep-Atmosphere or Anelastic',
271     & ' not yet implemented in Vector-Invariant momentum code'
272     CALL PRINT_ERROR( msgBuf , myThid)
273     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
274     ENDIF
275    
276 jmc 1.48 C-- Free-surface related limitations:
277 jmc 1.3 IF ( rigidLid .AND. implicitFreeSurface ) THEN
278     WRITE(msgBuf,'(A,A)')
279     & 'CONFIG_CHECK: Cannot select both implicitFreeSurface',
280     & ' and rigidLid.'
281     CALL PRINT_ERROR( msgBuf , myThid)
282     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
283 jmc 1.33 ENDIF
284 jmc 1.3
285     IF (rigidLid .AND. exactConserv) THEN
286 jmc 1.40 WRITE(msgBuf,'(A)')
287 jmc 1.3 & 'CONFIG_CHECK: exactConserv not compatible with'
288     CALL PRINT_ERROR( msgBuf , myThid)
289 jmc 1.1 WRITE(msgBuf,'(A)')
290 jmc 1.3 & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
291     CALL PRINT_ERROR( msgBuf , myThid)
292 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
293     ENDIF
294    
295 dfer 1.41 IF ( linFSConserveTr .AND. nonlinFreeSurf.NE.0 ) THEN
296     WRITE(msgBuf,'(A)')
297     & 'CONFIG_CHECK: Cannot select both a Nonlinear Free Surf.'
298     CALL PRINT_ERROR( msgBuf , myThid)
299     WRITE(msgBuf,'(A)')
300     & 'CONFIG_CHECK: and Tracer Correction of Lin. Free Surf.'
301     CALL PRINT_ERROR( msgBuf , myThid)
302     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
303     ENDIF
304    
305 jmc 1.3 IF (rigidLid .AND. useRealFreshWaterFlux) THEN
306 jmc 1.40 WRITE(msgBuf,'(A)')
307 jmc 1.3 & 'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'
308     CALL PRINT_ERROR( msgBuf , myThid)
309 jmc 1.1 WRITE(msgBuf,'(A)')
310     & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
311 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
312     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
313     ENDIF
314    
315 jmc 1.50 IF ( (implicSurfPress.NE.1. .OR. implicDiv2Dflow.NE.1.)
316 jmc 1.3 & .AND. nonHydrostatic ) THEN
317     WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: nonHydrostatic',
318     & ' NOT SAFE with non-fully implicit Barotropic solver'
319     CALL PRINT_ERROR( msgBuf , myThid)
320     WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: To by-pass this',
321     & 'STOP, comment this test and re-compile config_check'
322     CALL PRINT_ERROR( msgBuf , myThid)
323 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
324     ENDIF
325    
326     IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN
327 jmc 1.40 WRITE(msgBuf,'(A)')
328 jmc 1.1 & 'CONFIG_CHECK: nonlinFreeSurf cannot be used'
329 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
330 jmc 1.1 WRITE(msgBuf,'(A)')
331     & 'CONFIG_CHECK: without exactConserv'
332 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
333 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
334     ENDIF
335    
336 jmc 1.6 IF (select_rStar.NE.0 .AND. .NOT.exactConserv) THEN
337 jmc 1.40 WRITE(msgBuf,'(A)')
338 jmc 1.6 & 'CONFIG_CHECK: r* Coordinate cannot be used'
339     CALL PRINT_ERROR( msgBuf , myThid)
340     WRITE(msgBuf,'(A)')
341     & 'CONFIG_CHECK: without exactConserv'
342     CALL PRINT_ERROR( msgBuf , myThid)
343     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
344     ENDIF
345    
346 jmc 1.7 C- note : not implemented in checkpoint48b but it's done now (since 01-28-03)
347     c IF (select_rStar.GT.0 .AND. useOBCS ) THEN
348     c STOP 'ABNORMAL END: S/R CONFIG_CHECK'
349     c ENDIF
350 jmc 1.1
351 jmc 1.33 c IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN
352     IF (nonlinFreeSurf.NE.0 .AND. use3Dsolver) THEN
353 jmc 1.40 WRITE(msgBuf,'(A)')
354 jmc 1.1 & 'CONFIG_CHECK: nonlinFreeSurf not yet implemented'
355 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
356 jmc 1.1 WRITE(msgBuf,'(A)')
357     & 'CONFIG_CHECK: in nonHydrostatic code'
358 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
359 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
360     ENDIF
361 jmc 1.3
362 jmc 1.40 IF ( nonlinFreeSurf.NE.0 .AND.
363 jmc 1.18 & deltaTfreesurf.NE.dTtracerLev(1) ) THEN
364 jmc 1.40 WRITE(msgBuf,'(A)')
365 jmc 1.4 & 'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'
366     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
367 jmc 1.33 & SQUEEZE_RIGHT , myThid)
368 jmc 1.4 WRITE(msgBuf,'(A)')
369     & 'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'
370     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
371 jmc 1.33 & SQUEEZE_RIGHT , myThid)
372 jmc 1.3 ENDIF
373    
374 jmc 1.15 IF ( useRealFreshWaterFlux .AND. exactConserv
375 jmc 1.50 & .AND. implicDiv2Dflow.EQ.0. _d 0
376 jmc 1.21 & .AND. startTime.NE.baseTime .AND. usePickupBeforeC54 ) THEN
377 jmc 1.40 WRITE(msgBuf,'(A)')
378 jmc 1.3 & 'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'
379     CALL PRINT_ERROR( msgBuf , myThid)
380     WRITE(msgBuf,'(A)')
381     & 'CONFIG_CHECK: restart not implemented in this config'
382     CALL PRINT_ERROR( msgBuf , myThid)
383     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
384     ENDIF
385    
386 jmc 1.40 IF ( useRealFreshWaterFlux .AND. .NOT.exactConserv
387 jmc 1.50 & .AND. implicDiv2Dflow.NE.1. ) THEN
388 jmc 1.15 WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: **WARNNING** ',
389 jmc 1.50 & 'RealFreshWater & implicDiv2Dflow < 1'
390 jmc 1.15 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
391 jmc 1.33 & SQUEEZE_RIGHT , myThid)
392 jmc 1.15 WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: works better',
393     & ' with exactConserv=.T. (+ #define EXACT_CONSERV)'
394     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
395 jmc 1.33 & SQUEEZE_RIGHT , myThid)
396 jmc 1.15 ENDIF
397    
398     #ifdef EXACT_CONSERV
399 jmc 1.4 IF (useRealFreshWaterFlux .AND. .NOT.exactConserv
400     & .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
401 jmc 1.40 WRITE(msgBuf,'(A)')
402 jmc 1.4 & 'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'
403     CALL PRINT_ERROR( msgBuf , myThid)
404     WRITE(msgBuf,'(A)')
405     & 'CONFIG_CHECK: requires exactConserv=T'
406     CALL PRINT_ERROR( msgBuf , myThid)
407     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
408     ENDIF
409     #else
410     IF (useRealFreshWaterFlux
411     & .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
412 jmc 1.40 WRITE(msgBuf,'(A)')
413 jmc 1.4 & 'CONFIG_CHECK: E-P effects on wVel are not included'
414     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
415 jmc 1.33 & SQUEEZE_RIGHT , myThid)
416 jmc 1.4 WRITE(msgBuf,'(A)')
417 jmc 1.15 & 'CONFIG_CHECK: ==> use #define EXACT_CONSERV to fix it'
418 jmc 1.5 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
419 jmc 1.33 & SQUEEZE_RIGHT , myThid)
420 jmc 1.5 ENDIF
421 jmc 1.15 #endif /* EXACT_CONSERV */
422 jmc 1.5
423 jmc 1.50 IF ( selectAddFluid.LT.-1 .OR. selectAddFluid.GT.2 ) THEN
424     WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: selectAddFluid=',
425     & selectAddFluid, ' not allowed'
426     CALL PRINT_ERROR( msgBuf , myThid)
427     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
428     & 'should be =0 (Off), 1,2 (Add Mass) or -1 (Virtual Flux)'
429     CALL PRINT_ERROR( msgBuf , myThid)
430     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
431     ENDIF
432     IF ( selectAddFluid.GE.1 .AND. rigidLid ) THEN
433     WRITE(msgBuf,'(A)')
434     & 'CONFIG_CHECK: selectAddFluid > 0 not compatible with'
435     CALL PRINT_ERROR( msgBuf , myThid)
436     WRITE(msgBuf,'(A)')
437     & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
438     CALL PRINT_ERROR( msgBuf , myThid)
439     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
440     ENDIF
441     IF ( selectAddFluid.GE.1 .AND. .NOT.staggerTimeStep ) THEN
442     WRITE(msgBuf,'(2A)') '**WARNNING** ',
443     & 'CONFIG_CHECK: synchronous time-stepping =>'
444     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
445     & SQUEEZE_RIGHT , myThid)
446     WRITE(msgBuf,'(2A)') '**WARNNING** ',
447     & '1 time-step mismatch in AddFluid effects on T & S'
448     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
449     & SQUEEZE_RIGHT , myThid)
450     ENDIF
451    
452 jmc 1.48 C-- Momentum related limitations:
453 jmc 1.47 IF ( vectorInvariantMomentum.AND.momStepping ) THEN
454     IF ( highOrderVorticity.AND.upwindVorticity ) THEN
455     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: ',
456     & '"highOrderVorticity" conflicts with "upwindVorticity"'
457     CALL PRINT_ERROR( msgBuf , myThid)
458     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
459     ENDIF
460     ENDIF
461    
462 jmc 1.9 IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN
463 jmc 1.40 C- jmc: since useCDscheme is a new [04-13-03] flag (default=F),
464     C put this WARNING to stress that even if CD-scheme parameters
465     C (tauCD,rCD) are set, CD-scheme is not used without useCDscheme=T
466 jmc 1.9 C- and STOP if using mom_fluxform (following Chris advise).
467     C- jmc: but ultimately, this block can/will be removed.
468     IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN
469 jmc 1.40 WRITE(msgBuf,'(A)')
470 jmc 1.9 & 'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
471     CALL PRINT_ERROR( msgBuf , myThid)
472     WRITE(msgBuf,'(2A)')
473     & 'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
474 jmc 1.40 & ' in "data", namelist PARM01'
475 jmc 1.9 CALL PRINT_ERROR( msgBuf , myThid)
476     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
477     ENDIF
478     WRITE(msgBuf,'(2A)') '**WARNNING** ',
479     & 'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
480 jmc 1.5 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
481 jmc 1.33 & SQUEEZE_RIGHT , myThid)
482 jmc 1.9 WRITE(msgBuf,'(2A)')
483     & 'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
484 jmc 1.40 & ' in "data", namelist PARM01'
485 jmc 1.4 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
486 jmc 1.33 & SQUEEZE_RIGHT , myThid)
487 jmc 1.12 ENDIF
488    
489     IF ( useCDscheme .AND. useCubedSphereExchange ) THEN
490     WRITE(msgBuf,'(2A)')
491     & 'CONFIG_CHECK: CD-scheme not implemented on CubedSphere grid'
492     CALL PRINT_ERROR( msgBuf , myThid)
493 heimbach 1.51 cph STOP 'ABNORMAL END: S/R CONFIG_CHECK'
494 jmc 1.12 ENDIF
495    
496 jmc 1.48 C-- Time-stepping limitations
497 jmc 1.40 IF ( momForcingOutAB.NE.0 .AND. momForcingOutAB.NE.1 ) THEN
498 jmc 1.34 WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: momForcingOutAB=',
499     & momForcingOutAB, ' not allowed'
500     CALL PRINT_ERROR( msgBuf , myThid)
501     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: momForcingOutAB ',
502     & 'should be =1 (Out of AB) or =0 (In AB)'
503     CALL PRINT_ERROR( msgBuf , myThid)
504     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
505     ENDIF
506 jmc 1.40 IF ( tracForcingOutAB.NE.0 .AND. tracForcingOutAB.NE.1 ) THEN
507 jmc 1.34 WRITE(msgBuf,'(A,I10,A)') 'CONFIG_CHECK: tracForcingOutAB=',
508     & tracForcingOutAB, ' not allowed'
509     CALL PRINT_ERROR( msgBuf , myThid)
510     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: tracForcingOutAB ',
511     & 'should be =1 (Out of AB) or =0 (In AB)'
512 jmc 1.12 CALL PRINT_ERROR( msgBuf , myThid)
513     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
514 jmc 1.4 ENDIF
515 jmc 1.1
516 jmc 1.48 C-- Grid limitations:
517 mlosch 1.44 IF ( rotateGrid ) THEN
518     IF ( .NOT. usingSphericalPolarGrid ) THEN
519     WRITE(msgBuf,'(2A)')
520     & 'CONFIG_CHECK: specifying Euler angles makes only ',
521     & 'sense with usingSphericalGrid=.TRUE.'
522     CALL PRINT_ERROR( msgBuf , myThid)
523     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
524     ENDIF
525     IF ( useFLT .OR. useZonal_Filt .OR. useECCO ) THEN
526     WRITE(msgBuf,'(2A)')
527     & 'CONFIG_CHECK: specifying Euler angles will probably ',
528     & 'not work with pkgs FLT, ZONAL_FLT, ECCO'
529     CALL PRINT_ERROR( msgBuf , myThid)
530     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
531     ENDIF
532     #ifdef ALLOW_PROFILES
533     WRITE(msgBuf,'(2A)')
534     & 'CONFIG_CHECK: specifying Euler angles will probably ',
535     & 'not work with pkg profiles'
536     CALL PRINT_ERROR( msgBuf , myThid)
537     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
538     #endif /* ALLOW_PROFILES */
539     ENDIF
540    
541 jmc 1.48 C-- Packages conflict
542     IF ( useMATRIX .AND. useGCHEM ) THEN
543     WRITE(msgBuf,'(2A)')
544     & 'CONFIG_CHECK: cannot set both: useMATRIX & useGCHEM'
545     CALL PRINT_ERROR( msgBuf , myThid)
546     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
547     ENDIF
548    
549     IF ( useMATRIX .AND. .NOT.usePTRACERS ) THEN
550     WRITE(msgBuf,'(2A)')
551     & 'CONFIG_CHECK: cannot set useMATRIX without ',
552     & 'setting usePTRACERS'
553     CALL PRINT_ERROR( msgBuf , myThid)
554     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
555     ENDIF
556    
557 jmc 1.50 IF ( (useSEAICE .OR. useThSIce) .AND. allowFreezing ) THEN
558     WRITE(msgBuf,'(2A)')
559     & 'CONFIG_CHECK: cannot set allowFreezing',
560     & ' with pkgs SEAICE or THSICE'
561     CALL PRINT_ERROR( msgBuf , myThid)
562     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
563     ENDIF
564    
565 jmc 1.49 WRITE(msgBuf,'(A)')
566     &'// ======================================================='
567     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
568     & SQUEEZE_RIGHT, myThid )
569     WRITE(msgBuf,'(A)') '// CONFIG_CHECK : Normal End'
570     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
571     & SQUEEZE_RIGHT, myThid )
572     WRITE(msgBuf,'(A)')
573     &'// ======================================================='
574     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
575     & SQUEEZE_RIGHT, myThid )
576     WRITE(msgBuf,'(A)') ' '
577     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
578     & SQUEEZE_RIGHT, myThid )
579 jmc 1.1
580     RETURN
581     END

  ViewVC Help
Powered by ViewVC 1.1.22