/[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.15 - (hide annotations) (download)
Sun Jul 18 21:59:29 2004 UTC (19 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint54d_post, checkpoint54e_post, checkpoint55, checkpoint54f_post, checkpoint55c_post, checkpoint55g_post, checkpoint55d_post, checkpoint55d_pre, checkpoint55b_post, checkpoint55f_post, checkpoint55a_post, checkpoint55e_post
Changes since 1.14: +35 -26 lines
consistent with recent modifications of the code (post c54)

1 jmc 1.15 C $Header: /u/gcmpack/MITgcm/model/src/config_check.F,v 1.14 2004/03/25 15:35:53 adcroft 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     C \ev
20    
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.11 #ifndef ALLOW_CD_CODE
44 jmc 1.9 IF (useCDscheme) THEN
45 adcroft 1.14 WRITE(msgBuf,'(A)')
46     & 'CONFIG_CHECK: useCDscheme is TRUE and #undef ALLOW_CD_CODE'
47 jmc 1.9 CALL PRINT_ERROR( msgBuf , myThid)
48 adcroft 1.14 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
49     ENDIF
50     IF (tauCD.NE.0.) THEN
51 jmc 1.9 WRITE(msgBuf,'(A)')
52 adcroft 1.14 & 'CONFIG_CHECK: tauCD has been set but the cd_code package is',
53     & ' enabled'
54 jmc 1.9 CALL PRINT_ERROR( msgBuf , myThid)
55     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
56     ENDIF
57     #endif
58    
59 jmc 1.1 #ifndef ALLOW_NONHYDROSTATIC
60     IF (nonHydrostatic) THEN
61     WRITE(msgBuf,'(A)')
62     & 'CONFIG_CHECK: #undef ALLOW_NONHYDROSTATIC and'
63 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
64 jmc 1.1 WRITE(msgBuf,'(A)')
65     & '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.13 #ifndef INCLUDE_IMPLVERTADV_CODE
72     IF ( momImplVertAdv ) THEN
73     WRITE(msgBuf,'(A)')
74     & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
75     CALL PRINT_ERROR( msgBuf , myThid)
76     WRITE(msgBuf,'(A)')
77     & 'CONFIG_CHECK: but momImplVertAdv is TRUE'
78     CALL PRINT_ERROR( msgBuf , myThid)
79     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
80     ENDIF
81     IF ( tempImplVertAdv ) THEN
82     WRITE(msgBuf,'(A)')
83     & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
84     CALL PRINT_ERROR( msgBuf , myThid)
85     WRITE(msgBuf,'(A)')
86     & 'CONFIG_CHECK: but tempImplVertAdv is TRUE'
87     CALL PRINT_ERROR( msgBuf , myThid)
88     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
89     ENDIF
90     IF ( saltImplVertAdv ) THEN
91     WRITE(msgBuf,'(A)')
92     & 'CONFIG_CHECK: #undef INCLUDE_IMPLVERTADV_CODE'
93     CALL PRINT_ERROR( msgBuf , myThid)
94     WRITE(msgBuf,'(A)')
95     & 'CONFIG_CHECK: but saltImplVertAdv is TRUE'
96     CALL PRINT_ERROR( msgBuf , myThid)
97     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
98     ENDIF
99     #endif
100    
101 jmc 1.1 #ifndef EXACT_CONSERV
102     IF (exactConserv) THEN
103     WRITE(msgBuf,'(A)')
104     & 'CONFIG_CHECK: #undef EXACT_CONSERV and'
105 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
106 jmc 1.1 WRITE(msgBuf,'(A)')
107     & 'CONFIG_CHECK: exactConserv is TRUE'
108 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
109 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
110     ENDIF
111     #endif
112    
113     #ifndef NONLIN_FRSURF
114     IF (nonlinFreeSurf.NE.0) THEN
115     WRITE(msgBuf,'(A)')
116     & 'CONFIG_CHECK: #undef NONLIN_FRSURF and'
117 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
118 jmc 1.1 WRITE(msgBuf,'(A)')
119     & 'CONFIG_CHECK: nonlinFreeSurf is non-zero'
120 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
121 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
122     ENDIF
123     #endif
124    
125 jmc 1.9 #ifndef NONLIN_FRSURF
126     IF (select_rStar .NE. 0) THEN
127     WRITE(msgBuf,'(A)')
128     & 'CONFIG_CHECK: rStar is part of NonLin-FS '
129     CALL PRINT_ERROR( msgBuf, myThid)
130     WRITE(msgBuf,'(A)')
131     & 'CONFIG_CHECK: ==> use #define NONLIN_FRSURF to use it'
132     CALL PRINT_ERROR( msgBuf, myThid)
133     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
134     ENDIF
135     #endif /* NONLIN_FRSURF */
136    
137 jmc 1.1 #ifdef USE_NATURAL_BCS
138     WRITE(msgBuf,'(A)')
139 jmc 1.3 & 'CONFIG_CHECK: USE_NATURAL_BCS option has been replaced'
140     CALL PRINT_ERROR( msgBuf , myThid)
141 jmc 1.1 WRITE(msgBuf,'(A)')
142 jmc 1.3 & 'CONFIG_CHECK: by useRealFreshWaterFlux=TRUE in data file'
143     CALL PRINT_ERROR( msgBuf , myThid)
144 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
145 jmc 1.3 #endif
146    
147 jmc 1.4 C o If pLoadFile is set, then we should make sure the corresponing
148     C code is being compiled
149     #ifndef ATMOSPHERIC_LOADING
150     IF (pLoadFile.NE.' ') THEN
151     WRITE(msgBuf,'(A)')
152     & 'CONFIG_CHECK: pLoadFile is set but you have not'
153     CALL PRINT_ERROR( msgBuf , myThid)
154     WRITE(msgBuf,'(A)')
155     & 'compiled the model with the pressure loading code.'
156     CALL PRINT_ERROR( msgBuf , myThid)
157 jmc 1.15 WRITE(msgBuf,'(A)')
158     & 'Re-compile with: #define ATMOSPHERIC_LOADING'
159     CALL PRINT_ERROR( msgBuf , myThid)
160     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
161     ENDIF
162     IF ( useRealFreshWaterFlux .AND. useThSIce ) THEN
163     WRITE(msgBuf,'(A)')
164     & 'CONFIG_CHECK: sIceLoad is computed but'
165     CALL PRINT_ERROR( msgBuf , myThid)
166     WRITE(msgBuf,'(A)')
167     & 'pressure loading code is not compiled.'
168     CALL PRINT_ERROR( msgBuf , myThid)
169     WRITE(msgBuf,'(A)')
170     & 'Re-compile with: #define ATMOSPHERIC_LOADING'
171 jmc 1.4 CALL PRINT_ERROR( msgBuf , myThid)
172     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
173     ENDIF
174     #endif
175    
176     C o If taveFreq is finite, then we must make sure the diagnostics
177     C code is being compiled
178     #ifndef ALLOW_TIMEAVE
179     IF (taveFreq.NE.0.) THEN
180     WRITE(msgBuf,'(A)')
181 jmc 1.15 & 'CONFIG_CHECK: taveFreq <> 0 but pkg/timeave is not compiled'
182 jmc 1.4 CALL PRINT_ERROR( msgBuf , 1)
183     WRITE(msgBuf,'(A)')
184 jmc 1.15 & 'Re-compile with pkg "timeave" in packages.conf'
185 jmc 1.4 CALL PRINT_ERROR( msgBuf , 1)
186     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
187     ENDIF
188     #endif
189    
190 jmc 1.3 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
191    
192     C- check parameter consistency :
193 jmc 1.8
194     IF ( viscA4.NE.0. .AND. (Olx.LT.3 .OR. Oly.LT.3)) THEN
195     WRITE(msgBuf,'(A,A)')
196     & 'CONFIG_CHECK: cannot use Biharmonic Visc. (viscA4) with',
197     & ' overlap (Olx,Oly) smaller than 3'
198     CALL PRINT_ERROR( msgBuf , myThid)
199     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
200     ENDIF
201 jmc 1.3
202     IF ( rigidLid .AND. implicitFreeSurface ) THEN
203     WRITE(msgBuf,'(A,A)')
204     & 'CONFIG_CHECK: Cannot select both implicitFreeSurface',
205     & ' and rigidLid.'
206     CALL PRINT_ERROR( msgBuf , myThid)
207     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
208     ENDIF
209    
210     IF (rigidLid .AND. exactConserv) THEN
211 jmc 1.1 WRITE(msgBuf,'(A)')
212 jmc 1.3 & 'CONFIG_CHECK: exactConserv not compatible with'
213     CALL PRINT_ERROR( msgBuf , myThid)
214 jmc 1.1 WRITE(msgBuf,'(A)')
215 jmc 1.3 & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
216     CALL PRINT_ERROR( msgBuf , myThid)
217 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
218     ENDIF
219    
220 jmc 1.3 IF (rigidLid .AND. useRealFreshWaterFlux) THEN
221 jmc 1.1 WRITE(msgBuf,'(A)')
222 jmc 1.3 & 'CONFIG_CHECK: useRealFreshWaterFlux not compatible with'
223     CALL PRINT_ERROR( msgBuf , myThid)
224 jmc 1.1 WRITE(msgBuf,'(A)')
225     & 'CONFIG_CHECK: rigidLid (meaningless in that case)'
226 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
227     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
228     ENDIF
229    
230     IF ( (implicSurfPress.NE.1. .OR. implicDiv2DFlow.NE.1.)
231     & .AND. nonHydrostatic ) THEN
232     WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: nonHydrostatic',
233     & ' NOT SAFE with non-fully implicit Barotropic solver'
234     CALL PRINT_ERROR( msgBuf , myThid)
235     WRITE(msgBuf,'(A,A)') 'CONFIG_CHECK: To by-pass this',
236     & 'STOP, comment this test and re-compile config_check'
237     CALL PRINT_ERROR( msgBuf , myThid)
238 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
239     ENDIF
240    
241     IF (nonlinFreeSurf.NE.0 .AND. .NOT.exactConserv) THEN
242     WRITE(msgBuf,'(A)')
243     & 'CONFIG_CHECK: nonlinFreeSurf cannot be used'
244 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
245 jmc 1.1 WRITE(msgBuf,'(A)')
246     & 'CONFIG_CHECK: without exactConserv'
247 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
248 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
249     ENDIF
250    
251 jmc 1.6 IF (select_rStar.NE.0 .AND. .NOT.exactConserv) THEN
252     WRITE(msgBuf,'(A)')
253     & 'CONFIG_CHECK: r* Coordinate cannot be used'
254     CALL PRINT_ERROR( msgBuf , myThid)
255     WRITE(msgBuf,'(A)')
256     & 'CONFIG_CHECK: without exactConserv'
257     CALL PRINT_ERROR( msgBuf , myThid)
258     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
259     ENDIF
260    
261 jmc 1.7 C- note : not implemented in checkpoint48b but it's done now (since 01-28-03)
262     c IF (select_rStar.GT.0 .AND. useOBCS ) THEN
263     c WRITE(msgBuf,'(A)')
264     c & 'CONFIG_CHECK: r* Coordinate not yet implemented'
265     c CALL PRINT_ERROR( msgBuf , 1)
266     c WRITE(msgBuf,'(A)')
267     c & 'CONFIG_CHECK: in OBC package'
268     c CALL PRINT_ERROR( msgBuf , 1)
269     c STOP 'ABNORMAL END: S/R CONFIG_CHECK'
270     c ENDIF
271 jmc 1.1
272     IF (nonlinFreeSurf.NE.0 .AND. nonHydrostatic) THEN
273     WRITE(msgBuf,'(A)')
274     & 'CONFIG_CHECK: nonlinFreeSurf not yet implemented'
275 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
276 jmc 1.1 WRITE(msgBuf,'(A)')
277     & 'CONFIG_CHECK: in nonHydrostatic code'
278 jmc 1.3 CALL PRINT_ERROR( msgBuf , myThid)
279 jmc 1.1 STOP 'ABNORMAL END: S/R CONFIG_CHECK'
280     ENDIF
281 jmc 1.3
282 jmc 1.4 IF (nonlinFreeSurf.NE.0.AND.deltaTfreesurf.NE.deltaTtracer) THEN
283 jmc 1.3 WRITE(msgBuf,'(A)')
284 jmc 1.4 & 'CONFIG_CHECK: WARNING: nonlinFreeSurf might cause problems'
285     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
286     & SQUEEZE_RIGHT , myThid)
287     WRITE(msgBuf,'(A)')
288     & 'CONFIG_CHECK: with different FreeSurf & Tracer time-steps'
289     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
290     & SQUEEZE_RIGHT , myThid)
291 jmc 1.3 ENDIF
292    
293 jmc 1.15 IF ( useRealFreshWaterFlux .AND. exactConserv
294     & .AND. implicDiv2DFlow.EQ.0. _d 0
295     & .AND. startTime.NE.0. .AND. usePickupBeforeC54 ) THEN
296 jmc 1.3 WRITE(msgBuf,'(A)')
297     & 'CONFIG_CHECK: RealFreshWaterFlux+implicSurfP=0+exactConserv:'
298     CALL PRINT_ERROR( msgBuf , myThid)
299     WRITE(msgBuf,'(A)')
300     & 'CONFIG_CHECK: restart not implemented in this config'
301     CALL PRINT_ERROR( msgBuf , myThid)
302     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
303     ENDIF
304    
305 jmc 1.15 IF ( useRealFreshWaterFlux .AND. .NOT.exactConserv
306     & .AND. implicDiv2DFlow.NE.1. ) THEN
307     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: **WARNNING** ',
308     & 'RealFreshWater & implicDiv2DFlow < 1'
309     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
310     & SQUEEZE_RIGHT , myThid)
311     WRITE(msgBuf,'(2A)') 'CONFIG_CHECK: works better',
312     & ' with exactConserv=.T. (+ #define EXACT_CONSERV)'
313     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
314     & SQUEEZE_RIGHT , myThid)
315     ENDIF
316    
317     #ifdef EXACT_CONSERV
318 jmc 1.4 IF (useRealFreshWaterFlux .AND. .NOT.exactConserv
319     & .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
320     WRITE(msgBuf,'(A)')
321     & 'CONFIG_CHECK: RealFreshWaterFlux with OCEANICP'
322     CALL PRINT_ERROR( msgBuf , myThid)
323     WRITE(msgBuf,'(A)')
324     & 'CONFIG_CHECK: requires exactConserv=T'
325     CALL PRINT_ERROR( msgBuf , myThid)
326     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
327     ENDIF
328     #else
329     IF (useRealFreshWaterFlux
330     & .AND. buoyancyRelation.EQ.'OCEANICP' ) THEN
331     WRITE(msgBuf,'(A)')
332     & 'CONFIG_CHECK: E-P effects on wVel are not included'
333     CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
334     & SQUEEZE_RIGHT , myThid)
335     WRITE(msgBuf,'(A)')
336 jmc 1.15 & 'CONFIG_CHECK: ==> use #define EXACT_CONSERV to fix it'
337 jmc 1.5 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
338     & SQUEEZE_RIGHT , myThid)
339     ENDIF
340 jmc 1.15 #endif /* EXACT_CONSERV */
341 jmc 1.5
342 jmc 1.9 IF (.NOT.useCDscheme .AND. (tauCD.NE.0. .OR. rCD.NE.-1.) ) THEN
343     C- jmc: since useCDscheme is a new [04-13-03] flag (default=F),
344     C put this WARNING to stress that even if CD-scheme parameters
345     C (tauCD,rCD) are set, CD-scheme is not used without useCDscheme=T
346     C- and STOP if using mom_fluxform (following Chris advise).
347     C- jmc: but ultimately, this block can/will be removed.
348     IF (.NOT.vectorInvariantMomentum.AND.momStepping) THEN
349     WRITE(msgBuf,'(A)')
350     & 'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
351     CALL PRINT_ERROR( msgBuf , myThid)
352     WRITE(msgBuf,'(2A)')
353     & 'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
354     & ' in "data", namelist PARM01'
355     CALL PRINT_ERROR( msgBuf , myThid)
356     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
357     ENDIF
358     WRITE(msgBuf,'(2A)') '**WARNNING** ',
359     & 'CONFIG_CHECK: CD-scheme is OFF but params(tauCD,rCD) are set'
360 jmc 1.5 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
361     & SQUEEZE_RIGHT , myThid)
362 jmc 1.9 WRITE(msgBuf,'(2A)')
363     & 'CONFIG_CHECK: to turn ON CD-scheme: => "useCDscheme=.TRUE."',
364     & ' in "data", namelist PARM01'
365 jmc 1.4 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
366     & SQUEEZE_RIGHT , myThid)
367 jmc 1.12 ENDIF
368    
369     IF ( useCDscheme .AND. useCubedSphereExchange ) THEN
370     WRITE(msgBuf,'(2A)')
371     & 'CONFIG_CHECK: CD-scheme not implemented on CubedSphere grid'
372     CALL PRINT_ERROR( msgBuf , myThid)
373     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
374     ENDIF
375    
376     IF ( useOldFreezing .AND. allowFreezing ) THEN
377     WRITE(msgBuf,'(2A)')
378     & 'CONFIG_CHECK: cannot set both: allowFreezing & useOldFreezing'
379     CALL PRINT_ERROR( msgBuf , myThid)
380     STOP 'ABNORMAL END: S/R CONFIG_CHECK'
381 jmc 1.4 ENDIF
382 jmc 1.1
383     WRITE(msgBuf,'(A)') 'CONFIG_CHECK: OK'
384     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
385     & SQUEEZE_RIGHT,myThid)
386    
387     RETURN
388     END

  ViewVC Help
Powered by ViewVC 1.1.22