/[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.55 - (hide annotations) (download)
Tue Aug 10 17:58:30 2010 UTC (13 years, 9 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint62j
Changes since 1.54: +13 -1 lines
Adjoint related modifications -- allowing the
use of implicit vertical advection in adjoint model.

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

  ViewVC Help
Powered by ViewVC 1.1.22