/[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.40 - (hide annotations) (download)
Sun Dec 24 20:03:49 2006 UTC (17 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58t_post
Changes since 1.39: +65 -37 lines
deep-Atmosphere & Anelastic limitations (implementation not finished)

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

  ViewVC Help
Powered by ViewVC 1.1.22